Overview about Fortran 90/95 for C/C++ programmers

Fortran 95 is a procedure- and structure-based programming language with some (few) OOP (Object Oriented Programming) paradigmas like static overloading of functions. There is, however, no real OOP realised in this language which drives programming more back to C programming than C++ programming. The language has a very strict type-checking style which gives a skilled C/C++ programmer headaches concerning the realisation of some modern programming concepts. There are, however, some very handy advantages which one does not want to miss if one is familiar with the language:

  • The language is fast. Typically, Fortran code is at least 10-20 percent faster than usual C++ code due to advanced optimisation, which follows from the strict rules -- without any special optimization tricks like compiler pragmas, e.g.
  • Array operations are straightforward and simple to write down; this reminds Fortran code more to MatLab code than standard C/C++ code.
  • The language is highly portable and backward compatible. By the time, there are Fortran compilers available for small desktop machines as well as for high-performance Cluster systems, producing all nicely running code on the same code basis.

The following sections contain a brief introduction into this language from the view of a C/C++ programmer and highlight some important differences between the languages. Beginners are strongly advised to study the language by one of the countless pages in the Internet concerning the Fortran language.

Contents
1 Differences between C/C++ and Fortran
2 Introduction into Fortran 90/95
2.1 Hello world
2.2 Language constructs
2.3 Flow control commands
2.4 Multi-file projects
2.5 Special language constructs
3 Common Pitfalls
4 Links to the Fortran specification and language books

Differences between C/C++ and Fortran

There are a number of differences between C/C++ and Fortran one has to take into account when learning the Fortran language. Some of them are mentioned already above. The following list contains a more detailed overview about points that may confuse a C/C++ programmer:

  • There is no real OOP available as in C++. It is possible to use static overloading of routines, and it is even possible to overload standard operators (like +,*,/,...). However, dynamic overloading is not possible.

  • Fortran is case insensitive. For examples, an identifier (for a variable, a subroutine or whatever) like "IVAR", "ivar", "iVar" or "Ivar" are all the same for a Fortran compiler.

  • Pointers are always type-bound. Following the Fortran Standard, it is impossible to have a pointer without a type. Converting a pointer from one type to another is not possible.

    Remark: In Feat2, a special trick is used to circumvent this restriction using some special assumptions on the compiler which generally hold. This is, however, nonstandard.

  • A pointer is not realised as an integer pointing to the memory. A pointer is a descriptor pointing either to an object or to an array with elements of a specific type. In the case of arrays, the pointer-descriptor contains additional information like the size of the array (more precisely: upper/lower bound, size, type).

  • Pointers to functions or subroutines do not exist. It is possible to pass a function/subroutine as a parameter in another subroutine, but a pointer variable pointing to a subroutine is not possible in Fortran.

  • There is no standard preprocessor available.

    Remark: In Feat2, some special tricks allow the use of a quite powerful preprocessor also for Fortran. This allows the definition of general classes like lists.

  • It is not possible to have "circular dependencies" in the modules. Every module can have one or more parent modules (specified by the use statement), but a module must never depend directly or indirectly on itself.

  • Names are restricted to 31 characters. Lines are restricted to 132 characters.

  • There is at most one command per line (except special cases like the shorthand notation for the IF clause). Putting multiple commands to one line and seperating it with a ";" as in C/C++ is nonstandard Fortran and not supported by all compilers. However, Fortran ignores any indention by space characters similar to C/C++ - so authors can format code blocks arbitrarily.

  • Strings always have fixed length. If necessary, strings are filled with spaces.

  • Variables are always passed by reference. Even in the case that a constant is specified (as in call foobar(5)), a pointer to a constant "5" is passed.

  • Fortran subroutines/functions are not allowed to be called recursively by default.

  • In C/C++, subroutines do not exist. All named code blocks are defined as functions (probably with a void attribute) and can be called like intrinsic routines (e.g. foobar(5) or a=foobar(5)). Fortran strictly differs between functions and subroutines. Functions can be called similar to C/C++, while subroutines require an additional CALL command. (Thus, use call foobar(5) for subroutines and a=foobar(5) for functions.)

Introduction into Fortran 90/95

Hello world

In Fortran 95, a "Hello World" program reads like this:

program HelloWorld
  write (*,*) "Hello world."
end program

The write command is a general command for output to any device. The parameter (*,*) tells the compiler to print the output to the terminal stdout (first star) with default printing format (second star). It is also possible to print multiple pieces of data, e.g., some strings, integers and floating point values:

program HelloWorld
  write (*,*) "Hello world. This is Test", 1, ", data ", 0.0
end program

If one wants to have a specifal format for the numbers, a detailed "format" string has to be specified according to the parameters, e.g.:

program HelloWorld
  write (*,"(AIAE5.5") "Hello world. This is Test", 1, ", data ", 0.0
end program

As can be seen already in this example, Fortran 90 is "block oriented" without separate commands marking the start/end of a block. So there is no equivalent to a "{...}" construct as it is known from C. Instead, most commands that allow a subblock of commands (like an IF clause, see below) have a specific syntax that describes where a block starts and where it ends. Usually, there is an "END" command that tells the compiler the end of the block.

Long commands spanning over multiple lines

In contrast to C/C++, Fortran is strongly line-oriented:

  • There must be at most one command per line (except the shorthand notation of the IF clause, see below)
  • A command must not exceed one line, and a line can have at most 132 characters.

Long commands have to be split over multiple lines using the "&" character -- i.e., at the end of the line, a "&" character tells Fortran to continue reading the current command in the next line. Example:

program LongLineTest

  write (*,*) "This is a very long line " // &
      " that is split over ", 4 &
      , " lines with some stra" &
      // "nge splitting"

end program

The command is interpreted as being in one line, i.e.,

  write (*,*) "This is a very long line " //       " that is split over ", 4 ...

Language constructs

Comments

In Fortran, the "!" character starts a comment. Comments always last until the end of the line. Every line of comment has to start with a new "!" character. This is very similar to the "//" comment mark in C. Example:

program HelloWorldComment
  ! This is a comment
  ! in two lines.
  write (*,*) "Hello world."
end program

Variables

Variables must be defined in the beginning of a program/subroutine/function. Typical variables are integer variables, floating point variables, boolean variables, character variables and strings. Using the operator "=", values can be assigned to variables. The following instructive example demonstrates the definition.

program DefineVariables

  integer :: i      ! Integer variable
  real :: d         ! Floating point value
  logical :: b      ! Boolean variable
  character :: c    ! Character

  character(len=10) :: sstring  ! String of length 10

  i = 0
  d = 0.0
  b = .false.       ! Logical has values ".true." or ".false."
  sstring = "Hello"

  write (*,*) i, " ", d, " ", b, " ", sstring
end program

As can be seen, a "::" has to be placed between the type and the variable name. There are a couple of rules concerning variables, the basic rules read:

  • Strings must always have a specified length when being declared. Dynamic-length strings are not possible. Strings are always filled with spaces. So in the above example, the variable sstring will actually be assigned the value sstring = "Hello "

  • A computer system usually supports different types of integer and floating point numbers, and Fortran has a special way how to choose between them. A special "type" of a number format can be chosen by adding a "(xxx)" term to the end of the type. The actual implementation is system-dependent, however, the following definitions hold for most computer systems:

      integer(4) :: i      ! 32 Bit integer
      integer(8) :: j      ! 64 Bit integer
      real(8) :: f         ! Single precision
      real(16) :: d        ! Double precision
    

