Fortran comprises a huge body of software in high-performance computing. We look at Fortran’s evolution into a modern HPC language.

Modern Fortran: Fortran 90

Fortran has been one of the key languages for technical applications since almost forever. With the rise of C and C++, the popularity of Fortran waned a bit, but not before a massive library of Fortran code had been written. The rise of scripted languages such as Perl, Python, and R also dented Fortran a bit, but it is still being used today for many excellent reasons and because a HUGE library of Fortran code is still being used today.

Before you say “ewww … Fortran,” it is definitely worth reviewing what Fortran is today compared with what you knew about it in the past. I still code in Fortran for many good reasons, not the least of which is performance and readability.

Fortran was originally developed as a high-level language so code developers didn’t have to write in assembly. It was originally oriented toward “number crunching,” because that was the predominant use of computers at the time (Facebook and YouTube weren’t around yet). The language was simple enough and contained the major elements for numerical computations. Compilers were capable of producing very optimized machine language. Fortran had data types that were appropriate for numerical computations, including a complex data type (not many languages have that) and easily dealt with multidimensional arrays, which are also important for number crunching. All of these reasons led Fortran to be the language of numerical computation for many years.

The advent of C and systems programming caused much new numerical code to be written in C or C++. Also, web and systems programming started to move to other languages, such as Java, Perl, and Python. As a result, new numerical code was written in these languages. However, Fortran is definitely not dead, and a lot of numerical code is still being written today using modern Fortran.

This is the first of several parts presenting the evolution of Fortran, illustrating how it is still very much a language for writing applications with a “modern” twist. To begin, I start with Fortran 77, which comprises a huge amount of numerical code and libraries.

Fortran 77

Fortran began in about 1957 with the advent of the first compiler. It was used a great deal because it was much simpler than assembly language. In my experience, Fortran 77 brought forth the features that made the language easier to use to create many algorithms. As a result, a lot of older Fortran code was rewritten for Fortran 77.

The first thing you need to get used to in Fortran is the amount of code written in uppercase. The programmer is not angry or shouting at you, but in the past, Fortran was not case sensitive, so a great deal of code was written in caps, creating a precedent that was followed for many years. Therefore, you will find Fortran coders of some lineage code in uppercase. However, in this article I mix upper- and lowercase in the examples.

In Fortran 77, a very useful way to share data across functions and subroutines was the use of common blocks, in which you define multiple “named” common blocks that contain variables. (They could be of mixed type, including arrays.) A typical scenario was to put the common blocks in an include file and put each function or subroutine into its own file. Each file that needed access to the common block “included” the file of common blocks.

Another feature, or limitation, of Fortran is that all arrays have to be fixed in size at compile time (no dynamic memory). For example, if you declare an array such as x(100,100), then you cannot change the dimensions or size after the code has been compiled. One trick some applications used was to define one very large vector and then “give” parts of the vectors to various portions of the code. It was a little messy, but you could simulate dynamic memory somewhat if the array was large enough.

Fortran also had fixed formatting. Some languages sort of have this today, such as Python, which requires indentation. In Fortran, the first column of each line could contain a C or c, indicating the beginning of a comment line, although you couldn’t put comments just anywhere in the code. It could also be used for a numerical label. Column 6 was reserved for a continuation mark so that lines that were longer than one line could be continued. In column 7 you could start writing code. Columns 1 to 5 could be used for statement labels such as the following:

...
      SUM = 0.0
      D0 100 I=1,10
         SUM = SUM + REAL(I)
 100  CONTINUE
...
      Y = X1 + X2 + X3 + 
     1    X4 + X5 + X6
...

By default, Fortran 77 defines variables starting with i, j, k, l, m, and n as integers (also the uppercase equivalents). As a result, they are used as loop counters for do loops. Variables that use any other letter of the alphabet are real unless declared to be “double precision.” You could turn off this implicit definition with the command IMPLICIT NONE just after the program, subroutine, or function name, which forces the code writer to define each and every variable (which is not necessarily a bad thing).

