Fortran 95 language features


This is an overview of []Fortran 95 language features. Included are the additional features of TR-15581:Enhanced Data Type Facilities, which have been universally implemented. 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 maintain backward compatibility. The current standard is Fortran 2018; many of its new features are still being implemented in compilers. The additional features of Fortran 2003, Fortran 2008 and Fortran 2018 are described by Metcalf, Reid and Cohen.

Language elements

Fortran is case-insensitive. The convention of writing Fortran keywords in upper case and all other names in lower case is adopted in this article; except, by way of contrast, in the input/output descriptions.

[|Basics]

The basic component of the Fortran language is its character set. Its members are
Tokens that have a syntactic meaning to the compiler are built from those components. There are six classes of tokens:
From the tokens, statements are built. These can be coded using the new free source form which does not require positioning in a rigid column structure:

FUNCTION string_concat ! This is a comment
TYPE, INTENT :: s1, s2
TYPE string_concat
string_concat%string_data = s1%string_data // &
s2%string_data ! This is a continuation
string_concat%length = s1%length + s2%length
END FUNCTION string_concat

Note the trailing comments and the trailing continuation mark. There may be 39 continuation lines, and 132 characters per line. Blanks are significant. Where a token or character constant is split across two lines:

... start_of&
&_name
... 'a very long &
&string'

a leading & on the continued line is also required.
Automatic conversion of source form for existing programs can be carried out by .
Its options are
Fortran has five intrinsic data types: INTEGER, REAL, COMPLEX, LOGICAL and CHARACTER. Each of those types can be additionally characterized by a kind. Kind, basically, defines internal representation of the type: for the three numeric types, it defines the precision and range, and for the other two, the specifics of storage representation. Thus, it is an abstract concept which models the limits of data types' representation; it is expressed as a member of a set of whole numbers, but those values are not specified by the Standard and not portable. For every type, there is a default kind, which is used if no kind is explicitly specified. For each intrinsic type, there is a corresponding form of literal constant. The numeric types INTEGER and REAL can only be signed.

Literal constants and kinds

INTEGER
Integer literal constants of the default kind take the form

1 0 -999 32767 +10

Kind can be defined as a named constant. If the desired range is ±10kind, the portable syntax for defining the appropriate kind, two_bytes is

INTEGER, PARAMETER :: two_bytes = SELECTED_INT_KIND

that allows subsequent definition of constants of the form

-1234_two_bytes +1_two_bytes

Here, two_bytes is the kind type parameter; it can also be an explicit default integer literal constant, like

-1234_2

but such use is non-portable.
The KIND function supplies the value of a kind type parameter:

KIND KIND

and the RANGE function supplies the actual decimal range :

RANGE

Also, in DATA statements, binary, octal and hexadecimal constants may be used :

B'01010101' O'01234567' Z'10fa'
REAL
There are at least two real kindsthe default and one with greater precision. SELECTED_REAL_KIND functions returns the kind number for desired range and precision; for at least 9 decimal digits of precision and a range of 10−99 to 1099, it can be specified as:

INTEGER, PARAMETER :: long = SELECTED_REAL_KIND

and literals subsequently specified as

1.7_long

Also, there are the intrinsic functions

KIND PRECISION RANGE

that give in turn the kind type value, the actual precision, and the actual range.
COMPLEX
COMPLEX data type is built of two integer or real components:

LOGICAL
There are only two basic values of logical constants: .TRUE. and .FALSE.. Here, there may also be different kinds. Logicals don't have their own kind inquiry functions, but use the kinds specified for INTEGERs; default kind of LOGICAL is the same as of INTEGER.

.FALSE. .true._one_byte

and the KIND function operates as expected:

KIND
CHARACTER
The forms of literal constants for CHARACTER data type are

'A string' "Another" 'A "quote"' '

. Different kinds are allowed, but not widely supported by compilers. Again, the kind value is given by the KIND function:

KIND

Number model and intrinsic functions

The numeric types are based on number models with associated inquiry functions. These functions are important for portable numerical software:
DIGITSNumber of significant digits
EPSILONAlmost negligible compared to one
HUGELargest number
MAXEXPONENTMaximum model exponent
MINEXPONENTMinimum model exponent
PRECISIONDecimal precision
RADIXBase of the model
RANGEDecimal exponent range
TINYSmallest positive number

Scalar variables

Scalar variables corresponding to the five intrinsic types are specified as follows:

INTEGER :: i
REAL :: a
COMPLEX :: current
LOGICAL :: Pravda
CHARACTER :: word
CHARACTER :: kanji_word

where the optional KIND parameter specifies a non-default kind, and the :: notation delimits the type and attributes from variable name and their optional initial values, allowing full variable specification and initialization to be typed in one statement. While it is not required in [|above] examples, most Fortran-90 programmers acquire the habit to use it everywhere.
LEN= specifier is applicable only to CHARACTERs and specifies the string length.
The explicit KIND= and LEN= specifiers are optional:

CHARACTER :: kanji_word

works just as well.
There are some other interesting character features. Just as a substring as in

CHARACTER :: line
... = line ! substring

was previously possible, so now is the substring

'0123456789'

Also, zero-length strings are allowed:

line ! zero-length string

Finally, there is a set of intrinsic character functions, examples being
ACHARIACHAR
ADJUSTLADJUSTR
LEN_TRIMINDEX
REPEATSCAN
TRIMVERIFY

Derived data types

For derived data types, the form of the type must be defined first:

TYPE person
CHARACTER name
REAL age
END TYPE person

and then, variables of that type can be defined:

TYPE you, me

To select components of a derived type, % qualifier is used:

you%age

Literal constants of derived types have the form TypeName:

you = person

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 a, b, c
END TYPE triangle

and for a variable of type triangle, as in

TYPE t

each component of type point is accessed as

t%a t%b t%c

which, in turn, have ultimate components of type real:

t%a%x t%a%y t%b%x etc.

.

Implicit and explicit typing

Unless specified otherwise, all variables starting with letters I, J, K, L, M and N are default INTEGERs, and all others are default REAL; 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 statements, like:

IMPLICIT COMPLEX
IMPLICIT CHARACTER
IMPLICIT REAL

However, it is a good practice to explicitly type all variables, and this can be forced by inserting the statement IMPLICIT NONE
at 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. 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
INTEGER, DIMENSION :: map

declares two arrays, rank-1 and rank-2, whose elements are in column-major order. Elements are, for example,

a a

and are scalars. The subscripts may be any scalar integer expression.
Sections are parts of the array variables, and are arrays themselves:

a ! rank one
map ! rank two
a ! vector subscript
a ! zero length

Whole arrays and array sections are array-valued objects. Array-valued constants are available, enclosed in :


making use of an implied-DO loop notation. Fortran 2003 allows the use of brackets:
and
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 :: vertex
END TYPE triplet
TYPE, DIMENSION :: t

so that
Variables can be given initial values as specified in a specification statement:

REAL, DIMENSION :: a =

and a default initial value can be given to the component of a derived data type:

TYPE triplet
REAL, DIMENSION :: vertex = 0.0
END TYPE triplet

When local variables are initialized within a procedure they implicitly acquire the SAVE attribute:

REAL, DIMENSION :: point =

This declaration is equivalent to

REAL, DIMENSION, SAVE :: point =

for local variables within a subroutine or function. The SAVE attribute causes local variables to retain their value after a procedure call and then to initialize the variable to the saved value upon returning to the procedure.

PARAMETER attribute

A named constant can be specified directly by adding the PARAMETER attribute and the constant values to a type statement:

REAL, DIMENSION, PARAMETER :: field =
TYPE, PARAMETER :: t = triplet

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 :: t1, t2
DATA t1/triplet/, t2%vertex/123./
DATA array / 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 and TRANSFER :

INTEGER, PARAMETER :: long = SELECTED_REAL_KIND, &
array =

Specification 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
USE mod ! contains a
REAL, DIMENSION :: b
REAL, DIMENSION :: x
INTEGER :: m
CHARACTER :: c
CHARACTER :: cc
REAL :: z

Expressions and assignments

Scalar numeric

The usual arithmetic operators are available +, -, *, /, **.
Parentheses are used to indicate the order of evaluation where necessary:

a*b + c ! * first
a* ! + 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 as real1; the result is of same kind, and is converted to the kind of real2 for assignment.
These functions are available for controlled rounding of real numbers to integers:
For scalar relational operations of numeric types, there is a set of built-in operators:
< <= /= > >=
.LT..LE..EQ..NE..GT..GE.
. Example expressions:

a < b.AND. i /= j ! for numeric variables
flag = a b ! for logical variable flags

Scalar characters

In the case of scalar characters and given CHARACTER result
it is legal to write

result = result ! overlap allowed
result = result ! no assignment of null string

Concatenation is performed by the operator '//'.