Feat2 extension: In the module fsystem, Feat2 defines a couple of system independent number formats. So, if fsystem is included, one can use the following declarations:

      use fsystem

      ...
      integer(I32) :: i      ! 32 Bit integer
      integer(I64) :: j      ! 64 Bit integer
      real(SP) :: f          ! Single precision
      real(DP) :: d          ! Double precision
      ...
  • Fortran provides a set of routines to convert a number into another format. For example, the following commands explicitely convert "i" into a double precision value:

    integer :: i
    real(8) :: d
    
    i = 5
    d = real(i,8)
    

Constants

Variables can be defined as constant variables using the PARAMETER attribute. This is similar top defining a constant in C/C++ with the const attribute. Example:

program ConstTest

integer, parameter :: ncorners = 4
real, parameter :: PI = 3.14

  ...

end program

String handling

String handling in Fortran is much more tedious than in C/C++. As indicated above, strings in Fortran are realised as character blocks with fixed length. It is impossible with standard methods to realise dynamic strings (although there exist some libraries in the web which imitate such strings using dynamic memory allocation and character arrays). Let us assume, we define a string in the following way:

program StringDef

  character(len=10) :: sstr
  sstr = " Hallo"

  ...

There are a couple of commands possible to be applied to a string, e.g.,

Command Task
LEN(sstr) Returns the length of the string. The content is " Hallo ", so len(sstr)=10.
LEN_TRIM(sstr) Returns the length of the string without trailing spaces, so len_trim(sstr)=6.
ADJUSTR(sstr) Returns the right-adjusted string " Hallo"
ADJUSTL(sstr) Returns the left-adjusted string "Hallo "
TRIM(sstr) Returns the (rear-)trimmed string " Hallo"
INDEX(...) Search for a character in a string (with ... some parameters). Similar to strstr in C/C++

Extracting a character from a string can be done using the "(n:n)" notation. Extraction of a substring can be done via the "(m:n)" notation, with m<n. Example.

program StringCopy

  character(len=20) :: sstr1, sstr2
  character :: c

  sstr1 = "This is a litte string"

  c = sstr1(6:6)        ! Returns "i"

  sstr2 = sstr1(:4)     ! Returns "This"
  sstr2 = sstr1(11:15)  ! Returns "little"
  sstr2 = sstr1(16:)    ! Returns " string"

end program

Strings can be concatenated using the "//" operator. This is similar to a "+" operator in C++ for strings. However, care must be taken as strings have fixed length -- so spaces must be trimmed away from the string. Instructive example:

program StringCat

  character(len=20) :: sstr1
  character(len=10) :: sstr2

  sstr1 = "This " // "is " // "a string"  
                                  ! Gives "This is a string    "

  sstr2 = "This"
  sstr1 = sstr2 // "is a string"  
                                  ! Gives "This      is a strin"

  sstr2 = "This"
  sstr1 = trim(sstr2) // "is a string"  
                                  ! Gives "Thisis a string     "

  sstr2 = "This"
  sstr1 = trim(sstr2) // " " // "is a string"  
                                  ! Gives "This is a string    "

end program

Structures

Additionally to the build-in types, one can define structures in Fortran 90 using the "type" command. Later on, a type(...) command can be use to declare a variable of this structure. This is rather similar to the struct statement of C/C++. Entries in a structure can be accessed using the "%" qualifier, which is similar to a "." in C/C++. An example reads as follows:

program HelloStructure

  ! Define a structure
  type Complex
    real :: R
    real :: I
  end type

  ! Declare a variable
  type(Complex) :: myComplex

  ! Set real/imaginary value
  myComplex%R = 1.0
  myComplex%I = 0.0

end program

Structures can be embedded in other structures as can be seen below. Accessing substructures is possible using "%" as a "." in C/C++:

program HelloStructure2

  ! Define a structure
  type Complex
    real :: R
    real :: I
  end type

  ! Another structure
  type TooComplex
    type(Complex) :: complex1
    type(Complex) :: complex2
  end type

  ! Declare a variable of type TooComplex
  type(TooComplex) :: myComplex

  ! Set real/imaginary value
  myComplex%complex1%R = 1.0
  myComplex%complex1%I = 0.0

  myComplex%complex2%R = 2.0
  myComplex%complex2%I = 10.0

end program

1D Arrays

An array is defined by specifying the additional attribute "dimension(n)" in the definition of the variable, with n the size. The entries can be accessed with specifying the position using "(x)" in the notation. Similar to MatLab, ranges of entries are allowed. Using the "(:)" notation, parts of the array can be accessed. Examples:

program ArrayTest

integer, dimension(10) :: Iarray    ! Array of 10 integers
real, dimension(10)    :: Darray    ! Array of 10 floating point values

  Iarray(:) = 0     ! Set the complete array to zero.
  Iarray(5) = 1     ! Set entry 5 to 1

  Darray(:3)  = 0.0  ! Set entry 1..3 to 0.0
  Darray(4:6) = 1.0  ! Set entry 4..6 to 1.0
  Darray(7:)  = 2.0  ! Set entry 7..10 to 2.0

end program

Warning: In contrast to C/C++, arrays are "1-based" in Fortran -- so the lower bound is "1" and the upper bound "n" for arrays with length "n"!

Multidimensional arrays

Arrays can also be multidimensional in Fortran. The following example defines a 2-dimensional integer and a 3-dimensional floating point array with fixed size. Using the "(:)" notation of Fortran, parts of the array can be set to fixed numbers or copied.

program ArrayTest2

integer, dimension(10,20) :: Iarray    ! Array of 20x10 integers
real, dimension(10,20,30) :: Darray    ! Array of 30x20x10 floats

  Iarray(:,:) = 0      ! Clear the array
  Iarray(:,1) = 1      ! Set Iarray(1..10,1) = 1

  ! Copy Iarray(1..10,1) to Iarray(1..10,2)
  Iarray(:,2) = Iarray(:,1)

  ! Overwrite Darray(1..5,10..15,20..30) with zero
  Darray(:5, 10:15, 20:) = 0.0

end program

Remark: In contrast to C/C++, Fortran indexes arrays "column-wise" instead of "row-wise". A C/C++ array declared as

int myarray [10][20][30];

is declared in Fortran as

integer, dimension(30,20,10) :: myarray

As an example, let us assume, the array Iarray is initialised similar to C/C++ as follows:

integer, dimension(3,3) :: Iarray

Iarray(1,1) = 1
Iarray(1,2) = 2
Iarray(1,3) = 3
Iarray(2,1) = 4
Iarray(2,2) = 5
Iarray(2,3) = 6
Iarray(3,1) = 7
Iarray(3,2) = 8
Iarray(3,3) = 9

then internally, the array is set up in memoy as

1,4,7,2,5,8,3,6,9

which is probably not what one wants to have. In Fortran, the first dimension is the most "inner" dimension concerning ordering the data in memory. An initialisation like

integer, dimension(3,3) :: Iarray

Iarray(1,1) = 1
Iarray(2,1) = 2
Iarray(3,1) = 3
Iarray(1,2) = 4
Iarray(2,2) = 5
Iarray(3,2) = 6
Iarray(1,3) = 7
Iarray(2,3) = 8
Iarray(3,3) = 9

gives internally the sequence

1,2,3,4,5,6,7,8,9

Determining the size of an array

Using the UBOUND, LBOUND and SIZE commands allow to determine the size of an array component or the size of the array, respectively. Here an instructive example:

program sizetest

  integer, dimension(10)    :: Iarray1D
  integer, dimension(10,20) :: Iarray2D

  write (*,*) lbound(Iarray1D,1)
  write (*,*) ubound(Iarray1D,1)
  write (*,*) size(Iarray1D)

  write (*,*) lbound(Iarray2D,1)
  write (*,*) ubound(Iarray2D,1)
  write (*,*) lbound(Iarray2D,2)
  write (*,*) ubound(Iarray2D,2)
  write (*,*) size(Iarray2D)

end program

The first three write commands return

1    ( = lower bound of Iarray1D(:) )
10   ( = upper bound of Iarray1D(:) )
10   ( = size of Iarray1D )
  • LBOUND returns the lower bound which is always =1. (However we note here that it is possible to define arrays with a lower bound different than 1, but this will not be discussed here).
  • UBOUND returns the upper bound as defined in DIMENSION(10), so 10. Both commands are called with "...,1)" which returns the lower/upper bound for the first and only dimension.
  • SIZE returns the total size, which is also =10 here.

The next five lines return

1    ( = lower bound of Iarray2D(:,1) )
10   ( = upper bound of Iarray2D(:,1) )
1    ( = lower bound of Iarray2D(:,2) )
20   ( = upper bound of Iarray2D(:,2) )
200  ( = size of Iarray2D )
  • LBOUND(...,1) and UBOUND(...,1) return the lower/upper bound for the 1st dimension, which are =1 and =10 here, respectively.
  • Similarly, LBOUND(...,2) and UBOUND(...,2) return the lower/upper bound for the 2nd dimension, which are =1 and =20 here.
  • SIZE returns the total size which is =10*20=200 in this example.

Constant arrays

Arrays can be defined constant as well. Constant arrays have to be initialised immediately using the (/ ... /) array constructor. Example:

program ConstTest2

integer, dimension(5), parameter :: Ilist = (/ 1,2,3,4,5 /)
real(DP), dimension(3), parameter :: Dlist = (/ 0.1, 0.2, 0.3 /)

  ...

end program

Multidimensional arrays are slightly more complicated in the initialisation, the RESHAPE command has to be used. The RESHAPE command reshapes a one-dimensional array to a multidimensional array using a row-wise ordering of the elements. Example:

program ConstTest2

integer, dimension(5,2), parameter :: Ilist = &
    reshape ( (/ 1,2,3,4,5,6,7,8,9,10 /), (/5,2/) )

  ...

end program

In the above example, the array Ilist receives the values

Ilist(:,1) = 1,2,3,4,5
Ilist(:,2) = 6,7,8,9,10

Allocatable arrays

Allocatable arrays are arrays with a-priori unknown length. They can dynamically be allocated during runtime. Such arrays are declared with n=: and an additional allocatable flag. Example:

program AllocateExample

  integer, dimension(:), allocatable :: Iarray

  allocate (Iarray(10))    ! Allocates an array with 10 entries
  ...                      ! Do something with the array
  deallocate (Iarray)      ! Release memory

end program

The allocate/deallocate commands are equivalent to the malloc/free commands to C++.

Allocatable arrays are by design "automatically released", i.e., the end of a command unit (main program/subroutine/function) automatically invokes a deallocate of the allocatable array. So the above example could be shorteded to

program AllocateExample

  integer, dimension(:), allocatable :: Iarray

  allocate (Iarray(10))    ! Allocates an array with 10 entries
  ...                      ! Do something with the array

end program

At the point where end program is reached, the deallocate is automatically invoked. So allocatable arrays are perfect for large temporary data inside of a subroutine.

Of course, allocatable arrays can also be multidimensional; here an example:

program AllocateExample

  integer, dimension(:,:), allocatable :: Iarray

  allocate (Iarray(10,20))    ! Allocates 20x10 entries
  ...                         ! Do something with the array

end program

Pointers to variables

Fortran 90 introduces the concept of pointers, which is in contrast to C++ more strict but also more powerful. Any variable can be defined to be a pointer to another variable of the same type. This includes pointers single values as well as pointers to arrays.

To declare a variable as a pointer to another variable, the pointer qualifier must be specified. Every variable where the pointer may point to must be declared with a target quantifier. The "=>" operator is used to set a pointer to something. The nullify command or null() target can be used to clear the pointer. Here an instructive example:

program PointerDemo

  integer, target :: i1    ! Can be a target of a pointer
  integer         :: i2    ! Can NOT be a target of a pointer

  integer, pointer :: p_i  ! Pointer top an integer

  p_i => i1          ! p_i points to i1
  p_i = 50           ! The same as i1=50

  nullify (p_i)      ! Clear the pointer
  p_i => null()      ! Identical to "nullify (p_i)"

  p_i => i2          ! Compiler error. i2 is not "target"

end program

Pointer to arrays

Pointers can also refer to arrays if they are defined in the same shape as the array they should point to.

program PointerDemoArray

  ! Array with 10 integers
  integer, dimension(10), target :: Iarray

  ! Pointer to an integer array
  integer, dimension(:), pointer :: p_I

  p_I => Iarray      ! p_I points to Iarray
  p_I(:) = 0         ! The same as "Iarray(:)=0"

end program

Pointers to arrays automatically update their minimum/maximum bounds according to the target they point to. The corresponding bounds can be accessed using the ubounds routine, as can be seen in the following example with a multidimensional array.

program PointerDemoMulti

  ! Array with 20x10 integers
  integer, dimnension(10,20), target :: Iarray

  ! Pointer to a 2D integer array
  integer, dimension(:,:), pointer :: p_I

  p_I => Iarray      ! p_I points to Iarray

  ! Will give "10"
  write (*,*) "Dimension 1 has ", ubound(p_I,1), " entries"

  ! Will give "20"
  write (*,*) "Dimension 2 has ", ubound(p_I,2), " entries"

  ! Will give "1"
  write (*,*) "Dimension 1 starts at", lbound(p_I,1)

  ! Will give "1"
  write (*,*) "Dimension 2 starts at ", lbound(p_I,2)

  ! Will give "200"
  write (*,*) "Array has size ", size(p_I)

end program

Allocating data with pointers

Using allocate/deallocate, it is also possible to allocate memory like malloc/free in C/C++. This is similar to the concept of allocatable arrays, however, memory is NOT automatically deallocated. Here an example for allocating a single integer:

program PointerDemo

  integer, pointer :: p_i

  allocate (p_i)   ! Allocates one integer
  p_i = 5          ! Set the value
  deallocate (p_i) ! Release memory

end program

This concept is usually of more use for arrays,

program PointerDemo2

  integer, dimension(:), pointer :: p_I

  allocate (p_I(10))   ! Allocates 10 integers
  ...                  ! Do something with p_I
  deallocate (p_I)     ! Release memory

end program

or complex structures:

program PointerDemo3

  ! Declare a structure
  type ProblemStructure
    integer :: i
    real(DP) :: d
    character(len=100) :: s
  end type

  ! Define a pointer to the structure
  type(ProblemStructure), pointer :: p_myProblem

  ! Allocate the structure on the heap
  allocate(p_myProblem)

  ! Access variables
  p_myProblem%i = 5
  p_myProblem%d = 10.0
  p_myProblem%s = "Hello there"

  ! Release memory
  deallocate(p_myProblem)

end program

