The Queen's University of Belfast
Parallel Computer Centre

[Next] [Previous] [Top]

2 Sources, Types and Control Structures


2.1 Source Form

Fortran 90 supports two forms of source code; the old Fortran 77 source code form (now called fixed form), and the new free form. Using free source form, columns are no longer reserved and so Fortran statements can now appear anywhere on a source line. The source line may contain up to 132 characters.

The character set now includes both upper and lower case letters and the underscore. A good convention is that the words which are not in your control are in upper case and names which you invent yourselves, such as variable names, are in lower case.

Identifier names can consist of between 1 and 31 alphanumeric characters (including the underscore), the only restriction being that the first must be a letter. Remember that the use of sensible names for variables helps readability.

Fortran 90 introduces new symbols, including the exclamation mark, the ampersand, and the semicolon, and the alternative form of relational operators. These are discussed in the following paragraphs.

The exclamation mark introduces a comment. A comment can start anywhere on a source line and thus can be placed alongside the relevant code. The rest of the line after the ! is ignored by the compiler.

REAL :: length1 ! Length at start in mm (room temperature)
REAL :: length2 ! Length at end in mm (after cooling)

The ampersand character, &, means `continued on the next line'. Usually you will arrange the line break to be in a sensible place (like between two terms of a complicated expression), and then all that is needed is the & at the end of all lines except the last. If you split a string, though, you also need an ampersand at the start of the continuation line.

loggamma = f + (y-0.5)*log(y) - y + 0.91893853320 + &
(((-0.00059523810*z + 0.00079365079)*z - &
0.00277777778)*z + 0.08333333333)/y

WRITE(*,'UNIVERSITY OF MANCHESTER DEPARTMENT&
& OF THEORETICAL STUDIES')

The semicolon is used as a statement separator, allowing multiple statements to appear on one line. The use of multiple-statement lines can, however, produce unreadable code, and should therefore be used only for simple cases, for example:

a = 2; b = 7; c = 3

Alternative forms of the relational operators are now provided:

.LT. or <
.LE. or <=
.EQ. or ==
.NE. or /=
.GT. or >
.GE. or >=

2.2 Program and Subprogram Names

All programs and subprogram have names. A name can consist of up to 31 characters (letters, digits, or underscore), starting with a letter.

Using square brackets to signify optional items, the syntax of the PROGRAM and END statements in Fortran 90 is of the form:

PROGRAM test
...
...
END [PROGRAM [test]]

where test is the name of the program. The END statement may optionally be any of:

END
END PROGRAM
END PROGRAM test
END PROGRAM TEST

If the program name is present then the word PROGRAM must also be present, and the name must match that in the PROGRAM statement (but case is not significant).

The same syntax applies for other program elements, such as FUNCTION or MODULE.

2.3 Specifications

Fortran 90 allows an extended form of declaration, in which all the attributes of a particular entity may be declared together.

The general form of the declaration statement is:

type [ [, attribute ] ... :: ] entity list

where type represents one of the following:

INTEGER [([KIND=]kind-value)]
REAL [([KIND=]kind-value)]
COMPLEX [([KIND=]kind-value)]
CHARACTER [(actual-parameter-list)]
LOGICAL [([KIND=]kind-value)]
TYPE (type-name)

and attribute is one of the following:

PARAMETER
PUBLIC
PRIVATE
POINTER
TARGET
ALLOCATABLE
DIMENSION(extent-list)
INTENT(inout)
OPTIONAL
SAVE
EXTERNAL
INTRINSIC

For example, it is now possible to initialize variables when they are declared, so there is no need for a separate DATA statement:

REAL :: a=2.61828, b=3.14159
! two real variables declared and assigned initial values

INTEGER, PARAMETER :: n = 100, m = 1000
! two integer constants declared and assigned values

CHARACTER (LEN=8) :: ch
! character string of length 8 declared

INTEGER, DIMENSION(-3:5,7) :: ia
! integer array declared with negative lower bound

INTEGER, DIMENSION(-3:5,7) :: ia, ib, ic(5,5)
! integer array declared using default dimension

2.4 Strong Typing

For backward compatibility, the implicit typing of integers and reals by the first character is carried over, but the IMPLICIT statement has been extended to include the parameter NONE. It is recommended that the statement

IMPLICIT NONE

be included in all program units. This switches off implicit typing and so all variables must be declared. This helps to catch errors at compile time when they are easier to correct. The IMPLICIT NONE statement may be preceded within a program unit only by USE and FORMAT statements.

2.5 The Concept of KIND

In Fortran 90 each of the five intrinsic types REAL, INTEGER, COMPLEX, CHARACTER and LOGICAL,has an associated non negative integer value called the kind type parameter. A processor must support at least two kinds for REAL and COMPLEX, and one for INTEGER, COMPLEX and LOGICAL.

KIND values are system dependent. However, there are intrinsics provided for enquiring about and setting KIND values, and these allow the writing of portable code using specified precision.

2.5.1 Real Values

The kind type parameter associated with REAL variables specifies minimum precision and exponent range requirements. If the kind type parameter is not specified explicitly then default real is assumed. The assumption of default kind type parameter in the absence of explicit specification is usual for all intrinsic types. The kind value assigned to default real is, of course, processor-dependent.

A kind value is specified explicitly by including the value in brackets in the type declaration statement. For example:

REAL(KIND=2) :: a
! a is declared of kind type 2

REAL(KIND=4) :: b
! b is declared of kind type 4

The KIND= is optional and so the above declarations could also be given as:

REAL(2) :: a
REAL(4) :: b

The intrinsic function KIND, which takes one argument of any intrinsic type, returns the kind value of the argument. For example:

REAL(KIND=2) :: x !x declared of kind type 2
REAL :: y !y declared of default type
INTEGER :: i,j

i = KIND(x) !i=2
j = KIND(y) !j set to kind value of default real
!j is system dependent

The intrinsic function SELECTED_REAL_KIND has two optional integer arguments p and r (optional arguments will be discussed in more detail later in the course). The variable p specifies the minimum precision (number of decimal digits) required and r specifies the minimum exponent range required.

The function SELECTED_REAL_KIND(p,r) returns the kind value that meets, or minimally exceeds, the requirements specified by p and r. If more than one kind type satisfies the requirements, the value returned is the one with the smallest decimal precision. If the precision is not available the value -1 is returned, if the range is not available -2 is returned, and if neither is available -3 is returned. The use of kind type together with this function can provide complete portability.

The simplest example of KIND is to replace DOUBLE PRECISION:

INTEGER, PARAMETER :: idp = KIND(1.0D)
REAL(KIND=idp) ::ra

Here, the intrinsic function KIND returns the kind value of DOUBLE PRECISION and assigns the value to idp. The variable ra is declared as double precision by specifying KIND=idp. Note that in this case the kind value is system dependent.

In order to declare a real in a system independent way, a kind value associated with a required precision and exponent range must be specified. To do this, the function SELECTED_REAL_KIND should be used. For example:

INTEGER, PARAMETER :: i10=SELECTED_REAL_KIND(10,200)
REAL(KIND=i10) :: a,b,c

The real variables a, b and c are declared to have at least 10 decimal digits of precision and exponent range of at least 10^-200 to 10^+200, if permitted by the processor.

Constants can also be specified to be of a particular kind. The kind type parameter is explicitly specified by following the constant's value by an underscore and the kind parameter. If no kind type is specified then the type default is assumed. For example:

REAL, PARAMETER :: d = 5.78_2 !d is real of kind type 2
REAL, PARAMETER :: e = 6.44_wp !e is real of kind type wp
REAL, PARAMETER :: f = 2.7 !f is default real
!(system dependent)

2.5.2 Integer Values

The intrinsic function SELECTED_INT_KIND is used in a similar manner to SELECTED_REAL_KIND. The function has one integer argument, r, which specifies the integer range required. Thus, SELECTED_INT_KIND(r) returns the kind value that can represent, at least, all the integer values in the range -10^r to 10^r. If more than one kind type satisfies the requirement, the value returned is the one with the smallest exponent range. If this range is not available, then the function returns the value -1.

The following example shows the declaration of an integer in a system independent way, specifying a kind value associated with a required range:

INTEGER, PARAMETER :: i8=SELECTED_INT_KIND(8)
INTEGER(KIND=i8) :: ia,ib,ic

The integer variables ia, ib and ic can have values between -10^8 to 10^8 at least, if permitted by the processor.

Integer constants can also be specified to be of a particular kind in the same way as real constants. For example:

INTEGER, PARAMETER :: short = SELECTED_INT_KIND(2)
! the kind type short is defined
INTEGER, PARAMETER :: linefeed = 10_short
INTEGER, PARAMETER :: escape = 27_short
! constants linefeed and escape of kind type short

2.5.3 Intrinsics

The intrinsic function KIND, discussed in "Real Values", can take an argument of any intrinsic type. For example:

KIND(0) ! returns the default integer kind
! (processor dependent)
KIND(0.0) ! returns the default real kind
! (processor dependent)
KIND(.FALSE.) ! returns the default logical kind
! (processor dependent)
KIND('A') ! gives the default character kind (always 1)

Further intrinsic functions can be seen in the following examples:

INTEGER, PARAMETER :: i8 = SELECTED_INT_KIND(8)
INTEGER(KIND=i8) :: ia
PRINT *, HUGE(ia), KIND(ia)

This prints the largest integer available for this integer type, and its kind value.

INTEGER, PARAMETER :: i10 = SELECTED_REAL_KIND(10,200)
REAL(KIND=i10) :: a
PRINT *, RANGE(a), PRECISION(a), KIND(a)

This prints the exponent range, the decimal digits of precision, and the kind value of a.

2.5.4 Complex

Complex data types are built from two reals and so, by specifying the components as reals with the appropriate kind we could have the equivalent of DOUBLE PRECISION COMPLEX:

INTEGER, PARAMETER :: idp = KIND(1.0D)
COMPLEX(KIND=idp) :: firstroot, secondroot

2.5.5 Logical

There may be more than one logical kind. For example, on the Salford compiler there are two: the default kind is one `word' long and has kind value 2, but kind value 1 specifies compression to one byte.