result = 'abcde'//'123'
filename = result//'.dat'

Derived-data types

No built-in operations exist between derived data types mutually or with intrinsic types. The meaning of existing or user-specified operators can be defined though:

TYPE string80
INTEGER length
CHARACTER value
END TYPE string80
CHARACTER:: char1, char2, char3
TYPE:: str1, str2, str3

we 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 the intrinsic symbol // and the named operator, .concat.. A difference between the two cases 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 = + vector2

the 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 INTERFACE

The string concatenation function is a more elaborated version of that shown [|already] in Basics. Note that in order to handle the error condition that arises when the two strings together exceed the preset 80-character limit, it would be safer to use a subroutine to perform the concatenation

MODULE string_type
IMPLICIT NONE
TYPE string80
INTEGER length
CHARACTER :: string_data
END TYPE string80
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
TYPE, INTENT :: s
CHARACTER, INTENT :: c
s%string_data = c
s%length = LEN
END SUBROUTINE c_to_s_assign
SUBROUTINE s_to_c_assign
TYPE, INTENT :: s
CHARACTER, INTENT :: c
c = s%string_data
END SUBROUTINE s_to_c_assign
TYPE FUNCTION string_concat
TYPE, INTENT :: s1, s2
TYPE :: s
INTEGER :: n1, n2
CHARACTER :: ctot
n1 = LEN_TRIM
n2 = LEN_TRIM
IF then
s%string_data = s1%string_data//s2%string_data
ELSE ! This is an error condition which should be handled - for now just truncate
ctot = s1%string_data//s2%string_data
s%string_data = ctot
END IF
s%length = LEN_TRIM
string_concat = s
END FUNCTION string_concat
END MODULE string_type
PROGRAM main
USE string_type
TYPE :: s1, s2, s3
CALL c_to_s_assign
CALL c_to_s_assign
s3 = s1//s2
WRITE 'Result: ',s3%string_data
WRITE 'Length: ',s3%length
END PROGRAM

Defined operators such as these are required for the expressions that are
allowed also in structure constructors :

str1 = string ! structure constructor

Arrays

In the case of arrays then, as long as they are of the same shape, operations and assignments are extended in an obvious way, on an element-by-element basis. For example, given declarations of

REAL, DIMENSION :: a, b, c
REAL, DIMENSION :: v, w
LOGICAL flag

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 ! array division, and addition to section
flag = ab ! whole array relational test and assignment
c = a + b ! array section addition and assignment
v = v ! overlapping section assignment

The order of expression evaluation is not specified in order to allow for optimization on parallel and vector machines. Of course, any operators for arrays of derived type must be defined.
Some real intrinsic functions that are useful for numeric
computations are

CEILING FLOOR MODULO
EXPONENT FRACTION
NEAREST RRSPACING SPACING
SCALE SET_EXPONENT

These are array valued for array arguments, like all FORTRAN 77 functions :

INT REAL CMPLX
AINT ANINT NINT
ABS MOD SIGN
DIM MAX MIN
SQRT 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: IF x = y
A full-blown IF construct is illustrated by

IF THEN
IF THEN
x = 0.
ELSE
z = 0.
END IF
ELSE IF THEN
z = 1.
ELSE
x = 1.
END IF

CASE construct

The CASE construct is a replacement for the computed GOTO, but is better
structured and does not require the use of statement labels:

SELECT CASE ! number of type integer
CASE ! all values [|below] 0
n_sign = -1
CASE ! only 0
n_sign = 0
CASE ! all values above 0
n_sign = 1
END SELECT

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:

CASE

A default is available:

CASE DEFAULT

There is only one evaluation, and only one match.

DO construct

A simplified but sufficient form of the DO construct is illustrated by

outer: DO
inner: DO i = j, k, l ! from j to k in steps of l
:
IF CYCLE
:
IF EXIT outer
:
END DO inner
END DO outer

where we note that loops may be optionally named so that any EXIT or CYCLE
statement may specify which loop is meant.
Many, but not all, simple loops can be replaced by array expressions and
assignments, or by new intrinsic functions. For instance

tot = 0.
DO i = m, n
tot = tot + a
END DO

becomes simply tot = SUM

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 - these do something.
Subprograms are either functions or subroutines, which are
either external, internal or module subroutines.
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 program is

PROGRAM test
PRINT *, 'Hello world!'
END PROGRAM test

An example of a main program and an external subprogram, forming an executable program, is