This is by no means a complete rundown of Fortran 77, but it gives you the highlights and the limitations.

Fortran 90

For a fairly long time, the Fortran standard didn’t evolve past Fortran 77. Finally, the next Fortran standard, referred to as Fortran 90, was released in 1991 as an ISO standard and in 1992 as an ANSI standard. Fortran 90 is a huge step up from Fortran 77, with a number of new features, but also with deprecation of some of the older features. Fortran 90 was the first big step in creating the modern Fortran.

Several “big” features were embodied in Fortran 90. The first one of importance is free-form source input. As mentioned previously, with Fortran 77, column 1 was used to indicate a comment or set aside for a numerical label, with the actual code starting in column 7. Starting with Fortran 90, you were allowed to put the code anywhere you wanted, and you could label statements, as in the following code snippet.

...
     sum = 0.0
     do i =1,10
        sum = sum + real(i)
     end do
...
     sum = 0.0
all: do i=1,10
        sum = sum + real(i)
     enddo all
...

The next big feature embodied in Fortran 90 is my personal favorite – allocatable arrays. With Fortran 77 you had to define the size of arrays when you compiled the application. This forced many people into unnatural acts to “simulate” allocatable arrays. Now, it was possible to do it naturally within Fortran. Consider the following code:

      PROGRAM TEST1
      IMPLICIT NONE
      REAL, ALLOCATABLE :: a(:,:)
      INTEGER :: n
      INTEGER :: allocate_status
      n=1000
      ALLOCATE( a(n,n), STAT = allocate_status)
      IF (allocate_status /= 0) STOP "Could not allocate array"
! Do some computing
      DEALLOCATE( a )
      END PROGRAM TEST1

The third line shows how to define an allocatable array. In this case, array a is a two-dimensional array, defined by (:.:). The allocation does not occur until line 7. Along with the array allocation is a “status” that returns a nonzero value if the allocation was unsuccessful or 0 if it was successful.

One important thing to note is that allocatable arrays use heap memory and not stack memory, so you can use a lot more memory. In fact, for almost any large arrays, I always use allocatable arrays to make sure I have enough memory.

After performing some computations, you then deallocate the array, which returns the storage to the system. By the way, the ninth line is a comment line. Fortran 90 allows you to put a comment anyway by prefacing it with an exclamation mark. No longer do you have to put a C in column 1 for a comment.

Another feature added to Fortran was array programming. Rather than having to write do loops for every array operation, you could now just use array notation. For example, to multiple two, 2D arrays together, use

c = matmul(a, b)

where a, b, and c are compatible arrays. You could also use portions of an array:

d(1:4) = a(1:4) + b(8:11)

You rely on the compiler for good array operation performance. Early Fortran 90 compiler versions had this, but some people wrote their own Fortran code, typically with loop unrolling, to get slightly better performance. However, such changes would be specific to a CPU, so they would not be very portable. Over time, Fortran coders used array notation, because it was so simple to write and read and is very portable, which pushed compiler writers to create very high performance array intrinsic functions that adapted to various CPUs. Note that this includes standard intrinsic mathematical functions such as square root, cosine, or sine.

Fortran 90 also introduced derived data types (custom data types). Before Fortran 90, you could not create your own data type; however, creating a derived data type is not difficult, as this simple example with several components shows:

      program struct_test
      type other_struct
         real :: var1
         real :: var2
         integer :: int1
      end type other_struct
 
      type my_struct ! Declaration of a Derived Type
         integer :: i
         real :: r
         real*8 :: r8
         real, dimension(100,100) :: array_s           ! Uses stack
         real, dimension(:), allocatable :: array_h    ! Uses heap
         type(other_struct), dimension(5) :: meta_data ! structure
      end type my_struct
! ...
      end program struct_test

This derived type (customer data type) has some variables (e.g., i, r, and r8); a fixed-size array, array_s, which is allocated on the stack; an allocatable array, array_h, which is allocated on the heap; and another derived type, meta_data. Using derived types within derived types allows you to create some complex and useful custom data types.