Note that there is no additional "->" operator as in C/C++. The "%" operator always refers to the content of the pointer -- or in other words, the compiler automatically determins whether to use "." or "->". Here a more complex example with an embedded pointer.

program PointerDemo3

  ! Declare a structure
  type ProblemStructure
    integer, dimension(:), pointer :: p_Iarray
  end type

  ! Define a pointer to the structure
  type(ProblemStructure), pointer :: p_myProblem

  ! Allocate the structure on the heap
  allocate(p_myProblem)

  ! Allocate the subarray with 10 entries
  allocate (p_myProblem%p_Iarray(10))

  ! Set to zero
  p_myProblem%p_Iarray(:) = 0.0

  ! Release subarray
  deallocate(p_myProblem%p_Iarray)

  ! Release main structure
  deallocate(p_myProblem)

end program

Remark: The deallocate command automatically puts the pointer to => null().

Flow control commands

Conditions

Fortran defines the following condition operators which can be used, e.g., in IF commands. Most condition exists twice -- the ".xx." notation comes from Fortran 77 whereas the C-like notation has been introduced in Fortran 90.

Operation    | Condition in Fortran | in C/C++
-------------|----------------------|---------
less than    | .lt. , <             | <
greater than | .gt. , >             | >
less/equal   | .le. , <=            | <=
greater/equal| .ge. , >=            | >=
equal        | .eq. , ==            | ==
not equal    | .ne. , /=            | !=
logical and  | .and.                | &&
logical or   | .or.                 | ||
logical not  | .not.                | !
equivalence  | .eqv.                | == (for bool variables)
not equival. | .neqv.               | != (for bool variables)

Conditions are typically used in IF commands. The following instructive example demonstrates the typical syntax. Note that the condition is always enclosed by braces "(...)".

! Simple IF clause
if (a == b) then
  ...
end if  

! More complex expression
if (((a == b) .or. (a == c)) .and. (a == d)) then
  ...
end if  

! Complete IF-THEN-ELSE
if (a == b) then
  ...
else
  ...
end if

! IF-THEN-ELSEIF construct
if (a == b) then
  ...
else if (b == c) then
  ...
else
  ...
end if

! which is equivalent to
if (a == b) then
  ...
else 
  if (b == c) then
    ...
  else
    ...
  end if
end if

As can be seen above, an ELSE IF is formed by placing IF into the same line as ELSE. A linebreak would start a new block.

Remark: As noted above, the following statements are exactly identical:

if (a == b) ...
if (a .eq. b) ...

or

if (a < b) ...
if (a .lt. b) ...

Shorthand notation for IF clauses

Sometimes, IF clauses have a very short reaction to a condition that fits into one line. In this case, the "THEN" can be omitted if the command follows directly to the braces. Examples:

if (a < b) c = 0
if (a == b) write (*,*) "Error"

SELECT-CASE commands

The select-case construct is a handy notation for multiple IF clauses and similar to the switch-case in C/C++. However, in contrast to C/C++, the following rules hold:

  • There is no "fall-through", i.e, wherever a block ends, the select case-statement is left. Or in the words of a C/C++ programmer, there is an automatic break insered at the end of each block.
  • One can specify ranges of numbers, not only single values.

Here an example:

program PointerDemo3
integer :: i
  ...
  select case (i)
  case (1)
    write (*,*) "There is i=1"

  case (2)
    write (*,*) "There is i=2"

  case (3:10)
    write (*,*) "There is i between 3 and 10"

  case (11:)
    write (*,*) "There is i>=11"

  default
    write (*,*) "There is i<=0"

  end select
end program

DO-Loops

The most typical type of loop in Fortran 90 is the DO loop, which is closely releated to the FOR loop in C/C++:

program SmallLoop
  integer :: i

  do i = 1, 10
    write (*,*) i
  end do
end program

The value of the counting variable will be i=11 at the end. This loop is identical to the C/C++ for loop in the form

  int i;
  for (i=1; i <=10; i++)
  {
    printf ("%d\n", i);
  }

Fortran does not allow private in-block variables (like for (int i=...)); all variables must be specified in the beginning of the block.

A "striped" version that increments i in terms of 3 reads

program SmallLoopStriped
  integer :: i

  do i = 1, 11, 3
    write (*,*) i
  end do
end program

The value of the counting variable will be i=13 at the end. The last value written to the terminal is "10".

A "backward headed" loop counting down from 10 to 1 reads:

program SmallLoopBackward
  integer :: i

  do i = 10, 1, -1
    write (*,*) i
  end do
end program

The value of the counting variable will be i=0 at the end.

However, a special rules hold for such loops: The number of iterations must be available in advance. As a consequence, the upper/lower bound must not change inside of a loop. So a code like the following is NOT valid:

program SmallLoopWrong
  integer :: i,j

  j=10

  do i = 1, j
    write (*,*) i
    if (i .eq. 10) then
      j = 20              ! ERROR
    end if
  end do
end program

Conditional DO-WHILE loops

DO-Loops can depend on a condition and are named "DO-WHILE" loops in this case. This is very similar to an IF clause. An example reads as follows:

do while (i /= 10)
  ...
end do

Infinite DO-loops

Fortran 90 also defines infinite loops for complex stopping criteria. Leaving a loop is possible using the "exit" command. Example:

do
  if (i == 10) exit
  ...
end do

Nested DO loops, skipping of iterations, exiting loops

DO loops can be arbitrarily nested. Iterations can be skipped using the cycle command and left via the exit command. Loops can also be assigned a name, so an exit/cycle command can specify to jump out of an outer loop immediately. Examples:

! Nested loop
do i=1,10
  do j=1,10
    ...
  end do
end do

! Nested loop that skips i=5
do i=1,10
  if (i == 5) cycle
  do j=1,10
    ...
  end do
end do

! Nested loop that leaves the complete block if (i=j=5)
outerloop: do i=1,10      
  do j=1,10
    if ((i == 5) .and. (j == 5)) then
      exit outerloop
    end if
  end do
end do outerloop

As can be seen above, a named loop starts with a label in front of do (here outerloop:). The label must be releated at the end do.

Multi-file projects

Modules

For larger programs, Fortran allows the definition of so-called modules. A module is a separate program part that can be seen as a small, closed library. In contrast to C/C++, a there is no such a concept of header files; a module contains both, the declaration and the definition of structures, variables, subroutines and functions.

The following example demonstrates the definition of a simple module "ComplexNumbers":

module ComplexNumbers

implicit none
private

  type Complex
    real :: R
    real :: I
  end type

  public :: Complex

end module

The module starts with the commands IMPLICIT NONE and PRIVATE. These commands are optional, however, strongly advised.

  • IMPLICIT NONE prevents all symbols to be undefined, which matches the behaviour of C++; without this command, one could use variables without declaring them. Fortran has special rules for choosing the type of a variable depending on the first letter in this case. This should be avoided in good programming style!

  • PRIVATE declares all symbols to be private and invisible. Without this command, all types, subroutines, functions, etc. would be public by default, which is a usually undesired behaviour in large modules.

In a second step, a structure Complex is defined which is declared to be public in this module. A main program can include this module with the USE statement, which gives it access to the data in "ComplexNumbers" declared as public. The USE statement has a similar behaviour as the include statement in C/C++, however, it includes all public symbols and does not just copy a specified include file into the sourcecode as part of the preprocessor.

program HelloStructure

use ComplexNumbers
implicit none

  ! Declare a variable
  type(Complex) :: myComplex

  ! Set real/imaginary value
  myComplex%R = 1.0
  myComplex%I = 0.0

