- Fortran language features
This is a comprehensive overview of features of the
Fortran 95 language, the version supported by almost all existing Fortran compilers. Old features that have been superseded by new ones are not described — few of those historic features are used in modern programs (although most have been retained in the language to maintainbackward compatibility ). The current standard is known as Fortran 2003, but still,as of 2008 , none of the compilers on the market supports the entire set of its enhancements .Language elements
"Note. Fortran is
case-insensitive . Convention of writing Fortran keywords in upper case and all other names in lower case is adopted below (except, by way of contrast, in the input/output descriptions (Data transfer and Operations on external files))..Basics
The basic component of the Fortran language is its "character set". Its members are:
*the letters A ... Z and a ... z (which are equivalent outside a character context);
*the numerals 0 ... 9;
*the underscore _; and
*the special characters= : + blank - * / ( ) , . $ ' ! " % & ; < > ?
Tokens that have a syntactic meaning to the compiler are built from those components. There are six classes of tokens:
Derived data types
For derived data types, the form of the type must be defined first:
TYPE person CHARACTER(10) name REAL age END TYPE person
and then, variables of that type can be defined: TYPE(person) you, me
To select components of a derived type,
%
qualifier is used: you%ageLiteral constants of derived type have the form "
TypeName(1stComponentLiteral, 2ndComponentLiteral, ...)
": you = person('Smith', 23.5)which is known as a "structure constructor". Definitions may refer to a previously defined type:TYPE point REAL x, y END TYPE point TYPE triangle TYPE(point) a, b, c END TYPE triangle
and for a variable of type triangle, as in TYPE(triangle) teach component of type
point
is accessed as: t%a t%b t%cwhich, in turn, have ultimate components of type real: t%a%x t%a%y t%b%x etc.(Note that the%
qualifier was chosen rather than dot (.
) because of potential ambiguity with operator notation, like.OR.
).Implicit and explicit typing
Unless specified otherwise, all variables starting with letters I, J, K, L, M and N are default
INTEGER
s, and all others are defaultREAL; other data types must be explicitly declared. This is known as "implicit typing" and is a heritage of early FORTRAN days. Those defaults can be overridden by "
IMPLICIT TypeName (CharacterRange)
" statements, like: IMPLICIT COMPLEX(Z) IMPLICIT CHARACTER(A-B) IMPLICIT REAL(C-H,N-Y)However, it is a good practice to explicitly type all variables, and this can be forced by inserting the statement IMPLICIT NONEat the beginning of each program unit.Arrays
Arrays are considered to be variables in their own right. Every array is characterized by its type, rank, and "shape" (which defines the extents of each dimension). Bounds of each dimension are by default 1 and "size", but arbitrary bounds can be explicitly specified.
DIMENSION
keyword is optional and considered an attribute; if omitted, the array shape must be specified after array-variable name. For example:REAL:: a(10) INTEGER, DIMENSION(0:100, -50:50) :: map
declares two arrays, rank-1 and rank-2, whose elements are in
column-major order . Elements are, for example, a(1) a(i*j)and are scalars. The subscripts may be any scalar integer expression."Sections" are parts of the array variables, and are arrays themselves:
a(i:j) ! rank one map(i:j, k:l:m) ! rank two a(map(i, k:l)) ! vector subscript a(3:2) ! zero length
Whole arrays and array sections are array-valued objects. Array-valued constants (constructors) are available, enclosed in
(/ ... /)
: (/ 1, 2, 3, 4 /) (/ ( (/ 1, 2, 3 /), i = 1, 4) /) (/ (i, i = 1, 9, 2) /) (/ (0, i = 1, 100) /) (/ (0.1*i, i = 1, 10) /)making use of an implied-DO loop notation. Fortran 2003 allows the use of brackets:[1, 2, 3, 4]
and[( [1,2,3] , i=1,4)]
instead of the first two examples above, and many compilers support this now.A derived data type may, of course, contain array components: TYPE triplet REAL, DIMENSION(3) :: vertex END TYPE triplet TYPE(triplet), DIMENSION(4) :: tso that t(2) is a scalar (a structure) t(2)%vertex is an array component of a scalarData initialization
Variables can be given initial values as specified in a specification statement: REAL, DIMENSION(3) :: a = (/0.1, 0.2, 0.3 /)and a default initial value can be given to the component of a derived data type: TYPE triplet REAL, DIMENSION(3) :: vertex = 0 END TYPE triplet
PARAMETER
attributeA named constant can be specified directly by adding the
PARAMETER
attribute and the constant values to a type statement: REAL, DIMENSION(3), PARAMETER :: field = (/ 0., 1., 2. /) TYPE(triplet), PARAMETER :: t = & triplet( 0., (/ 0., 0., 0. /) )DATA statement
The
DATA
statement can be used for scalars and also for arrays and variables of derived type. It is also the only way to initialise just parts of such objects, as well as to initialise to binary, octal or hexadecimal values: TYPE(triplet) :: t1, t2 DATA t1/triplet( 0., (/ 0., 1., 2. /) )/, t2%u/0./ DATA array(1:64) / 64*0/ DATA i, j, k/ B'01010101', O'77', Z'ff'/Initialization expressions
The values used in DATA and PARAMETER statements, or with these attributes, are constant expressions that may include references to: array and structure constructors, elemental intrinsic functions with integer or character arguments and results, and the six transformational functions
REPEAT, SELECTED_INT_KIND, TRIM, SELECTED_REAL_KIND, RESHAPE
andTRANSFER
(see Intrinsic procedures): INTEGER, PARAMETER :: long = SELECTED_REAL_KIND(12), & array(3) = (/ 1, 2, 3 /)pecification expressions
It is possible to specify details of variables using any non-constant, scalar, integer expression that may also include inquiry function references: SUBROUTINE s(b, m, c) USE mod ! contains a REAL, DIMENSION(:, :) :: b REAL, DIMENSION(UBOUND(b, 1) + 5) :: x INTEGER :: m CHARACTER(LEN=*) :: c CHARACTER(LEN= m + LEN(c)) :: cc REAL (SELECTED_REAL_KIND(2*PRECISION(a))) :: z
Expressions and assignments
calar numeric
The usual arithmetic operators are available —
+, -, *, /, **
(given here in increasing order of precedence._Parentheses are used to indicate the order of evaluation where necessary: a*b + c ! * first a*(b + c) ! + first
The rules for "scalar numeric" expressions and assignments accommodate the non-default kinds. Thus, the mixed-mode numeric expression and assignment rules incorporate different kind type parameters in an expected way: real2 = integer0 + real1
converts
integer0
to a real value of the same kind asreal1
; the result is of same kind, and is converted to the kind ofreal2
for assignment.calar relational operations
For "scalar relational" operations of numeric types, there is a set of built-in operators: < <= = /= > >= .LT. .LE. .EQ. .NE. .GT. .GE.(the forms above are new to Fortran-90, and older equivalent forms are given below them). Example expressions:
IF (a < b .AND. i /= j) THEN ! for numeric variables
calar characters
In the case of "scalar characters" and given CHARACTER(8) result
it is legal to write result(3:5) = result(1:3) ! overlap allowed result(3:3) = result(3:2) ! no assignment of null string
Derived-data types
No built-in operations (except assignment, defined on component-by component basis) exist between "derived data types" mutually or with intrinsic types. Meaning of existing or user-specified operators can be (re)defined though: TYPE string INTEGER length CHARACTER(80) value END TYPE string CHARACTER:: char1, char2, char3 TYPE(string):: str1, str2, str3we can write str3 = str1//str2 ! must define operation str3 = str1.concat.str2 ! must define operation char3 = char2//char3 ! intrinsic operator only str3 = char1 ! must define assignment
Notice the "overloaded" use of intrinsic symbol
//
and of named operator,.concat.
. A difference is that, for an intrinsic operator token, the usual precedence rules apply, whereas for named operators, precedence is the highest as a unary operator or the lowest as a binary one. In vector3 = matrix * vector1 + vector2 vector3 =(matrix .times. vector1) + vector2the two expressions are equivalent only if appropriate parentheses are added as shown. In each case there must be defined, in a module, procedures defining the operator and assignment, and corresponding operator-procedure association, as follows: INTERFACE OPERATOR(//) !Overloads the // operator as invoking string_concat procedure MODULE PROCEDURE string_concat END INTERFACEThe string concatenation function was shown already in Basics. MODULE string_type TYPE string INTEGER length CHARACTER(LEN=80) :: string_data END TYPE string INTERFACE ASSIGNMENT(=) MODULE PROCEDURE c_to_s_assign, s_to_c_assign END INTERFACE INTERFACE OPERATOR(//) MODULE PROCEDURE string_concat END INTERFACE CONTAINS SUBROUTINE c_to_s_assign(s, c) TYPE (string), INTENT(OUT) :: s CHARACTER(LEN=*), INTENT(IN) :: c s%string_data = c s%length = LEN(c) END SUBROUTINE c_to_s_assign SUBROUTINE s_to_c_assign(c, s) TYPE (string), INTENT(IN) :: s CHARACTER(LEN=*), INTENT(OUT) :: c c = s%string_data(1:s%length) END SUBROUTINE s_to_c_assign FUNCTION string_concat(s1, s2) : END FUNCTION string_concat END MODULE string_type
Defined operators such as these are required for the expressions that are allowed also in structure constructors (see Derived-data types): str1 = string(2, char1//char2) ! structure constructor
Arrays
In the case of arrays then, as long as they are of the same shape (conformable), operations and assignments are extended in an obvious way, on an element-by-element basis. For example, given declarations of REAL, DIMENSION(10, 20) :: a, b, c REAL, DIMENSION(5) :: v, w LOGICAL flag(10, 20)it can be written: a = b ! whole array assignment c = a/b ! whole array division and assignment c = 0. ! whole array assignment of scalar value w = v + 1. ! whole array addition to scalar value w = 5/v + a(1:5, 5) ! array division, and addition to section
Some real intrinsic functions that are useful for numeric computations are: CEILING FLOOR MODULO (also integer) EXPONENT FRACTION NEAREST RRSPACING SPACING SCALE SET_EXPONENTThese are array valued for array arguments (elemental), like all FORTRAN 77 functions (except LEN):
(the last seven are for characters).INT REAL CMPLX AINT ANINT NINT ABS MOD SIGN DIM MAX MINSQRT EXP LOG LOG10 SIN COS TAN ASIN ACOS ATAN ATAN2 SINH COSH TANH
AIMAG CONJG
LGE LGT LLE LLT ICHAR CHAR INDEX
Control statements
Branching and conditions
The simple GO TO "label" exists, but is usually avoided — in most cases, a more specific branching construct will accomplish the same logic with more clarity.
The simple conditional test is the IF statement:
A full-blown IF construct is illustrated by:IF (a > b) x = yIF (i < 0) THEN IF (j < 0) THEN x = 0. ELSE z = 0. END IF ELSE IF (k < 0) THEN z = 1. ELSE x = 1. END IFCASE construct
The CASE construct is a replacement for the computed GOTO, but is better structured and does not require the use of statement labels:
Each CASE selector list may contain a list and/or range of integers, character or logical constants, whose values may not overlap within or between selectors:SELECT CASE (number) ! number of type integer CASE (:-1) ! all values below 0 n_sign = -1 CASE (0) ! only 0 n_sign = 0 CASE (1:) ! all values above 0 n_sign = 1 END SELECT
A default is available:CASE (1, 2, 7, 10:17, 23)
There is only one evaluation, and only one match.CASE DEFAULTDO construct
A simplified but sufficient form of the DO construct is illustrated by
where we note that loops may be optionally named so that any EXIT or CYCLE statement may specify which loop is meant.outer: DO inner: DO i = j, k, l ! from j to k in steps of l (l is optional) : IF (...) CYCLE : IF (...) EXIT outer END DO inner END DO outerMany, but not all, simple loops can be replaced by array expressions and assignments, or by new intrinsic functions. For instance
becomes simplytot = 0. DO i = m, n tot = tot + a(i) END DOtot = SUM( a(m:n) )Program units and procedures
Definitions
In order to discuss this topic we need some definitions. In logical terms, an executable program consists of one "main program" and zero or more "subprograms" (or "procedures") - these do something. Subprograms are either "functions "or "subroutines", which are either "external, internal" or "module" subroutines. (External subroutines are what we knew from FORTRAN 77.)
From an organizational point of view, however, a complete program consists of "program units". These are either "main programs, external subprograms" or "modules" and can be separately compiled.
An example of a main (and complete) program is:
An example of a main program and an external subprogram, forming an executable program, is:PROGRAM test PRINT *, 'Hello world!' END PROGRAM test
The form of a function is:PROGRAM test CALL print_message END PROGRAM test SUBROUTINE print_message PRINT *, 'Hello world!' END SUBROUTINE print_message
The form of reference of a function is:FUNCTION name(arg1, arg2) ! zero or more arguments : name = ... : END FUNCTION namex = name(a, b)Internal procedures
An internal subprogram is one "contained" in another (at a maximum of one level of nesting) and provides a replacement for the statement function:
We say that outer is the "host" of inner, and that inner obtains access to entities in outer by "host association" (e.g. to x), whereas y is a "local" variable to inner.SUBROUTINE outer REAL x, y : CONTAINS SUBROUTINE inner REAL y y = x + 1. : END SUBROUTINE inner ! SUBROUTINE mandatory END SUBROUTINE outerThe "scope" of a named entity is a "scoping unit", here outer less inner, and inner.
The names of program units and external procedures are "global", and the names of implied-DO variables have a scope of the statement that contains them.
Modules
Modules are used to package
- global data (replaces COMMON and BLOCK DATA from Fortran 77);
- type definitions (themselves a scoping unit);
- subprograms (which among other things replaces the use of ENTRY from Fortran 77);
- interface blocks (another scoping unit, see Interface blocks);
- namelist groups (see any textbook).
and the simple statementMODULE interval_arithmetic TYPE interval REAL lower, upper END TYPE interval INTERFACE OPERATOR(+) MODULE PROCEDURE add_intervals END INTERFACE : CONTAINS FUNCTION add_intervals(a,b) TYPE(interval), INTENT(IN) :: a, b TYPE(interval) add_intervals add_intervals%lower = a%lower + b%lower add_intervals%upper = a%upper + b%upper END FUNCTION add_intervals ! FUNCTION mandatory : END MODULE interval_arithmetic
provides "use association" to all the module's entities. Module subprograms may, in turn, contain internal subprograms.USE interval_arithmeticControlling accessibility
The PUBLIC and PRIVATE attributes are used in specifications in modules to limit the scope of entities. The attribute form is
and the statement form isREAL, PUBLIC :: x, y, z ! default INTEGER, PRIVATE :: u, v, w
The statement form has to be used to limit access to operators, and can also be used to change the overall default:PUBLIC :: x, y, z, OPERATOR(.add.) PRIVATE :: u, v, w, ASSIGNMENT(=), OPERATOR(*)
For derived types there are three possibilities: the type and its components are all PUBLIC, the type is PUBLIC and its components PRIVATE (the type only is visible and one can change its details easily), or all of it is PRIVATE (for internal use in the module only):PRIVATE ! sets default for module PUBLIC :: only_thisMODULE mine PRIVATE TYPE, PUBLIC :: list REAL x, y TYPE(list), POINTER :: next END TYPE list TYPE(list) :: tree : END MODULE mineThe USE statement's purpose is to gain access to entities in a module. It has options to resolve name clashes if an imported name is the same as a local one:
or to restrict the used entities to a specified set:USE mine, local_list => list
These may be combined:USE mine, ONLY : listUSE mine, ONLY : local_list => listArguments
We may specify the intent of dummy arguments:
Also, INOUT is possible: here the actual argument must be a variable (unlike the default case where it may be a constant).SUBROUTINE shuffle (ncards, cards) INTEGER, INTENT(IN) :: ncards INTEGER, INTENT(OUT), DIMENSION(ncards) :: cardsArguments may be optional:
allows us to call mincon bySUBROUTINE mincon(n, f, x, upper, lower, equalities, inequalities, convex, xstart) REAL, OPTIONAL, DIMENSION :: upper, lower :
Arguments may be keyword rather than positional (which come first):CALL mincon (n, f, x, upper) : IF (PRESENT(lower)) THEN ! test for presence of actual argument :
Optional and keyword arguments are handled by explicit interfaces, that is with internal or module procedures or with interface blocks.CALL mincon(n, f, x, equalities=0, xstart=x0)Interface blocks
Any reference to an internal or module subprogram is through an interface that is 'explicit' (that is, the compiler can see all the details). A reference to an external (or dummy) procedure is usually 'implicit' (the compiler assumes the details). However, we can provide an explicit interface in this case too. It is a copy of the header, specifications and END statement of the procedure concerned, either placed in a module or inserted directly:
An explicit interface is obligatory for:REAL FUNCTION minimum(a, b, func)! returns the minimum value of the function func(x)! in the interval (a,b) REAL, INTENT(in) :: a, b INTERFACE REAL FUNCTION func(x) REAL, INTENT(IN) :: x END FUNCTION func END INTERFACE REAL f,x : f = func(x) ! invocation of the user function. : END FUNCTION minimum- optional and keyword arguments;
- POINTER and TARGET arguments (see Pointers);
- POINTER function result;
- new-style array arguments and array functions (Array handling).
Overloading and generic interfaces
Interface blocks provide the mechanism by which we are able to define generic names for specific procedures:
where a given set of specific names corresponding to a generic name must all be of functions or all of subroutines. If this interface is within a module, then it is simplyINTERFACE gamma ! generic name FUNCTION sgamma(X) ! specific name REAL (SELECTED_REAL_KIND( 6)) sgamma, x END FUNCTION dgamma(X) ! specific name REAL (SELECTED_REAL_KIND(12)) dgamma, x END END INTERFACE
We can use existing names, e.g. SIN, and the compiler sorts out the correct association.INTERFACE gamma MODULE PROCEDURE sgamma, dgamma END INTERFACEWe have already seen the use of interface blocks for defined operators and assignment (see Modules).
Recursion
Indirect recursion is useful for multi-dimensional integration. For
We might havevolume = integrate(fy, ybounds)
and to integrate "f(x, y)" over a rectangle:RECURSIVE FUNCTION integrate(f, bounds) ! Integrate f(x) from bounds(1) to bounds(2) REAL integrate INTERFACE FUNCTION f(x) REAL f, x END FUNCTION f END INTERFACE REAL, DIMENSION(2), INTENT(IN) :: bounds : END FUNCTION integrate
Direct recursion is when a procedure calls itself, as inFUNCTION fy(y) USE func ! module func contains function f REAL fy, y yval = y fy = integrate(f, xbounds) END
Here, we note the RESULT clause and termination test.RECURSIVE FUNCTION factorial(n) RESULT(res) INTEGER res, n IF(n.EQ.1) THEN res = 1 ELSE res = n*factorial(n-1) END IF ENDPure Procedures
This is a feature for parallel computing.
In the FORALL Statement and Construct, anyside effects in a function canimpede optimization on a parallel processor --the order of execution of the assignments could affect the results.To control this situation, weadd the PURE keyword to theSUBROUTINE or FUNCTIONstatement -- an assertion that the procedure (expressed simply):
- alters no global variable,
- performs no I/O,
- has no saved variables (variables with the SAVE attribute that retains values between invocations), and
- does not alter its INTENT(IN) arguments for subroutines, orany for functions.
All the intrinsic functions are pure.PURE FUNCTION calculate (x)Array handling
Array handling is included in Fortran for two main reasons:
- the notational convenience it provides, bringing the code closer to the underlying mathematical form;
- for the additional optimization opportunities it gives compilers (although there are plenty of opportunities for degrading optimization too!).
Zero-sized arrays
A zero-sized array is handled by Fortran as a legitimate object, without special coding by the programmer. Thus, in
no special code is required for the final iteration where i = n. We note that a zero-sized array is regarded as being defined; however, an array of shape (0,2) is not conformable with one of shape (0,3), whereasDO i = 1,n x(i) = b(i) / a(i, i) b(i+1:n) = b(i+1:n) - a(i+1:n, i) * x(i) END DO
is a valid 'do nothing' statement.x(1:0) = 3Assumed-shape arrays
These are an extension and replacement for assumed-size arrays. Given an actual argument like:
the corresponding dummy argument specification defines only the type and rank of the array, not its size. This information has to be made available by an explicit interface, often using an interface block (see Interface blocks). Thus we write justREAL, DIMENSION(0:10, 0:20) :: a : CALL sub(a)
and this is as if da were dimensioned (11,21). However, we can specify any lower bound and the array maps accordingly. The shape, not bounds, is passed, where the default lower bound is 1 and the default upper bound is the corresponding extent.SUBROUTINE sub(da) REAL, DIMENSION(:, :) :: daAutomatic arrays
A partial replacement for the uses to which EQUIVALENCE was put is provided by this facility, useful for local, temporary arrays, as in
The actual storage is typically maintained on a stack.SUBROUTINE swap(a, b) REAL, DIMENSION(:) :: a, b REAL, DIMENSION(SIZE(a)) :: work work = a a = b b = work END SUBROUTINE swapALLOCATABLE and ALLOCATE
Fortran provides dynamic allocation of storage; it relies on a heap storage mechanism (and replaces another use of EQUIVALENCE). An example, for establishing a work array for a whole program, is
The work array can be propagated through the whole program via a USE statement in each program unit. We may specify an explicit lower bound and allocate several entities in one statement. To free dead storage we write, for instance,MODULE work_array INTEGER n REAL, DIMENSION(:,:,:), ALLOCATABLE :: work END MODULE PROGRAM main USE work_array READ (input, *) n ALLOCATE(work(n, 2*n, 3*n), STAT=status) : DEALLOCATE (work)
Deallocation of arrays is automatic when they go out of scope.DEALLOCATE(a, b)Elemental operations, assignments and procedures
We have already met whole array assignments and operations:
In the second assignment, an intrinsic function returns an array-valued result for an array-valued argument. We can write array-valued functions ourselves (they require an explicit interface):REAL, DIMENSION(10) :: a, b a = 0. ! scalar broadcast; elemental assignment b = sqrt(a) ! intrinsic function result as array object
Elemental procedures are specified with scalar dummy arguments that may be called witharray actual arguments. In the case of a function, the shape of the result is the shape of the arrayarguments.PROGRAM test REAL, DIMENSION(3) :: a = (/ 1., 2., 3./), & b = (/ 2., 2., 2. /), r r = f(a, b) PRINT *, r CONTAINS FUNCTION f(c, d) REAL, DIMENSION(:) :: c, d REAL, DIMENSION(SIZE(c)) :: f f = c*d ! (or some more useful function of c and d) END FUNCTION f END PROGRAM testMost intrinsic functions are elemental andFortran 95 extends this feature to non-intrinsic procedures, thus providing the effectof writing, in Fortran 90, 22 different versions, for ranks 0-0, 0-1, 1-0, 1-1, 0-2,2-0, 2-2, ... 7-7, and is further an aid to optimization on parallel processors.An elemental procedure must be pure.
The dummy arguments cannot be used in specification expressions (see above) except asarguments to certain intrinsic functions (BIT_SIZE, KIND, LEN, and the numeric inquiry ones, (see below).ELEMENTAL SUBROUTINE swap(a, b) REAL, INTENT(INOUT) :: a, b REAL :: work work = a a = b b = work END SUBROUTINE swapWHERE
Often, we need to mask an assignment. This we can do using the WHERE, either as a statement:
(note: the test is element-by-element, not on whole array), or as a construct:WHERE (a /= 0.0) a = 1.0/a ! avoid division by 0
orWHERE (a /= 0.0) a = 1.0/a b = a ! all arrays same shape END WHERE
Further:WHERE (a /= 0.0) a = 1.0/a ELSEWHERE a = HUGE(a) END WHERE- it is permitted to mask not only the WHEREstatement of the WHERE construct,but also any ELSEWHERE statement that it contains;
- a WHERE construct may containany number of masked ELSEWHERE statements but at most oneELSEWHEREstatement without a mask, and that must be the final one;
- WHERE constructs may be nested within one another, justFORALL constructs;
- a WHEREassignment statement is permitted to be a defined assignment,provided that it is elemental;
- a WHERE construct may be named in the same way as other constructs.
The FORALL Statement and Construct
When a DO constructis executed, each successiveiteration is performed in order and one after the other --an impediment to optimizationon a parallel processor.
wherethe individual assignments may be carried out in any order, andeven simultaneously.The FORALL may be considered to be an array assignmentexpressed with the help of indices.FORALL(i = 1:n) a(i, i) = x(i)
with masking condition.FORALL(i=1:n, j=1:n, y(i,j)/=0.) x(j,i) = 1.0/y(i,j)The FORALL constructallows severalassignment statements to be executed in order.
is equivalent to the array assignmentsa(2:n-1,2:n-1) = a(2:n-1,1:n-2) + a(2:n-1,3:n) + a(1:n-2,2:n-1) + a(3:n,2:n-1) b(2:n-1,2:n-1) = a(2:n-1,2:n-1)
The FORALL version is more readable.FORALL(i = 2:n-1, j = 2:n-1) a(i,j) = a(i,j-1) + a(i,j+1) + a(i-1,j) + a(i+1,j) b(i,j) = a(i,j) END FORALLAssignment in a FORALLis like an array assignment: as if all the expressions were evaluated in any order, heldin temporary storage, then all the assignments performed in any order.The first statement must fully complete before the second can begin. A FORALLmay be nested, andmay include a WHERE.Procedures referenced within a FORALLmust be pure.
Array elements
For a simple case: given
we can reference a single element as, for instance, a(1, 1). For a derived-data type likeREAL, DIMENSION(100, 100) :: a
we can declare an array of that type:TYPE triplet REAL u REAL, DIMENSION(3) :: du END TYPE triplet
and a reference likeTYPE(triplet), DIMENSION(10, 20) :: tar
is an element (a scalar!) of type triplet, buttar(n, 2)
is an array of type real, andtar(n, 2)%du
is an element of it. The basic rule to remember is that an array element always has a subscript or subscripts qualifying at least the last name.tar(n, 2)%du(2)Array subobjects (sections)
The general form of subscript for an array section is ["lower"] : ["upper"] [:"stride"]
(where [ ] indicates an optional item) as in
Note that a vector subscript with duplicate values cannot appear on the left-hand side of an assignment as it would be ambiguous. Thus,REAL a(10, 10) a(i, 1:n) ! part of one row a(1:m, j) ! part of one column a(i, : ) ! whole row a(i, 1:n:3) ! every third element of row a(i, 10:1:-1) ! row in reverse order a( (/ 1, 7, 3, 2 /), 1) ! vector subscript a(1, 2:11:2) ! 11 is legal as not referenced a(:, 1:7) ! rank two section
is illegal. Also, a section with a vector subscript must not be supplied as an actual argument to an OUT or INOUT dummy argument. Arrays of arrays are not allowed:b( (/ 1, 7, 3, 7 /) ) = (/ 1, 2, 3, 4 /)
We note that a given value in an array can be referenced both as an element and as a section:tar%du ! illegal
depending on the circumstances or requirements. By qualifying objects of derived type, we obtain elements or sections depending on the rule stated earlier:a(1, 1) ! scalar (rank zero) a(1:1, 1) ! array section (rank one)tar%u ! array section (structure component) tar(1, 1)%u ! component of an array element
Arrays intrinsic functions
"Vector and matrix multiply"
"Array reduction"DOT_PRODUCT Dot product of 2 rank-one arrays MATMUL Matrix multiplication
"Array inquiry"ALL True if all values are true ANY True if any value is true. Example: IF (ANY( a > b)) THEN COUNT Number of true elements in array MAXVAL Maximum value in an array MINVAL Minimum value in an array PRODUCT Product of array elements SUM Sum of array elements
"Array construction"ALLOCATED Array allocation status LBOUND Lower dimension bounds of an array SHAPE Shape of an array (or scalar) SIZE Total number of elements in an array UBOUND Upper dimension bounds of an array
"Array reshape"MERGE Merge under mask PACK Pack an array into an array of rank SPREAD Replicate array by adding a dimension UNPACK Unpack an array of rank one into an array under mask
"Array manipulation"RESHAPE Reshape an array
"Array location"CSHIFT Circular shift EOSHIFT End-off shift TRANSPOSE Transpose of an array of rank twoMAXLOC Location of first maximum value in an array MINLOC Location of first minimum value in an arrayPointers
Basics
Pointers are variables with the POINTER attribute; they are not a distinct data type (and so no 'pointer arithmetic' is possible).
They are conceptually a descriptor listing the attributes of the objects (targets) that the pointer may point to, and the address, if any, of a target. They have no associated storage until it is allocated or otherwise associated (by pointer assignment, see below):REAL, POINTER :: var
and they are dereferenced automatically, so no special symbol required. InALLOCATE (var)
the value of the target of var is used and modified. Pointers cannot be transferred via I/O. The statementvar = var + 2.3
writes the value of the target of var and not the pointer descriptor itself.WRITE *, varA pointer can point to other pointers, and hence to their targets, or to a static object that has the TARGET attribute:
but they are strongly typed:REAL, POINTER :: object REAL, TARGET :: target_obj var => object ! pointer assignment var => target_obj
and, similarly, for arrays the ranks as well as the type must agree.INTEGER, POINTER :: int_var var => int_var ! illegal - types must matchA pointer can be a component of a derived type:
and we can define the beginning of a linked chain of such entries:TYPE entry ! type for sparse matrix REAL value INTEGER index TYPE(entry), POINTER :: next ! note recursion END TYPE entry
After suitable allocations and definitions, the first two entries could be addressed asTYPE(entry), POINTER :: chain
but we would normally define additional pointers to point at, for instance, the first and current entries in the list.chain%value chain%next%value chain%index chain%next%index chain%next chain%next%nextAssociation
A pointer's association status is one of
- undefined (initial state);
- associated (after allocation or a pointer assignment);
- disassociated: DEALLOCATE (p, q) ! for returning storage NULLIFY (p, q) ! for setting to 'null'
The intrinsic function ASSOCIATED can test the association status of a defined pointer:
or between a defined pointer and a defined target (which may, itself, be a pointer):IF (ASSOCIATED(pointer)) THEN
An alternative way to initialize a pointer, also in a specification statement,is to use the NULL function:IF (ASSOCIATED(pointer, target)) THENREAL, POINTER, DIMENSION(:) :: vector => NULL() ! compile time vector => NULL() ! run timePointers in expressions and assignments
For intrinsic types we can 'sweep' pointers over different sets of target data using the same code without any data movement. Given the matrix manipulation "y = B C z", we can write the following code (although, in this case, the same result could be achieved more simply by other means):
For objects of derived type we have to distinguish between pointer and normal assignment. InREAL, TARGET :: b(10,10), c(10,10), r(10), s(10), z(10) REAL, POINTER :: a(:,:), x(:), y(:) INTEGER mult : DO mult = 1, 2 IF (mult = 1) THEN y => r ! no data movement a => c x => z ELSE y => s ! no data movement a => b x => r END IF y = MATMUL(a, x) ! common calculation END DO
the assignment causes first to point at current, whereasTYPE(entry), POINTER :: first, current : first => current
causes current to overwrite first and is equivalent tofirst = currentfirst%value = current%value first%index = current%index first%next => current%nextPointer arguments
If an actual argument is a pointer then, if the dummy argument is also a pointer,
- it must have same rank,
- it receives its association status from the actual argument,
- it returns its final association status to the actual argument (note: the target may be undefined!),
- it may not have the INTENT attribute (it would be ambiguous),
- it requires an interface block.
REAL, POINTER :: a (:,:) : ALLOCATE (a(80, 80)) : CALL sub(a) : SUBROUTINE sub(c) REAL c(:, :)Pointer functions
Function results may also have the POINTER attribute; this is useful if the result size depends on calculations performed in the function, as in
where the module data_handler containsUSE data_handler REAL x(100) REAL, POINTER :: y(:) : y => compact(x)
The result can be used in an expression (but must be associated with a defined target).FUNCTION compact(x) REAL, POINTER :: compact(:) REAL x(:) ! A procedure to remove duplicates from the array x INTEGER n : ! Find the number of distinct values, n ALLOCATE(compact(n)) : ! Copy the distinct values into compact END FUNCTION compactArrays of pointers
These do not exist as such: given
thenTYPE(entry) :: rows(n)
would be such an object, but with an irregular storage pattern. For this reason they are not allowed. However, we can achieve the same effect by defining a derived data type with a pointer as its sole component:rows%next ! illegal
and then defining arrays of this data type:TYPE row REAL, POINTER :: r(:) END TYPE
where the storage for the rows can be allocated by, for instance,TYPE(row) :: s(n), t(n)
The array assignmentDO i = 1, n ALLOCATE (t(i)%r(1:i)) ! Allocate row i of length i END DO
is then equivalent to the pointer assignmentss = t
for all components.s(i)%r => t(i)%rPointers as dynamic aliases
Given an array
REAL, TARGET :: table(100,100)that is frequently referenced with the fixed subscripts
these references may be replaced bytable(m:n, p:q)
The subscripts of window are 1:n-m+1, 1:q-p+1. Similarly, forREAL, DIMENSION(:, :), POINTER :: window : window => table(m:n, p:q)
(as defined in already), we can use, say,tar%u
to point at all the u components of tar, and subscript it astaru => tar%u
The subscripts are as those of tar itself. (This replaces yet more of EQUIVALENCE.)taru(1, 2)In the pointer association
the lower bounds for pointer are determined as if lbound wasapplied to array_expression. Thus, when a pointer is assigned to awhole array variable, it inherits the lower bounds of the variable, otherwise,the lower bounds default to 1.pointer => array_expressionFortran 2003 allows specifying arbitrary lower bounds on pointer association, like
so that the bounds of window become r:r+n-m,s:s+q-p.window(r:,s:) => table(m:n,p:q)Fortran 95 does not have this feature; however, it can be simulated using thefollowing trick (based on the pointer association rules for assumed shape array dummy arguments):function remap_bounds2(lb1,lb2,array) result(ptr) integer,intent(in) :: lb1,lb2 real,dimension(lb1:,lb2:),intent(in),target :: array real,dimension(:,:),pointer :: ptr ptr => arrayend function :window => remap_bounds2(r,s,table(m:n,p:q))The source code of an extended example of the use of pointers to support a data structure is in [ftp://ftp.numerical.rl.ac.uk/pub/MRandC/pointer.f90 pointer.f90] .
Intrinsic procedures
Most of the intrinsic functions have already been mentioned. Here, we deal only with their general classification and with those that have so far been omitted. All intrinsic procedures can be used with keyword arguments:
and many have optional arguments.CALL DATE_AND_TIME (TIME=t)The intrinsic procedures are grouped into four categories:
- elemental - work on scalars or arrays, e.g. ABS(a);
- inquiry - independent of value of argument (which may be undefined), e.g. PRECISION(a);
- transformational - array argument with array result of different shape, e.g. RESHAPE(a, b);
- subroutines, e.g. SYSTEM_CLOCK.
Bit inquiry BIT_SIZE Number of bits in the model Bit manipulation BTEST Bit testing IAND Logical AND IBCLR Clear bit IBITS Bit extraction IBSET Set bit IEOR Exclusive OR IOR Inclusive OR ISHFT Logical shift ISHFTC Circular shift NOT Logical complement Transfer function, as in INTEGER :: i = TRANSFER('abcd', 0) (replaces part of EQUIVALENCE) Subroutines DATE_AND_TIME Obtain date and/or time MVBITS Copies bits RANDOM_NUMBER Returns pseudorandom numbers RANDOM_SEED Access to seed SYSTEM_CLOCK Access to system clock CPU_TIME Returns processor time in secondsData transfer
(This is a subset only of the actual features and, exceptionally, lower case is usedin the code examples.)
Formatted input/output
These examples illustrate various forms of I/O lists with some simple formats (see below):
Variables, but not expressions, are equally valid in inputstatements using the read statement:integer :: i real, dimension(10) :: a character(len=20) :: word print "(i10)", i print "(10f10.3)", a print "(3f10.3)", a(1),a(2),a(3) print "(a10)", word(5:14) print "(3f10.3)", a(1)*a(2)+i, sqrt(a(3:4))read "(i10)", iIf an array appears as an item, it is treated as if the elements werespecified in array element order.
Any pointers in an I/O listmust be associated with a target, and transfer takes placebetween the file and the targets.
An item of derived type is treated as if the components were specifiedin the same order as in the type declaration, so
has the same effect as the statementread "(8f10.5)", p, t ! types point and triangle
An object in an I/O list is not permitted to be of a derived typethat has a pointer component at any level of component selection. Note that a zero-sized arraymay occur as an item in an I/O list.Such an item corresponds to no actual data transfer.read "(8f10.5)", p%x, p%y, t%a%x, t%a%y, t%b%x, & t%b%y, t%c%x, t%c%yThe format specification may alsobe given in the form of a character expression:
or as an asterisk -- this is a type of I/O known as"list-directed"I/O (see below), in which the format is defined by the computer system:character(len=*), parameter :: form="(f10.3)" : print form, q
Input/output operations are used to transfer data between thestorage of an executing program and an external medium, specified by a "unit number".However, two I/O statements, print and a variant ofread, do notreference any unit number: this is referred to as terminal I/O. Otherwise the form is:print *, "Square-root of q = ", sqrt(q)
where unit= is optional.The value may be any nonnegative integer allowed by the systemfor this purpose (but 5 and 6 often denote the keyboard and terminal).read (unit=4, fmt="(f10.3)") q read (unit=nunit, fmt="(f10.3)") q read (unit=4*i+j, fmt="(f10.3)") aAn asterisk is a variant -- again from the keyboard:
read (unit=*, fmt="(f10.3)") qA read with a unit specifier allowsexception handling:
read (unit=nunit, fmt="(3f10.3)", iostat=ios) a,b,c if (ios = 0) then! Successful read - continue execution. : else! Error condition - take appropriate action. call error (ios) end ifThere a second type of formatted output statement, thewrite statement:
write (unit=nout, fmt="(10f10.3)", iostat=ios) aInternal files
Theseallow format conversion between various representations to becarried outby the program in a storage area defined within the program itself.
If an internal file is a scalar,it has a single record whose length is that of the scalar.If it is an array, its elements, in array element order, aretreated as successive records of the file and each has length that of anarray element.An example using a write statement isinteger, dimension(30) :: ival integer :: key character(len=30) :: buffer character(len=6), dimension(3), parameter :: form=(/ "(30i1)", "(15i2)","(10i3)" /) read (unit=*, fmt="(a30,i1)") buffer, key read (unit=buffer, fmt=form (key)) ival(1:30/key)
that might writeinteger :: day real :: cash character(len=50) :: line :! write into line write (unit=line, fmt="(a, i2, a, f8.2, a)") "Takings for day ", day, " are ", cash, " dollars"Takings for day 3 are 4329.15 dollarsList-directed I/O
An example of a read without a specified format for input is:
If this reads the input recordinteger :: i real :: a complex, dimension(2) :: field logical :: flag character(len=12) :: title character(len=4) :: word : read *, i, a, field, flag, title, word
(in which blanks are used as separators),then i, a, field, flag, and title will acquire the values 10, 6.4, (1.0,0.0) and (2.0,0.0), .true.and test respectively,while word remains unchanged.10 6.4 (1.0,0.0) (2.0,0.0) t test/Quotation marks or apostrophes are required as delimiters for a string thatcontains a blank.
Non-advancing I/O
This is a form of reading and writingwithout always advancing the file position to ahead of the next record.Whereas an advancing I/O statement always repositions the file after the lastrecord accessed, a non-advancing I/O statement performs nosuch repositioning and may therefore leave the file positioned within arecord.
A non-advancing read might read the firstfew characters of a record and a normal read the remainder.character(len=3) :: key integer :: u, s, ios : read(unit=u, fmt="(a3)", advance="no", size=s, iostat=ios) key if (ios = 0) then : else! key is not in one record key(s+1:) = "" : end ifIn order to write a prompt to aterminal screen and to read from the next character position on thescreen without an intervening line-feed, we can write:
Non-advancing I/O is for external files, and is not available for list-directed I/O.write (unit=*, fmt="(a)", advance="no") "enter next prime number:" read (unit=*, fmt="(i10)") prime_numberEdit descriptors
It is possible to specify that an edit descriptor be repeated a specified number of times, using a "repeat count"::
The slash edit descriptor (see below)may have a repeat count, and a repeat count can also apply to a group of editdescriptors, enclosed in parentheses, with nesting:10f12.3
Repeats are possible:print "(2(2i5,2f8.2))", i(1),i(2),a(1),a(2), i(3),i(4),a(3),a(4)
will write 100 values eight to a line (apart from the last).print "(10i8)", (/ (i(j), j=1,100) /)Data edit descriptors
- Integer: iW iW.M
- Real: fW.D esW.D esW.DeE
- Complex: pairs of f or es edit descriptors
- Logical: lW
- Character: a aW
- Derived types: are edited by theappropriate sequence of edit descriptors corresponding to theintrinsic types of the ultimatecomponents of the derived type.type, public :: string integer :: length character(len=20) :: word end type string type(string) :: text read(unit=*, fmt="(i2, a)") text
Control edit descriptors
"Control edit descriptors setting conditions":
The ss (sign suppress) edit descriptor suppressesleading plus signs. To switch on plus sign printing, the sp (sign print) descriptor is used.Thes edit descriptor restores the option to the processor.
This descriptorremains in force for the remainderof the format specification,unless another of them is met.
"Control edit descriptors for immediate processing":
- Tabulation: tN trN tlNread (unit=*, fmt="(t3,i4, tl4,i1, i2)") i,j,k
- New records: / N/
Note thatread "(i5,i3,/,i5,i3,i2)", i, j, k, l, m
separates the two values by three blank records.print "(i5,4/,i5)", i, j - Colon editing: :terminates format control if there are no further items inan I/O list.
stops new records if n equals 1 or 2.print "( i5, :, /, i5, :, /, i5)", (/(l(i), i=1,n)/)
Unformatted I/O
This type of I/O should be used only in cases where the records aregenerated by a program on one computer, to be read back on the samecomputer or another computer using thesame internal number representations:
open(unit=4, file='test', form='unformatted') read(unit=4) q write(unit=nout, iostat=ios) a ! no fmt=Direct-access files
This form of I/O is also known as random access or indexed I/O.Here, all the records have the samelength, and eachrecord is identified by an index number. It is possible to write,read, or re-write any specified record without regard to position.
The file must be an external file and list-directed formatting and non-advancing I/O areunavailable.integer, parameter :: nunit=2, length=100 real, dimension(length) :: a real, dimension(length+1:2*length) :: b integer :: i, rec_length : inquire (iolength=rec_length) a open (unit=nunit, access="direct", recl=rec_length, status="scratch", action="readwrite") :! Write array b to direct-access file in record 14 write (unit=nunit, rec=14) b :!! Read the array back into array a read (unit=nunit, rec=14) a : do i = 1, length/2 a(i) = i end do!! Replace modified record write (unit=nunit, rec=14) aOperations on external files
Once again, this is an overview only.
File positioning statements
- The backspace statement:backspace (unit=u [,iostat=ios] ) ! where [ ] means optional
- The rewind statement:rewind (unit=u [,iostat=ios] )
- The endfile statement:endfile (unit=u [,iostat=ios] )
The open statement
The statement is used to connect an external file to a unit,create a file that is preconnected, or create a file and connect it to aunit.The syntax is
where olist is a list of optional specifiers.The specifiers may appear in any order.open (unit=u, status=st, action=act [,olist] )
Other specifiers are form and position.open (unit=2, iostat=ios, file="cities", status="new", access="direct", & action="readwrite", recl=100)The close statement
This is used to disconnect a file from a unit.
as inclose (unit=u [,iostat=ios] [,status=st] )close (unit=2, iostat=ios, status="delete")The inquire statement
At any time during the execution of a program it is possibleto inquire aboutthe status and attributes of a file using this statement.Using a variant of this statement,it is similarly possible to determine the status of aunit, for instance whether the unit number exists for that systemAnother variant permits an inquiry about the length of an output listwhen used to write an unformatted record.
For inquire by unit:
or for inquire by file:inquire (unit=u, ilist)
or for inquire by I/O list:inquire (file=fln, ilist)
As an example:inquire (iolength=length) olist
yieldslogical :: ex, op character (len=11) :: nam, acc, seq, frm integer :: irec, nr inquire (unit=2, exist=ex, opened=op, name=nam, access=acc, sequential=seq, form=frm, & recl=irec, nextrec=nr)
(assuming no intervening read or write operations).ex .true.op .true.nam citiesacc DIRECTseq NOfrm UNFORMATTEDirec 100nr 1Other specifiers are iostat, opened, number,named, formatted, position, action, read, write, readwrite.
Wikimedia Foundation. 2010.