To access a specific part or member of a derived type, you simply use a percent sign (%), as shown here with a few additions to the previous example:

      program struct_test2
      type other_struct
         ...
      end type other_struct
 
      type my_struct ! Declaration of a Derived Type
         ...
      end type my_struct
      type(my_struct) :: a   ! Use derived type for variable "a"
! ...
      write(*,*) "i is ",a%i
!
      end program struct_test2

You can also make an allocatable derived type. Again, building on the last example:

      program struct_test3
      type other_struct
         ...
      end type other_struct
 
      type my_struct ! Declaration of a Derived Type
         ...
      end type my_struct
! Structures (Variables) of the the derived type my_struct
      type(my_struct) :: data
      type(my_struct), dimension(10) :: data_array
!
    end program struct_test3

A very, very convenient feature called modules was added to Fortran (generically referred to as “modular programming." This feature allows you to group procedures and data together. Code can take advantage of a module, and you can control access to it through the use of simple commands (e.g., public, private, contains, use). For all intents and purposes, it replaces the old common blocks feature of Fortran 77.

Modules are extremely useful. They can contain all kinds of elements, such as parameters (named constants), variables, arrays, structures, derived types, functions, and subroutines. This simple example a module is used to define some parameters:

    module circle_constant
    real, parameter :: pi = 3.14159
    end module circle_constant
 
    program circle_comp
! make the content of module available
    use circle_constant
    real :: r
!
    r = 2.0
    write(*,*) 'Area = ', pi * r**2
    end program circle_comp

In this case, the module just defined a single constant, pi. The program then uses the module (use) to make the contents available to the program.

The following example shows the use of contains within a module and accessing its content outside the module:

    module circle_constant
    real, parameter :: pi = 3.14159
 
    
    type meta_data
        character(len=10) :: color
        real :: circumference
        real :: diameter
        real :: radius
        real :: area
    end type meta_data
 
    contains
        subroutine meta_comp(r, item)
           type(meta_data) :: item
           item%diameter = 2.0 * r
           item%area = pi * r **2
           item%circumference = 2.0 * pi * r
        end subroutine
 
    end module circle_constant
 
    program circle_comp
! make the content of module available
    use circle_constant
    real :: r
    integer :: iloop
    type(meta_data), dimension(10) :: circles
!
    r = 2.0
    circles(1)%radius = 4
    circles(1)%color = "red"
    call meta_comp(r, circles(1))  ! Call the module function
 
    circles(2:10)%color = "blue"   ! array operation
    r = 4.0
    circles(2:10)%radius = r       ! array operation
    do iloop=2,10
       call meta_comp(r,circles(iloop)) 
    end do
 
    end program circle_comp

You can go one step further and denote public (the default) and private components in a module. Public components can be used outside the module, as in the previous example. However, you can make components, such as a function or subroutine, private so that they can only be used within the module, giving you a lot more control over what can be accessed by other parts of the code.

Although some programmers consider the pointer a minor feature in modern Fortran, I want to touch briefly on it. A POINTER is a new type of variable in Fortran 90 that references data stored by another variable, called a TARGET. They are typically used as an alternative to allocatable arrays or as a way to manipulate dynamic data structures, as in linked-lists.

A pointer has to be defined as the same data type and rank as the target and has to be declared a pointer. The same is true for the target, which has to have the same data type as the pointer and be declared a target. In the case of array pointers, the rank, but not the shape (i.e. the bounds or extent of the array), has to be specified. Here is a simple example of the declaration:

      INTEGER, TARGET :: a(3), b(6), c(9)
      INTEGER, DIMENSION(:), POINTER :: pt2

Another quick example of multidimension arrays is:

      INTEGER, POINTER :: pt3(:,:)
      INTEGER, TARGET :: b(:,:)

You cannot use the POINTER attribute with the following attributes: ALLOCATABLE, EXTERNAL, INTRINSIC, PARAMETER, INTENT, and TARGET. The TARGET attribute is not compatible with the attributes EXTERNAL, INTRINSIC, PARAMETER, and POINTER.

Using pointers is very simple, having only two operators, as the example below illustrates:

      PROGRAM PTR_TEST1
      INTEGER, POINTER :: PTR1
      INTEGER, TARGET :: X=42, Y=114
! ...
      PTR1 => X    ! PTR1 points to X
      Y = PTR1     ! Y equals X
      PTR1 => Y    ! PTR1 points to Y
      PTR1 = 38    ! Y equals 38
 
      END PROGRAM PTR_TEST1

In some code, pointers are also used with blocks of dynamic memory. To do this, you still use the allocate statement (function):

    PROGRAM PTR_TEST2
    REAL, POINTER :: PTR2:wq:w
    REAL, POINTER :: PTRA(:)
    INTEGER :: N
!
    N = 1000
    ALLOCATE( PTR2, PTRA(N) )
! Do some computing
    DEALLOCATE(PTR2, PTRA)
 
    END PROGRAM PTR_TEST2

In this example, the pointer PTR2 points to a single real value, and the pointer PTRA points to a block of dynamic memory for 1,000 real values. After you’re done using the block of memory, you can deallocate it. In this regard, the pointers behave very much like allocatable arrays.

One other common use for pointers is to divide arrays into smaller sections with the pointer pointing to that subsection. For example:

      program array_test
      implicit none
      real, allocatable, target :: array(:,:)
      real, pointer :: subarray(:,:)
      real, pointer :: column(:)
      integer :: n
      integer :: allocate_status
!
      n = 10
      allocate( array(n, n), stat  = allocate_status )
      if (allocate_status /= 0) stop "Could not allocate array"
!
      subarray => array(3:7,3:7)
      column => array(:,8)
!
      nullify(subarray)
      nullify(column)
      deallocate(array)
 
      end program array_test

A linked list is a very useful data structure. It is a sequence of “nodes” that contain information and point to the next node in the sequence (variations allow the node to point to the previous node). Although it’s not difficult to write for specific cases, generic linked lists are more difficult. One instructive example creates a linked list manager.

Fortran 90 created a way of specifying precision to make the code more portable across systems. The generic term used is kind. Real variables have three kinds: 4-byte (real*4), 8-byte (real*8) which is usually referred to as double precision, and 16-byte (real*16). In this example, I assign various kinds of precision to variables.

      real*8 :: x8  ! kind=8 or doule precision
      real*4 :: x4  ! kind=4 or single precision
      real(kind=4) :: y4   ! 
      integer*4 :: i4  ! integer single precision (kind=4)
      integer(kind=8) :: i8   ! Integer double precision

By using kind or the equivalent *n notation, you made your code much more portable across systems.

Fortran 90 had a number of other additions that would require a lot more space to write about. At a high level, in addition to the features mentioned, Fortran 90 also introduced the following:

  • Inline comments
  • Operator overloading
  • Unlabeled do loops (constructs such as do, if, case, where, etc. may have names.)
  • The case statement

In Fortran 90, the language developers also decided to deprecate, or outright delete, some outdated Fortran 77 features. The list below is from the Wikipedia article on Fortran.

  • Arithmetic IF
  • Non-integer DO parameters for control variables (deleted)
  • Branching to ENDIF from outside a block (deleted)
  • PAUSE statement
  • ASSIGN and assigned GOTO statement (deleted)
  • Assigned FORMAT specifiers (deleted)
  • H edit descriptors (deleted – the dreaded Hollerith fields)
  • Computed GO TO statement (obsolete)
  • DATA statements among executables (obsolete)
  • CHARACTER* form of CHARACTER declaration (obsolete)
  • Assumed character length functions (obsolete)
  • Fixed-form source code (obsolete)

You can easily discover what features have been deprecated or deleted by taking some Fortran 77 code, switching the extension to .f90, and trying to compile it with a Fortran 90 compiler.

Next time I’ll take a look at more modern features introduced in Fortran 95.

This blog represents my own viewpoints and not those of my employer, Amazon Web Services.