end program

As can be seen here, IMPLICIT NONE can (and should) also be specified in the main program.

Modules can of course be used in other modules as well. Example:

module ComplexNumbers2D

use ComplexNumbers

implicit none
private

  type Complex2D
    type(Complex) :: C1
    type(Complex) :: C2
  end type

  public :: Complex2D

end module

The USE statement in the beginning of the module "includes" the module "ComplexNumbers" into the module "ComplexNumbers2D", so the symbols defined there are available here as well. It has to be used before any IMPLICIT or PRIVATE statement.

Subroutines

The module concept allows to encapsule parts of the code in subroutines and offer them in a kind of library to other parts of the program. A simple extension of the above example reads as follows:

module ComplexNumbers

implicit none
private

  type Complex
    real :: R
    real :: I
  end type

  public :: Complex
  public :: Init

contains

  subroutine Init(c)
  type(Complex), intent(inout) :: c
    c%R = 0.0
    c%I = 0.0
  end subroutine

end module

This module publishes the type "Complex" as well as a subroutine "init". The subroutine is declared after an initial contains statement that subdivides the module into a "header" part (with structures) and a "code" part (containing only subroutines and functions). The subroutine has one parameter "c" which is declared as intent(inout) -- which tells the compiler that the routine is allowed to modify the content of "c". Indeed, the subroutine overwrites the content with zero. A main program now can access all public routines/structures of the module. In particular, the subroutine can be used by "calling" it, i.e., there must be a call precede the subroutine name. This is different to C/C++ where subroutines can be used like any other qualifier. Example:

program HelloStructure2

use ComplexNumbers

  ! Declare a variable
  type(Complex) :: myComplex

  ! Initialise
  call Init(myComplex)

  ! Set real/imaginary value
  myComplex%R = 1.0

end program

All local variables used in a subroutine (and a function, see below) must be declared in the header of the subroutine. This reads as follows:

subroutine sum1to10 (isum)
integer, intent(out) :: isum

  ! local variables
  integer :: i

  isum = 0
  do i = 1,10
    isum = isum + i
  end do
end do

As indicated above, Fortran does not allow private in-block variables (like for (int i=...)); all variables must be specified in advance.

WARNING: In contrast to C/C++, variables are ALWAYS PASSED BY REFERENCE. This is independent of whether a variable is a single integer, a complex structure or an array. So the use of the intent specifier (see below) is strongly advised to prevent mistakes in the code.

Inside of a subroutine, the RETURN command can be used to immediately return to the caller. This is similar to the return command in C/C++. Example:

module ComplexNumbers

implicit none
private

  type Complex
    real :: R
    real :: I
  end type

  public :: Complex
  public :: Init

contains

  subroutine Init(c)
  type(Complex), intent(inout) :: c
    if ((c%R == 0.0) .and. (c%I == 0.0)) then
      return
    end if
    c%R = 0.0
    c%I = 0.0
  end subroutine

end module

Functions

Similar to subroutines, it is possible to define functions in Fortran 90. Functions are parts of the code that must return a value given by a special return variable. There are two possibilities to define a function, either without or with specified return variable. Return variables can be declared, however, they must not contain an INTENT qualifier. If no return variable is declared, the name of the function defines the return variable. Here an example:

module ComplexNumbers

implicit none
private

  ...

  ! Publish functions
  public :: RealPart
  public :: ImaginaryPart

contains

  ...

  ! Function without explicit return variable
  !
  real function RealPart (c)
  type(Complex), intent(in) :: c
    ! Return variable is function name
    RealPart = c%R
  end function

  ! Function with explicit return variable. No INTENT for Im!
  !
  function ImaginaryPart (c) result (Im)
  type(Complex), intent(in) :: c
  real :: Im
    ! Return variable is "Im"
    Im = c%I
  end function

end module

The first function, RealPart, is written without explicit declaration of the return variable. This syntax is similar to C/C++. The key words real before function defines the return value. The name of the return value is the name of the function, so the assignment RealPart = ... sets the return value of the function, a real-typed value.

The second function, ImaginaryPart, is written with explicit declaration of a return variable. The name of the return variable is defined as Im with the result qualifier. Note that the declaration of Im in the parameter list does not contain any IMPLICIT attribute - this is not allowed!

Functions can be used in a main program similar to C/C++; example:

program HelloStructure3

use ComplexNumbers

  ! Declare a variable
  type(Complex) :: myComplex

  ...

  ! Print real/imaginary part

  write (*,*) "Real part     : ", RealPart(c)
  write (*,*) "Imaginary part: ", ImaginaryPart(c)

end program

However, in contrast to C/C++, the return value has to be used somewhere. Just calling the function and not using the return value is not allowed.

Special language constructs

Extended data types

Fortran 90 defines a set of basic data types:

Name data type
integer Standard integer type
real Standard float type
character A character value
logical A boolean value, only .true. or .false.

For many purposes, these data types are not appropriate. The real data type, for example, corresponds to the float data type in C/C++, which is rarely used in scientific applications. It is more common to use the double data type in C/C++ which has a larger set of possible values.

For this purpose, Fortran 90 introduces a machine-independent extensions to the above data types in terms of an accuracy modifier. The crucial commands in this context are SELECTED_REAL_KIND and SELECTED_INT_KIND. These commands return a modifier which can be specified in the declaration of a variable and which leads to a modified data type with at least the specified accuracy. Here an example:

integer, parameter :: DP = selected_real_kind(15,307)

This command initialises a constant DP with a value that identifies a floating point number type that is capable of

  • Having an accuracy of (at least) 15 digits.
  • Having an exponent up to (at least) E+307.

The smallest possible floating point type that supports this accuracy is the "double precision" type. A variable in type "double precision" is then declared with this modifier specified in braces after the real type qualifier. The following example declares a double precision variable dvalue.

real(DP) :: dvalue

Remark: On most machines, there is DP=8 chosen by the above selected_real_kind command, where the number "8" corresponds to the number of bytes, a double precision value needs. So on most machines, double precision variables are equivalently declared by

real(8) :: dvalue

However, one should be careful with this assumption, as the number "8" is machine dependent. Using a constant DP declared using selected_real_kind offers a machine-independent way of declaring double precision variables.

Having defined such a type qualifier, one can also define constant numbers in this data format by appending "_DP" to a number. This is very much like appending a type quantifier to a number in C/C++, e.g., like in a definition of a single precision / float variable "1.0f". Examples:

real(DP), parameter :: PI = 3.14159265358979_DP

write (*,*) "ARCCOS(0) = ", acos(0.0_DP)

The first command declares a constant PI in double precision and assigns it a value in double precision. The second command calls the function "ACOS" with a value "0.0" in double precision.

Using the REAL(...) function, one can typecast one type into another using the above type qualifier. For example, the following code casts an integer i into a double and prints it in a loop:

integer :: i

do i=1,10
  write (*,*) "Integer: ", i, ", double: ", real(i,DP)
end do

A similar logic also holds for integer. The command

integer, parameter, public :: I32 = selected_int_kind(8)

defines a qualifier "I32" that identifies integers with a value set of (at least) $[-10^{8}, 10^{8}]$, which is fulfilled by a 32 bit integer. A 32 bit variable is then declared by

integer(I32) :: i

and a type cast of a real value into an integer is done using the function INT(...), e.g.,

write (*,*) "Real: ", 5.0, ", Int: ", int(5.0,I32)