2.5.6 Character

Only one kind is generally available, which maps to the standard ASCII set, but the language now allows for other kinds to be provided to cater for foreign language characters.

CHARACTER (LEN=5) :: 'aeiou'
CHARACTER (LEN=5, KIND=1) :: 'aeiou'

For character constants, the kind value precedes the constant (separated by an underscore):

CHARACTER, LEN=5, PARAMETER :: vowels = 1_'aeiou'

2.6 Derived Types

One of the major advances of Fortran 90 over previous versions is the ability to define your own types. These are called derived types, but are often also called structures.

Let us define a new type, point, which will be constructed from three values representing the x, y, and z values in Cartesian space.

TYPE point
REAL :: x, y, z
END TYPE point

We can now declare new variables to be of type point as follows:

TYPE (point) :: centre, apex

Here we have declared two variables, apex, and centre to be of type point. Notice that the syntax of Fortran 90 doesn't allow us to say simply:

point :: centre, apex ! Illegal

You have to put the word TYPE. The compiler knows whether we are defining a new type or are declaring a variable of that type because we put the type name point in brackets for the declarations of the variables, but not for the type definition.

Each of the components of the variable apex may be referenced individually by means of the component selector character, %.

apex%x = 0.0
apex%y = 1.0
apex%z = 0.0