PROGRAM test
CALL print_message
END PROGRAM test
SUBROUTINE print_message
PRINT *, 'Hello world!'
END SUBROUTINE print_message

The form of a function is

FUNCTION name ! zero or more arguments
:
name =...
:
END FUNCTION name

The form of reference of a function is x = name

Internal procedures

An internal subprogram is one contained in another and provides a replacement for the statement function:

SUBROUTINE outer
REAL x, y
:
CONTAINS
SUBROUTINE inner
REAL y
y = x + 1.
:
END SUBROUTINE inner ! SUBROUTINE mandatory
END SUBROUTINE outer

We say that outer is the host of inner, and that inner obtains
access to entities in outer by host association, whereas
y is a local variable to inner.
The 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
An example of a module
containing a type definition, interface block and function subprogram is

MODULE interval_arithmetic
TYPE interval
REAL lower, upper
END TYPE interval
INTERFACE OPERATOR
MODULE PROCEDURE add_intervals
END INTERFACE
:
CONTAINS
FUNCTION add_intervals
TYPE, INTENT :: a, b
TYPE 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

and the simple statement

USE interval_arithmetic

provides use association to all the module's entities. Module
subprograms may, in turn, contain internal subprograms.

Controlling accessibility

The PUBLIC and PRIVATE attributes are used in specifications in
modules to limit the scope of entities. The attribute form is

REAL, PUBLIC :: x, y, z ! default
INTEGER, PRIVATE :: u, v, w

and the statement form is

PUBLIC :: x, y, z, OPERATOR
PRIVATE :: u, v, w, ASSIGNMENT, OPERATOR

The statement form has to be used to limit access to operators, and can
also be used to change the overall default:

PRIVATE ! sets default for module
PUBLIC :: only_this

For derived types there are three possibilities: the type and its
components are all PUBLIC, the type is PUBLIC and its components PRIVATE, or all of it is
PRIVATE :

MODULE mine
PRIVATE
TYPE, PUBLIC :: list
REAL x, y
TYPE, POINTER :: next
END TYPE list
TYPE :: tree
:
END MODULE mine

The 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:

USE mine, local_list => list

or to restrict the used entities to a specified set:

USE mine, ONLY : list

These may be combined:

USE mine, ONLY : local_list => list

Arguments

We may specify the intent of dummy arguments:

SUBROUTINE shuffle
INTEGER, INTENT :: ncards
INTEGER, INTENT, DIMENSION :: cards

Also, INOUT is possible: here the actual argument must be a variable
.
Arguments may be optional:

SUBROUTINE mincon
REAL, OPTIONAL, DIMENSION :: upper, lower
:
IF THEN ! test for presence of actual argument
:

allows us to call mincon by

CALL mincon

Arguments may be keyword rather than positional :

CALL mincon

Optional and keyword arguments are handled by explicit interfaces, that is
with internal or module procedures or with interface blocks.

[|Interface blocks]

Any reference to an internal or module subprogram is
through an interface that is 'explicit'. A reference to an external procedure is usually 'implicit'
. 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:

REAL FUNCTION minimum
! returns the minimum value of the function func
! in the interval
REAL, INTENT :: a, b
INTERFACE
REAL FUNCTION func
REAL, INTENT :: x
END FUNCTION func
END INTERFACE
REAL f,x
:
f = func ! invocation of the user function.
:
END FUNCTION minimum

An explicit interface is obligatory for
It allows
full checks at compile time between actual and dummy arguments.
In general, the best way to ensure that a procedure interface is explicit is either to place the procedure concerned in a module or to use it as an internal procedure.

Overloading and generic interfaces

Interface blocks provide the
mechanism by which we are able to define generic names for specific procedures:

INTERFACE gamma ! generic name
FUNCTION sgamma ! specific name
REAL sgamma, x
END
FUNCTION dgamma ! specific name
REAL dgamma, x
END
END INTERFACE

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 simply

INTERFACE gamma
MODULE PROCEDURE sgamma, dgamma
END INTERFACE

We can use existing names, e.g. SIN, and the compiler sorts out the
correct association.
We have already seen the use of interface blocks for defined operators and
assignment.

Recursion

Indirect recursion is useful for multi-dimensional
integration. For

volume = integrate

We might have

RECURSIVE FUNCTION integrate
! Integrate f from bounds to bounds
REAL integrate
INTERFACE
FUNCTION f
REAL f, x
END FUNCTION f
END INTERFACE
REAL, DIMENSION, INTENT :: bounds
:
END FUNCTION integrate

