Fortran/Program structure
This is the print version of Fortran You won't see this message or any elements not part of the book's content when you print or preview this page. |
The current, editable version of this book is available in Wikibooks, the open-content textbooks collection, at
https://en.wikibooks.org/wiki/Fortran
Why learn Fortran?
Fortran is a general purpose programming language mainly used by the scientific community. It is fast, portable and it has seamless handling of arrays and parallelism. It is one of the earliest high level programming languages, and many recognize the original versions which used punched cards to encode the programs. Its name is a contraction of FORmula TRANslation (old versions of the language are typically stylized as FORTRAN) and its creation marked the representation of mathematical expressions with more ease than lower level assembly language. It is still widely used today in numerical weather prediction, physical and chemical modelling, applied mathematics, and other high performance computing purposes. Fortran has a rich array of mathematical libraries and scientific codebases available. The newer standards continuously add modern functionality and are fully backward compatible.
This book is intended to help write code modern Fortran. Where appropriate the differences in usage between legacy versions and the modern standard will be highlighted as there is a significant code base written in older versions, especially FORTRAN 77.
When are other languages better?
editFortran is a very verbose, statically typed compiled language. It can take more time to write, compile and debug than other dynamically typed and interpreted languages. Therefore, many people have moved to languages (such as Python and Ruby) for productivity purposes.
History
Origins
editFortran was created by a team lead by John Backus at IBM in 1957. Originally, the name was written in all capital letters, but current standards and implementations only require the first letter to be capital. The name Fortran stands for FORmula TRANslator. Initially it was specifically aimed at scientific calculations and thereby had very limited support for working with character strings and lacked other provisions important for a general purpose programming language, which it will attain later during its extensive development that ensued after its successful debut. Until the C language became popular, Fortran had been one of the few high level languages with a reasonable degree of portability between different computer systems. Several websites indicate that the work on Fortran was started in 1954 and released commercially in 1957. It is believed that the first successful compilation of a small Fortran program took place on September 20, 1954.
Fortran Versions
editThere have been several versions of Fortran. FORTRAN I, II, III and IV are considered obsolete and contained many machine-dependent features. FORTRAN 66 was the first standardized version and was released in 1966. All later versions of Fortran are numbered after the year the standard was released. The versions of Fortran most commonly remaining in use are FORTRAN 77, Fortran 90 and later.
In FORTRAN II, IF
statements had the form: IF (numeric_expression) label_if_negative, label_if_zero, label_if_positive
. It also had an odd type of string literal, called Hollerith literals (after the inventor of the keypunch and IBM). Where today one might code 'hello', FORTRAN II used 5Hhello. However, there was no string variable type.
FORTRAN IV added the IF
/THEN
concept, the concept of logical expressions, with operators .AND., .OR., .EQ., .NE., et cetera. Complex numbers as a basic type were also added.
FORTRAN 77 added strings as a distinct type.
Fortran 90 added various sorts of threading, and direct array processing.
Fortran 2003 added object orientated features, derived types, language interoperability with C, data manipulation and many I/O enhancements.
Fortran 2008 added coarrays and parallelism and submodules.
Fortran 2018 added even more C interoperability and parallelism features.
Although Fortran became a standardized language early, many companies had their own extensions to it. Strangely, IBM and DEC had virtually the same set of extensions.
Differences between versions
edit- FORTRAN 66 comments are denoted by the
C
character in column 1, while FORTRAN 77 comments may also use*
in column 1 instead. Fortran 90 also allows the use of!
character. - FORTRAN 77 symbolic names are limited to 6 character lengths, while Fortran 90 allows names up to 31 characters long.
- FORTRAN 77 files need 6 spaces before words begin, while Fortran 90 doesn't (as it uses the free-form code style.)
Hello world
Simple Fortran program
editBelow is a simple Fortran program. You can paste this into a text editor (such as Emacs or Vim). Source code must be in a plain text file, so don't use a word processor (such as Microsoft Word), because its native format is usually not plain text, or otherwise contains special formatting data. Give the file a name such as hello.f90. The filename extension .f90 is conventionally used for modern Fortran source code. Other common Fortran file extensions are .f, .FOR, .for, .f77, .f90 and .f95, which can denote the use of old or specific Fortran standards. You may also use .F, .fpp and .FPP for files that support Preprocessing.
program hello
print *, "Hello World!"
end program
Because Fortran is case insensitive, one could just as easily write the first 'hello' program as:
Program Hello
Print *, "Hello World!"
End Program
The only case sensitive part of this program is what contained in the quotation marks of the print statement. ("Hello World!")
Compiling
editUnix
editThere are several Fortran compilers available for Unix. Among the most popular are:
- GNU Fortran compiler from the GCC, which is a fork of G95. Invocation:Note: the GNU Fortran compiler uses the FORTRAN 77 standard by default, so the input file must have the .f90 (or of later standard) suffix, so that the compiler can guess the desired standard automatically. Alternatively you can supply the
gfortran -o hello hello.f90
-ffree-form
option with the usual .f suffix to enable free-form format instead of the fixed-form format used by the FORTRAN 77 standard. - Fortran 95 optimizing compiler from Oracle Solaris Studio. Invocation:
f95 -o hello hello.f90
Once the program is compiled and linked, you may execute it:
./hello
Windows
editOn Windows, you will need to install a compiler. You may also want to install an IDE for that compiler, which acts as an editor and allows you to compile the program more easily.
When you have a compiler, open a command prompt (MS-DOS prompt). This looks like
C:\>
or something similar. At the prompt, you need to move into the folder containing the .f90 file. Then, to compile, type
f95 hello.f90 -o hello.exe
This assumes the compiler is called "f95". The Intel compiler is typically "ifort". You may need to specify where this is, for example if it's in Program Files\Compiler, use:
"C:\Program Files\Compiler\f95" hello.f90 -o hello.exe
Alternatively, you could install a text editor with support for Fortran compilers. Such as SciTE [1] The above commands produce an executable called hello.exe - to run this, just type
hello
at the command prompt
OpenVMS
editOn VMS you will need the DEC Fortran90 compiler installed and licenses loaded. This is available as part of the hobbyist project. These commands work for Fortran on both Alpha and VAX.
To compile, type the following at the DCL prompt:
$ FORTRAN HELLO.F
To link the file to the Run-Time Lib (RTL) type the following:
$ LINK HELLO.OBJ
To Run the executable image, type the following:
$ RUN HELLO.EXE
Hello World!
$
Enjoy all that VMS and Fortran offers.
Beginning Fortran
Introduction
editFortran programs are made up of the main program and modules, each can contain subroutines and functions.
Code that should be executed when the program is run should be placed in a program
block, like this:
program name_of_program
! <variable declarations> ...
! <program statements> ...
end program
Indentation is not required, but is recommended. The name of the program must start with a letter, and can otherwise contain letters, numbers, and the _ (underscore) character. Each statement terminates with the end of the line.
Free Form and Fixed Form
editThe Fortran 77 syntax requires that you give 6 spaces before any commands. These 6 spaces originate from the punched card version of Fortran. After the first 6 spaces, you may place additional spaces for indentation if you wish.
However, there is a maximum total line width of 72 characters (including the first 6 spaces). If you require extra space you can put any character (except 0 with some compilers) in column 6; this is called a "continuation character". With punched cards, this meant that you could continue the line onto a second card.
C2345678...
PRINT *,"This is a really....
*...long line.
On some compilers you can turn off the 6 spaces rule, and turn off fixed length lines, by specifying "free form" and not "fixed form" mode. If you use the GNU Fortran compiler (gfortran), you can use the -ffree-form command line option when compiling for the same purpose.
Commenting
editInclusion of an exclamation mark, !, on a line makes the rest of the line a comment, like this:
a = b ! this is a comment
c = d ! this!! is also a comment
In fixed-form mode, you can also mark a whole line as a comment by placing a * or a c in the first column.
Variables
editSee Variables
There are many different types and options for variables, but for now we'll stick to the basics.
real :: a ! Decimal number.
integer :: b ! Whole number.
character :: c ! Single character.
It is recommended to use the implicit none
statement before variable declarations to avoid typing errors by forcing the explicit declaration of every program variable.
Mathematical operators
editSee Mathematics
- Add, subtract, multiply, divide
+
-
*
/
- Assignment
=
- To the power of ( 2**4 is two to the fourth power = 16 )
**
The mathematical operators have a certain precedence order:
** [exponentiation] always comes first, it is right to left associative. i.e. 2**3**2 = 512, not 64
Next comes * [multiplication] and / [division], these are left to right associative, i.e., 1.0/1.0/2.0*6.0 = ((1.0/1.0)/2.0)*6.0 = 3.0, not 12.0.
Next in order is + [addition] and - [subtraction], these are left to right associative as well, so x-y+z = (x-y)+z = x+(-y)+z.
Finally comes = [assignment].
Intrinsic functions
edit
Fortran has a wide range of functions useful in numerical work, such as sin
, exp
, and log
. The argument of a function must have the proper type, and it is enclosed in parentheses:
x = sin(3.14159) ! Sets x equal to sin(pi), which is zero.
The intrinsic math functions of Fortran are elemental
, meaning that they can take arrays as well as scalars as arguments and return a scalar or an array of the same shape:
real :: x(2), pi=3.14159
x = sin([pi, pi/2])
The above program fragment sets the two elements of array x
, x(1)
and x(2)
, equal to sin(pi)
and sin(pi/2)
respectively.
Comparative and Logical operators
editIn if
statements, and in some other places, you can code relational operators =, <, >, ≤, ≥, and ≠, respectively as .eq.
, .lt.
, .gt.
, .le.
, .de.
, and .ne.
. Another way to write these operators would be: ==, <, >, <=, >=, and /=, respectively.
You can also use the logical operators .and.
, .or.
and .not.
, as well as the logical constants .true.
and .false.
. When combining these items, do not double up on the dots. For instance, a .and. .not. b
is the same as a.and.not.b
, but not a.and..not.b
.
WRITE statements
editSee Input and Output
write (*,*) "Hello World", variablename, "More text", anothervariable
(*,*)
means to use the default output with default options, usually print to screen. Things inside quotes are printed as they look in the code, and the value of the variable is printed. Objects must be separated by commas, and the write statement automatically ends the line by default.
The full formal syntax is:
write (unit=unit_num, FMT=fmt_label, err=label) "Hello World", variablename, "More text", anothervariable
Note that some versions of Fortran don't allow double-quotes, and require single-quotes. An enclosed single-quote can be represented by doubling. For instance, 'don''t'
.
The first parenthesized argument to WRITE
or READ
is the unit number. Unit numbers are associated with input or output streams in a way determined by the operating system. In very old systems, the unit number is the device address. In IBM JCL systems, the association between unit numbers and files are done with JCL DD
statements. In other versions, there is some statement that associates files and units. The UNIT=
tag may be omitted. If an asterisk is used for the unit number, then the I/O involved is the standard input channel, or the standard output channel.
The second parenthesized argument to WRITE
or READ
is the record number. Note that this argument, if present, is separated from the unit number by a single quote. If present, this variable defines which record number is read from or written to. For instance,
record_number = 5
write (2, record_number) x, y, z
writes x, y, and z in packed machine-specific format into record number 5. Note, of course, that this usage requires that your OS or Fortran compiler know what constitutes a record. In byte-organized files, the above code would write x, y, and z starting at the file's byte #5.
The third parenthesized argument to WRITE
or READ
is the format number. If this third argument is present as an asterisk, as above, then the formatting is the obvious default. If you'd rather use a FORMAT
statement to format the input or output, then include the statement number for the FORMAT
statement. For example:
write (7,1) 'Hello, world!', i, 'More text', x
1 format (A,I,A,F)
Note that a format
statement is not executable as an in-line statement. It is only used where referenced by read
or write
. The fmt=
tag may be omitted. The entire argument may be omitted, too. However, if you omit the format argument, the I/O will be performed unformatted, using machine-specific, packed data.
The last parenthesized argument to write
or read
is the error handler statement label. For instance, if
write (5,err=2) x, y, z
is coded, this means that output is to be unformatted to unit 5. If an error occurs, execution continues at statement 2 (the statement with a statement label of 2 in front of it). If an error occurs, and there is no ERR=
argument, then the program abnormally terminates. Thus, ERR=
is the closest equivalent of catch
in other languages. Although this last argument may be omitted entirely, ERR=
can't be omitted from the argument once used.
Example Code
editprogram nearlyuseless
implicit none
real :: temperature
integer :: cows
temperature = 98.6
cows = 9
print *, "There are ", cows, " cows outside."
print *, "You are probably ", temperature, " right now"
end program
Some versions of Fortran, or in some settings, use format characters. When formatting characters are used, the first character of the line determines how the line is printed. 1
means new page. 0
means 2 line-feeds before the line (double-space). -
means 3 line-feeds before the line (triple-spacing). +
means no line-feeds before the line (overprinting). And a space means a single line-feed before the line (normal printing).
Here's the same program in archaic form, with this forms-control character:
temperature = 98.6
i_cows = 6
write (*,*) ' There are ', i_cows, ' cows outside.'
write (*,*) ' You are probably ', temperature, ' right now.'
end
Fortran variables
Introduction
editIn programming, a variable is a container for data that the program can change. You typically declare variables before you use them to provide information on what kind of data they should store. However, Fortran allows variables to be created implicitly. Absent an implicit
statement, undeclared variables and arguments beginning with i
/I
through n
/N
(the "in" group) will be integer
, and all other undeclared variables and arguments will be real
.
Many consider using variables without declaring them bad practice. If you want to be forced to declare variables, code implicit none
first.
General Examples
editExamples of usual variables are listed below
! Declare a constant, whose value cannot be changed.
integer, parameter :: num_days_week = 7
! Declare i as an integer, j as an array of 2 integers from j(1) to j(2), k as
! an array of 2 integers from '''k(0)''' to k(1), and m as a 2-dimensional
! array of 12 elements.
integer :: i, j(2), k(0:1), m(3,4)
! Declare c as an array of 4 floating point numbers from c(0) to c(3).
real :: c(0:3)
! Declare word as a string of length 5
character (len=5) :: word
! Declare a boolean variable with values .TRUE. or .FALSE.
logical :: tf
The following does exactly the same thing, but in the shorter, more archaic form:
INTEGER, PARAMETER :: num_days_week = 7
DIMENSION j(2), k(0:1), m(3,4), c(0:3)
CHARACTER*5 word
LOGICAL tf
If memory layout counts to you, note that m(1,1) is followed in memory by m(2,1), and not by m(1,2).
A variable can be set by placing it before an equal sign, which is followed by the value to which it is set. Given the declarations above, the following assignments are possible:
i = 3*4 ! Set i to 3*4 = 12
j = [1, 4] ! Set j(1) to 1, j(2) to 4
c = [1.0, 4.0, 5.0, 9.0] ! Set c(0) to 1.0, c(1) to 4.0, c(2) to 5.0, c(3) to 9.0
word = 'dog' ! Set word = "dog " . The variable word is padded with spaces on the right
tf = .true. ! Set tf to True
A variable can appear on both sides of an assignment. The right hand side is evaluated first, and the variable is then assigned to that value:
i = 3 ! i has value 3
i = i**i ! i has value 3**3 = 27
Variables can be converted from one type to another, but unlike in C++ or Java where you would typecast the variable, in Fortran you use the intrinsic procedures:
real :: r = 1.5
real (kind=8) :: d = 1.5
integer :: i = 1
print *, dble(r), dble(d), dble(i) ! Convert number to a double precision
print *, real(r), real(d), real(i) ! Convert number to a single precision (REAL)
print *, int(r), int(d), int(i) ! Convert number to an integer
Again, the same thing in the simpler, archaic form:
DOUBLE PRECISION d = 1.5
r = 1.5
i = 1
PRINT *, DBLE(r), DBLE(d), DBLE(i)
PRINT *, REAL(r), REAL(d), REAL(i)
PRINT *, INT(r), INT(d), INT(i)
Arrays
editDeclaration
editOne can declare arrays using two different notations. The following example illustrates the notations for arrays of integer
type and of length 5.
integer, dimension (5) :: arr1
integer :: arr2(5)
For multidimensional arrays one needs to specify the length of each dimension. The following example highlights the case of a 5x6 integer matrix aka a two-dimensional array of length (5,6). (Again, showing both notations.)
integer, dimension (5,6) :: arr1
integer :: arr2(5,6)
Initialization
editTo initialize arrays with actual values one has multiple options: set specific elements, specific ranges, or the whole array.
integer :: arr(3)
arr(1) = 4 ! set specific element
arr(1:2) = [4, 5] ! set a range aka slicing notation
arr = [4, 5, 6] ! set whole array
To set multidimensional arrays one need to make use of reshape
, and shape
commands.
integer :: arr(2,3)
arr = reshape([1,2,3,4,5,6], shape(arr))
! arr = reshape([1,2,3,4,5,6], shape=[2,1]) ! same effect as above command - hardcode the shape of arr
! arr represents matrix:
! 1 3 5
! 2 4 6
Fortran uses column-major ordering such that the upper example produces a often confusing matrix. For a row-major ordering one can use the following example which highlights the use of the order argument to specify along which dimension to sort first.
integer :: arr(2,3)
arr = reshape([1,2,3,4,5,6], shape(arr), order=[2,1])
! arr represents matrix:
! 1 2 3
! 4 5 6
Fortran simple input and output
C. PROGRAM TO EVALUATE SUM OF FINITE SERIES
WRITE(*,*)'ENTER THE VALUE OF X' READ(*,*)X WRITE(*,*)'ENTER THE VALUE OF N' READ(*,*)N SUM=0.0 DO 10I=1,N TERM=((-1)**I)*(X**(I*0.5))/I*(I+1)) SUM=SUM+TERM
10 CONTINUE WRITE (*,*)`SUM OF SERIES'=,SUM PAUSE STOP END
Default output
editA Fortran program reads from standard input or from a file using the read statement, and it can write to standard output using the print statement. With the write statement one can write to standard output or to a file. Before writing to a file, the file must be opened and assigned a unit number with which the programmer may reference the file. If one wishes to use the write statement to write a statement to the default output, the syntax is write(*,*). It is used as follows:
program hello_world
implicit none
write (*,*) "Hello World!"
end program
This code writes "Hello World!" to the default output (usually standard output, the screen), similar to if one had used the print *,
statement.
File output
editAs a demonstration of file output, the following program reads two integers from the keyboard and writes them and their product to an output file:
program xproduct
implicit none
integer :: i, j
integer, parameter :: out_unit=20
print *, "enter two integers"
read (*,*) i,j
open (unit=out_unit,file="results.txt",action="write",status="replace")
write (out_unit,*) "The product of", i, " and", j
write (out_unit,*) "is", i*j
close (out_unit)
end program xproduct
The file "results.txt" will contain these lines:
The product of 2 and 3 is 6
Each print or write statement on a new line by default starts printing on a new line. For example:
program hello_world
implicit none
print *, "Hello"
print *, "World!"
end program
Prints, to standard output:
Hello World!
If one had put "Hello World!" in one print statement, the text "Hello World!" would have appeared on one line.
Fortran control
Selection
editIf-then(-else) conditional
editConditional execution is done using the if
, then
and else
statements in the following construct:
if (logical_expression1) then
! Block of code
else if (logical_expression2) then
! Block of code
else
! Block of code
end if
You may have as many else if
statements as you desire.
The following operators can be used when making expressions:
Operation | Modern Fortran | Old FORTRAN |
---|---|---|
Less than | < | .LT. |
Greater than | > | .GT. |
Greater than/equal | >= | .GE. |
Less than/equal | <= | .LE. |
Equal | == | .EQ. |
Not equal | /= | .NE. |
Logical equivalent | .EQV. | |
Logical not equivalent | .NEQV. | |
Logical not | .NOT. | |
Logical and | .AND. | |
Logical or | .OR. |
Note: The Fortran standard mandates .EQ.
and .NEQ.
cannot be used with logicals but some compilers will not enforce the standard
To check more than one statement, use parentheses.
if ((a .gt. b) .and. .not. (a .lt. c)) then
The following program generates a random number between 0 and 1 and tests if it is between 0 and 0.3, 0.3 and 0.6, or between 0.6 and 1.0.
program xif
implicit none
real :: x
real, parameter :: x1 = 0.3, x2 = 0.6
call random_seed()
call random_number(x)
if (x < x1) then
print *, x, "<",x1
else if (x < x2) then
print *, x, "<", x2
else
print *, x, ">=", x2
end if
end program xif
There are two interesting archaic forms of IF
:
IF (<logical_expression>) GOTO <statement_label>
IF (<arithmetic_expression>) <first_label>, <second_label>, <third_label>
In the first form, things are pretty straightforward. In the second form, the arithmetic expression is evaluated. If the expression evaluates to a negative number, then execution continues at the first line number. If the expression evaluates to zero, then execution continues at the second line number. Otherwise, execution continues at the third line number.
case (switch)
edit- select case(...) case (...); ... end select
If an if block consists of repeated tests on a single variable, it may be possible to replace it with a select case construct. For example, the code
if (month=="January" .or. month=="December") then
num_days = 31
else if (month=="February") then
num_days = 28
else if (month=="March") then
num_days = 31
else
num_days = 30
end if
can be replaced by
select case (month)
case ("January", "December")
num_days = 31
case ("February")
num_days = 28
case ("March")
num_days = 31
case default
num_days = 30
end select
Fortran does not need a break statement.
Loops
edit- do i=1,10 ... end do
To iterate, Fortran has a do loop. The following loop prints the squares of the integers from 1 to 10:
do i=1,10
print *, i**2
end do
One can exit a loop early using exit, as shown in the code below, which prints the squares of integers until one of the squares exceeds 25.
do i=1,10
isquare = i**2
if (isquare > 25) exit
print *, isquare
end do
Loops can be nested. The following code prints powers 2 through 4 of the integers from 1 to 10
do i=1,10
do ipower=1,3
print *, i, ipower, i**ipower
end do
end do
In an archaic form of DO
, a line number on which the loop(s) end is used. Here's the same loop, explicitly stating that label 1
is the last line of each loop:
DO 1 i=1,10
DO 1 ipower=1,3
1 PRINT *, i, ipower, i**ipower
If using the archaic form, the loop must not end on an IF
or GO TO
statement. You may use a CONTINUE
statement as an anchor for a the 1
label.
There is also an optional increment argument when declaring a do loop. The following will count up by two's. 2, 4, 6, ...
do i=2,10,2
write (*,*) i
end do
Arguments to the do loop don't have to be numbers, they can be any integer that is defined elsewhere in the program. first, last, and increment can be any variable name.
do i=first,last,increment
! Code goes here
end do
Simple statements
editgoto statement_label
will jump to the specified statement number.
stop exit_code
will stop with the specified condition code or exit code. stop
may be coded without an argument. Note that on many systems, stop 0
is still a failure. Also note that pre-Fortran 2008, the condition code must be a constant expression and not a variable.
exit
will leave a loop.
continue
can be used to end an archaic DO
loop when it would otherwise end on an IF
.
cycle
will transfer the control of the program to the next end do
statement.
return
leaves a subroutine or function.
Fortran procedures and functions
Functions and Subroutines
editIn most programs, a block of code is often re-used at several places. In order to minimize duplicating code and facilitate maintaining the code, such blocks of code should be placed within a function or subroutine. A Fortran function
is similar to a mathematical function, which takes one or many parameters as inputs and returns a single output value. A Fortran subroutine
is a block of code that performs some operation on the input variables, and as a result of calling the subroutine, the input variables are modified.
An expression containing a function call:
! func1 is a function defined elsewhere.
! It takes an integer as an input and returns another integer as the output.
a = func1(b)
A call to a subroutine:
! sub1 is a subroutine defined elsewhere.
! sub1 performs some operation on input variables e and f.
call sub1(e, f)
! Now e or f, or both (or neither) may be modified.
Many programming languages do not distinguish between functions and subroutines (e.g. C/C++, Python, Java). Pure functional programming languages (e.g. Haskell) only allow functions, because subroutines can, in some case, modify input variables as side-effects, which can complicate the code.
Functions are simpler than subroutines. A function must return a single value, and can be invoked from within expressions, like a write
statement, inside an if declaration if (function) then
, etc. A subroutine does not return a value, but can return many values via its arguments and can only be used as a stand-alone command (using the keyword call
).
Function
editIn Fortran, one can use a function
to return a value or an array of values. The following program calls a function to compute the sum of the square and the cube of an integer.
function func(i) result(j)
integer, intent (in) :: i ! input
integer :: j ! output
j = i**2 + i**3
end function
program main
implicit none
integer :: i
integer :: func
i = 3
print *, "sum of the square and cube of", i, "is", func(i)
end program
The intent (in)
attribute of argument i
means that i
cannot be changed inside the function and in contrast, the return value j
has automatic intent (out)
. Note that the return type of func
needs to be declared. If this is omitted, some compilers will not compile. Open64 will compile the resulting code with warning, but the behavior is ill-defined.
An alternative formulation (F77 compatible) is
FUNCTION func_name(a, b)
INTEGER :: func_name
INTEGER :: a
REAL :: b
func_name = (2*a)+b
RETURN
END FUNCTION
PROGRAM cows
IMPLICIT NONE
INTEGER :: func_name
PRINT *, func_name(2, 1.3)
END PROGRAM
The return type of the func_name
still needs to be declared, as above. The only difference is how the return type of func_name
is referenced within func_name
. In this case, the return variable has the same name as the function itself.
Recursion
editRecursive functions can be declared , in a way such as the one shown below, in order for the code to compile.
recursive function fact(i) result(j)
integer, intent (in) :: i
integer :: j
if (i==1) then
j = 1
else
j = i * fact(i - 1)
end if
end function fact
Subroutine
editA subroutine
can be used to return several values through its arguments. It is invoked with a call
statement. Here is an example.
subroutine square_cube(i, isquare, icube)
integer, intent (in) :: i ! input
integer, intent (out) :: isquare, icube ! output
isquare = i**2
icube = i**3
end subroutine
program main
implicit none
external square_cube ! external subroutine
integer :: isq, icub
call square_cube(4, isq, icub)
print *, "i,i^2,i^3=", 4, isq, icub
end program
Intent
editWhen declaring variables inside functions and subroutines that need to be passed in or out, intent may be added to the declaration. The default is no intent checking - which can allow erroneous coding to be undetected by the compiler.
intent (in)
- the value of the dummy argument may be used, but not modified, within the procedure.
intent (out)
- the dummy argument may be set and then modified within the procedure, and the values returned to the caller.
intent (inout)
- initial values of the dummy argument may be both used and modified within the procedure, and then returned to the caller.
More on Functions vs. Subroutines
editDifferent function result definitions
editFunctions can define the data type of their result in different forms: either as a separate variable or by the function name.
See the examples below
function f1(i) result (j)
!! result's variable: separately specified
!! result's data type: separately specified
integer, intent (in) :: i
integer :: j
j = i + 1
end function
integer function f2(i) result (j)
!! result's variable: separately specified
!! result's data type: by prefix
integer, intent (in) :: i
j = i + 2
end function
integer function f3(i)
!! result's variable: by function name
!! result's data type: by prefix
integer, intent(in) :: i
f3 = i + 3
end function
function f4(i)
!! result's variable: by function name
!! result's data type: separately specified
integer, intent (in) :: i
integer :: f4
f4 = i + 4
end function
program main
implicit none
integer :: f1, f2, f3, f4
print *, 'f1(0)', f1(0) ! output: 1
print *, 'f2(0)', f2(0) ! output: 2
print *, 'f3(0)', f3(0) ! output: 3
print *, 'f4(0)', f4(0) ! output: 4
end program
External
editProcedures must be included by module use
or by specifying them as external
procedures. external
supplies only an implicit interface which is inferior as the compiler doesn't know the number of arguments and neither their data types. Thus, it cannot yield warnings at compile time (in contrast to an explicit interface given from a module use
, c.f. Fortran/OOP in Fortran).
subroutine square_cube(i, isquare, icube)
integer, intent (in) :: i ! input
integer, intent (out) :: isquare, icube ! output
isquare = i**2
icube = i**3
end subroutine
integer function pow4(i)
integer, intent (in) :: i
pow4 = i**4
end function
program main
implicit none
external square_cube ! external subroutine (only implicit interface)
integer :: pow4 ! external function (only implicit interface)
integer :: i, isq, icub
i = 5
call square_cube(i, isq, icub)
print '(A,4I5)', "i,i^2,i^3,i^4=", i, isq, icub, pow4(i)
end program
Pure procedures
editBoth functions and subroutines can modify their input variables. By necessity, subroutines modify input variables, since they do not return any output value. Functions do not have to, but are allowed, by default, to modify input variables. A function can be turned into a pure function, which does not have any side-effects through the use of the intent
attribute on all input variables, and further enforced through the keyword pure
. The pure
keyword imposes additional restrictions, which essentially prevents the function from having any side-effects.
An example of a pure
function.
pure real function square(x)
real, intent (in) :: x
square = x*x
end function
program main
real :: a, b, square
a = 2.0
b = square(a)
! After invoking the square(.) pure function, we can be sure that
! besides assigning the output value of square(a) to b,
! nothing else has been changed.
end program
Keyword arguments
editOne can use any order of the input arguments if one specifies them by their dummy name. That is possible as long as the calling procedure has an interface block of the intended procedure (which is automatically created if one includes the function by module
usage uses modules).
There is also a hybrid method where one specifies some parameters by position and the rest by their dummy name.
An example is given
real function adder(a,b,c,d)
real, intent (in) :: a, b, c, d
adder = a+b+c+d
end function
program main
interface
real function adder(a,b,c,d)
real, intent (in) :: a, b, c, d
end function
end interface
print *, adder(d=1.0, b=2.0, c=1.0, a=1.0) ! specify each parameter by dummy name
print *, adder(1.0, d=1.0, b=2.0, c=1.0) ! specify some parameters by dummy names, other by position
end program
Optional arguments
editArguments can be set optional
. The intrinsic function present
can be used to check if a specific parameter is set.
An example is given below.
real function tester(a)
real, intent (in), optional :: a
if (present(a)) then
tester = a
else
tester = 0.0
end if
end function
program main
interface
real function tester(a)
real, intent (in), optional :: a
end function
end interface
print *, "[no args] tester() :", tester() ! yields: 0.0
print *, "[ args] tester(1.0):", tester(1.0) ! yields: 1.0
end program
Interface block
editIf a procedure has another procedure as dummy argument then one has to specify its type, just as the type of other parameters. An interface
block is used for this case. It consists of the procedure statement with the definitions of its arguments.
Note, that each interface block has its own scope. Thus, if one needs to access outside values one needs to explicitly load them. This can be achieved by the import
, or use
statements.
An example is given below.
function tester(a)
real, intent (in) :: a
real :: tester
tester = 2*a + 3
end function tester
program main
interface
function tester(a)
real, intent (in) :: a
real :: tester
end function tester
end interface
print *, "tester(1.0):", tester(1.0) ! yields: 5.0
end program main
Save attribute
editThe value of a variable can be saved in-between procedure calls by explicitly giving the save
attribute.
An example is given below.
subroutine f()
implicit none
integer, save :: i = 0
i = i + 1
print *, "value i:", i
end
program main
implicit none
interface
subroutine f()
integer, save :: i = 0
end
end interface
call f() ! yields: 1
call f() ! yields: 2
call f() ! yields: 3
end program main
Generic
editIt is possible to create generic functions with the same name for different input arguments, similar to the abs
function which works for integer, real, and complex data types.
The following example illustrates how to create a function add
which adds either two integers or character strings.
module add_mod
implicit none
private
public :: add
interface add
procedure add_int, add_char
end interface add
contains
pure function add_int( x, y )
integer, intent (in) :: x, y
integer :: add_int
add_int = x+y
end function add_int
pure function add_char( x, y )
character (len=*), intent (in) :: x, y
character (len=len(x)+len(y)), allocatable :: add_char
add_char = x // y
end function add_char
end module add_mod
program main
use add_mod
implicit none
print *, "add ints: ", add( 1, 2 )
print *, "add chars: ", add("abc", "def")
end program main
Deferred
editOne can set type-bound procedures of an abstract type as deferred
such that it needs to be reimplemented in derived types.
For more information see the section on abstract types.
Elemental
editOne can create procedures that operate parameters of arbitrary dimension. The keyword elemental
is used where one defines the operation on a single object (e.g. integer) and the general case is automatically handled.
An example for the addition of arbitrary long integer dimension is given.
pure elemental function add_int(x, y)
integer, intent (in) :: x, y
integer :: add_int
add_int = x + y
end function add_int
program main
implicit none
interface
pure elemental function add_int(x, y)
integer, intent (in) :: x, y
integer :: add_int
end function add_int
end interface
print *, "add ints:", add_int(1, 2) ! yields: 3
print *, "add arrays:", add_int([1, 2], [2, 3]) ! yields: 3 5
end program main
complex types
Warning: Display title "Fortran/data types" overrides earlier display title "Fortran/Fundamentals".
Variables and data declarations must occur at the start of all Fortran program units before any executable statements. Variables may have a "kind" that specifies its size in memory. The kind parameter can have different meanings for each compiler or processor, so be sure to check what kinds are available to you in your compiler's documentation.
Declaration style
editThere are several ways to declare a variable. The modern Fortran style is to be verbose and explicit. The following example declares an real array with the a kind of 8 (on most compilers this means 8 bytes long, i.e. double precision).
! Modern variable declaration
! <datatype> [(kind=<num>), <attribute>, ... ::] <identifier>[, ...]
! Example:
real (kind=8), dimension (3) :: variable
The dimension
attribute is quite long to type out, but may be more concise when declaring multiple arrays on a single line. If only a single variable is to be declared then it may be more concise to specify the dimension with parentheses next to the identifier.
real (kind=8) :: variable(3)
Variables may also be initialized with an assignment.
real (kind=8) :: variable(3) = 1.0
The ::
is optional for backwards compatibility with older versions of Fortran. The older style of declarations use a *
to denote the kind of a variable.
REAL*8 variable(3)
Furthermore, the kind may be omitted entirely to simply use the default kind for your compiler.
real variable(3)
Intrinsic data types
editInteger
edit
The integer data type stores signed integer values (i.e. ..., -3, -2, -1, 0, 1, 2, 3, ...). On most compilers, the default kind stores integers as short integers 4 bytes in size (kind=4
). Long integers are usually 8 bytes (kind=8
). The allowed attributes are: allocatable, intrinsic, public, asynchronous, optional, save, parameter, bind, pointer, target, dimension (dims), private, value, external, protected, volatile and intent (inout).
integer :: variable
Logical
edit
The logical data type stores boolean vales and can only contain values .true.
or .false.
. The default logical kind for most compilers is 4, occupying 4 bytes. Therefore, logicals are much like integers in terms of memory, but integers and logicals are generally not compatible for most operations. The allowed attributes are: allocatable, intrinsic, public, asynchronous, optional, save, parameter, bind, pointer, target, dimension (dims), private, value, external, protected, volatile, intent (inout).
logical :: variable
Real
editThe real data type stores floating point data. Vales are stored in memory in scientific notation as a mantissa and an exponent. The default kind for real variables is 4, which consists of 4 bytes (32 bits). In this case 24 bits are used for the mantissa and 8 bits are used for the exponent. The allowed attributes are: allocatable, intrinsic, public, asynchronous, optional, save, parameter, bind, pointer, target, dimension (dims), private, value, external, protected, volatile, intent (inout).
All compilers support at least two kinds of real kinds for low precision and high precision numbers. But the standard does not specify what size these precisions should be. Most compilers use 32 bits for single precision and 64 bits for double precision. Therefore, many compilers support a double precision
real data type that uses the higher precision that is available. However, for portablility it is much better to use the selected_real_kind
intrinsic function to select the required kind parameter for your variables precision.
real :: variable
double precision :: variable2
Complex
editIn mathematics, a complex number has a real and an imaginary component. Complex numbers in Fortran are stored in rectangular coordinates as a pair of real numbers (real part first, followed by the imaginary part). The default kind of complex numbers is always the same as the default kind of the real data type. So a complex variable of kind 4 will contain two reals of kind 4. If kind 4 reals corresponds to 4 bytes, then the default complex variables will be 8 bytes in size. The allowed attributes are: allocatable, intrinsic, public, asynchronous, optional, save, parameter, bind, pointer, target, dimension (dims), private, value, external, protected, volatile, intent (inout).
complex :: variable
Complex operations
editAll of the arithmetic operators can take a complex number on either side. Fortran automatically handles complex arithmetic and the special rules of imaginary numbers.
Care must be taken in using function calls that might cause an error. For instance, taking the square root of the real number -1.0
will result in an error, because -1 is outside of the domain of real square root. Taking the square root of the complex number (-1.0,0.0)
is allowed because -1 is in the domain of complex square root.
Character
edit
The character data type stores strings of characters. The default kind of character variables is usually 1 which represents ASCII characters. Kind 2 usually represents the ISO 10646 standard characters. Character variables are unique in that they also have a len
parameter in addition to kind
which specifies the number of characters in the string. Typically a single character occupies 1 byte in memory. In addition to this, character data types can also be arrays.
character (len=5,kind=1), dimension (2) :: strings
The old style declarations does not have a kind parameter and only has the length parameter.
CHARACTER*5 strings(2)
Constants
editLiteral constants
editData embedded in expressions are referred to as literals or constants. Literals can have a particular data type depending on how they are written. For example, in the below line the value 1 is an integer.
a = a + 1
The below table demonstrate how to type literal constants.
Type | Example literals |
---|---|
integer | 0 , -1 , 9999
|
logical | .true. , .false. , T , F
|
real | 1.1 , 0.0005 , -99.9e-99
|
complex | (-1.0,3) , (0.5,-3e5)
|
character | 'Hello'
|
Note that the parentheses notation for complex numbers cannot be used with variables. For example, (a, b)
is invalid. To convert real variables to complex, use the cmplx
function:
cmplx(a, b)
Any expression involving complex numbers and other numbers is promoted to complex.
Parameter constants
edit
Constants literals are simply unnamed data. Variables can be constants too. They are declared with the parameter
attribute. These variables are immutable and assigning to them after they have been declared will cause an error. They must be initialized with a value when they are declared.
real, parameter :: PI = 3.141592
Fortran structure and style
Warning: Display title "Fortran/Program structure" overrides earlier display title "Fortran/data types".
Style
editOlder versions of Fortran had strict guidelines on how a program was formatted. Fortran 90 lifted this restriction and would accept free format code as well as historical fixed format code.
Fixed format
editPrior to Fortran 90, source code followed a well-defined fixed format. Comments are indicated with a 'C' in the first column, columns 2-5 were reserved for an optional numerical statement label, a non-blank character in column 6 indicated the current line was a continuation from the previous one, and columns 7 through 72 were available for program statements. Columns 73 through 80 were ignored and often contained line sequence numbers. Blank lines were not allowed. This rigid formatting was the result of Fortran being developed in the era of batch computing and punched card input. The sequence number was used in the case a program 'deck' was dropped; program order could be recovered if the punch cards were placed in a card reader and sorted on columns 73-80. Compiler vendors offered extensions to this formatting, but it was rarely portable (for example, interpreting tab characters as 6 spaces.)
Note that while column position was significant, white space was not. The following program illustrates legal use of white space in fixed-format Fortran:
C2345678901234567890
PROGRAM Z
GOTO11
11 CONTINUE
GO TO 780
780 CONTINUE
G OTO3 60
360 CONTINUE
STOP
END
While this code is technically legal, it is strongly encouraged to use white space to separate keywords, labels, and data to maintain readability.
Fortran was developed before the standardization of the ASCII character set and traditionally Fortran code has been written in all-caps. Variable names were limited to six characters, but this was often extended by compiler vendors.
Free format
editAs of Fortran 90 and onward, source code does not require fixed column formatting. In this case, commands can freely start on any column. The 72 column limit has also been released. This allows for much more space for indentation.
program test
implicit none
integer four
four = 4
write (*,*) four
end program
Case sensitivity
editFortran is not case sensitive. Fortran was typically used on systems that only supported capital letters. In fact, the language itself was called FORTRAN (in capitals). It remains customary, though completely unnecessary, to type Fortran commands in all capitals. This is useful to distinguish keywords in source code that is displayed on monocrome displays and print. These days, syntax highlighting is available to replace this. However it may be useful to visually distinguish older Fortran code from modern source code.
Whitespace
editWhitespace and empty lines usually won't matter in Fortran 90 or above. Some statements require whitespace, for example, program
, function
and subroutine
require whitespace between the statement keyword and the program unit identifier.
However, unlike many other languages such as C, C++, and Java, the line delimiter ';' is optional, so each line of code may stay on its own line. However, the use of the command separator character ';' is discouraged.
Structure
editProgram units
editFortran programs are made up of program units. A single source code file can contain several program units but it is conventional to place each program unit in its own separate source code file. At their most basic they consist of a series of Fortran statements and conclude with the end
statement.
Main program
editEvery executable program must have a main program unit. For example, the following is a complete compilable and executable program.
write (*,*) "Hello, world"
end
However, it is much clearer to use the program
statement to indicate that it is the main program unit.
program main
write (*,*) "Hello, world!"
end program main
The main program is separated into sections. The first section should consist of module use
statements. This is followed by implicit
/ implicit none
statements that control whether undeclared variables are implicitly typed. This is followed by the declaration section where variables, types, interfaces and procedures are declared. Then comes the executable statements of the main program. The last section is the internal subprograms initiated by the contains
statement.
program main
! Use statements section
use module_name
! Implicit none statement section
implicit none
! Declarations section
integer :: a
real :: b
! Executable section
write (*,*) "Blah, blah, blah..."
end program main
Subprograms
editProgram units may also be subprograms: these can be procedures (functions and subroutines), block data, modules or submodules.
External subprograms
editThe following code shows a main program and a function. The increment function is external to the main program, and therefore needs a declaration in the main program on line 4.
program main
implicit none
integer :: a
integer, external :: increment
a = increment(34)
write (*,*) a
end program main
function increment(input) result (output)
implicit none
integer :: output
integer :: input
output = input + 1
end function increment
However, the interface of the function is still implicit. To explicitly declare an external procedure, one can use an interface that declares all the inputs and outputs of external procedures. In which case, the main program would be as follows.
program main
implicit none
integer :: a
interface
integer function increment(input)
integer :: input
end function
end interface
a = increment(34)
write (*,*) a
end program main
Internal subprograms
edit
Internal subprograms do not need an explicit interface or a declaration, because they are part of the parent program unit. A subprogram is internal if it is contained within the contains
section of a program unit.
program main
implicit none
integer :: a
a = increment(34)
write (*,*) a
contains
function increment(input) result (output)
integer :: output
integer :: input
output = input + 1
end function increment
end program main
Functions
editSubroutines
editBlock Data
editModules
editSubmodules
edit
io
It is often useful, in Fortran and other languages, to specify where, and how you want something to print or be read. Fortran offers many commands and formatting specifications which can serve these purposes. In the following sections we will be considering the I/O operations (open
, close
, inquire
, rewind
, backspace
, endfile
, flush
, print
, read
, write
and namelist
) and I/O formatting (format
). In Fortran 2008, a significant addition has been the ability to extend the basic facilities with user-defined routines to output derived types including those that are themselves composed of other derived types.
Together these commands form a very powerful assembly of facilities for reading and writing formatted and unformatted files with sequential, direct or asynchronous access. Indeed, the options can look bewildering at first. However, the basic operations are simple enough but they are backed up by the power and flexibility to read or write almost any file.
However, it is worth mentioning, at this stage, what Fortran cannot do simply and directly from a language-defined perspective: Fortran will not address a file defined by a URL, files must be available locally or on a mapped network drive or equivalent. Similarly, Fortran does not natively support XML, except that XML is simple ASCII text so it can be read easily but parsing it out is down to the programmer! The Fortran language knows nothing about computer graphics; you are not going to find a language-defined draw command. Fortran will happily open and read a jpg file but there is no language-defined method of displaying the file as a picture; a suitable external library will have to be used. Finally, Fortran does not have any language-defined mouse operations or touch screen gestures.
I/O Operations
editIntroduction
editModern Fortran has a rich vocabulary for I/O operations. These operations can generally be used on the screen and keyboard, external files and internal files. In recent versions of Fortran, the syntax of these commands has been rationalized but most of the original syntax has been retained for backwards compatibility. I/O operations are notoriously error-prone and Fortran now supports a unified mechanism for identifying and processing errors.
Simple I/O Operations
editThis is the classic "Hello World" operation, but is rarely used in production code. print
is one of two formatted output operations and it is also much simpler that the write
statement. The main purpose of the print
statement is to print to the screen (standard output unit) and it has no options for file output. The general form is:
print fmt, list
Both fmt
and list
are optional and the fmt
can be explicit or list-directed (as indicated by *
), and being optional can take the name=value
format. The list is a comma separated list of literals or intrinsic type variables. So here are some examples:
program hello
implicit none
integer :: i
! List-directed fmt
print *, "Hello World"
do i = 1, 10
! An explicit fmt and a two element list
print '(A,I0)', "Hello ", i
end do
! Name=value for fmt
print fmt='(A)', 'Goodbye'
end program hello
Note that print
is just about the only I/O operation that still does not support iostat
and iomsg
clauses, and for this reason alone should not be used in new code except for temporary output and debugging. print
has no explicit mechanism for printing user-defined types and this is another reason for not using it in production code.
I/O Channels & Files
editIn the example on print
shown above, the print
statement is automatically pre-connected to the standard output device also known as the computer screen. However, in general, Fortran requires a two stage process to connect code to external files. First we have to connect the file to a Fortran channel (manually identified by a positive integer or automatically assigned a negative value): the open
command, and then we can read
and write
to the now open channel. read
and write
operations to a channel that is not open, results in an error; there is no language-specified buffering until the relevant channel is opened. Once an I/O operation is complete we can close
the connection between the file and the Fortran channel. If a Fortran program terminates before a channel is closed to a file, Fortran will usually close the channel without significant loss of data.
The state of availability of Fortran channels can be ascertained through one form of the inquire
command. The inquire
command can also be used to determine the existence and other properties of a file before it is connected to a Fortran channel.
Fortran I/O to internal files does not require a pre-connection process. Fortran input from the keyboard and output to the screen is automatically pre-connected on a special channel (*). Compiler vendors are free to assign a channel number to these standard I/O devices and the user can determine which channel numbers have been used via the intrinsic module iso_fortran_env
.
Open
editThis is the command required to establish a connection between an external file and a Fortran channel. The open
command can be used to create a new file or connect to existing files. Subsequent I/O to the file, once open, is made via this channel number. The open
command has options to ensure that the file already exists or does not already exist, to ensure that it is used only for input, or only for output, or for both. The expected format of the file can be specified in the open
command and errors can be trapped. The full syntax of the command can appear to be rather complicated, but generally any one call to open
uses only a small subset of all the available options.
The open
command originated when external files were usually card images. open
can now specify that the connection to a file be fixed-format, asynchronous, a binary stream and many combinations of these. It is worth remembering that I/O is a major source of potential coding errors and where critical data are read they should be written again to confirm correct processing.
The value of the Fortran channel number has global scope within any one image of a Fortran program. Even if an integer variable is used to open a channel and that variable has very limited scope, the actual channel number is effectively ubiquitous. This needs to be considered at design time because one module can open, say, channel 10, and another module can close channel 10 without any use association between them. For this reason, in large programs, it is often the case that a single module is used to control all file i/o operations so that a clear and obvious "open - read/write - close" chain can be maintained.
Finally, as usual with Fortran, there are options and clauses which are retained for legacy purposes which should not be used in new code.
Open Command Syntax
editopen ([unit=]u[, olist])
Where [] indicate optional sections and olist
is a comma separated list of options. In the above, u is a scalar integer expression or equivalent and is required unless the newunit
option is specified. (Bad luck: we cannot open more than one file in one open
statement). Technically, u is called the external file unit number, or channel number for short.
Common Options
editnewunit=nu
where nu is a default integer variable. This allows the processor to select the channel number and, to avoid conflicts with legacy code, a negative value (not -1) will be selected that does not conflict with any current unit number in use. This is the form that should be used in all new code.
iostat=ios
where ios is a default integer variable which will be set to zero if the open statement does not detect an error, but will be set to a positive value is an error does occur, and the exact value is vendor dependent. Although technically an option, this is a highly recommended option for all open
commands. If this option is not present (and the err=
option is not present, see below) the program will stop if there is an error. The presence of this option confers on the programmer the responsibility to check the value returned and have the program act accordingly.
iomsg=iom
where iom is a scalar character variable of default kind. Again, although technically an option, this is a highly recommended option for all open
commands in new code. The length of the message is error and vendor specific and may require some trial and error.
file=fln
where fln is a default character variable, literal or expression which specifies the name of the external file. The file name can be a fully qualified path or a local filename. If the path points to a file on a network drive the drive must be preconnected and there is no language defined way of making this connection. (Except that we can always resort to execute_command_line
)
status=stn
where stn is also a default character variable, literal or expression which must evaluate (case independently) to one of 'old', 'new', 'replace', 'scratch' or 'unknown'. 'old' requires the file to exist and is typically used when the purpose of the open statement is to allow a file to be read. 'new' and 'replace' require the presence of the file=
option described above, and 'new' requires the file to not exist, and 'replace' allows the file to already exist but if it does it will be overwritten. 'scratch' is special in that the file=
option must not be used and the file created cannot be kept on subsequent execution of a close
command. 'scratch' is typically used for the temporary warehousing of large data structures to a hard disk or similar mass storage. If 'unknown' is specified this is also the default if the status=
option is not given, and the file status becomes vendor and system dependent, i.e. a manual will have to be consulted.
action=act
where act is a default kind character expression, variable or value that evaluates to 'read', 'write' or 'readwrite'. Somewhat amazingly, the default is processor dependent, so the manual will have to be consulted. If 'read' is specified, the file is to be regarded as read only and attempt to execute write
, print
or end file
statements on this channel will result in errors. Similarly if 'write' is specified, the file is to be regarded as write only and attempts to execute a read
statement will result in an error. When 'write' is specified some other statements may result in an error in a processor dependent manner (e.g. backspace
).
Simple Example of Open
editprogram opena
implicit none
integer :: nout !channel number
integer :: my_iostat !integer scalar to catch error status
character (len=256) :: my_iomsg !Default-kind character variable to catch error msg
open (newunit=nout, file="local.dat", iostat=my_iostat, iomsg=my_iomsg)
if (my_iostat /= 0) then
write (*,*) 'Failed to open local.dat, iomsg='//trim(my_iomsg)
stop
end if
write (nout,*)
end program
Less Common Options
editaccess=acl
where acl is a character expression, variable or literal that evaluates to either 'sequential', 'direct' or 'stream'. When opening a file that already exists, this value must correspond to an allowed value which is usually the value given when the file was created. The default for a new file is 'sequential'. 'stream' access is new at Fortran 2008 and provides some compatibility with C binary stream files. The other really important feature of 'stream' access is that a file can be positioned for write and part of the file overwritten without changing the rest of the file. For formatted stream files the new_line(nl)
function will return the relevant new line characters in the character variable nl.
recl=rcl
where rcl is an integer expression, variable or literal that must evaluate to a positive value. For a file to be opened for direct access this 'option' is required and must specify the length of each record. For sequential files it is optional and can be used to specify the maximum length of a record. For a file that already exists, the value or rcl must correspond to the value used to create the file. In any case, the value of rcl must also be allowed by the underlying operating system.
form=frm
where frm is a character expression, variable or literal that evaluates to either 'formatted' or 'unformatted'. This option can often be omitted since the default is 'formatted' for sequential access and 'unformatted' for direct access.
blank=blk
where blk is a character expression, variable or literal that provides the value 'null' or 'zero' for formatted i/o only. See bn and bz formats below.
position=psn
where psn is a character expression, variable or literal that evaluates to 'asis', 'rewind' or 'append' and applies only when the access method is sequential. The default value is 'asis'. When opened, a new file is always positioned at its initial point but for existing files, the user has the option of where to position the current position.s
delim=
pad=
Options to Avoid
editThere is much legacy code out there and this section describes features that are still legal but which should be considered for replacement, and certainly not used in new code.
err=eno
where eno is a literal integer label number. If an error occurs in the processing of the open
statement the program will transfer control to the statement with label number eno. The presence of the err= option caused the program to continue if there was an error. This option should now be replaced with iostat=
and iomsg=
. (It is legal to specify both err=
and iostat=
, but without either the program will stop if an error occurs processing the open
statement.)
unit=nu
where nu is a default integer expression, variable or literal value which must be positive and which must not coincide with any unit already in use. If this option is placed first in the list of options the "unit=" can be omitted. This was very widely used and should now be replaced with newunit=
. In very old code, nu was a fixed value and the programmer had to ensure that it did not clash with other channels in use at the same time. More recently, the inquire
statement can be used to select a unit number not already in use, but this could not guard against a subsequent open
statement trying to use a fixed value already in use. This is why the newunit
option, and only the newunit
option, is allowed to specify a negative value for the channel number.
Read
editThe read
statement is a statement which reads from the specified input in the specified form, a variable. For example,
program reada
implicit none
integer :: a
read (*,*) a
end program
will create an integer memory cell for a
, and then it will read a value with the default formatting from the default input and store it in a
. The first *
in (*,*)
signifies where the value should be read from. The second *
specifies the format the user wants the number read with. Let us first discuss the format strings available. In Fortran we have at our disposal many format strings with which we may specify how we want numbers, or character strings to appear on the screen. For fixed point reals: Fw.d
; w is the total number of spaces allotted for the number, and d is the number of decimal places. The decimal place always takes up one position. For example,
program reada
implicit none
real :: a
read (*,'(F5.2)') a
end program
The details of the I/O formatting e.g. '(F5.2)' will be described below
Write
editInquire
editThe inquire
statement has two basic forms: "inquire
by unit" and "inquire
by file" and both are very useful and well worth getting to know. There is a more obscure form called "inquire
by length" which is useful for checking the unformatted record length of potential output in order to decide what record length may be required, or whether a file with an already defined record length can cope with a given output.
Inquire by unit
editInquire by file
editInquire by length
editThis rather more obscure version of the inquire
command is used to obtain the length of an unformatted record required to contain a given form of output and hence allow the user to either check or specify the length of a record required.
Inquire errors
editClose
editThe close
command releases the connection between a file and a Fortran channel. In the process, and depending on how the file was opened, the file can be saved or discarded. The general form of the close
command is as follows:
close ([unit=]u, [, olist])
Where u
is a default integer expression, variable or literal value that evaluates to the number of the channel to close, and unit=
is optional. The options available in the option list are as follows:
iostat=ios
where ios
is a default integer variable which will return with the value 0 if the close
command is executed correctly. If an error occurs the return value will be positive and a message describing the error will be provided via the iomsg
option described below.
err=eno
where eno
is a literal integer label number. If an error occurs in the processing of the close
statement, the program will transfer control to the statement with label number eno. The presence of the err= option caused the program to continue if there was an error. This option should now be replaced with iostat=
and iomsg=
. (It is legal to specify both err=
and iostat=
, but without either the program will stop if an error occurs processing the open
statement.)
iomsg=iom
where iom
is a scalar character variable of default kind. Again, although technically an option, this is a highly recommended option for all close
commands in new code. The length of the message is error and vendor specific and may require some trial and error.
status=st
Close errors
editIt is perhaps counter intuitive, but Fortran does not consider attempting to CLOSE a channel that is already closed to be an error. Like inquire
and open
, the errors close
will report are effectively operating system errors. For example, close
with status="delete"
on a channel which is already closed is an error especially if the file no longer exists. Similarly, Fortran will report an error if a file created as 'scratch' is closed with status="keep"
because the only option for scratch files is status='delete'
. These limitations are predicated on the iostat
(and iomsg
) clause being used to allow the user to program for graceful termination when necessary, and not to obtain a full report on the performance of a close
command.
I/O Formatting
editList-Directed Formatting
editWe describe explicit formatting below but it is immediately clear that there is a whole "language within a language" so Fortran provides a short cut, or language-defined format guessing. It turns out that this default formatting is very close to a comma separated variable (CSV) processor for input. List-directed I/O is specified by a fmt=*
clause, but the fmt clause is optional and can be replaced with just *.
Explicit Formatting
editFortran has a rich, but very terse, language for controlling the formatting of I/O operations. The format commands can be placed in an explicit fortmat
statement or they can be placed within a clause of the relevant READ or WRITE statement either literally or stored in a character
variable.
strings
Modern Fortran has a wide range of facilities for handling string or text data but some of these language-defined facilities have not been widely implemented by the compiler developers. It should be remembered that Fortran is designed for scientific computing and is probably not a good choice for writing a new word processor.
Character type
editThe main feature in Fortran that supports strings is the intrinsic data type character
. A character literal constant can be delimited by either single or double quotes, and, where necessary, these can be escaped by using two consecutive single or double quotes. The concatenation operator is //
(but this cannot be used to concatenate character entities of different KIND). Character scalar variables and arrays are allowed. Character variables have a sub-string notation to refer to and extract sub-strings.
Example
program string_1
implicit none
! Declarations
character (len=6) :: word1
character (len=2) :: word2
word1 = "abcdef" ! Assignment
word2 = word1(5:6) ! Substring
word1 = 'Don''t ' ! Escape with a double quote
write (*,*) word2//word1 ! Concatenation
end program string_1
In the above example, the two character
variables word1
and word2
are declared to have length 6 and 2 characters respectively.
In character
assignment operations, if the right hand side of the assignment is shorter than the left hand side, the remaining characters on the left hand side are filled with blanks. If the right hand side is longer than the left hand side, then the right hand side is truncated. In neither case is an error raised either by the compiler or at run time.
character
arrays and coarrays are permitted and can be declared and accessed in the same way as any other Fortran array. Where the array index and substring notations are to be combined, the array indices appear first and the substring expression appears second as illustrated in the final line of the following example:
character (len=120), dimension (10) :: text
text(1) = 'This is the first element of the array "text"'
text(2:3) = ' ' ! Elements 2 and 3 are blank.
text(4)(20:20) = '!' ! Character 20 of element 4.
Unlike some programming languages, Fortran character
data and variables do not require an explicit character to terminate a string. Also, unlike C-type languages, Fortran character
data do not accommodate embedded and escaped control characters (e.g. /n) and all processing of output control is done via an extensive format
sub-system.
Character collating sequence
editInternally, Fortran maintains a collating sequence for all the permitted characters. Non-printing characters may be included in the collating sequence. The collating sequence is not specified by the language standard but most vendors support either ASCII or EBCDIC. This collating sequence means that lexical comparisons can be performed to ascertain whether e.g. 'a'<'b'
, but the outcome is essentially vendor specific. Hence there is a difference between functions such as ichar
and iachar
that is described below.
Character kind
editcharacter
can also have a kind
, but this is vendor-specific. It can allow compilers to support unicode, or the Russian alphabet or Japanese characters etc. It is not necessary to specify the length or kind of a character
variable. If a character
variable is declared with neither, the result is a variable of default kind and one character long. A single number is to indicate length, and two numbers indicate length and kind in that order. It is generally much clearer, but slightly more verbose to be explicit, as shown in lines 6-8 of the following example. The compiler vendor has control over which kinds of character are supported and the integer values assigned to access the corresponding character sets.
program string_2
implicit none
character :: one
character (5) :: english_name
character (5,2) :: japanese_name
character (len=80) :: line
character (len=120, kind=3) :: unicode_line
character (kind=4, len=256) :: ebcdic_string
!...
end program string_2
The intrinsic function selected_char_kind(name)
returns the positive integer kind value of the character set with the corresponding name (e.g default, ascii, kanji, iso_10646 etc) but the only character set that must be supported is default
, and if the name is not supported then -1 will be returned. Disappointingly, vendors generally have been slow to implement more than the default kind but gfortran, for instance, is a notable exception.
Language-defined Intrinsic Functions and Subprograms
editFortran has a fairly limited set of intrinsic functions to support character manipulation, searching and conversion. But the basic set is enough to construct some powerful features as required. There are some strange absences such as the ability to convert from lower-case to upper-case but this can be understood and forgiven since these concepts may not exist in many of the languages or character sets that may be represented by different character
kinds. Functions such as size
, lbound
and ubound
which apply to arrays of any data type, including character type, are not described here.
achar
editachar(i, kind)
returns the ith character in the ASCII collating sequence for the characters of the specified kind. The integer i
must be in the range 0 < i < 127. Kind is an optional integer. If kind is not specified the default kind is assumed. achar(72)
has the value 'H'. One really useful feature of achar
is that it permits access to the non-printing ASCII characters such as return (achar(13)
). achar
will always return the ASCII character even if the processor's collating sequence is not ASCII. If kind is present, the kind parameter of the result is that specified by kind; otherwise, the kind parameter of the result is that of default character. If the processor cannot represent the result value in the kind of the result, the result is undefined. Using achar
is highly recommended in preference to char
, described below, because it is portable from one processor to another.
adjustl
editadjustl(string)
left justifies by removing leading (left) blanks from string and filling the right of string with blanks so that the result has the same length as the input string.
adjustr
editadjustr(string)
right justifies by removing trailing (right) blanks from string and filling the left of the string with blanks so that the result has the same length as the input string.
char
editchar(i, kind)
returns the ith character in the processor collating sequence for the characters of the specified kind. The integer i
does not have to be in the range 0 < i < 127. Kind is an optional integer. If kind is not specified the default kind is assumed. If the processor cannot represent the result value in the kind of the result, the result is undefined.
iachar
editiachar(c, kind)
is the inverse of achar
described above. c is a single input character and iachar(c)
returns the position of c in the ASCII character set as a default integer. Kind is an optional input integer and if kind is specified, it specifies the kind of the integer returned by iachar
.
ichar
editichar(c, kind)
is the inverse of CHAR described above. c is a single input character and ichar(c)
returns the position of c in the selected character set as a default integer. Kind is an optional input integer and if kind is specified, it specifies the kind of the integer returned by ichar
.
index
editindex(string, substring)
returns a default integer representing the position of the first instance of substring in string searching from left to right. There are two optional arguments: back and kind. If the logical back is set true the search is conducted from right to left, and if the integer kind is specified, then the integer returned by index
will be of that kind. If substring does not appear in string the result is 0.
len
editlen(c, kind)
returns an integer representing the declared length of character c. This can be extremely useful in subprograms which receive character dummy arguments. c
can be a character array. Kind is an optional integer which controls the kind of the integer returned by len
.
len_trim
editlen_trimc, kind)
returns the length of c excluding any trailing blanks (but including leading blanks). If c is only blanks the result is 0. Hence expressions like len_trim(adjustl(c))
can be used to count the number of characters in c between the first and last non-blank characters. Kind is an optional integer which controls the kind of the integer returned by len_trim
.
new_line
editnew_line(c)
is a character function that returns the new line character for the current processor. The kind of the returned character will be the same as the kind of c
. A blank character may be returned if the character kind from which c
is drawn does not contain a relevant newline character. This function is not likely to be used except in some very specific circumstances.
repeat
editrepeat(string, ncopies)
concatenates integer ncopies of the string. Hence repeat('=',72)
is a string of 72 equals signs. String must be scalar but can be of any length. Trailing blanks in string are included in the result.
scan
editscan(string, set, back, kind)
returns a default integer (or an integer of the optional kind) that represents the first position that any character in set appears in string. To search right to left, the optional logical back must be set true. string can be an array in which case, the result in an integer array. If string is an array then set can be an array of the same size and shape as string and each element of set is scanned for in the corresponding element of string. index
, described above, is a special case of scan
, because every character of set must be found and in the order of the characters in set.
selected_char_kind
editselected_char_kind(name)
is an integer function that returns the kind value of the character set named. The only set that must be supported by the language standard is name='DEFAULT'
. If name is not supported the result is -1.
trim
edittrim(string)
is a character valued function that returns a string with the trailing blanks removed. If string is all blanks the result has zero length.
verify
editverify(string, set, back, kind)
is an integer function that returns the position of the first character in string that is not in set. So verify
is roughly the obverse of scan
. In verify
back and kind are both optional and have the same role as described in scan
above. If every character in string is also in set (or string has zero length), then the function returns 0.
Regular expressions
editFortran does not have any language-defined regex or sorting capability for character data. Fortran does not have a language-defined text tokenizer but, with a little ingenuity, list directed input can provide a partial solution. However, there are Fortran libraries that wrap C regex libraries.
I/O of character data
editread formatting
editread
for character data can be list-directed or formated using the "a" or "an" forms of this edit descriptor. In the "a" form, the width is taken from the width of the corresponding item in the list. In the "an" form, the integer n specifies the number of characters to transfer. The general edit description "gn" can also be used.
Example
character (120) :: line
open (10,"test.dat")
read (10,'(a)') line ! Read up to 120 characters into line
read (10,'(a5)') line(115:) ! Read 5 character and put them at the end of line
write Formatting
editThe a and g edit descriptors exist for write
as described above. The "a" form will write the whole character variable including all the trailing blanks so it is common to use trim
or adjustl
or both.
Example
character (len=512) :: line
!...
write (10,'(a)') trim(adjustl(line))
Internal Read and Write
editFortran has many hidden secrets and one of the most useful is that read
and write
statements can be used on character variables as if they were files. Hence the otherwise mystifying lack of functions to convert numbers to strings and vice versa. The character variable is treated as an 'internal file'
Example
character (120) :: text_in, text_out
integer :: i
real :: x
!...
write (text_in,'(A,I0)') 'i = ', i ! Formatted
!...
read (text_out,*) x ! List-directed
In addition to type conversion, this internal read/write can be used as a very flexible and bullet proof method of reading files where the contents may be of uncertain format. The external file is read line by line into a character variable, scan
and verify
can be used on the line to determine what is present and then an internal file read is done on the character variable to convert to real
, integer
, complex
etc as appropriate.
Recent Extensions
editcharacter(:), allocatable
editThe size of character scalar data can be deferred (or "allocatable") and therefore free from being required to be declared of a specific length. The resulting scalar can then be formally allocated, or it can be automatically allocated as shown in the following example.
Example
character (:), allocatable :: string
!...
string = 'abcdef'
!...
string = '1234567890'
!...
string = trim(line)
!...
It is even possible to declare an array of assumed length elements, as illustrated below.
Example
character (:), dimension (:), allocatable :: strings
However, this feature should be used carefully and some restrictions apply
Actual/Dummy arguments of type character
editIt is frequently the case that a procedure may be written with a character dummy argument where the length of that argument is not known in advance. Modern Fortran allows dummy arguments to be declared with assumed length using len=*
. Functions of type character can be written so that the result assumed a length related to the length of the dummy arguments.
Example
call this('Hello')
call this('Goodbye')
!...
subroutine this(string)
implicit none
character (len=*), intent (in) :: string
character (len=len(string)+5) :: temp
!...
end subroutine
In the above example, the character
variable temp
is declared to have 5 more characters than string, no matter how long the actual argument is. In the next example, a function return a string, the length of which is related to the length of one or more arguments.
Example
string = that('thing', 7)
!...
function that(in_string, n) result (out_string)
implicit none
character (len=*), intent (in) :: in_string
integer, intent(in) :: n
character (len=len(in_string)*n) :: out_string
!...
end function
In circumstances where the character function has to return a string and the length of this string is not simply related to the inputs, the assumed length, allocatable form described above can be used, and is illustrated in the case conversion examples below.
character parameters
editcharacter
parameters can be declared without explicitly stating the length, for example;
character (*), parameter :: place = 'COEFF_LIST_initialise'
Approaches to Case Conversion
editHere are some further examples of the ideas above, but directed to the case conversion for languages where case conversion as a concept exists. In the first example, the ASCII character set functions iachar
and achar
are used to check each character in a string consecutively.
Example
function up_case(in) result (out)
implicit none
character (*), intent (in) :: in
character (:), allocatable :: out
integer :: i, j
out = in ! Transfer whole array
do i = 1, LEN_TRIM(out) ! Each character
j = iachar(out(i:i)) ! Get the ASCII position
select case (j)
case (97:122) ! The lower case characters
out(i:i) = ACHAR(j-32) ! Offset to the upper case
end select
end do
end function up_case
An alternative approach that does not rely on the ASCII representation function could be as follows:
Example
function to_upper(in) result (out)
implicit none
character (*), intent (in) :: in
character (:), allocatable :: out
integer :: i, j
character (*), parameter :: upp = 'ABCDEFGHIJKLMNOPQRSTUVWXYZ'
character (*), parameter :: low = 'abcdefghijklmnopqrstuvwxyz'
out = in ! Transfer all characters
do i = 1, len_trim(out) ! All non-blanks
j = index(low, out(i:i)) ! Is ith character in low
if (j>0) out(i:i) = upp(j:j) ! Yes, then subst with upp
end do
end function to_upper
Which routine is quicker will depend on the relative speed of the index
and iachar
intrinsics. In one less than very scientific test, the first method above seemed to be slightly more than twice as fast as the second method, but this will vary from vendor to vendor.
structures
Structures, structured types, or derived types(DT) were first introduced in Fortran 90.[1] Structures allow the user to create data types that hold multiple different variables.
Derived types are often implemented within modules such that one can easily reuse them. They might also hold type-bound procedures which are intended to process the structure. The arguments pass(name), nopass
indicate whether the object should be passed as the first argument.
Similar to the character
data type, structures can be parameterized by two different parameter types: kind, len
. The kind
parameters must be known at compile type (consist of constants) whereas the len
parameters can change at runtime.
Simple example
editAs an example, we can define a new structure type, 'Fruit' which stores some basic fruit variables:
type fruit
real :: diameter ! in mm
real :: length ! in mm
character :: colour
end type
We can declare two 'fruit' variables, and assign them values:
type (fruit) :: apple, banana
apple = fruit(50, 45, "red")
banana%diameter = 40
banana%length = 200
banana%colour = "yellow"
And we can then use the fruit variables and their child values in normal Fortran operations.
Example: type-bound procedures
edit!> show the usage of type-bound procedures (pass/nopass arguments)
module test_m
implicit none
private
public test_type
type test_type
integer :: i
contains
procedure, nopass :: print_hello
procedure :: print_int
end type
contains
!> do not process type specific data => nopass
subroutine print_hello
print *, "hello"
end subroutine
!> process type specific data => first argument is "this" of type "class(test_type)"
!! use class and not type below !!!!
subroutine print_int(this)
class(test_type), intent(in) :: this
print *, "i", this%i
end subroutine
end module
program main
use test_m
implicit none
type (test_type) :: obj
obj%i = 1
call obj%print_hello
call obj%print_int
end program
Example: parameterized type
edit! testing types with params: kind + len
program main
implicit none
type matrix(rows, cols, k)
integer, len :: rows, cols
integer, kind :: k = kind(0.0) ! optional/default value
real (kind=k), dimension(rows, cols) :: vals
end type
type (matrix(rows=3, cols=3)) :: my_obj
end program
References
edit- ↑ A Look at Fortran 90 - Lahey computer systems
memory management
Introduction and historical background
editMost Fortran programs prior to the Fortran90 standard used self-contained data, without structures, and without much in the way of shared, structured data. However, it was possible to share data, in structured and unstructured ways, using common blocks. Furthermore, there used to be little memory management going on in a Fortran program. Until Fortran90 allocated storage wasn't even possible, except via certain extensions (e.g. Cray pointers). Modern Fortran, however, supports many modern programming paradigms, has full support for allocatable data (including allocatable types), and allows for the use of pointers.
Shared variables in modules
editSince Fortran90, shared variables are conveniently managed by the use of modules. Common blocks were used to define global memory prior to the Fortran90 standard; their use in modern Fortran is discouraged. A Fortran module can also contain subroutines and functions, but we shall leave the discussion of these features for later. As for the management of shared variables, they may be defined in a module:
module shared_variables
implicit none
private
integer, public, save :: shared_integer
integer, public, save :: another_shared_integer
type, public :: shared_type
logical :: my_logical
character :: my_character
end type shared_type
type (shared_type), public :: shared_stuff
end module shared_variables
Note that it is considered good practice to declare any module private, even if it contains only public variables. Although save
is the default for a variable in a module, meaning that it retains its previous value whenever the variables within the modules are used, it is sometimes considered good practice to make this explicit. The module can then be used in the main program:
program my_example
use shared_variables, only: shared_integer, shared_stuff
implicit none
integer :: some_local_integer
! This will work and assign shared_integer to some local variable.
shared_integer = some_local_integer
! This will print the component my_character from type shared_stuff
! to stdout.
write (*,*) shared_stuff%my_character
! This, however, will not work, since another_shared_integer was not
! imported from the module - the program will not compile.
shared_integer = another_shared_integer
end program my_example
Common blocks
editCommon blocks have been replaced by the use of public variables in modules in modern Fortran standards (Fortran90 and later). They are, however, historically important due to their use in older Fortran standards (77 and prior). A common block was Fortran's way of using shared, common storage for standards prior to Fortran90. In its simplest form, a common block is a way of defining global memory. Be careful, though. In most languages, each item in common memory is shared as a globally known name separately. In Fortran, however, the common block is a shared thing. I'll show several examples, but each example will share i
and another_integer
, and my_array
, a 10x10 array of real numbers.
In C, for instance, I can define the shared memory using:
int i;
int another_integer;
float my_array[10][10];
and use these data elsewhere with:
extern float my_array[10][10];
extern int i;
extern int another_integer;
Note that one module declares the storage, and another uses the storage. Also note that the definitions and usages are not in the same order. This is because in C, as in most languages, i
, another_integer
, and my_array
are all shared items. Not so in Fortran. In Fortran, all routines sharing this storage would have a definition something like this:
common i, another_integer, my_array
integer another_integer
real my_array(10,10)
This common block is stored as a block of data, as a linkable named structure. The only problem is that we don't know its name. Various compilers will give various names to this block. In some systems, the block actually doesn't have a name. We can avoid this problem by giving the structure a name. For instance,
common /my_block/ i, another_integer, my_array
integer another_integer
real my_array(10,10)
Using this form, two different Fortran programs can identify the same area of storage and share it, without having to know the structure of all shared storage. Also using this format, a C or other program could share the storage. For instance, a C program wanting to share this storage would declare the same storage as follows:
extern struct {
int i;
int another_integer;
float my_array[10][10];
} my_block;
In the above example, having the my_block
names match is critical, as well as having the types, sizes, and order match. However, having the names internally match is not since these names are known only locally. Also note that in the above example, Fortran's my_array(i,j)
matches C's my_block.my_aArray[j][i]
.
Byte alignment
editByte alignment of intrinsic data types can mostly be ensured simply by using the appropriate kind. Fortran does not have any way of automatically ensuring derived data types are byte aligned. However, it is quite simple for the programmer to ensure that appropriate padding for data is inserted. For example, let's say we have a derived type that contains a character and an integer
type :: my_type
integer (kind=4) :: ival
character (len=1) :: letter
end type
Arrays of this type will have elements of size 5 bytes. If we want the elements of an array of this type to align every 8 bytes we need to add 3 more bytes of padding. We can do this by adding characters that serve no other purpose than as padding.
type :: my_type
integer (kind=4) :: ival
character (len=1) :: letter
character (len=3) :: padding
end type
Memory management with pointers
editIn Fortran one can use pointers as some kind of alias for other data, e.g. such as a row in a matrix.
Pointer states
editEach pointer is in one of the following states
- undefined: right after definition if it has not been initialized
- defined
- null/not associated: not the alias of any data
- associated: alias of some data.
The intrinsic function associated
distinguished between the second and third states.
Assignments
editOverview
editWe will use the following example: Let a pointer ptr
be the alias of some real value x
.
real, target :: x
real, pointer :: ptr
ptr => x
For the next example we will use a real matrix matr
as target and the pointer ptr
should alias a specific row.
real, dimension (4, 4), target :: matr
real, dimension (:), pointer :: ptr
ptr => matr(2, :)
Pointers can also be appointed to other pointers. This causes them to be an alias of the same data that the first pointer is. See the example below.
real, target :: x
real, pointer :: ptr1, ptr2
ptr1 => x
ptr2 => ptr1
Ordinary vs. pointer assignments
editThe difference between ordinary and pointer assignments of pointers can be explained by the following equalities. Assume this setup
real, target :: x1, x2
real, pointer :: ptr1, ptr2
ptr1 => x1
ptr2 => x2
Ordinary assignments of pointers lead to assignments of the data they point to. One can see this by the following two statements which are equal.
! Two equal statements
ptr1 = ptr2
x1 = x2
In contrast, pointer assignments changes the alias of one of the pointers and no change on the underlying data. See the equal example statements.
! Two equal statements
ptr1 => ptr2
ptr1 => x2
Memory allocation
editAfter definition of pointers one can allocate memory for it using the allocate
command. The memory pointed to by a pointer is given free again by the deallocate
command. See the following example.
program main
implicit none
real, allocatable :: ptr
allocate (ptr)
ptr = 1.
print *, ptr
deallocate (ptr)
end program main
Examples
editAllocatable vs. pointer
editYou can declare an array to have a known number of dimensions, but an unknown size using allocation:
real, dimension (:,:), allocatable :: my_array
allocate (my_array(10,10))
deallocate (my_array)
You can also declare something as a pointer:
real, dimension (:,:), pointer :: some_pointer
allocate (some_pointer(10,10))
deallocate (some_pointer)
In archaic versions of FORTRAN (77 and before), you'd just have a big static array and use whatever portion of it you need.
error handling
Typically in an error situation, your program will stop, and you'll get an error message. The only exception to this is that at the end of read
and write
statements' parenthesized control list, you can add, err=label
to determine which line to jump to in the event of an error.
Modern Fortran (from Fortran 90 onwards) has introduced four main areas for error capture:
1) File handling and i/o operation error handling
2) IEEE floating point error detection and reporting
3) Dynamic allocation
4) Command line operations
File handling and I/O Operations
editAll the external file handling statements and I/O operations (open
, read
, write
, close
, inquire
, backspace
, endfile
, flush
, rewind
and wait
) can now take optional iostat
and iomsg
clauses. iostat
is an integer which returns a non-zero value if there is an error, in which case, the character variable assigned to iomsg
will return a brief error message. The non-zero integers and the messages are compiler dependent but the intrinsic module, iso_fortran_env
, gives access to two important values: iostat_end
and iostat_eor
. If an error occurs, and iostat
is non-zero, execution will not stop. The ERR clause is still supported but should not be used.
Example
editinteger :: my_iostat
character (256) :: my_iomsg
open (file='my.dat', unit=10, iostat=my_iostat, iomsg=my_iomsg)
if (my_iostat/=0) then
write (*,*) 'Open my.dat failed with iostat = ', my_iostat, ' iomsg = '//trim(my_iomsg)
end if
Note that the length required for the message character is vendor and error dependent.
IEEE floating point error detection and reporting
editThis is a big topic, but in essence modern Fortran provides access to three intrinsic modules: IEEE_arithmetic
, IEEE_exceptions
and IEEE_features
. These features can be used to intercept errors such as divide by zero and overflow but at the expense of some performance.
The IEEE_features
module controls access to the features the programmer may require, by use association in the scoping unit where the programmer places the use statement,
Example
editsubroutine blah
use, intrinsic :: ieee_features
! ...
end subroutine blah
See Chapter 11 in Metcalf et al, Modern Fortran Explained, OUP. All the necessary basic facilities exist in order for the programmer to construct a try/catch system if desired.
Dynamic Allocation
editModern Fortran allows run-time allocation and deallocation of arrays of any type, and a typical error might be to try to dynamically allocate an array so large that there is not enough memory, or an attempt to deallocate an array which is not already allocated. There are optional clauses stat
and errmsg
which can be used to prevent program failure and allow the programmer to take evasive action.
Example
editreal, allocatable, dimension (:) :: x
integer :: my_stat
character (256) :: my_errmsg
allocate (x(100000000), stat=my_stat, errmsg=my_errmsg)
if (my_stat/=0) then
write(*,*) 'Failed to allocate x with stat = ', my_stat, ' and errmsg '//trim(my_errmsg)
end if
These features are available in the equivalent coarray features.
Command Line Operations
editModern Fortran also supports error detection for the execution of command line operations,
Example
editinteger :: my_cmdstat
character (256) :: my_cmdmsg
call execute_command_line('my.exe', cmdstat=my_cmdstat, cmdmsg=my_cmdmsg )
if (my_cmdstat/=0) stop
In this example, the programmer of the my.exe program has the responsibility for what codes are returned and what error messages are exposed, except that -1 and -2 are reserved for allowing the compiler vendor indicating what features may be supported.
parallel processing
Parallelism is included in the Fortran 2008 standard. To use parallel features, a Fortran program must be compiled with parallelism enabled. For example, the Intel ifort compiler uses the flag -coarray
.
Images
editFortran uses a Partitioned Global Address Space (PGAS) model for parallelism. For each processor, the program is executed as a separate duplicate "image" of the program, each with their own separate memory partition. Consider the following program:
program hello
implicit none
write (*,*) 'Hello from ', this_image(), 'of', num_images()
end program hello
The intrinsic function this_image
returns the number of the image that is being executed, and the intrinsic function num_images
returns the total number of images for the program. If the program is compiled and executed with 4 processors, the output might look something like this:
Hello from image 1 of 4 Hello from image 4 of 4 Hello from image 2 of 4 Hello from image 3 of 4
Note that the images are executed asynchronously and so the output may not appear in the order 1, 2, 3 then 4.
Coarrays
edit
Coarrays are a way of communicating data in arrays across images. A coarray is just like a normal array but it has extra codimensions for each image. Codimensions can be declared and indexed using the square brackets []
. For example to declare a rank 1 coarray with size of 10 and a codimension of size 4:
real :: coarr(10)[4]
! Or you can use declaration attributes to do the same thing
real, dimension (10), codimension [4] :: another_coarr
Scalar variables can also be coarrays:
integer :: scalar[*]
Here, * denotes the maximum number of available processors. The codimensions can have multiple axes just like normal dimensions, however, there is a limit of rank 15 for codimensions. Transferring data between images is as simple as indexing on the codimensions.
! Set all images to 1
coarr = 1
! Indexing
another_coarr(3)[4] = coarr(3)[3]
OOP in Fortran
Object-oriented programming
editModule
editOverview
editData can be gathered in module
s. The general form is given by
module <name>
[use <module_names>]
[<declarations>]
contains
[<subroutines and functions>]
end module [<name>]
Data access
editThere are three possible access properties: public, private, protected
.
public
: Outside code has read and write access.private
: Outside code has no access.public, protected
: Outside code has read access.
Using module in other code
editOne can include the module's public data in outside code. There are three ways.
use <moduleName>
: includes all public data and methodsuse <moduleName>, <renames>
: includes all public data and methods, but renames some public data or methodsuse <moduleName>, only: <subset>
: includes only some public data and methods
Example
editGeneral overview
editmodule test_m
implicit none
private ! All data is by default private.
! These procedures are set public -> accessible outside
public print_coords, set_coords
real :: x, y ! Not accessible outside module.
contains
subroutine print_coords
print *, "x, y", x, y
end subroutine
subroutine set_coords(new_x, new_y)
real, intent(in) :: new_x, new_y
x = new_x
y = new_y
end subroutine
end module
program main
use test_m ! Import the "test_m" module
implicit none
call set_coords(1.0, 1.0) ! Call the public procedure from test_mod
call print_coords
end program
Data access
editmodule data_access_m
implicit none
private
public a, b
protected b
private c
integer :: a = 1
integer :: b = 1
integer :: c = 1
end module
program main
use data_access_m
! Accessing public object works.
print *, a
! Editing public object works.
a = 2
! Accessing protected object works.
print *, b
! Editing protected object does not work.
!b = 2 <- ERROR
! Accessing private object does not work
!print *, c <- ERROR
! Editing private object does not work
!c = 2 <- ERROR
end program
Using modules
editmodule test_module
implicit none
private
integer, public :: a = 1
integer, public, protected :: b = 1
integer, private :: c = 1
end module test_module
!> Import all public data of test_module.
program main
use test_module
print *, a, b
end program main
!> Import all data, and rename.
program main
use test_module, better_name => a
! New name use available.
print *, better_name
! Old name is not available anymore.
!print *, a <- ERROR
end program main
!> Import only a subset of the public data.
program main
use test_module, only : a
! Only a is loaded
print *, a
! b is not loaded
!print *, b <- ERROR
end program main
Submodule
editModules can be extended using submodules. Multiple advantages arise
- splitting of large modules
- splitting of interface definitions and implementations such that dependent modules do not need to be recompiled if the implementations change
- two modules need data from each other.
Example
editSplitting of definitions and implementations
edit!> simple module about circles
module circle_mod
implicit none
private
public :: area, radius
real :: radius
real, parameter :: PI = 3.1415
interface ! Interface block needed. Each function implemented via submodule needs an entry here.
module function area() ! Important. Note the "module" keyword.
real :: area
end function
end interface
end module
submodule (circle_mod) circle_subm ! Submodule (parent_mod) child_mod.
contains
module function area() ! Again "module" keyword.
area = PI*radius**2
end function
end submodule
program main
use circle_mod
implicit none
radius = 1.0
print *, "area:", area()
end program
Derived data types
editIn Fortran one can derive structures off of other structures, so called derived data types. The derived types will have the features of the parent type as well as the newly added ones and the general syntax is given by:
type, extends(<parentTypeName>) :: <newTypeName>
<definitions>
end type
The following example shows different types of people within a company.
module company_data_mod
implicit none
private
public phone_type, address_type, person_type, employee_type, salaried_worker_type, hourly_worker_type
type phone_type
integer :: area_code, number
end type
type address_type
integer :: number
character (len=:), allocatable :: street, city
character (len=2) :: state
integer :: zip_code
end type
type person_type
character (len=:), allocatable :: name
type (address_type) :: address
type (phone_type) :: phone
character (len=:), allocatable :: remarks
end type
type, extends (person_type) :: employee_type
integer :: phone_extension, mail_stop, id_number
end type
type, extends (employee_type) :: salaried_worker_type
real :: weekly_salary
end type
type, extends (employee_type) :: hourly_worker_type
real :: hourly_wage, overtime_factor, hours_worked
end type
end module
program main
use company_data_mod
implicit none
type (hourly_worker_type) :: obj
end program
Destructors
editOne can define procedures which will be invoked before the object is automatically deleted (out of scope). This is done with the statement final
. The following example illustrates it
module person_m
implicit none
type person
integer, allocatable :: numbers(:)
contains
final :: del
end type
contains
subroutine del(this)
!! example for a derived type's destructor. allocatables are
!! deallocated automatically anyways. this is just to show the usage of
!! "final".
type (person), intent (inout) :: this
if (allocated(this%numbers)) deallocate (this%numbers)
end subroutine
end module
Abstract base type and deferred procedure
editOne can set the base type as abstract
such that one cannot initialize objects of that type but one can derive sub-types of it (via extends
). Specific procedures which should be defined in the sub-type need the property deferred
as well as an explicit interface.
The following example illustrates their use.
module shape_m
implicit none
type, abstract :: shape
real :: a, b
contains
procedure :: print => shape_print
procedure (area_shape), deferred :: area
end type
interface
real function area_shape(this)
import :: shape
class (shape), intent (in) :: this
end function
end interface
contains
subroutine shape_print(this)
class (shape), intent (in) :: this
print *, 'a,b', this%a, this%b
end subroutine
end module
module line_m
use shape_m
implicit none
private
public line
type, extends (shape) :: line
contains
procedure :: area
end type
contains
real function area(this)
class (line), intent (in) :: this
area = abs(this%a - this%b)
end function
end module
module rectangle_m
use shape_m
implicit none
private
public rectangle
type, extends(shape) :: rectangle
contains
procedure :: area
end type
contains
real function area(this)
class (rectangle), intent (in) :: this
area = this%a * this%b
end function
end module
program main
use line_m
use rectangle_m
implicit none
type (line) :: l
type (rectangle) :: r
! line
l%a = 2.0
l%b = 4.0
print *, "line ... "
call l%print
print *, "-> from: ", l%a
print *, "-> to: ", l%b
print *, "-> length:", l%area()
! rectangle
r%a = 3.0
r%b = 5.0
print *
print *, "rectangle ..."
call r%print
print *, "-> side a:", r%a
print *, "-> side b:", r%b
print *, "-> area: ", r%area()
end program
Polymorphic Pointer
editOne can create pointers to child classes by using type definitions in allocate
statements and the select type
environment.
The following example highlights its use.
module shape_m
implicit none
type, abstract :: shape
! Just an empty class used to implement a parent class.
! reason for abstract: there shouldnt be objects of TYPE(!) shape, just
! polymorphic CLASS instances.
end type
end module
module line_m
use shape_m
implicit none
type, extends (shape) :: line
! A child class w/ one attribute.
! Reason for extends(shape): polymorphic shape pointer can point to
! objects of this type.
real :: length
end type
end module
module rectangle_m
use shape_m
implicit none
type, extends (shape) :: rectangle
! A child class w/ another attribute
! Reason for extends(shape): (see explanation in line type)
real :: area
end type
end module
program main
use rectangle_m
use line_m
implicit none
class (shape), allocatable :: sh ! Pointer to parent class.
! allocate (line :: sh)
allocate (rectangle :: sh) ! Allocate using child types
select type (x => sh) ! Associate block. "x" will be a pointer to the child object and of its type(!!)
type is (line) ! Select the right child type (the one we used in the allocate statement)
x%length = 1.0
print *, 'line length', x%length
type is (rectangle)
x%area = 2.0
print *, 'rectangle area', x%area
! class is () ! Select by using classes.
class default ! If nothing of the above applied.
error stop 'class/type not specified!'
end select
end program
language extensions
Procedure Overloading
editLike several other languages, Fortran 90 and newer supports the ability to select the appropriate routine from a list of routines based on the arguments passed. This selection is done at compile time and is thus unencumbered by run-time performance penalties. This feature is accessed by use of modules and the interface block.
In the following example, a module is specified which contains an interface function f
which can handle arguments of various types.
module extension_m
implicit none
private
public f ! Only the interface f is accessable outside the module.
interface f ! The overloaded function is called "f".
module procedure f_i ! "f(x)" for integer argument "x" will call "f_i"
module procedure f_r ! "f(x)" for real argument "x" will call "f_r"
module procedure f_z ! ... complex .... "f_z"
end interface
contains
integer function f_i(x) result (y)
integer, intent (in) :: x
y = x**2 - 1
end function
real function f_r(x) result(y)
real, intent (in) :: x
y = x**2 - 1.0
end function
complex function f_z(x) result(y)
complex, intent (in) :: x
y = x**2 - 1.0
end function
end module
A program which uses this module now has access to a single interface function f
which accepts arguments that are of integer, real, or complex type. The return type of the function is the same as the input type. In this way the routine is much like many of the intrinsic functions defined as part of the Fortran standard. An example program is given below:
program main
use extension_m
implicit none
complex :: xz, yz
integer :: xi, yi
real :: xr, yr
xi = 2
xr = 2.0
xz = 2.0
yi = f(xi)
yr = f(xr)
yz = f(xz)
end program
Intrinsic functions
editOne can extend intrinsic functions. This is similar to overload operators.
Here we will demonstrate this by extending the sqrt
function. The intrinsic function is not implemented for arguments of integer type. This is because there is no clear idea how to define the result of non integer type (e.g. , but how to define ). We implement a method here where the result is always the nearest integer.
module sqrt_int_m
implicit none
private
public sqrt
! use intrinsic sqrt for data types which are not overloaded
intrinsic :: sqrt
! extend sqrt for integers
interface sqrt
module procedure sqrt_int
end interface
contains
pure integer function sqrt_int(i)
integer, intent (in) :: i
sqrt_int = nint(sqrt(real(i)))
end function
end module
program main
use sqrt_int_m
implicit none
integer :: i
! sqrt can be called by real and integer arguments
do i = 1, 7
print *, "i, sqrt(i), sqrt(real(i))", i, sqrt(i), sqrt(real(i))
end do
end program
Derived Data Types
editFortran 90 and newer supports the creation of new data types which are composites of existing types. In some ways this is similar to an array, but the components need not be all of the same type and they are referenced by name, not index. Such data types must be declared before variables of that type, and the declaration must be in scope to be used. An example of a simple 2d vector type is given below.
type :: vec_t
real :: x,y
end type
Variables of this type can be declared much like any other variable, including variable characteristics such are pointer or dimension.
type (vec_t) :: a,b
type (vec_t), dimension (10) :: vecs
Using derived data types, the Fortran language can be extended to represent more diverse types of data than those represented by the primitive types.
Operator Overloading
editOperators can be overloaded so that derived data types support the standard operations, opening the possibility of extending the Fortran language to have new types which behave nearly like the native types.
Assignment
editThe assignment operator = can be overloaded. We will demonstrate this by the following example. Here, we define how the assignment of a logical type on the left and an integer on the right should be performed.
module overload_assignment_m
implicit none
private
public assignment (=)
interface assignment (=)
module procedure logical_gets_integer
end interface
contains
subroutine logical_gets_integer(tf, i)
logical, intent (out) :: tf
integer, intent (in) :: i
tf = (i == 0)
end subroutine
end module
program main
use overload_assignment_m
implicit none
logical :: tf
tf = 0
print *, "tf=0:", tf ! Yields: T
tf = 1
print *, "tf=1:", tf ! Yields: F
end program
Intrinsic operators
editOne can overload intrinsic operators, such as +,-,*
.
In the following example we will overload the *
operator to work as the logical .and.
.
module overload_asterisk_m
implicit none
private
public operator (*)
interface operator (*)
module procedure logical_and
end interface
contains
pure logical function logical_and(log1, log2)
logical, intent (in) :: log1, log2
logical_and = (log1 .and. log2)
end function
end module
program main
use overload_asterisk_m
implicit none
logical, parameter :: T = .true., F = .false.
print *, "T*T:", T*T ! Yields: T
print *, "T*F:", T*F ! Yields: F
print *, "F*T:", F*T ! Yields: F
print *, "F*F:", F*F ! Yields: F
end program
New operators
editOne can create newly self-created operators.
We demonstrate this by the following example: We create an unary operator .even. <int>
which outputs a logical
if the given integer
is even as well as a binary operator <reals> .cross. <reals>
that performs the standard cross product of two real
vectors.
module new_operators_m
implicit none
private
public operator (.even.)
public operator (.cross.)
interface operator (.even.)
module procedure check_even
end interface
interface operator (.cross.)
module procedure cross_product
end interface
contains
pure logical function check_even(i)
integer, intent (in) :: i
check_even = (modulo(i, 2) == 0)
end function
function cross_product(x, y) result(z)
real, intent (in) :: x(3), y(3)
real :: z(3)
z(1) = x(2)*y(3) - x(3)*y(2)
z(2) = x(3)*y(1) - x(1)*y(3)
z(3) = x(1)*y(2) - x(2)*y(1)
end function
end module
program main
use new_operators_m
implicit none
integer :: i
real :: x(3), y(3)
do i = 1, 6
print *, "i:", i, "even?", .even. i
end do
print *
x = [ 1, 2, 3]
y = [-1, 2, -3]
print *, 'x', x
print *, 'y', y
print *, 'x cross_product y', x .cross. y
end program
Mixing languages
Types
editFortran types map quite well to intrinsic types in other compiled languages. The following is a table of Fortran-to-C types:
Fortran C
======= =
COMMON extern struct
INTEGER*1 signed char
INTEGER*2 short
INTEGER*4 long
INTEGER*8 long long
INTEGER int
REAL float
REAL*4 float
REAL*8 double
REAL*16 long double
LOGICAL int
LOGICAL*n char [n]
CHARACTER*n char [n]
DOUBLE PRECISION double
COMPLEX float [2]
COMPLEX*8 float [2]
COMPLEX*16 double [2]
COMPLEX*32 long double [2]
Arrays
editThe layout of Fortran arrays in memory contrasts with arrays in C and many C-based languages. When iterating over contiguous array elements in C, the rightmost array subscript varies the fastest, while in Fortran, the leftmost array subscript varies the fastest. Hence the element following x(1,1)
in contiguous memory is x(2,1)
, not x(1,2)
. Furthermore, the element sub-scripting in C starts at 0, while Fortran starts at 1 by default. An element in Fortran may be x(1)
, while the equivalent value in C code would be x[0]
. However, when passing a Fortran array to a C function, you do not need to (and should not) reshape the array into C-style subscripts first; the compiler will automatically do this for you.
Global Storage
editSee the Common Blocks section.
Subroutine and function calls
editMany languages push their arguments onto the stack, some as constants and some as addresses. In most compilers, Fortran will compile a block of pointers to variables and constants, and push the address of that block. So, if we had a Fortran procedure defined as follows:
subroutine my_sub(i, j, x)
then the C definition would be:
struct my_sub_args {
int *i;
int *j;
float *x;
} my_sub_args = {&i, &j, &x};
void my_sub(my_sub_args*);
The C code could call the routine as follows:
my_sub(&my_sub_args);
The PL/1 Special Case
editIn PL/1, you can define an external common block, subroutine, or procedure to be of type FORTRAN. When you do this, everything, down to subscript order, will be handled for you. Likewise, you can define a PL/1 item, such as a subroutine, to be of type FORTRAN, and it will then be callable by Fortran using Fortran's calling conventions.
Documenting Fortran
FORD - FORtran Documenter
editA great program for documenting fortran source code is FORD.
See the github page for instructions on installing, and usage of FORD: github.com.
Documenting Fortran using Doxygen
editDocumentation can be created right from source code using Doxygen.
The commandline program doxygen
creates the documentation using configuration files.
The gui program doxygen-wizard
helps creating those files.
Overview
editThe source code needs to be documented using special comment syntax: !>
, and !!
.
One should always set OPTIMIZE_FOR_FORTRAN = YES
within the configuration file.
Doxygen commands are usually ended by an empty comment line or a new doxygen command.
Note that support for Fortran is rather bad in doxygen.
Even simple constructs such as public/private
statements inside of type
s are not supported (see here github.com).
LaTeX
editOne can also include LaTeX code within the documentation. Doxygen's website gives detailed information.
Examples
editsubroutine
edit!> @brief inserts a value into an ordered array
!!
!! An array "list" consisting of n ascending ordered values. The method insert a
!! "new_entry" into the array.
!! hint: use cshift and eo-shift
!!
!! @param[in,out] list a real array, size: max_size
!! @param[in] n current values in the array
!! @param[in] max_size size if the array
!! @param[in] new_entry the value to insert
subroutine insert(list, n, max_size, new_entry)
implicit none
real, dimension (:), intent (inout) :: list
integer, intent (in) :: n, max_size
real, intent (in) :: new_entry
! code ........
end subroutine insert
function
edit!> @brief calcs the angle between two given vectors
!!
!! using the standard formula:
!! \f$\cos \theta = \frac{ \vec v \cdot \vec w}{\abs{v}\abs{w}}\f$.
!!
!! @param[in] \f$v,w\f$ real vectors
!! @return a real value describing the angle. 0 if \f$\abs v\f$ or \f$\abs w\f$ below a
!! threshold.
pure function calc_angle(v, w) result (theta)
implicit none
real, dimension (:), intent (in) :: v, w
real :: theta
! code .......
end function calc_angle
Troubleshooting
editEmpty documentation
editIf the documentation is just an empty page then one can try setting EXTRACT_ALL = YES
.
prettify code
Prettify Source Code
editThere are tools available to automatically edit source code such that it is more easily readable. This includes topics such as
- indentation
- alignment
- lower/uppercase words
fprettify
editA python script fprettify for auto-indentation and whitespace formatting is readily available from github or PyPI.
Fortran examples
The following Fortran code examples or sample programs show different situations depending on the compiler. The first set of examples are for the Fortran II, IV, and 77 compilers. The remaining examples can be compiled and run with any newer standard Fortran compiler (see the end of the main Fortran article for lists of compilers). By convention most contemporary Fortran compilers select the language standard to use during compilation based on source code file name suffix: FORTRAN 77 for .f
(or the less common .for
), Fortran 90 for .f90
, Fortran 95 for .f95
. Other standards, if supported, may be selected manually with a command line option.
FORTRAN II, IV, and 77 compilers
editNOTE: Before FORTRAN 90, most FORTRAN compilers enforced fixed-format source code, a carryover from IBM punch cards
- comments must begin with a * or C or ! in column 1
- statement labels must occur in columns 1-5
- continuation lines must have a non-blank character in column 6
- statements must start in column 7
- the line-length may be limited to 72 characters (derived from the 80-byte width of a punch-card, with last 8 characters reserved for (optional) sequence numbers)
If errors are produced when you compile your FORTRAN code, first check the column alignment. Some compilers also offer free form source by using a compiler flag
Area Of a Triangle program
editSimple Fortran II program
editOne data card input
If one of the input values is zero, then the program will end with an error code of "1" in the job control card listing following the execution of the program. Normal output will be one line printed with A, B, C, and AREA. No specific units are stated.
C AREA OF A TRIANGLE - HERON'S FORMULA
C INPUT - CARD READER UNIT 5, INTEGER INPUT
C OUTPUT -
C INTEGER VARIABLES START WITH I,J,K,L,M OR N
READ(5,501) IA,IB,IC
501 FORMAT(3I5)
IF (IA) 701, 777, 701
701 IF (IB) 702, 777, 702
702 IF (IC) 703, 777, 703
777 STOP 1
703 S = (IA + IB + IC) / 2.0
AREA = SQRT( S * (S - IA) * (S - IB) * (S - IC) )
WRITE(6,801) IA,IB,IC,AREA
801 FORMAT(4H A= ,I5,5H B= ,I5,5H C= ,I5,8H AREA= ,F10.2,
$13H SQUARE UNITS)
STOP
END
Simple Fortran IV program
editMultiple data card input
This program has two input checks: one for a blank card to indicate end-of-data, and the other for a zero value within the input data. Either condition causes a message to be printed.
C AREA OF A TRIANGLE - HERON'S FORMULA
C INPUT - CARD READER UNIT 5, INTEGER INPUT, ONE BLANK CARD FOR END-OF-DATA
C OUTPUT - LINE PRINTER UNIT 6, REAL OUTPUT
C INPUT ERROR DISPAY ERROR MESSAGE ON OUTPUT
501 FORMAT(3I5)
601 FORMAT(4H A= ,I5,5H B= ,I5,5H C= ,I5,8H AREA= ,F10.2,
$13H SQUARE UNITS)
602 FORMAT(10HNORMAL END)
603 FORMAT(23HINPUT ERROR, ZERO VALUE)
INTEGER A,B,C
10 READ(5,501) A,B,C
IF(A.EQ.0 .AND. B.EQ.0 .AND. C.EQ.0) GO TO 50
IF(A.EQ.0 .OR. B.EQ.0 .OR. C.EQ.0) GO TO 90
S = (A + B + C) / 2.0
AREA = SQRT( S * (S - A) * (S - B) * (S - C) )
WRITE(6,601) A,B,C,AREA
GO TO 10
50 WRITE(6,602)
STOP
90 WRITE(6,603)
STOP
END
Simple Fortran 77 program
editMultiple data card input
This program has two input checks in the READ statement with the END and ERR parameters, one for a blank card to indicate end-of-data; and the other for zero value along with valid data. In either condition, a message will be printed.
C AREA OF A TRIANGLE - HERON'S FORMULA
C INPUT - CARD READER UNIT 5, INTEGER INPUT, NO BLANK CARD FOR END OF DATA
C OUTPUT - LINE PRINTER UNIT 6, REAL OUTPUT
C INPUT ERROR DISPAYS ERROR MESSAGE ON OUTPUT
501 FORMAT(3I5)
601 FORMAT(" A= ",I5," B= ",I5," C= ",I5," AREA= ",F10.2,
$"SQUARE UNITS")
602 FORMAT("NORMAL END")
603 FORMAT("INPUT ERROR OR ZERO VALUE ERROR")
INTEGER A,B,C
10 READ(5,501,END=50,ERR=90) A,B,C
IF(A=0 .OR. B=0 .OR. C=0) GO TO 90
S = (A + B + C) / 2.0
AREA = SQRT( S * (S - A) * (S - B) * (S - C) )
WRITE(6,601) A,B,C,AREA
GO TO 10
50 WRITE(6,602)
STOP
90 WRITE(6,603)
STOP
END
"Retro" FORTRAN IV
editA retro example of a FORTRAN IV (later evolved into FORTRAN 66) program deck is available on the IBM 1130 page, including the IBM 1130 DM2 JCL required for compilation and execution. An IBM 1130 emulator is available at IBM 1130.org that will allow the FORTRAN IV program to be compiled and run on a PC.
Hello, World program
editIn keeping with computing tradition, the first example presented is a simple program to display the words "Hello, world" on the screen (or printer).
FORTRAN 66 (also FORTRAN IV)
edit C FORTRAN IV WAS ONE OF THE FIRST PROGRAMMING
C LANGUAGES TO SUPPORT SOURCE COMMENTS
WRITE (6,7)
7 FORMAT(13H HELLO, WORLD)
STOP
END
This program prints "HELLO, WORLD" to Fortran unit number 6, which on most machines was the line printer or terminal. (The card reader or keyboard was usually connected as unit 5). The number 7 in the WRITE
statement refers to the statement number of the corresponding FORMAT
statement. FORMAT
statements may be placed anywhere in the same program or function/subroutine block as the WRITE
statements which reference them. Typically a FORMAT
statement is placed immediately following the WRITE
statement which invokes it; alternatively, FORMAT
statements are grouped together at the end of the program or subprogram block. If execution flows into a FORMAT
statement, it is a no-op; thus, the example above has only two executable statements, WRITE
and STOP
.
The initial 13H
in the FORMAT
statement in the above example defines a Hollerith constant, here meaning that the 13 characters immediately following are to be taken as a character constant (note that the Hollerith constant is not surrounded by delimiters). (Some compilers also supported character literals enclosed in single quotes, a practice that came to be standard with FORTRAN 77.)
The space immediately following the 13H is a carriage control character, telling the I/O system to advance to a new line on the output. A zero in this position advances two lines (double space), a 1 advances to the top of a new page and + character will not advance to a new line, allowing overprinting.
FORTRAN 77
editAs of FORTRAN 77, single quotes are used to delimit character literals, and inline character strings may be used instead of references to FORMAT
statements. Comment lines may be indicated with either a C
or an asterisk (*
) in column 1.
PROGRAM HELLO
* The PRINT statement is like WRITE,
* but prints to the standard output unit
PRINT '(A)', 'Hello, world'
STOP
END
Fortran 90
editAs of Fortran 90, double quotes are allowed in addition to single quotes. An updated version of the Hello, world example (which here makes use of list-directed I/O, supported as of FORTRAN 77) could be written in Fortran 90 as follows:
program HelloWorld
write (*,*) 'Hello, world!' ! This is an inline comment
end program HelloWorld
Fortran 77 examples
editGreatest common divisor
editThe following introductory example in FORTRAN 77 finds the greatest common divisor for two numbers and using a verbatim implementation of Euclid's algorithm.
* euclid.f (FORTRAN 77)
* Find greatest common divisor using the Euclidean algorithm
PROGRAM EUCLID
PRINT *, 'A?'
READ *, NA
IF (NA.LE.0) THEN
PRINT *, 'A must be a positive integer.'
STOP
END IF
PRINT *, 'B?'
READ *, NB
IF (NB.LE.0) THEN
PRINT *, 'B must be a positive integer.'
STOP
END IF
PRINT *, 'The GCD of', NA, ' and', NB, ' is', NGCD(NA, NB), '.'
STOP
END
FUNCTION NGCD(NA, NB)
IA = NA
IB = NB
1 IF (IB.NE.0) THEN
ITEMP = IA
IA = IB
IB = MOD(ITEMP, IB)
GOTO 1
END IF
NGCD = IA
RETURN
END
The above example is intended to illustrate the following:
- The
PRINT
andREAD
statements in the above use '*
' as a format, specifying list-directed formatting. List-directed formatting instructs the compiler to make an educated guess about the required input or output format based on the following arguments. - As the earliest machines running Fortran had restricted character sets, FORTRAN 77 uses abbreviations such as
.EQ.
,.NE.
,.LT.
,.GT.
,.LE.
, and.GE.
to represent the relational operators =, ≠, <, >, ≤, and ≥, respectively. - This example relies on the implicit typing mechanism to specify the INTEGER types of
NA
,NB
,IA
,IB
, andITEMP
. - In the function
NGCD(NA, NB)
, the values of the function argumentsNA
andNB
are copied into the local variablesIA
andIB
respectively. This is necessary as the values ofIA
andIB
are altered within the function. Because argument passing in Fortran functions and subroutines utilize call by reference by default (rather than call by value, as is the default in languages such as C), modifyingNA
andNB
from within the function would effectively have modified the corresponding actual arguments in the mainPROGRAM
unit which called the function.
The following shows the results of compiling and running the program.
$ g77 -o euclid euclid.f
$ euclid
A?
24
B?
36
The GCD of 24 and 36 is 12.
Complex numbers
editThe following FORTRAN 77 example prints out the values of (where ) for values of .
* cmplxd.f (FORTRAN 77)
* Demonstration of COMPLEX numbers
*
* Prints the values of e ** (j * i * pi / 4) for i = 0, 1, 2, ..., 7
* where j is the imaginary number sqrt(-1)
PROGRAM CMPLXD
IMPLICIT COMPLEX(X)
PARAMETER (PI = 3.141592653589793, XJ = (0, 1))
DO 1, I = 0, 7
X = EXP(XJ * I * PI / 4)
IF (AIMAG(X).LT.0) THEN
PRINT 2, 'e**(j*', I, '*pi/4) = ', REAL(X), ' - j',-AIMAG(X)
ELSE
PRINT 2, 'e**(j*', I, '*pi/4) = ', REAL(X), ' + j', AIMAG(X)
END IF
2 FORMAT (A, I1, A, F10.7, A, F9.7)
1 CONTINUE
STOP
END
The above example is intended to illustrate the following:
- The
IMPLICIT
statement can be used to specify the implicit type of variables based on their initial letter if different from the default implicit typing scheme described above. In this example, this statement specifies that the implicit type of variables beginning with the letterX
shall beCOMPLEX
. - The
PARAMETER
statement may be used to specify constants. The second constant in this example (XJ
) is given the complex-valued value , where is the imaginary unit . - The first number in the
DO
statement specifies the number of the last statement considered to be within the body of theDO
loop. In this example, as neither theEND IF
nor theFORMAT
is a single executable statement, theCONTINUE
statement (which does nothing) is used simply in order for there to be some statement to denote as the final statement of the loop. EXP()
corresponds to the exponential function . In FORTRAN 77, this is a generic function, meaning that it accepts arguments of multiple types (such asREAL
and, in this example,COMPLEX
). In FORTRAN 66, a specific function would have to be called by name depending on the type of the function arguments (for this example,CEXP()
for aCOMPLEX
-valued argument).- When applied to a
COMPLEX
-valued argument,REAL()
andAIMAG()
return the values of the argument's real and imaginary components, respectively.
Incidentally, the output of the above program is as follows (see the article on Euler's formula for the geometric interpretation of these values as eight points spaced evenly about a unit circle in the complex plane).
$ cmplxd
e**(j*0*pi/4) = 1.0000000 + j0.0000000
e**(j*1*pi/4) = 0.7071068 + j0.7071068
e**(j*2*pi/4) = 0.0000000 + j1.0000000
e**(j*3*pi/4) = -0.7071068 + j0.7071068
e**(j*4*pi/4) = -1.0000000 - j0.0000001
e**(j*5*pi/4) = -0.7071066 - j0.7071069
e**(j*6*pi/4) = 0.0000000 - j1.0000000
e**(j*7*pi/4) = 0.7071070 - j0.7071065
Error can be seen occurring in the last decimal place in some of the numbers above, a result of the COMPLEX
data type representing its real and imaginary components in single precision. Incidentally, Fortran 90 also made standard a double-precision complex-number data type (although several compilers provided such a type even earlier).
FORTRAN 90 program to find the area of a triangle
editprogram area
implicit none
real :: A, B, C, S
! area of a triangle
read *, A, B, C
S = (A + B + C)/2
A = sqrt(S*(S-A)*(S-B)*(S-C))
print *,"area =",A
stop
end program area
Fortran 90/95 examples
editSummations with a DO loop
editIn this example of Fortran 90 code, the programmer has written the bulk of the code inside of a DO loop. Upon execution, instructions are printed to the screen and a SUM variable is initialized to zero outside the loop. Once the loop begins, it asks the user to input any number. This number is added to the variable SUM every time the loop repeats. If the user inputs 0, the EXIT statement terminates the loop, and the value of SUM is displayed on screen.
Also apparent in this program is a data file. Before the loop begins, the program creates (or opens, if it has already been run before) a text file called "SumData.DAT". During the loop, the WRITE statement stores any user-inputted number in this file, and upon termination of the loop, also saves the answer.
! sum.f90
! Performs summations using in a loop using EXIT statement
! Saves input information and the summation in a data file
program summation
implicit none
integer :: sum, a
print *, "This program performs summations. Enter 0 to stop."
open (unit=10, file="SumData.DAT")
sum = 0
do
print *, "Add:"
read *, a
if (a == 0) then
exit
else
sum = sum + a
end if
write (10,*) a
end do
print *, "Summation =", sum
write (10,*) "Summation =", sum
close(10)
end
When executed, the console would display the following:
This program performs summations. Enter 0 to stop.
Add:
1
Add:
2
Add:
3
Add:
0
Summation = 6
And the file SumData.DAT would contain:
1
2
3
Summation = 6
Calculating cylinder area
editThe following program, which calculates the surface area of a cylinder, illustrates free-form source input and other features introduced by Fortran 90.
program cylinder
! Calculate the surface area of a cylinder.
!
! Declare variables and constants.
! constants=pi
! variables=radius squared and height
implicit none ! Require all variables to be explicitly declared
integer :: ierr
character(1) :: yn
real :: radius, height, area
real, parameter :: pi = 3.141592653589793
interactive_loop: do
! Prompt the user for radius and height
! and read them.
write (*,*) 'Enter radius and height.'
read (*,*,iostat=ierr) radius,height
! If radius and height could not be read from input,
! then cycle through the loop.
if (ierr /= 0) then
write(*,*) 'Error, invalid input.'
cycle interactive_loop
end if
! Compute area. The ** means "raise to a power."
area = 2*pi * (radius**2 + radius*height)
! Write the input variables (radius, height)
! and output (area) to the screen.
write (*,'(1x,a7,f6.2,5x,a7,f6.2,5x,a5,f6.2)') &
'radius=',radius,'height=',height,'area=',area
yn = ' '
yn_loop: do
write(*,*) 'Perform another calculation? y[n]'
read(*,'(a1)') yn
if (yn=='y' .or. yn=='Y') exit yn_loop
if (yn=='n' .or. yn=='N' .or. yn==' ') exit interactive_loop
end do yn_loop
end do interactive_loop
end program cylinder
Dynamic memory allocation and arrays
editThe following program illustrates dynamic memory allocation and array-based operations, two features introduced with Fortran 90. Particularly noteworthy is the absence of DO
loops and IF
/THEN
statements in manipulating the array; mathematical operations are applied to the array as a whole. Also apparent is the use of descriptive variable names and general code formatting that comport with contemporary programming style. This example computes an average over data entered interactively.
program average
! Read in some numbers and take the average
! As written, if there are no data points, an average of zero is returned
! While this may not be desired behavior, it keeps this example simple
implicit none
integer :: number_of_points
real, dimension(:), allocatable :: points
real :: average_points=0., positive_average=0., negative_average=0.
write (*,*) "Input number of points to average:"
read (*,*) number_of_points
allocate (points(number_of_points))
write (*,*) "Enter the points to average:"
read (*,*) points
! Take the average by summing points and dividing by number_of_points
if (number_of_points > 0) average_points = sum(points)/number_of_points
! Now form average over positive and negative points only
if (count(points > 0.) > 0) positive_average = sum(points, points > 0.) &
/count(points > 0.)
if (count(points < 0.) > 0) negative_average = sum(points, points < 0.) &
/count(points < 0.)
deallocate (points)
! Print result to terminal
write (*,'(''Average = '', 1g12.4)') average_points
write (*,'(''Average of positive points = '', 1g12.4)') positive_average
write (*,'(''Average of negative points = '', 1g12.4)') negative_average
end program average
Writing functions
editModern Fortran features available for use with procedures, including deferred-shape, protected, and optional arguments, are illustrated in the following example, a function to solve a system of linear equations.
function gauss_sparse(num_iter, tol, b, A, x, actual_iter) result(tol_max)
! This function solves a system of equations (Ax = b) by using the Gauss-Seidel Method
implicit none
real :: tol_max
! Input: its value cannot be modified from within the function
integer, intent(in) :: num_iter
real, intent(in) :: tol
real, intent(in), dimension(:) :: b, A(:,:)
! Input/Output: its input value is used within the function, and can be modified
real, intent(inout) :: x(:)
! Output: its value is modified from within the function, only if the argument is required
integer, optional, intent(out) :: actual_iter
! Locals
integer :: i, n, iter
real :: xk
! Initialize values
n = size(b) ! Size of array, obtained using size intrinsic function
tol_max = 2. * tol
iter = 0
! Compute solution until convergence
convergence_loop: do while (tol_max >= tol .and. iter < num_iter); iter = iter + 1
tol_max = -1. ! Reset the tolerance value
! Compute solution for the k-th iteration
iteration_loop: do i = 1, n
! Compute the current x-value
xk = (b(i) - dot_product(A(i,:i-1),x(:i-1)) - dot_product(A(i,i+1:n),x(i+1:n))) / A(i, i)
! Compute the error of the solution
! dot_product(a,v)=a'b
tol_max = max((abs(x(i) - xk)/(1. + abs(xk))) ** 2, abs(A(i, i) * (x(i) - xk)), tol_max)
x(i) = xk
enddo iteration_loop
enddo convergence_loop
if (present(actual_iter)) actual_iter = iter
end function gauss_sparse
Note that an explicit interface to this routine must be available to its caller so that the type signature is known. This is preferably done by placing the function in a MODULE
and then USE
ing the module in the calling routine. An alternative is to use an INTERFACE
block, as shown by the following example:
program test_gauss_sparse
implicit none
! explicit interface to the gauss_sparse function
interface
function gauss_sparse(num_iter, tol, b, A, x, actual_iter) result(tol_max)
real :: tol_max
integer, intent(in) :: num_iter
real, intent(in) :: tol
real, intent(in), dimension(:) :: b, A(:,:)
real, intent(inout) :: x(:)
integer, optional, intent(out) :: actual_iter
end function
end interface
! declare variables
integer :: i, N = 3, actual_iter
real :: residue
real, allocatable :: A(:,:), x(:), b(:)
! allocate arrays
allocate (A(N, N), b(N), x(N))
! Initialize matrix
A = reshape([(real(i), i = 1, size(A))], shape(A))
! Make matrix diagonally dominant
do i = 1, size(A, 1)
A(i,i) = sum(A(i,:)) + 1
enddo
! Initialize b
b = [(i, i = 1, size(b))]
! Initial (guess) solution
x = b
! invoke the gauss_sparse function
residue = gauss_sparse(num_iter = 100, &
tol = 1E-5, &
b = b, &
A = a, &
x = x, &
actual_iter = actual_iter)
! Output
print '(/ "A = ")'
do i = 1, size(A, 1)
print '(100f6.1)', A(i,:)
enddo
print '(/ "b = " / (f6.1))', b
print '(/ "residue = ", g10.3 / "iterations = ", i0 / "solution = "/ (11x, g10.3))', &
residue, actual_iter, x
end program test_gauss_sparse
Writing subroutines
editIn those cases where it is desired to return values via a procedure's arguments, a subroutine is preferred over a function; this is illustrated by the following subroutine to swap the contents of two arrays:
subroutine swap_real(a1, a2)
implicit none
! Input/Output
real, intent(inout) :: a1(:), a2(:)
! Locals
integer :: i
real :: a
! Swap
do i = 1, min(size(a1), size(a2))
a = a1(i)
a1(i) = a2(i)
a2(i) = a
enddo
end subroutine swap_real
As in the previous example, an explicit interface to this routine must be available to its caller so that the type signature is known. As before, this is preferably done by placing the function in a MODULE
and then USE
ing the module in the calling routine. An alternative is to use a INTERFACE
block.
Internal and Elemental Procedures
editAn alternative way to write the swap_real
subroutine from the previous example, is:
subroutine swap_real(a1, a2)
implicit none
! Input/Output
real, intent(inout) :: a1(:), a2(:)
! Locals
integer :: N
! Swap, using the internal subroutine
N = min(size(a1), size(a2))
call swap_e(a1(:N), a2(:N))
contains
elemental subroutine swap_e(a1, a2)
real, intent(inout) :: a1, a2
real :: a
a = a1
a1 = a2
a2 = a
end subroutine swap_e
end subroutine swap_real
In the example, the swap_e
subroutine is elemental, i.e., it acts upon its array arguments, on an element-by-element basis. Elemental procedures must be pure (i.e., they must have no side effects and can invoke only pure procedures), and all the arguments must be scalar. Since swap_e
is internal to the swap_real
subroutine, no other program unit can invoke it.
The following program serves as a test for any of the two swap_real
subroutines presented:
program test_swap_real
implicit none
! explicit interface to the swap_real subroutine
interface
subroutine swap_real(a1, a2)
real, intent(inout) :: a1(:), a2(:)
end subroutine swap_real
end interface
! Declare variables
integer :: i
real :: a(10), b(10)
! Initialize a, b
a = [(real(i), i = 1, 20, 2)]
b = a + 1
! Output before swap
print '(/"before swap:")'
print '("a = [", 10f6.1, "]")', a
print '("b = [", 10f6.1, "]")', b
! Call the swap_real subroutine
call swap_real(a, b)
! Output after swap
print '(// "after swap:")'
print '("a = [", 10f6.1, "]")', a
print '("b = [", 10f6.1, "]")', b
end program test_swap_real
Pointers and targets methods
editIn Fortran, the concept of pointers differs from that in C-like languages. A Fortran 90 pointer does not merely store the memory address of a target variable; it also contains additional descriptive information such as the target's rank, the upper and lower bounds of each dimension, and even strides through memory. This allows a Fortran 90 pointer to point at submatrices.
Fortran 90 pointers are "associated" with well-defined "target" variables, via either the pointer assignment operator (=>
) or an ALLOCATE
statement. When appearing in expressions, pointers are always dereferenced; no "pointer arithmetic" is possible.
The following example illustrates the concept:
module SomeModule
implicit none
contains
elemental function A(x) result(res)
integer :: res
integer, intent(IN) :: x
res = x + 1
end function
end module SomeModule
program Test
use SomeModule, DoSomething => A
implicit none
!Declare variables
integer, parameter :: m = 3, n = 3
integer, pointer :: p(:)=>null(), q(:,:)=>null()
integer, allocatable, target :: A(:,:)
integer :: istat = 0, i, j
character(80) :: fmt
! Write format string for matrices
! (/ A / A, " = [", 3( "[",3(i2, 1x), "]" / 5x), "]" )
write (fmt, '("(/ A / A, "" = ["", ", i0, "( ""["",", i0, "(i2, 1x), ""]"" / 5x), ""]"" )")') m, n
allocate(A(m, n), q(m, n), stat = istat)
if (istat /= 0) stop 'Error during allocation of A and q'
! Matrix A is:
! A = [[ 1 4 7 ]
! [ 2 5 8 ]
! [ 3 6 9 ]
! ]
A = reshape([(i, i = 1, size(A))], shape(A))
q = A
write(*, fmt) "Matrix A is:", "A", ((A(i, j), j = 1, size(A, 2)), i = 1, size(A, 1))
! p will be associated with the first column of A
p => A(:, 1)
! This operation on p has a direct effect on matrix A
p = p ** 2
! This will end the association between p and the first column of A
nullify(p)
! Matrix A becomes:
! A = [[ 1 4 7 ]
! [ 4 5 8 ]
! [ 9 6 9 ]
! ]
write(*, fmt) "Matrix A becomes:", "A", ((A(i, j), j = 1, size(A, 2)), i = 1, size(A, 1))
! Perform some array operation
q = q + A
! Matrix q becomes:
! q = [[ 2 8 14 ]
! [ 6 10 16 ]
! [12 12 18 ]
! ]
write(*, fmt) "Matrix q becomes:", "q", ((q(i, j), j = 1, size(A, 2)), i = 1, size(A, 1))
! Use p as an ordinary array
allocate (p(1:m*n), stat = istat)
if (istat /= 0) stop 'Error during allocation of p'
! Perform some array operation
p = reshape(DoSomething(A + A ** 2), shape(p))
! Array operation:
! p(1) = 3
! p(2) = 21
! p(3) = 91
! p(4) = 21
! p(5) = 31
! p(6) = 43
! p(7) = 57
! p(8) = 73
! p(9) = 91
write(*, '("Array operation:" / (4x,"p(",i0,") = ",i0))') (i, p(i), i = 1, size(p))
deallocate(A, p, q, stat = istat)
if (istat /= 0) stop 'Error during deallocation'
end program Test
Module programming
editA module is a program unit which contains data definitions, global data, and CONTAIN
ed procedures. Unlike a simple INCLUDE
file, a module is an independent program unit that can be compiled separately and linked in its binary form. Once compiled, a module's public contents can be made visible to a calling routine via the USE
statement.
The module mechanism makes the explicit interface of procedures easily available to calling routines. In fact, modern Fortran encourages every SUBROUTINE
and FUNCTION
to be CONTAIN
ed in a MODULE
. This allows the programmer to use the newer argument passing options and allows the compiler to perform full type checking on the interface.
The following example also illustrates derived types, overloading of operators and generic procedures.
module GlobalModule
! Reference to a pair of procedures included in a previously compiled
! module named PortabilityLibrary
use PortabilityLibrary, only: GetLastError, & ! Generic procedure
Date ! Specific procedure
! Constants
integer, parameter :: dp_k = kind (1.0d0) ! Double precision kind
real, parameter :: zero = (0.)
real(dp_k), parameter :: pi = 3.141592653589793_dp_k
! Variables
integer :: n, m, retint
logical :: status, retlog
character(50) :: AppName
! Arrays
real, allocatable, dimension(:,:,:) :: a, b, c, d
complex(dp_k), allocatable, dimension(:) :: z
! Derived type definitions
type ijk
integer :: i
integer :: j
integer :: k
end type ijk
type matrix
integer m, n
real, allocatable :: a(:,:) ! Fortran 2003 feature. For Fortran 95, use the pointer attribute instead
end type matrix
! All the variables and procedures from this module can be accessed
! by other program units, except for AppName
public
private :: AppName
! Generic procedure swap
interface swap
module procedure swap_integer, swap_real
end interface swap
interface GetLastError ! This adds a new, additional procedure to the
! generic procedure GetLastError
module procedure GetLastError_GlobalModule
end interface GetLastError
! Operator overloading
interface operator(+)
module procedure add_ijk
end interface
! Prototype for external procedure
interface
function gauss_sparse(num_iter, tol, b, A, x, actual_iter) result(tol_max)
real :: tol_max
integer, intent(in) :: num_iter
real, intent(in) :: tol
real, intent(in), dimension(:) :: b, A(:,:)
real, intent(inout) :: x(:)
integer, optional, intent(out) :: actual_iter
end function gauss_sparse
end interface
! Procedures included in the module
contains
! Internal function
function add_ijk(ijk_1, ijk_2)
type(ijk) add_ijk, ijk_1, ijk_2
intent(in) :: ijk_1, ijk_2
add_ijk = ijk(ijk_1%i + ijk_2%i, ijk_1%j + ijk_2%j, ijk_1%k + ijk_2%k)
end function add_ijk
! Include external files
include 'swap_integer.f90' ! Comments SHOULDN'T be added on include lines
include 'swap_real.f90'
end module GlobalModule
FAQ
This article contains some frequently-asked questions (FAQs) regarding Fortran and their answers.
Q. Should I learn Fortran? Is it obsolete?
editA: Fortran is not obsolete and it will not be any time soon. Fortran is a general purpose programming language and is suitable for many applications. However, it excells at numerical computation and high performance computing. It is fast, portable and it has seamless handling of arrays. Because of this, there are many high-quality Fortran libraries for numerical algorithms and it is widespread in scientific communities (e.g. numerical weather predicion). The language itself is still maintained and regularly updated with modern features; the latest version is Fortran 2023.
Q: What Fortran compiler should I use?
editA: Oracle Solaris Studio, GNU Fortran, G95, and Silverfrost (Windows only) are free software Fortran 95 compilers, and Absoft, IBM, Intel, Lahey, NAG, Pathscale and PGI sell Fortran compilers. Comparative information on Fortran compilers is available at Wikipedia.
Q: How do I create numbered file names such as out_01.txt, out_02.txt etc.?
editA: Use an "internal write" to create the file names, for example
write (file_name,"('out_',i2.2,'.txt')") i
A: A neater way to do this would be:
i=<file number>
WRITE(file_name, fmt = '(A4,I0,A4)')'out_',i,'.txt'
This way the formatting is clear and you are writing the correct string to the variable. I assume you wanted an integer as the number. 'I' format statement requires an Integer length, or zero in some cases. You are probably thinking of F where the decimal point denotes the number of decimals to consider.
Q: What does the open statement look like using this technique? OPEN(UNIT = __, FILE = ???, STATUS='NEW')?
editA: Gfortran does not accept this block
write(file_name,'cp',(i5.5),'.out') ITN
open (67,file = file_name)
Gives, ERROR, file tag must be of type CHARACTER
Can someone else help with this?
A: See the answer above. Basically the way you have written the variable file_name is incorrect.
WRITE(file_name,fmt='(A2,I0,A4)')'cp',ITN,'.out'
OPEN(UNIT=67, file=file_name, status='new')
Assuming that ITN has been declared as an integer and given a value.
Q: How can I convert a string to an integer and other types? What about the reverse?
editA: Use an "internal read" or "internal write". In effect, you use a character variable as the file name and read or write the I/O list. You write things like
read (character_variable, format) list of variables
to convert a string to another type and
write (character_variable, format) list of variables
to convert to a string from another type, as demonstrated by the following program:
program xconvert_integer_string
character(20) :: cnum
integer :: i
i = 445
write(cnum,'(i5)') i
write(*,'(a)') trim(cnum) ! should output " 445"
write(cnum,'(i5.5)') i
write(*,'(a)') trim(cnum) ! should output "00445"
i = 34
write(cnum,'(i0)') i
write(*,'(a)') trim(cnum) ! should output "34"
end program xconvert_integer_string
This answer is based on messages in comp.lang.fortran by Paul van Delst and Dick Hendrickson.
Q. How do I issue a command to the operating system within a Fortran program?
editA. The Fortran 2008 standard provides the execute_command_line
intrinsic procedure to make system calls. Prior versions have no standard way to make system calls, but many compilers have an extension named "system" or something similar. Please consult the documentation of your compiler. In Fortran 2003, one can call C code, and it is possible to call the operating system from C.