Fortran 90 Tutorial
Fortran 90 Tutorial
Fortran 90 Tutorial
Michael Metcalf
CN Division, CERN, CH 1211, Geneva 23, Switzerland
1 2 3 4 5 6 7 8 9
Language Elements Expressions and Assignments Control Statements Program Units and Procedures Array handling Pointers Specication Statements Intrinsic Procedures Input/Output Index
1 6 8 9 12 16 20 22 23 25
Full details of all the items in this tutorial can be found in Fortran 90/95 Explained, by M. Metcalf and J. Reid, (Oxford, 1996), the book upon which it has been based. Fortran 90 contains the whole of FORTRAN 77only the new features are described in this tutorial. The tutorial is also available on WWW using the URL http://wwwcn.cern.ch/asdoc/f90.html. The author wishes to thank Michel Goossens (CERN/CN) for his helpful and skilful assistance in preparing this tutorial. Version of October 1995
Fortran 90 Tutorial
1. Language Elements
The basic components of the Fortran language are its character set. The members are: the letters A ... Z and a ... the numerals 0 ... 9; the underscore _ and the special characters
= ! : " + % blank & < * > / ? ( ) z (which are equivalent outside a character context);
From these components, we build the tokens that have a syntactic meaning to the compiler. There are six classes of token: Label: 123 Constant: 123.456789_long Keyword: ALLOCATABLE Operator: .add. Name: solve_equation (can have up to 31 characters, including a _). Separator: / ( ) (/ /) , = => : :: % From the tokens, we can build statements. These can be coded using the new free source form which does not require positioning in a rigid column structure, as follows:
FUNCTION string_concat(s1, s2) ! This is a comment TYPE (string), INTENT(IN) :: s1, s2 TYPE (string) string_concat string_concat%string_data = s1%string_data(1:s1%length) // & s2%string_data(1:s2%length) ! 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 signicant. Where a token or character constant is split across two lines:
... &_name ... &string' 'a very long & start_of&
a leading & on the continued line is also required. Automatic conversion of source form for existing programs can be carried out by CONVERT (CERN Program Library Q904). Its options are: signicant blank handling; indentation; CONTINUE replaced by END DO; name added to subprogram END statement; and INTEGER*2 etc. syntax converted. The source code of the CONVERT program can be obtained by anonymous ftp to jkr.cc.rl.ac.uk (130.246.8.23). The directory is /pub/MandR and the le name is convert.f90.
Fortran 90 Tutorial
Fortran has ve intrinsic data types. For each there is a corresponding form of literal constant. For the three numeric intrinsic types they are:
INTEGER
Examples are: for the default kind; but we may also dene, for instance for a desired range of ;104 to 104 , a named constant, say two_bytes:
INTEGER, PARAMETER :: two_bytes = SELECTED_INT_KIND(4) 1 0 -999 32767 +10
Here, two_bytes is the kind type parameter; it can also be a default integer literal constant, like
-1234_2
but use of an explicit literal constant would be non-portable. The KIND function supplies the value of a kind type parameter:
KIND(1) KIND(1_two_bytes)
and the RANGE function supplies the actual decimal range (so the user must make the actual mapping to bytes):
RANGE(1_two_bytes)
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 kinds the default, and one with greater precision (this replaces DOUBLE PRECISION). We might specify for at least 9 decimal digits of precision and a range of 10;99 to 1099, allowing
1.7_long INTEGER, PARAMETER :: long = SELECTED_REAL_KIND(9, 99)
that give in turn the kind type value, the actual precision (here at least 9), and the actual range (here at least 99).
COMPLEX
The numeric types are based on model numbers with associated inquiry functions (whose values are independent of the values of their arguments). These functions are important for writing portable numerical software.
DIGITS(X) EPSILON(X) HUGE(X) MAXEXPONENT(X) MINEXPONENT(X) PRECISION(X) RADIX(X) RANGE(X) TINY(X)
Number of signicant digits Almost negligible compared to one (real) Largest number Maximum model exponent (real) Minimum model exponent (real) Decimal precision (real, complex) Base of the model Decimal exponent range Smallest postive number (real)
Fortran 90 Tutorial
The forms of literal constants for the two non-numeric data types are:
CHARACTER 'A string' "Another" 'A "quote"' 2_' '
''
(the last being a null string). Other kinds are allowed, especially for support of non-European languages: and again the kind value is given by the KIND function:
KIND('ASCII') LOGICAL
Here, there may also be different kinds (to allow for packing into bits):
.FALSE. .true._one_bit
where the optional KIND parameter species a non-default kind, and the LEN= specier replaces the *len form. The explicit KIND and LEN speciers are optional and the following works just as well:
CHARACTER(2, Kanji) kanji_word
For derived-data types we must rst dene the form of the type:
TYPE person CHARACTER(10) name REAL age END TYPE person
Fortran 90 Tutorial
Denitions may refer to a previously dened type:
TYPE point REAL x, y END TYPE point TYPE triangle TYPE(point) a, b, c END TYPE triangle
We note that the % qualier was chosen rather than . because of ambiguity difculties. Arrays are considered to be variables in their own right. Given
REAL a(10) INTEGER, DIMENSION(0:100, -50:50) :: map
(the latter an example of the syntax that allows grouping of attributes to the left of :: and of variables sharing those attributes to the right), we have two arrays whose elements are in array element order (column major), but not necessarily in contiguous storage. Elements are, for example,
a(1) a(i*j)
and are scalars. The subscripts may be any scalar integer expression. Sections are
a(i:j) map(i:j, k:l:m) a(map(i, k:l)) a(3:2) ! ! ! ! rank one rank two vector subscript zero length
Whole arrays and array sections are array-valued objects. Array-valued constants (constructors) are available:
(/ (/ (/ (/ (/ 1, 2, 3, 4, 5 /) (i, i = 1, 9, 2) /) ( (/ 1, 2, 3 /), i = 1, 10) /) (0, i = 1, 100) /) (0.1*i, i = 1, 10) /)
making use of the implied-DO loop notation familiar from I/O lists. A derived data type may, of course, contain array components:
TYPE triplet REAL, DIMENSION(3) :: vertex END TYPE triplet TYPE(triplet), DIMENSION(1) :: t
so that
t(2) t(2)%vertex ! a scalar (a structure) ! an array component of a scalar
Fortran 90 Tutorial
There are some other interesting character extensions. Just as a substring as in
CHARACTER(80), DIMENSION(60) :: page ... = page(j)(i:i) ! substring
Fortran 90 Tutorial
converts integer 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. For scalar relational operations, there is a set of new, alternative operators:
< <= == /= > >=
In the case of scalar characters, two old restrictions are lifted. Given
CHARACTER(8) result
For an operation between derived-data types, or between a derived type and an intrinsic type, we must dene the meaning of the operator. (Between intrinsic types, there are intrinsic operations only.) Given
TYPE string INTEGER length CHARACTER(80) value END TYPE string CHARACTER char1, char2, char3 TYPE(string) str1, str2, str3
we can write
str3 str3 char3 str3 = = = = str1//str2 str1.concat.str2 char2//char3 char1 ! ! ! ! must define operation must dedine operation intrinsic operator only must define assignment
For the rst three cases, assignment applies on a component-by-component basis (but can be overridden), and the rst two cases require us to dene the exact meaning of the // symbol. We see here the use both of an intrinsic symbol and of a named operator, .concat. . A difference is that, for an intrinsic operator token, the usual precedence rules apply, whereas for named operators their precedence is the highest as a unary operator or the lowest as a binary one. In
vector3 = matrix * vector1 + vector2 vector3 =(matrix .times. vector1) + vector2
the two expresions are equivalent only if appropriate parentheses are added as shown. In each case, we have to provide, in a module, procedures dening the operator and assignment, and make the association by an interface block, also in the module (we shall return to this later).
Fortran 90 Tutorial
For the moment, here is an example of an interface for string concatenation
INTERFACE OPERATOR(//) MODULE PROCEDURE string_concat END INTERFACE
and an example of part of a module containing the denitions of character-to-string and string to character assignment. The string concatenation function was shown already in part 1.
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) :: CHARACTER(LEN=*), INTENT(IN) :: 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) :: CHARACTER(LEN=*), INTENT(OUT) :: 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 s c
s c
Dened operators such as these are required for the expressions that are allowed too in structure constructors (see chapter 1):
str1 = string(2, char1//char2) ! structure constructor
So far we have discussed scalar variables. In the case of arrays, 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
REAL, DIMENSION(10, 20) :: a, b, c REAL, DIMENSION(5) :: v, w LOGICAL flag(10, 20)
can write
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 flag = a==b ! whole array relational test and assignment c(1:8, 5:10) = a(2:9, 5:10) + b(1:8, 15:20) ! array section addition and assignment v(2:5) = v(1:4) ! overlapping section assignment
The order of expression evaluation is not specied in order to allow for optimization on parallel and vector machines. Of course, any operators for arrays of derived type must be dened. There are some new real intrinsic functions that are useful for numeric computations:
CEILING EXPONENT NEAREST SCALE FLOOR FRACTION RRSPACING SET_EXPONENT MODULO (also integer) SPACING
Like all FORTRAN 77 functions (SIN, ABS, etc., but not LEN), these are array valued for array arguments (i.e. are elemental).
Fortran 90 Tutorial
3. Control Statements
The CASE construct is a replcement for the computed GOTO, but is better structured and does not require the use of statement labels:
SELECT CASE CASE (:-1) n_sign = CASE (0) n_sign = CASE (1:) n_sign = END SELECT (number) -1 ! only 0 0 ! all values above 0 1 ! NUMBER of type integer ! all values below 0
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 (1, 2, 7, 10:17, 23)
A default is available:
CASE DEFAULT
There is only one evaluation, and only one match. A simplied but sufcient form of the DO construct is illustrated by
outer: DO inner: DO i = j, k, l ! only integers : IF (...) CYCLE : IF (...) EXIT outer END DO inner END DO outer
where we note that loops may be named so that the EXIT and CYCLE statements 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(i) END DO
becomes simply
tot = SUM( a(m:n) )
Fortran 90 Tutorial
! SUBROUTINE mandatory
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. 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 are used to package global data (replaces COMMON and BLOCK DATA); type denitions (themselves a scoping unit); subprograms (which among other things replaces the use of ENTRY); interface blocks (another scoping unit, see next article); namelist groups. An example of a module containing a type detion, 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(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 modules entities. Module subprograms may, in turn, contain internal subprograms.
Fortran 90 Tutorial
10
Arguments
We may specify the intent of dummy arguments:
SUBROUTINE shuffle (ncards, cards) INTEGER, INTENT(IN) :: ncards INTEGER, INTENT(OUT), DIMENSION(ncards) :: cards ! input values ! output values
Also, INOUT is possible: here the actual argument must be a variable (unlike the default case where it may be a constant). Arguments may be optional:
SUBROUTINE mincon(n, f, x, upper, lower, equalities, inequalities, convex, xstart) REAL, OPTIONAL, DIMENSION :: upper, lower . .
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 (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, specications and END statement of the procedure concerned, either placed in a module or inserted directly:
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
An explicit interface is obligatory for: optional and keyword arguments, POINTER and TARGET arguments (see later article), a POINTER function result (later) and new-style array arguments and array functions (later). It allows full checks at compile time between actual and dummy arguments.
Fortran 90 Tutorial
11
where a given set of specic names corresponding to a generic name must all be of functions or all of subroutines. 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 dened operators and assignment (see Part 2).
Recursion
Indirect recursion is useful for multi-dimensional integration. To calculate
volume = integrate(fy, ybounds)
we might have
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
Fortran 90 Tutorial
12
5. Array handling
Array handling is included in Fortran 90 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!). At the same time, major extensions of the functionality in this area have been added. We have already met whole arrays in Parts 1 and 2here we develop the theme. Zero-sized arrays A zero-sized array is handled by Fortran 90 as a legitimate object, without special coding by the programmer. Thus, in
DO 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
no special code is required for the nal iteration where i = n. We note that a zero-sized array is regarded as being dened; however, an array of shape, say, (0,2) is not conformable with one of shape (0,3), whereas
x(1:0) = 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(0:10, 0:20) :: a : CALL sub(a)
the corresponding dummy argument specication denes 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 part 4). Thus we write just
SUBROUTINE sub(da) REAL, DIMENSION(:, :) :: da
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. Automatic arrays A partial replacement for the uses to which EQUIVALENCE is put is provided by this facility, useful for local, temporary arrays, as in
SUBROUTINE swap(a, b) REAL, DIMENSION(:) :: a, b REAL, DIMENSION(SIZE(a)) :: work work = a a = b b = work END SUBROUTINE swap
Fortran 90 Tutorial
ALLOCATABLE and ALLOCATE
13
Fortran 90 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
MODULE work_array INTEGER n REAL, DIMENSION(:,:,:), ALLOCATABLE :: work END MODULE PROGRAM main USE work_array READ (*, *) n ALLOCATE(work(n, 2*n, 3*n), STAT=status) : DEALLOCATE (work)
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(a, b)
We will meet this later, in the context of pointers. Elemental operations and assignments We have already met whole array assignments and operations:
REAL, DIMENSION(10) :: a, b a = 0. ! scalar broadcast elemental assignment b = sqrt(a) ! 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 arrayvalued functions ourselves (they require an explicit interface):
PROGRAM test REAL, DIMENSION(3) :: a = (/ 1., 2., 3./), b = (/ 2., 2., 2. /), 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 test r
WHERE Often, we need to mask an assignment. This we can do using the WHERE, either as a statement:
WHERE (a /= 0.0) a = 1.0/a ! avoid division by 0
(note: test is element-by-element, not on whole array), or as a construct (all arrays of same shape):
WHERE (a /= 0.0) a = 1.0/a b = a END WHERE WHERE (a /= 0.0) a = 1.0/a ELSEWHERE a = HUGE(a) END WHERE
Fortran 90 Tutorial
14
Array elements
Simple case: given REAL, DIMENSION(100, 100) :: a we can reference a single element of a as, for instance, a(1, 1). For a derived data type like
TYPE triplet REAL u REAL, DIMENSION(3) :: du END TYPE triplet
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.
lower ] :
as in
upper ] :stride ]
REAL a(10, 10) a(i, 1:n) a(1:m, j) a(i, : ) a(i, 1:n:3) a(i, 10:1:-1) a( (/ 1, 7, 3, 2 /), 1) a(1, 2:11:2) a(:, 1:7)
! ! ! ! ! ! ! !
part of one row part of one column whole row every third element of row row in reverse order vector subscript 11 is legal as not referenced 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( (/ 1, 7, 3, 7 /) ) = (/ 1, 2, 3, 4 /)
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
Fortran 90 Tutorial
We note that a given value in an array can be referenced both as an element and as a section:
a(1, 1) a(1:1, 1) ! ! scalar (rank zero) array section (rank one)
15
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 tar(1, 1)%u ! ! array section (structure component) component of an array element
Array reduction
ALL ANY COUNT MAXVAL MINVAL PRODUCT SUM True if all values are true True if any value is true. Example: IF (ANY( a > b)) THEN Number of true elements in array Maximum value in an array Minimum value in an array Product of array elements Sum of array elements
Array inquiry
ALLOCATED LBOUND SHAPE SIZE UBOUND Array Lower Shape Total Upper allocation status dimension bounds of an array of an array (or scalar) number of elements in an array dimension bounds of an array
Array construction
MERGE PACK SPREAD UNPACK Merge under mask Pack an array into an array of rank Replicate array by adding a dimension Unpack an array of rank one into an array under mask
Array reshape
RESHAPE Reshape an array
Array manipulation
CSHIFT EOSHIFT TRANSPOSE Circular shift End-off shift Transpose of an array of rank two
Array location
MAXLOC MINLOC Location of first maximum value in an array Location of first minimum value in an array
Fortran 90 Tutorial
16
6. Pointers
Basics
Pointers are variables with the POINTER attribute; they are not a distinct data type (and so no pointer arithmetic is possible):
REAL, POINTER :: var
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):
ALLOCATE (var)
the value of the target of var is used and modied. Pointers cannot be transferred via I/Othe statement
WRITE *, var
writes the value of the target of var and not the pointer descriptor itself. A pointer can point to other pointers, and hence to their targets, or to a static object that has the TARGET attribute:
REAL, POINTER :: object REAL, TARGET :: target_obj var => object var => target_obj
! pointer assignment
and, similarly, for arrays the ranks as well as the type must agree. A pointer can be a component of a derived data type:
TYPE entry REAL value INTEGER index TYPE(entry), POINTER :: next END TYPE entry ! type for sparse matrix
! note recursion
After suitable allocations and denitions, the rst two entries could be addressed as
chain%value chain%index chain%next chain%next%value chain%next%index chain%next%next
but we would normally dene additional pointers to point at, for instance, the rst and current entries in the list.
Fortran 90 Tutorial
17
Association
A pointers association status is one of undened (initial state); associated (after allocation or a pointer assignment); disassociated:
DEALLOCATE (p, q) NULLIFY (p, q) ! for returning storage ! for setting to 'null'
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 dened pointer:
IF (ASSOCIATED(pointer)) THEN
or between a dened pointer and a dened target (which may, itself, be a pointer):
IF (ASSOCIATED(pointer, target)) THEN
For objects of derived data type we have to distinguish between pointer and normal assignment. In
TYPE(entry), POINTER :: first, current : first => current
Fortran 90 Tutorial
18
Pointer 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 nal association status to the actual argument (note: the target may be undened!), it may not have the INTENT attribute (it would be ambiguous), it requires an interface block. If the dummy argument is not a pointer, it becomes associated with the target of the actual argument:
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
USE 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 dened target).
Arrays of pointers
These do not exist as such: given
TYPE(entry) :: rows(n)
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 dening a derived data type with a pointer as its sole component:
Fortran 90 Tutorial
TYPE row REAL, POINTER :: r(:) END TYPE
19
where the storage for the rows can be allocated by, for instance,
DO i = 1, n ALLOCATE (t(i)%r(1:i)) ! Allocate row i of length i END DO
The subscripts are as those of tar itself. (This replaces yet more of EQUIVALENCE.) The source code of an extended example of the use of pointers to support a data structure can be obtained by anonymous ftp to jkr.cc.rl.ac.uk (130.246.8.23). The directory is /pub/MandR and the le name is appxg.f90.
Fortran 90 Tutorial
20
7. Specication Statements
This part completes what we have learned so far about specication statements.
Implicit typing
The implicit typing rules of Fortran 77 still hold. However, it is good practice to explicitly type all variables, and this can be forced by inserting the statement
IMPLICIT NONE
PARAMETER attribute
A named constant can be specied 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 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./ ! only one component of t2 initialized DATA array(1:64) / 64*0/ ! only a section of array initialized DATA i, j, k/ B'01010101', O'77', Z'ff'/
Characters
There are many variations on the way character arrays may be specied. Among the shortest and longest are
CHARACTER name(4, 5)*20 CHARACTER (KIND = kanji, LEN = 20), DIMENSION (4, 5) :: name
Initialization expressions
The values used in DATA and PARAMETER statements, or in specication statements 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(12), array(3) = (/ 1, 2, 3 /)
Specication 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 REAL, DIMENSION(:, :) :: REAL, DIMENSION(UBOUND(b, 1) + 5) :: INTEGER CHARACTER(LEN=*) CHARACTER(LEN= m + LEN(c)) REAL (SELECTED_REAL_KIND(2*PRECISION(a))) ! contains a ! assumed-shape array ! automatic array ! assumed-length ! automatic object ! precision of z twice that of a
b x m c cc z
Fortran 90 Tutorial
21
The statement form has to be used to limit access to operators, and can also be used to change the overall default:
PRIVATE PUBLIC :: only_this ! sets default for module
For a derived data type 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):
MODULE mine PRIVATE TYPE, PUBLIC :: list REAL x, y TYPE(list), POINTER :: next END TYPE list TYPE(list) :: tree : END MODULE mine
USE statement
To gain access to entities in a module, we use the USE statement. It has options to resolve name clashes if an imported name is the same as a local one:
USE mine, local_list => list
Fortran 90 Tutorial
22
8. Intrinsic Procedures
We have already met most of the new intrinsic functions in previous parts of this series. Here, we deal only with their general classication and with those that have so far been omitted. All intrinsic procedures can be referenced using keyword arguments:
CALL DATE_AND_TIME (TIME=t)
and many have optional arguments. They are grouped into four categories: 1. 2. 3. 4. elemental work on scalars or arrays, e.g. ABS(a); inquiry independent of value of argument (which maybe undened), e.g. PRECISION(a); transformational array argument with array result of different shape, e.g. RESHAPE(a, b); subroutines, e.g. SYSTEM_CLOCK.
Bit manipulation
BTEST IAND IBCLR IBITS IBSET IEOR IOR ISHFT ISHFTC NOT Bit testing Logical AND Clear bit Bit extraction Set bit Exclusive OR Inclusive OR Logical shift Circular shift Logical complement
Transfer function, as in
INTEGER :: i = TRANSFER('abcd', 0) ! replaces part of EQUIVALENCE
Subroutines
DATE_AND_TIME MVBITS RANDOM_NUMBER RANDOM_SEED SYSTEM_CLOCK Obtain date and/or time Copies bits Returns pseudorandom numbers Access to seed Access to system clock
Fortran 90 Tutorial
23
9. Input/Output
Non-advancing input/output
Normally, records of external, formatted les are positioned at their ends after a read or write operation. This can now be overridden with the additional speciers:
ADVANCE = 'NO' EOR = eor_label SIZE = size (default is 'YES') (optional, READ only) (optional, READ only)
The next example shows how to read a record three characters at a time, and to take action if there are fewer than three left in the record:
CHARACTER(3) key INTEGER unit, size READ (unit, '(A3)', ADVANCE='NO', SIZE=size, EOR=66) key : ! key is not in one record 66 key(size+1:) = '' :
binary, octal, hexadecimal. engineering, multiple-of-three exponent: 0.0217 --> 21.70E-03 (EN9.2) scientic, leading nonzero digit: 0.0217 --> 2.17E-02 (ES9.2)
and the G edit descriptor is generalized to all intrinsic types (E/F, I, L, A). For entities of derived types, the programmer must elaborate a format for the ultimate components:
TYPE string INTEGER length CHARACTER(LEN=20) word END TYPE string TYPE(string) :: text READ(*, '(I2, A)') text
Fortran 90 Tutorial
24
New speciers
On the OPEN and INQUIRE statements there are new speciers:
POSITION ACTION DELIM PAD = = = = 'ASIS' 'READ' 'APOSTROPHE' 'YES' 'REWIND' 'WRITE' 'QUOTE' 'NO' 'APPEND' 'READWRITE' 'NONE'
and this is useful to set RECL, or to check that a list is not too long. It is in the same processor-dependent units as RECL and thus is a portability aid.
Index
actual argument, 10, 12, 18 aliases, 19 ALLOCATE, 13 argument, 10 array construction, 15 array constructors, 4 array elements, 14 array inquiry, 15 array location, 15 array manipulation, 15 array reduction, 15 array reshape, 15 array sections, 4 array subobjects, 14 arrays, 4 arrays intrinsic functions, 15 arrays of pointers, 18 assignment, 6, 13 association, 17 assumed-shape arrays, 12 automatic arrays, 12 binary, 2, 20 bit inquiry, 22 bit manipulation, 22 blank, 1 CASE construct, 8 CHARACTER, 3, 20 comments, 1 COMPLEX, 2 components, 3 constant expressions, 20 continuation, 1 conversion, 1 cursor, 23 DATA, 20 dened operators, 7 derived data type, 14, 16, 17, 21 DO construct, 8 dummy argument, 10, 12, 18 edit descriptors, 23 element, 4, 14 elemental, 7 elemental operation, 13 explicit interface, 10 expressions initialization of 20 , specication of 20 , formatted les, 23 generic interfaces, 11 generic names, 11 heap storage, 13 25 hexadecimal, 2, 20 implicit typing, 20 initialization of expressions, 20 input/output new edit descriptors, 23 new speciers, 24 non-advancing , 23 inquiry functions, 2 INTEGER, 2 INTENT, 1, 7, 9 interface, 6 interface block, 10, 11, 18 intrinsic functions, 7, 15, 17, 20, 22 keyword, 22 kind type parameter, 2 letters, 1 linked chain, 16 LOGICAL, 3 lower bound, 12, 13 matrix multiply, 15 model numbers, 2 modules, 7, 9, 10, 21 named constant, 2 named operators, 6 numerals, 1 octal, 2, 20 operator, 6 optional, 22 overloading, 11 PARAMETER, 20 parentheses, 6 POINTER, 16 pointer s as dynamic aliases, 19 s in expressions and assignments, 17 arguments, 18 arrays of s, 18 functions, 18 pointer assignment, 16, 17, 19 precedence, 6 PRIVATE, 21 prompt, 23 PUBLIC, 21 range, 2 rank, 12, 18 REAL, 2 recursion, 11 scope, 21
Fortran 90 Tutorial
section, 14 shape, 7 signicant blank, 1 special characters, 1 statements, 1 structure constructor, 3 structures, 3 subscripts, 4, 19 targets, 16 unary operator, 6 underscore, 1 upper bound, 12 USE, 21 vector multiply, 15 vector subscript, 14 WHERE, 13 zero-length strings, 5 zero-sized arrays, 12
26