The INTENT qualifier

Parameters in functions/subroutines should be declared with an intent qualifier. There are three possible qualifiers:

  • intent(in): Variable can only be read
  • intent(inout): Variable can be read and modified
  • intent(out): Variable will be defined in the subroutine

Parameters that are declared as intent(in) can only be read in the subroutine. This is similar to the const specifier in C/C++. However, there is an additional benefit: Parameters declared as intent(in) are allowed to be defined by a constant in the call. Here an example:

module intentmod

implicit none
private

  public :: mysub

contains

  subroutine mysub(i,j)
  integer, intent(in) :: i
  integer, intent(inout) :: j
    j = 5*i
  end subroutine

end module

A main program as this one

program test
use intentmod
implicit none

  integer :: j

  call mysub(5,j)

end program

is ok. However, doing it like this

program test
use intentmod
implicit none

  call mysub(5,10)

end program

the compiler would complain as "10" is not a variable, and mysub probably wants to write to it -- and writing into a constant does not make sense.

The intent(out) statement finally is good for making the compiler check that output variables are set. So for a subroutine like this one,

  subroutine mysub(i,j,k)
  integer, intent(in) :: i
  integer, intent(inout) :: j
  integer, intent(out) :: k
    j = 5*i
  end subroutine

the compiler would complain that "k" is not set.

WANRNING: INTENT should be used whereever possible. Assume that a subroutine is declared without the INTENT qualifier as follows:

module intentmod2

implicit none
private

  public :: myerrsub

contains

  subroutine myerrsub(i,j)
  integer :: i
  integer :: j
    j = 5*i
  end subroutine

end module

Syntactically, this is completely ok. However, Having defined myerrsub like this, one could use the routine in an errorneous way as follows:

program test2
use intentmod2

  call myerrsub(5,10)

end program

The compiler would NOT complain and the program would run. However, it would overwrite an internally defined constant "10" which usually leads to very undesireable and unpredictable results.

Example: The following example compares the declaration of variables between Fortran and C/C++. Let a Fortran 90 subroutine be given as

subroutine doiteration(a, b, c)
real, intent(in) :: a
real, intent(inout) :: b
real, intent(out) :: c
real :: dtemp
  ...
end subroutine

The subroutine has two input, one output and one temp variable. A corresponding declaration in C/C++ would read

void doiteration(const float & a, float & b, float & c) 
{
  float dtemp;
  ...
}