and to integrate f over a rectangle:

FUNCTION fy
USE func ! module func contains function f
REAL fy, y
yval = y
fy = integrate
END

Direct recursion is when a procedure calls itself, as in

RECURSIVE FUNCTION factorial RESULT
INTEGER res, n
IF THEN
res = 1
ELSE
res = n*factorial
END IF
END

Here, we note the RESULT clause and termination test.

Pure procedures

This is a feature for parallel computing.
In [|the FORALL statement and construct], any side effects in a function can impede optimization on a parallel processor the order of execution of the assignments could affect the results. To control this situation, we add the PURE keyword to the SUBROUTINE or FUNCTION statementan assertion that the procedure :
A compiler can check that this is the case, as in

PURE FUNCTION calculate

All the intrinsic functions are pure.

[|Array handling]

Array handling is included in Fortran for two main reasons:
At the same time, major extensions of the functionality in this area have been
added. We have already met whole arrays above [|#Arrays 1] and here #Arrays 2 - now
we develop the theme.

Zero-sized arrays

A zero-sized array is handled by Fortran as a
legitimate object, without special coding by the programmer. Thus, in

DO i = 1,n
x = b / a
b = b - a * x
END DO

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
is not conformable with one of shape, whereas x = 3 is a valid 'do nothing' statement.

Assumed-shape arrays

These are an extension and replacement for
assumed-size arrays. Given an actual argument like:

REAL, DIMENSION :: a
:
CALL sub

the corresponding dummy argument specification defines only the type and
rank of the array, not its shape. This information has to be made available by an
explicit interface, often using an interface block. Thus we write just

SUBROUTINE sub
REAL, DIMENSION :: da

and this is as if da were dimensioned. However, we can specify any
lower bound and the array maps accordingly.

REAL, DIMENSION :: da

The shape, not bounds, is passed, where the default lower bound is 1 and the default upper bound is the corresponding extent.

Automatic arrays

A partial replacement for the uses to which EQUIVALENCE
was put is provided by this facility, useful for local, temporary arrays, as in

SUBROUTINE swap
REAL, DIMENSION :: a, b
REAL, DIMENSION :: work
work = a
a = b
b = work
END SUBROUTINE swap

The actual storage is typically maintained on a stack.

ALLOCATABLE and ALLOCATE

Fortran provides dynamic allocation of
storage; it relies on a heap storage mechanism. An example for establishing a work array for a whole program is

MODULE work_array
INTEGER n
REAL, DIMENSION, ALLOCATABLE :: work
END MODULE
PROGRAM main
USE work_array
READ n
ALLOCATE
:
DEALLOCATE

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,

DEALLOCATE

Deallocation of arrays is automatic when they go out of scope.

Elemental operations, assignments and procedures

We have already met whole array
assignments and operations:

REAL, DIMENSION :: a, b
a = 0. ! scalar broadcast; elemental assignment
b = SQRT ! intrinsic function result as array object

In the second assignment, an intrinsic function returns an array-valued
result for an array-valued argument. We can write array-valued functions
ourselves :

PROGRAM test
REAL, DIMENSION :: a =, &
b =, r
r = f
PRINT *, r
CONTAINS
FUNCTION f
REAL, DIMENSION :: c, d
REAL, DIMENSION :: f
f = c*d !
END FUNCTION f
END PROGRAM test

Elemental procedures are specified with scalar dummy arguments that may be called with
array actual arguments. In the case of a function, the shape of the result is the shape of the array
arguments.
Most intrinsic functions are elemental and
Fortran 95 extends this feature to non-intrinsic procedures, thus providing the effect
of 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.

ELEMENTAL SUBROUTINE swap
REAL, INTENT :: a, b
REAL :: work
work = a
a = b
b = work
END SUBROUTINE swap

The dummy arguments cannot be used in specification expressions except as arguments to certain intrinsic functions.

WHERE

Often, we need to mask an assignment. This we can do using the WHERE, either as a statement:

WHERE a = 1.0/a ! avoid division by 0

, or as a construct:

WHERE
a = 1.0/a
b = a ! all arrays same shape
END WHERE

or

WHERE
a = 1.0/a
ELSEWHERE
a = HUGE
END WHERE

Further:
When a DO construct is executed, each successive iteration is performed in order and one after the otheran impediment to optimization on a parallel processor.

FORALL a = x

where the individual assignments may be carried out in any order, and even simultaneously. The FORALL may be considered to be an array assignment expressed with the help of indices.

FORALL x = 1.0/y

with masking condition.
The FORALL construct allows several assignment statements to be executed in order.

a = a + a + a + a
b = a

is equivalent to the array assignments

FORALL
a = a + a + a + a
b = a
END FORALL

The FORALL version is more readable.
Assignment in a FORALL is like an array assignment:
as if all the expressions were evaluated in any order, held in temporary storage, then all the assignments performed in any order. The first statement must fully complete before the second can begin.
A FORALL may be nested, and may include a WHERE.
Procedures referenced within a FORALL must be pure.

Array elements

For a simple case, given

REAL, DIMENSION :: a

we can reference a single element as, for instance, a. For a
derived-data type like

TYPE fun_del
REAL u
REAL, DIMENSION :: du
END TYPE fun_del

we can declare an array of that type:

TYPE, DIMENSION :: tar

and a reference like tar is an element of type fun_del, but tar%du is an array of type real, and tar%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.

Array subobjects (sections)

The general form of subscript for an array
section is
:
as in

REAL a
a ! part of one row
a ! part of one column
a ! whole row
a ! every third element of row
a ! row in reverse order
a ! vector subscript
a ! 11 is legal as not referenced
a ! rank two section

Note that a vector subscript with duplicate values cannot appear on the
left-hand side of an assignment as it would be ambiguous. Thus,

b =

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:

tar%du ! illegal

We note that a given value in an array can be referenced both as an
element and as a section:

a ! scalar
a ! array section

depending on the circumstances or requirements. By qualifying objects of
derived type, we obtain elements or sections depending on the rule stated
earlier:

tar%u ! array section
tar%u ! component of an array element

Arrays intrinsic functions

Vector and matrix multiply
DOT_PRODUCT Dot product of 2 rank-one arrays
MATMUL Matrix multiplication
Array reduction
ALL True if all values are true
ANY True if any value is true. Example:
IF 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 inquiry
ALLOCATED Array allocation status
LBOUND Lower dimension bounds of an array
SHAPE Shape of an array
SIZE Total number of elements in an array
UBOUND Upper dimension bounds of an array
Array construction
MERGE Merge under mask
PACK Pack an array into an array of rank one under a mask
SPREAD Replicate array by adding a dimension
UNPACK Unpack an array of rank one into an array under mask
Array reshape
RESHAPE Reshape an array
Array manipulation
CSHIFT Circular shift
EOSHIFT End-off shift
TRANSPOSE Transpose of an array of rank two
Array location
MAXLOC Location of first maximum value in an array
MINLOC Location of first minimum value in an array

[|Pointers]

Basics

Pointers are variables with the POINTER attribute; they are not a
distinct data type.

REAL, POINTER :: var

They are conceptually a descriptor listing the attributes of the objects
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
:

ALLOCATE

and they are dereferenced automatically, so no special symbol required. In

var = var + 2.3

the value of the target of var is used and modified. Pointers cannot be
transferred via I/O. The statement

WRITE *, var

writes the value of the target of var and not the pointer descriptor
itself.
A pointer can point to another pointer, and hence to its target, or to a
static object that has the TARGET attribute:

REAL, POINTER :: object
REAL, TARGET :: target_obj
var => object ! pointer assignment
var => target_obj

but they are strongly typed:

INTEGER, POINTER :: int_var
var => int_var ! illegal - types must match

and, similarly, for arrays the ranks as well as the type must agree.
A pointer can be a component of a derived type:

TYPE entry ! type for sparse matrix
REAL value
INTEGER index
TYPE, POINTER :: next ! note recursion
END TYPE entry

and we can define the beginning of a linked chain of such entries:

TYPE, POINTER :: chain

After suitable allocations and definitions, the first two entries could be
addressed as

chain%value chain%next%value
chain%index chain%next%index
chain%next chain%next%next

but we would normally define additional pointers to point at, for
instance, the first and current entries in the list.

Association

A pointer's association status is one of
Some care has to be taken not to leave a pointer 'dangling' by
use of DEALLOCATE on its target without nullifying any other pointer referring
to it.
The intrinsic function ASSOCIATED can test the association status of a
defined pointer:

IF THEN

or between a defined pointer and a defined target :

IF THEN

An alternative way to initialize a pointer, also in a specification statement,
is to use the NULL function:

REAL, POINTER, DIMENSION :: vector => NULL ! compile time
vector => NULL ! run time

Pointers 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 :

REAL, TARGET :: b, c, r, s, z
REAL, POINTER :: a, x, y
INTEGER mult
DO mult = 1, 2
IF THEN
y => r ! no data movement
a => c
x => z
ELSE
y => s ! no data movement
a => b
x => r
END IF
y = MATMUL ! common calculation
END DO

For objects of derived type we have to distinguish between pointer and
normal assignment. In

TYPE, POINTER :: first, current
first => current

the assignment causes first to point at current, whereas

first = current

causes current to overwrite first and is equivalent to

first%value = current%value
first%index = current%index
first%next => current%next

Pointer arguments

If an actual argument is a pointer then, if the dummy
argument is also a pointer,
If the dummy argument is not a
pointer, it becomes associated with the target of the actual argument:

REAL, POINTER :: a
:
ALLOCATE
:
CALL sub
:
SUBROUTINE sub
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

USE data_handler
REAL x
REAL, POINTER :: y
y => compact

where the module data_handler contains

FUNCTION compact
REAL, POINTER :: compact
REAL x
! A procedure to remove duplicates from the array x
INTEGER n
: ! Find the number of distinct values, n
ALLOCATE
: ! Copy the distinct values into compact
END FUNCTION compact

The result can be used in an expression.

Arrays of pointers

These do not exist as such: given

TYPE :: rows

then

rows%next ! illegal

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:

TYPE row
REAL, POINTER :: r
END TYPE

and then defining arrays of this data type

TYPE :: s, t

where the storage for the rows can be allocated by, for instance,

DO i = 1, n
ALLOCATE %r) ! Allocate row i of length i
END DO

The array assignment s = tis then equivalent to the pointer assignments s%r => t%r for all components.

Pointers as dynamic aliases

Given an array

REAL, TARGET :: table

that is frequently referenced with the fixed subscripts

table

these references may be replaced by

REAL, DIMENSION, POINTER :: window
:
window => table

The subscripts of window are 1:n-m+1, 1:q-p+1. Similarly, for tar%u
, we can use, say, taru => tar%u to point at all the u components of tar, and subscript it as taru
The subscripts are as those of tar itself.
In the pointer association

pointer => array_expression

the lower bounds for pointer are determined as if lbound was applied to array_expression. Thus, when a pointer is assigned to a whole array variable, it inherits the lower bounds of the variable, otherwise, the lower bounds default to 1.
Fortran 2003 allows specifying arbitrary lower bounds on pointer association, like

window => table

so that the bounds of window become r:r+n-m,s:s+q-p.
Fortran 95 does not have this feature; however, it can be simulated using the
following trick :

FUNCTION remap_bounds2 RESULT
INTEGER, INTENT :: lb1,lb2
REAL, DIMENSION, INTENT, TARGET :: array
REAL, DIMENSION, POINTER :: ptr
ptr => array
END FUNCTION
:
window => remap_bounds2

The source code of an extended example of the use of pointers to support a
data structure is in .

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:

CALL DATE_AND_TIME

and many have optional arguments.
The intrinsic procedures are grouped into four categories:
  1. elemental - work on scalars or arrays, e.g. ABS;
  2. inquiry - independent of value of argument, e.g. PRECISION;
  3. transformational - array argument with array result of different shape, e.g. RESHAPE;
  4. subroutines, e.g. SYSTEM_CLOCK.
The procedures not already
introduced are
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

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 seconds

Data transfer

Formatted input/output

These examples illustrate various forms of I/O lists with some simple formats :

integer :: i
real, dimension :: a
character :: word
print "", i
print "", a
print "", a,a,a
print "", word
print "", a*a+i, sqrt

Variables, but not expressions, are equally valid in input
statements using the read statement:

read "", i

If an array appears as an item, it is treated as if the elements were specified in array element order.
Any pointers in an I/O list must be associated with a target, and transfer takes place between the file and the targets.
An item of derived type is treated as if the components were specified
in the same order as in the type declaration, so

read "", p, t ! types point and triangle

has the same effect as the statement

read "", p%x, p%y, t%a%x, t%a%y, t%b%x, &
t%b%y, t%c%x, t%c%y

An object in an I/O list is not permitted to be of a derived type
that has a pointer component at any level of component selection.
Note that a zero-sized array
may occur as an item in an I/O list.
Such an item corresponds to no actual data transfer.
The format specification may also
be given in the form of a character expression:

character, parameter :: form=""
print form, q

or as an asterisk this is a type of I/O known as
list-directed
I/O, in which the format is defined by the computer system:

print *, "Square-root of q = ", sqrt

Input/output operations are used to transfer data between the
storage of an executing program and an external medium, specified by a unit number.
However, two I/O statements, print and a variant of
read, do not
reference any unit number: this is referred to as terminal I/O.
Otherwise the form is:

read q
read q
read a

where unit= is optional.
The value may be any nonnegative integer allowed by the system
for this purpose.
An asterisk is a variantagain from the keyboard:

read q

A read with a unit specifier allows exception handling:

read a,b,c
if then
! Successful read - continue execution.
:
else
! Error condition - take appropriate action.
call error
end if

There a second type of formatted output statement, the
write statement:

write a

Internal files

These allow format conversion between various representations to be carried out by the program in a storage area defined within the program itself.

integer, dimension :: ival
integer :: key
character :: buffer
character, dimension, parameter :: form=", "","
read buffer, key
read ival

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, are treated as successive records of the file and each has length that of an array element.
An example using a write statement is

integer :: day
real :: cash
character :: line
! write into line
write "Takings for day ", day, " are ", cash, " dollars"

that might write

Takings for day 3 are 4329.15 dollars

List-directed I/O

An example of a read without a specified format for input is

integer :: i
real :: a
complex, dimension :: field
logical :: flag
character :: title
character :: word
read *, i, a, field, flag, title, word

If this reads the input record

10 6.4 t test/

,
then i, a,
field, flag, and title will acquire the values 10, 6.4,
and, .true.
and test respectively,
while word remains unchanged.
Quotation marks or apostrophes are required as delimiters for a string that
contains a blank.

Non-advancing I/O

This is a form of reading and writing
without always advancing the file position to ahead of the next record.
Whereas an advancing I/O statement always repositions the file after the last
record accessed, a non-advancing I/O statement performs no
such repositioning and may therefore leave the file positioned within a
record.

character :: key
integer :: u, s, ios
read key
if then
:
else
! key is not in one record
key = ""
:
end if

A non-advancing read might read the first
few characters of a record and a normal read the remainder.
In order to write a prompt to a
terminal screen and to read from the next character position on the
screen without an intervening line-feed, we can write

write "enter next prime number:"
read prime_number

Non-advancing I/O is for external files, and is
not available for list-directed I/O.

Edit descriptors

It is possible to specify that an edit descriptor be repeated a specified number of times,
using a repeat count: 10f12.3
The slash edit descriptor
may have a repeat count, and a repeat count
can also apply to a group of edit
descriptors, enclosed in parentheses, with nesting:

print "", i,i,a,a, i,i,a,a

Entire format specifications can be repeated:

print "",

writes 10 integers, each occupying 8 character positions, on each of 20 lines.

Data edit descriptors

Control edit descriptors

Control edit descriptors setting conditions:
Control edit descriptors for immediate processing:

Unformatted I/O

This type of I/O should be used only in cases where the records are
generated by a program on one computer, to be read back on the same
computer or another computer using the
same internal number representations:

open
read q
write 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 same
length, and each
record is identified by an index number. It is possible to write,
read, or re-write any specified record without regard to position.

integer, parameter :: nunit=2, length=100
real, dimension :: a
real, dimension :: b
integer :: i, rec_length
inquire a
open
! Write array b to direct-access file in record 14
write b
! Read the array back into array a
read a
do i = 1, length/2
a = i
end do
! Replace modified record
write a

The file must be an external file and
list-directed formatting and non-advancing I/O are
unavailable.

Operations on external files

Once again, this is an overview only.

File positioning statements

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 a
unit.
The syntax is

open

where olist is a list of optional specifiers.
The specifiers may appear in any order.

open

Other specifiers are form and position.

The close statement

This is used to disconnect a file from a unit.

close

as in

close

The inquire statement

At any time during the execution of a program it is possible to inquire about the status and attributes of a file using this statement.
Using a variant of this statement, it is similarly possible to determine the status of a unit, for instance whether the unit number exists for that system.
Another variant permits an inquiry about the length of an output list when used to write an unformatted record.
For inquire by unit

inquire

or for inquire by file

inquire

or for inquire by I/O list

inquire olist

As an example

logical :: ex, op
character :: nam, acc, seq, frm
integer :: irec, nr
inquire

yields

ex .true.
op .true.
nam cities
acc DIRECT
seq NO
frm UNFORMATTED
irec 100
nr 1

.
Other specifiers are iostat, opened, number,
named, formatted, position, action, read, write, readwrite
.