The value apex%y is a real quantity and the assignment operator (=) is defined for real quantities. For derived types the assignment is implicitly defined to be on a component by component basis, which will usually be what is wanted, so we can say, for example:

centre = apex

No other operators are defined for our new type by default, however, and we might not want assignment to do a straight copy (for example, one component might be a date field and we might want to update it, or check it). This problem is overcome by overloading the assignment operator. This and the associated problem of defining what interpretation should be given to other operations on variables of our new type will be dealt with later in the course.

We can use our new type as a primitive in constructing further more complicated types:

TYPE block
TYPE (point) :: bottomleftnear, toprightfar
END TYPE block

To refer to the x component of the bottom left corner of a variable firstbrick (say) of type block, we would need two % signs:

xoffset = firstbrick%bottomleftnear%x

2.6.1 Arrays of a Derived Type

We can declare an array of a derived type:

INTEGER, PARAMETER :: male = 1, female = 0
INTEGER, PARAMETER :: nbefore = 53, nafter = 37

TYPE person
INTEGER :: ident
INTEGER :: sex
REAL :: salary
END TYPE person

TYPE (person), DIMENSION (nbefore) :: group1
TYPE (person), DIMENSION (nafter) :: group2

Here we have declared two arrays, group1, and group2 of type person. If we now say

group1%sex = female

we will set the sex of all the members of our first group to female.

2.6.2 Constants of Derived Types

We can define a constant of a derived type:

TYPE (point) :: origin = point(0.0, 0.0, 0.0)
TYPE (person) :: boss = person(1, male, 100000.0)

The order of the components must follow the order in the definition. The constants, such as point(0.0,0.0,0.0) may appear anywhere that a variable of the appropriate type may appear.

2.6.3 Derived Type Examples

Define the form of the derived type:

TYPE vreg
CHARACTER (LEN=1) :: year
INTEGER :: number
CHARACTER (LEN=3) :: place
END TYPE vreg

Declare structures of type vreg:

TYPE(vreg) mycar1, mycar2

Assign a constant value to mycar1:

mycar1 = vreg('L',240,'VPX')

Use % to assign a component of mycar2:

mycar2%year = 'R'

Define an array of a derived type:

TYPE (vreg), DIMENSION(n) :: mycars

Define a derived type including another derived type:

TYPE household
CHARACTER (LEN=1) :: name
CHARACTER (LEN=50) :: address
TYPE(vreg) :: car
END TYPE household

Declare a structure of type household:

TYPE(household) :: myhouse

Use % to refer to year component:

myhouse%car%year = 'R'

2.7 Control Statements

Fortran 90 contains three block control constructs:

All three constructs may be nested, and additionally may be named in order to help readability and increase flexibility.

2.7.1 IF Statements

The general form of the IF construct is:

[name:] IF (logical expression) THEN
block
[ELSE IF (logical expression) THEN [name]
block]...
[ELSE [name]
block]
END IF [name]

Notice there is one minor extension, which is that the IF construct may be named. The ELSE or ELSE IF parts may optionally be named, but, if either is, then the IF and END IF statements must also be named (with the same name).

select: IF (i < 0) THEN
CALL negative
ELSE IF (i==0) THEN select
CALL zero
ELSE select
CALL positive
END IF select

For long or nested code this can improve readability.

2.7.2 DO Loop

The general form of the DO loop is:

[name:] DO [control clause]
block
END DO [name]

The END DO statement should be used to terminate a DO loop. This makes programs much more readable than using a labelled CONTINUE statement, and, as it applies to one loop only, avoids the possible confusion caused by nested DO loops terminating on the same CONTINUE statement.

Old style code:

DO 10 I = 1,N
DO 10 J = 1,M
10 A(I,J) = I + J

Fortran 90 code:

DO i = 1,n
DO j = 1,m
a(i,j) = i + j
END DO
END DO

Notice that there is no need for the statement label at all.

The DO and END DO may be named:

rows: DO i = 1,n
cols: DO j = 1,m
a(1,j) = i + j
END DO cols
END DO rows

One point to note is that the loop variable must be an integer and it must be a simple variable, not an array element.

The DO loop has three possible control clauses:

2.7.3 DO WHILE

A DO construct may be headed with a DO WHILE statement:

DO WHILE (logical expression)

body of loop

END DO

The body of the loop will contain some means of escape, usually by modifying some variable involved in the test in the DO WHILE line.

DO WHILE (diff > tol)
.
.
.
diff = ABS(old - new)
.
.
.
END DO

Note that the same effect can be acheived using the DO loop with an EXIT statement which is described below.

2.7.4 EXIT and CYCLE

The EXIT statement permits a quick and easy exit from a loop before the END DO is reached. (It is similar to the break statement in C.)

The CYCLE statement is used to skip the rest of the loop and start again at the top with the test-for-completion and the next increment value (rather like the continue statement in C).

Thus, EXIT transfers control to the statement following the END DO, whereas CYCLE transfers control to a notional dummy statement immediately preceding the END DO.

These two statements allow us to simplify the DO statement even further to the `do forever' loop:

DO
.
.
.
IF ( ... ) EXIT
.
.
.
END DO

Notice that this form can have the same effect as a DO WHILE loop.

By default the CYCLE statement applies to the inner loop if the loops are nested, but, as the DO loop may be named, the CYCLE statement may cycle more than one level. Similarly, the EXIT statement can specify the name of the loop from which the exit should be taken, if loops are nested, the default being the innermost loop.

outer: DO i = 1,n
middle: DO j = 1,m
inner: DO k = 1,l
.
.
.
IF (a(i,j,k)<0) EXIT outer ! Leave loops
IF (j==5) CYCLE middle ! Omit j==5 and set j=6
IF (i==5) CYCLE ! Skip rest of inner loop, and
. ! go to next iteration of
. ! inner loop
.
END DO inner
END DO middle
END DO outer

2.7.5 CASE Construct

Repeated IF ... THEN ... ELSE constructs can be replaced by a CASE construct, as can the `computed GOTO'. The general form of the CASE construct is:

[name:] SELECT CASE (expression)
[Case (selector)[name]
block]
.
.
.
END SELECT [name]

The expression can be of type INTEGER,LOGICAL, or CHARACTER, and the selectors must not overlap. If a valid selector is found, the corresponding statements are executed and control then passes to the END SELECT. If no valid selector is found, execution continues with the first statement after END SELECT.

SELECT CASE (day) ! sunday = 0, monday = 1, etc
CASE (0)
extrashift = .TRUE.
CALL weekend
CASE (6)
extrashift = .FALSE.
CALL weekend
CASE DEFAULT
extrashift = .FALSE.
CALL weekday
END SELECT

The CASE DEFAULT clause is optional and covers all other possible values of the expression not included in the other selectors. It need not necessarily come at the end.

A colon may be used to specify a range, as in:

CASE ('a':'h','o':'z')

which will test for letters in the ranges a to h and o to z.

2.7.6 GOTO

The GOTO statement is still available, but, it is usually better to use IF, DO, and CASE constructs, and EXIT and CYCLE statements instead.

2.8 Exercises

Derived Types:

  1. Run the program vehicle.f90. What difference do you notice in the output of the two WRITE statements?

  2. Run the program circle.f90. Create a new derived type for a rectangle and assign and write out the corners of the rectangle. (rectdef.f90)

  3. Create a file circle.dat which contains the components of the centre and radius of a circle so that it can be read by program circle2.f90. Run the program.

  4. Alter program circle4.f90 so that it prints a circle centred at the origin (0,0) with radius 4.0.

  5. Define a derived type that could be used to store a date of birth in the following type of format:

    15 May 1990

    Write a program to test your derived type in a similar manner to the above examples. (birth1.f90)

  6. Modify the derived type in exercise 7 to include a component for a name. (birth2.f90).

Control Structure:

  1. Write a program containing a DO construct which reads numbers from the data file square.dat, skips negative numbers, adds the square root of positive numbers, and concludes if the present number is zero (use EXIT and CYCLE). (sq_sum.f90)

  2. Write a program that reads in a month number (between 1 and 12) and a year number. Use the CASE construct to assign the number of days for that month, taking leap years into account. (no_days.f90)

  3. Write a program that reads in a character string. Use the CASE construct in converting upper case characters to lower case and vice versa, and write out the new string. (Use IACHAR("a") - IACHAR("A") to determine the difference in the position in the collation sequence between lower and upper case characters.) (convert.f90)

Kind Values:

  1. Run the program kind_int.f90. Notice how this program uses SELECTED_INT_KIND to find the kind values for integer variables on this system. Modify this program to find the kind values for real variables. (kind_rl.f90)

  2. Run the program mc_int.f90. Notice how this program uses the kind values of integer variables found in exercise 1, and the numeric intrinsic functions to find some of the machine constants for this system. Modify this program by using the kind values of real variables found in exercise 1 and the numeric intrinsic functions (PRECISION, HUGE, TINY and RANGE) to find some of the machine constants for this system. (mc_real.f90)


[Next] [Previous] [Top]
All documents are the responsibility of, and copyright, © their authors and do not represent the views of The Parallel Computer Centre, nor of The Queen's University of Belfast.
Maintained by Alan Rea, email A.Rea@qub.ac.uk
Generated with CERN WebMaker