"INTENT(IN)" variables are translated to "const" variables, "INTENT(INOUT)" variables to "nothing". However, C/C++ does not have an explicit declaration of "out" variables (like, e.g., C#). One would just declare "c" as a reference and overwrite it, similar to "INTENT(INOUT)".

The difference between "INTENT(OUT)" and "INTENT(INOUT)" can be seen if structures are involved. A Fortran 90 subroutine as follows

type Complex
  real :: r = 0.0
  real :: d = 0.0
end type

...

subroutine add(a,b,c)
type(Complex), intent(in) :: a
type(Complex), intent(inout) :: b
type(Complex), intent(out) :: c
  ...
end subroutine

would be translated in C/C++ as

struct Complex
{
  float r;
  float i;
};

...

void add(const Complex & a, Complex & b, Complex & c) 
{
  c.r = 0.0
  c.i = 0.0
  ...
}

Thus, "c" is initialised in the beginning of the subroutine.

Passing strings as parameters

For passing strings to subroutines, a special rule holds. Strings defined as parameter can be defined with unknown length, using the (len=*) attribute. The length is automatically adjusted to the length of the string used in the call. Example:

program stringtest
  character(len=10) :: str
  str = "Hello"
  call mystringsub (str)
end program

subroutine mystringsub(s)
character(len=*), intent(in) :: s
  write (*,*) len(s), " ", len_trim(s)
end subroutine

This program prints

10 5

to the terminal -- 10 as a result of the LEN function (returning the length of s=str) and 5 as a result of the length of the word "Hello" in the string str.

Symbol overloading with Interfaces

In modules, subroutines can be statically overloaded similar C++. This is implemented by the interface command. Here an example:

module clearmodule

implicit none
private

  interface ClearVariable
    module procedure ClearInt
    module procedure ClearReal
  end interface

  public :: ClearVariable

contains

  subroutine ClearInt (i)
  integer, intent(out) :: i
    i = 0
  end subroutine

  subroutine ClearReal (d)
  real, intent(out) :: d
    d = 0.0
  end subroutine

end module

The module publishes the symbol ClearVariable which is a synonym for ClearInt and ClearReal. On a call, the compiler automatically determins which routine to use. Example:

program ClearTest
use clearmodule

  integer :: i
  real :: d

  ClearVariable(i)    ! Calls ClearInt
  ClearVariable(d)    ! Calls ClearReal
end program

Predefined values in structures

During the definition of structures, it is possible to prescribe initial values for the variables. These values are realised in the moment, the structure is created -- either as a variable or as a result of an INTENT(OUT) in a subroutine. Example:

program StdInitVar

  type Complex
    real :: R = 5.0
    real :: I = 10.0
  end type

  type(Complex) :: myC

  write (*,*) myC%R, " ", myC%I

end program

In the moment, the variable myC is created, it is initialised as prescribed in the type statement. As a consequence, the output of the routine will be

5.0 10.0

For an INTENT(OUT) statement in a subroutine, there is a special rule. INTENT(OUT) triggers the initialisation. So a very simple initialisation routine for complex numbers could be written as follows:

module complexnumbers

implicit none
private

  type Complex
    real :: R = 0.0
    real :: I = 0.0
  end type

  public :: Complex
  public :: Init

contains

  subroutine Init (c)
  type(Complex), intent(out) :: c
    ! nothing to do
  end subroutine

end module

Note that Init does not contain any statement. However, this is not completely true: Init contains the INTENT(OUT) statement in the definition of the variable "c". This will trigger initialisation as prescribed in the structure. So in a main program like the following,

program ctest

  use complexnumbers

  type(Complex) :: myC

  myC%R = 5.0
  myC%I = 10.0

  Init(myC)

  write (*,*) myC%R, " ", myC%I
end program

the Init command overwrites myC with zero and the output will be

0.0 0.0

Remark: Pointers in structures can be predefined as pointing to null(); this reads as follows:

module list

implicit none
private

  type ListEl
    real :: d = 0.0
    type(ListEl), pointer :: next => null()
  end type

  public :: ListEl

end module    

Optional variables

One very common feature of Fortran 90 is the possibility to define optional parameters in subroutines or functions. Optional parameters are declared using the OPTIONAL attribute in the declaration of a variable. Such variables must always be at the end of the parameter list of a subroutine. Whether or not an argument is present in the call of the subroutine can be checked with the command PRESENT. Here an example:

module optvarsmodule

implicit none
private

  public :: mysub

contains

  subroutine mysub (dlen,dmult,dfinal)

  real, intent(in)            :: dlen
  real, intent(in), optional  :: dmult
  real, intent(out), optional :: dfinal

  ! local variables
  real :: dtemp

    if (present(dmult)) then
      dtemp = dlen*dmult
    else
      dtemp = dlen
    end if

    write (*,*) dlen

    if (present(dfinal)) then
      dfinal = dlen
    end if

  end subroutine

end module    

The routine mysub calculates and prints dlen or dlen*dmult, depending on whether dmult is given or not. The parameter list (dlen,dmult,dfinal), starts with the non-optional parameter dlen, while the optional parameters dmult and dfinal are at the ent of the list. The calculated value is written to dfinal if specified. The routine can be called in a main program with or without the optional arguments:

program optvars1
use optvarsmodule
implicit none

  real :: d

  call mysub (5.0)
  call mysub (5.0,10.0)
  call mysub (5.0,10.0,d)

  call mysub (5.0,d)
  call mysub (5.0,dfinal = d)

end 
  • The first call prints "5.0" to the terminal.
  • The second call prints "50.0".
  • The third call prints "50.0" and returns d=50.
  • The 4th call prints "250.0" as there is still d=50.
  • The last call prints "5.0" and returns d=5.

The last call is a bit special. Optional parameters can be arbitrarily omitted in the parameter list. However, if optional parameters are omitted, one has to specify the actual parameter name for any additional optional parameter. In this case, the statement dfinal = specifies that "d" should be used as dfinal.

Remark: This syntax sometimes leads to confusion. The following program prints "5.0" to the terminal and assigns "dfinal=5":

program optvars1
use optvarsmodule
implicit none
  real :: dfinal
  call mysub (5.0,dfinal=dfinal)
end 

This is exactly identical to

program optvars1
use optvarsmodule
implicit none
  real :: d
  call mysub (5.0,dfinal=d)
end 

Optional variables can be passed to other subroutines if they are defined there as optional as well. Example:

module optvarsmodule2

implicit none
private

  public :: mysub

contains

  subroutine mysub (dlen)
  real, intent(in), optional  :: dlen
    call mysub2(dlen)
    write (*,*) "Here is mysub."
  end subroutine

  subroutine mysub2 (dlen)
  real, intent(in), optional  :: dlen
    if (present(dlen)) then
      write (*,*) dlen
    else
      write (*,*) "-"
    end if
  end subroutine

end module    

program opttest2
use optvarsmodule2
implicit none
  call mysub()
  call mysub(2.0)
end program

In this example, mysub can pass dlen to mysub2, independent of whether dlen is actually specified in the call to mysub or not. mysub2 "inherits" the optional status of the variable dlen.

Passing subroutines as parameters

Fortran does not allow pointers to functions/subroutines like in C/C++. However, Fortran allows to pass a function/subroutine as parameter with a defined interface, such that it can be called in another subroutine. Here an example:

module stringmodule

implicit none
private

  public :: submul2
  public :: submul4
  public :: multiply

contains

  subroutine submul2(i)
  integer, intent(inout) :: i
    i = 2*i
  end subroutine

  subroutine submul4(i)
  integer, intent(inout) :: i
    i = 4*i
  end subroutine

  subroutine multiply(i,sub)
  integer, intent(inout) :: i

  interface
    subroutine sub(k)
    integer, intent(inout) :: k
    end subroutine
  end interface

    call sub(i)

  end subroutine

end module

program stringtest
use stringmodule
implicit none
  integer :: i
  i = 1
  call multiply(i,submul2)
  call multiply(i,submul4)
  write (*,*) i
end program

The main program calls multiply twice, once with submul2 as parameter and once with submul4. The routine multiply just calls this subroutine, which multiplies i by 2 and by 4. So the output of the main program will be "8".

Inside of the subroutine multiply, an interface block introduces one or more function interfaces for the subroutine. By this block, the multiply "knowns" that sub is a subroutine with the specified parameters - and thus, it can be called in call sub(...). The subroutines submul2 and submul4 match the interface in multiply and are therefore allowed to be passed as parameter.

Remark: This functionality is typically used to design "callback" functionalities in Fortran. Subroutines in a Fortran library (kernel) usually defines interfaces for user-defined "callback" routines that provide additional information to the worker routine.

Recursive subroutines/functions

Subroutines/functions in Fortran are not allowed to recursively call themself (directly or indirectly) by default. Instead, subroutines that should be used in a recursive way have to be marked with a RECURSIVE attribute. Without this attribute, the compiler usually does not guarantee that a recursive call leads to the desired result. Example:

recursive subroutine recsub(i)
integer, intent(in) :: i
  write (*,*) i
  if (i > 1) then
    call recsub(i-1)
  end if
end subroutine

Recursive functions are possible as well. However, one needs the special function declaration style with a separate return parameter as the function keyword is only allowed to be preceded by one other keyword:

recursive function recfunc (i) result (myresult)
integer, intent(in) :: i
integer :: myresult
  if (i > 1) then
    myresult = recfunc(i-1)
  else
    myresult = 1
  end if
end subroutine

A declaration in the style

recursive integer function recfunc (i)

is not valid Fortram 90/95 syntax and will be rejected by most compilers.

Embedded subroutines

Fortran allows to define subroutines/functions to be embedded in other subroutines/functions. Such embedded subroutines have access to all variables of the outer block. Embedded subroutines are declared at the end of a subroutine/function after a CONTAINS statement, similar to modules. Example:

module multmodule

implicit none
private

  public :: mysub

contains

  subroutine mysub (n)
  integer, intent(in) :: n

    integer :: i
    integer :: iresult

    iresult = 1
    do i = 1,n
      call mult_result (i)
    end do

    call div_result(5)

    write (*,*) iresult

  contains

    subroutine mult_result (j)
    integer, intent(in) :: j
      iresult = iresult * j
    end subroutine

    subroutine div_result (j)
    integer, intent(in) :: j
      iresult = iresult / j
    end subroutine

  end subroutine

end module    

The subroutine mysub "contains" the subroutines mult_result and div_result. mult_result and div_result are local subroutines, only assiciated to mysub, and have access to all variables of mysub. In particular, they are allowed to modify the variable iresult.

This language construct also holds for the main program, so it is possible to write a main program with local subroutines attached:

program multtest

implicit none

  integer :: i
  integer :: iresult

  iresult = 1
  do i = 1,n
    call mult_result (i)
  end do

  call div_result(5)

  write (*,*) iresult

contains

  subroutine mult_result (j)
  integer, intent(in) :: j
    iresult = iresult * j
  end subroutine

  subroutine div_result (j)
  integer, intent(in) :: j
    iresult = iresult / j
  end subroutine

end program

WARNING: Years of experience have shown that embedded subroutines should be avoided. There has been more than one compiler failing in a proper handling of this construct, and the usage quickly leads to confusion to the reader and hard problems in debugging mistakes. Avoid it!

A better version of the above main program with additional subroutines reads as follows:

program multtest

implicit none

  integer :: i
  integer :: iresult

  iresult = 1
  do i = 1,n
    call mult_result (i,iresult)
  end do

  div_result(5)

  write (*,*) iresult

end program

subroutine mult_result (j,iresult)
integer, intent(in) :: j
integer, intent(inout) :: iresult
  iresult = iresult * j
end subroutine

subroutine div_result (j)
integer, intent(in) :: j
integer, intent(inout) :: iresult
  iresult = iresult / j
end subroutine

In this example, the routines are not included in a module (which would even enhance the structure of the code). Such "global" subroutines outside of modules are allowed by Fortran and accessible from everywhere.

Common Pitfalls

PITFALL: Multiple commands in one line

Sometimes, there is Fortran code using mutiple commands in one line, e.g.

program linetest
implicit none
integer :: i,j,k

  i = 5; j = 3; k = 2

end program

The commands are separated by semicolons ";" and are that way nicely readable.

WARNING: This construct is NONSTANDARD Fortran, and you cannot expect the code to be compiled on all compilers. Standard Fortran does not allow the ";" character, so avoid this under all circumstances!

PITFALL: Performance loss due to inefficient array access

If a loop modifies a multidimensional array, it should prefer the first component, not the last. This is a typical performance loss, as Fortran works column ordered, not row-ordered as in C/C++. A wrong access makes the CPU jump through the memory, leading to a slower program. So the following loop is fast:

do i=1,10
  do k=1,1000
     Iarray(k,i) = ...
  end do
end do

while this loop is slow:

do k=1,1000
  do i=1,10
     Iarray(k,i) = ...
  end do
end do

PITFALL: Passing subarrays

In Fortran 90, it is possible to pass subarrays to subroutines. Here an example:

module subarraymod

implicit none
private

  public :: printsubarray

contains

  subroutine printsubarray (Iarray)
  integer, dimension(:), intent(in) :: Iarray

    integer :: i

    ! Print the array
    do i=1,ubound(Iarray,1)
      write (*,*) Iarray(i)
    end do

  end do

end module


program subarraytest

use subarraymod
implicit none

  integer, dimension(4,3) :: Iarray2D

  ! Define the array
  Iarray2D = reshape ( (/ 1,2,3,4, 5,6,7,8, 9,10,11,12 /), (/4,3/) )

  ! Print the second four numbers
  call printsubarray (Iarray2D(:,2))

end subroutine

The call to printsubarray prints the numbers "5,6,7,8" to the terminal. Internally, no memory is allocated. The definition Iarray2D(:,2) forms a pointer to a subarray of Iarray2D and passes it to printsubarray. This call is very fast.

However, one can theoretically also pass a subarray:

program subarraytest

use subarraymod
implicit none

  integer, dimension(4,3) :: Iarray2D

  ! Define the array
  Iarray2D = reshape ( (/ 1,2,3,4, 5,6,7,8, 9,10,11,12 /), (/4,3/) )

  ! Print a subarray
  call printsubarray (Iarray2D(2:3,2))

end subroutine

THIS IS DANGEROUS!!! It is not possible in Fortran to define a pointer to a subarray. Such a call invokes a pass by value:

Fortran creates a local copy of Iarray2D(2:3,2) on the stack. This is costly and may lead to a stack overflow error if the stack is not large enough. Furthermore, if the parameter is not declared as INTENT(IN) but as INTENT(INOUT), Fortran creates a local copy, calls the subroutine and copies the values back to the original array after the subroutine is finished. AVOID THIS!

PITFALL: Implicit publishing of symbols

The PRIVATE statement in front of a module has an extended meaning in the context of using a module in another module. In the following example:

module ComplexNumbers

implicit none
private

  type Complex2D
    real :: R
    real :: I
  end type

  public :: Complex

end module


module ComplexNumbers2D

use ComplexNumbers

implicit none

  type Complex2D
    type(Complex) :: C1
    type(Complex) :: C2
  end type

end module

the symbol Complex2D from ComplexNumbers2D and the symbol Complex from ComplexNumbers would be published by ComplexNumbers2D. For the main program, it would be enough to include "ComplexNumbers2D" only:

program ComplexTest

use ComplexNumbers2D
implicit none

type(Complex) :: myC
type(Complex2D) :: myC2d
  ...

There have already been compilers seen on the market that really got into trouble with such "implicit publishing" (e.g. due to exorbitant large compiling time), so a PRIVATE statement in front of a module is strongly advised.

PITFALL: Overlapping arrays

One very cruel pitfall when dealing with Fortran 90 is an array overlap in a subroutine. In Fortran, overlapping arrays in parameters are not allowed. This mistake is not detected by the compiler and will usually give strange results, depending on how much the compiler tries to optimise the code.

Here an example for such overlapping arrays. The routine CopyVector should copy the array Iarray1 to the array Iarray2:

module shifttest
implicit none
private

  public :: CopyVector

contains

  subroutine CopyVector (Iarray1, Iarray2)
  integer, dimension(:), intent(in) :: Iarray1
  integer, dimension(:), intent(inout) :: Iarray2
    integer :: i

    do i=ubound(Iarray1,1),1,-1
      Iarray2(i) = Iarray1(i)
    end do
  end subroutine

end module

program test
use shifttest
implicit none
integer, dimension(:), pointer :: Iarray

  allocate(Iarray(10))
  Iarray = (/ 1,2,3,4,5,6,7,8,9,10 /)
  call CopyVector (Iarray(1:7),Iarray(4:10))

  write(*,*) Iarray
  deallocate(Iarray)

end program

In the main program, an array Iarray is allocated, initialised and passed to the routine CopyVector. The two parameters in this call overlap which is not allowed by the Fortran Standard. The loop in CopyVector is applied backwards, so one would expect CopyVector to copy the subarray (1:7) successfully to (4:10). However, this is not always the case.

The following test was done with the Intel Fortran compiler 13. At first, the program is compiled without any optimisation:

> ifort -O0 -o test test.f90
> ./test
        1           2           3           1           2
        3           4           5           6           7

As one can see, the subarray is successfully copied. However, the output looks different if the code is compiled in "optimised" mode:

> ifort -fast -o test test.f90
> ./test
       1           2           3           1           2
       3           1           2           3           1

The result is a completely destroyed array.

What happens here?: In Fortran, overlapping arrays are not allowed. The routine CopyVector assumes that Iarray1 and Iarray2 are independent. Therefore, there is no real reason why the loop should go backwards. The compiler takes advantages of the fact and converts the loop to a forward loop: do i = 1,ubound(Iarray1,1). But in this form, the loop fails.

One should note that this rule does not apply for C/C++. A C/C++ compiler would never convert a backward loop into a forward loop as it cannot assume independence of the parameters. For such reasons, the Fortran compiler generates faster code if being compiled in optimised mode. A disadvantage is this pitfall, a user has to know to avoid it.

PITFALL: INTENT-attribute on pointer variables

There is one exception concerning the use of the INTENT attribute: Pointers passed to a subroutine or a function cannot be modified with an INTENT attribute! (Although most compilers would not complain about it).

So, the following code is wrong and will not compile on all machines:

subroutine mysub (p_Iarray)
integer, dimension(:), pointer, intent(in) :: p_Iarray
  ! Gives an error              ^^^^^^^^^^
  ...
end subroutine

Instead, the routine has to be declared without INTENT:

subroutine mysub (p_Iarray)
integer, dimension(:), pointer :: p_Iarray
  ...
end subroutine

The reason is simple: The subroutine is allowed to modify the pointer. This is similar to the declaration of return values for functions which are also not allowed to be modified by an INTENT attribute. For example, the following code is valid Fortran code and returns a pointer to a newly allocated array:

subroutine mysub (p_Iarray)
integer, dimension(:), pointer :: p_Iarray
  allocate (p_Iarray(100))
end subroutine

For parameters declared as pointers, the calling routine must specify a pointer (which is then allowed to be changed inside of the subroutine). Passing an array is not allowed. Example:

program PointerArrayTest
implicit none
  integer, dimension(:), pointer :: p_Iarr
  integer, dimension(100)        :: IarrayFix

  call mysub(p_Iarr)       ! Is ok
  call mysub(IarrayFix)    ! Will give a compiler error!

end program

subroutine mysub (p_Iarray)
integer, dimension(:), pointer :: p_Iarray
  allocate (p_Iarray(100))
end subroutine

Links to the Fortran specification and language books

The following links provide direct access to some information about the Fortran 90/95 language which a new Fortran user is adviced to read: