Fortran

From Wikipedia, the free encyclopedia

This is an old revision of this page, as edited by Jwmwalrus (talk | contribs) at 09:02, 27 February 2006 (Pointers And Targets). The present address (URL) is a permanent link to this revision, which may differ significantly from the current revision.

Jump to navigation Jump to search

Fortran (also FORTRAN) is a computer programming language originally developed in the 1950s; it is still used for scientific computing and numerical computation half a century later. It is sometimes considered the earliest "cross platform" (standardized) programming language.

The name is a portmanteau of Formula Translator/Translation. Early versions of the language were known as FORTRAN, but the capitalization has been dropped in newer revisions beginning with Fortran 90. The official language standards now refer to the language as "Fortran".

Fortran is statically typed, compiled (though sometimes interpreted), and imperative. Although originally a spaghetti (Fortran 66) and procedural (Fortran 77) programming language, recent versions of Fortran have included some features to support vector (Fortran 90) and object-oriented (Fortran 2003) programming language.

History

Fortran punch card. Note column markings.

The first FORTRAN compiler was developed for the IBM 704 in 195457 by an IBM team led by John W. Backus. This was an optimizing compiler, because the authors reasoned that no one would use the language if its performance were not comparable to assembly language.

The language was widely adopted by scientists for writing numerically intensive programs, which encouraged compiler writers to produce compilers that generate faster code. The inclusion of a complex number data type in the language made Fortran especially suited to scientific computation. There are many vendors of high performance Fortran compilers today. Many advances in the theory and design of compilers were motivated by the need to generate good code for Fortran programs.

Several standards of the language have appeared: FORTRAN II in 1958, FORTRAN IV in 1961, FORTRAN 66 in 1966, FORTRAN 77 in 1977, Fortran 90 in 1990, Fortran 95 in 1995, and Fortran 2003 in 2003. Fortran III was designed in 1958, allowing for inline assembler code; but it was never released because the portability concept of a high-level language would be lost. It also included other new features such as boolean expressions. It was used by about 20 IBM customers but was never released as a commercial product. Boolean expressions and IF tests were also included in Fortran IV. Fortran II only had a three way IF branch, based on whether a numeric expression was negative, zero or positive.

Early FORTRAN programs were written on punch cards, and had strict rules for formatting. Line length was limited to 72 columns, originally because this was the maximum number of columns the online punch card reader of the 704 could read. Source statements were punched in columns 7 through 72. The first five columns were reserved for statement numbers or the C in column one that indicated a comment. Statements longer than 66 characters could be continued to additional cards by making a punch in column 6 of the continuation cards. There was a limit on the number of continuation cards allowed, in some implementations as few as three or four. Columns 73 to 80 were often used for sequence numbers, allowing a deck of cards to be resorted if it was dropped. Symbols were usually limited to the number of alphanumeric characters that fit in one machine word, six was typical but implementations on machines with small words might limit you to as few as three. As programs moved to magnetic media, vendors offered different extensions to increase line lengths. FORTRAN 77 was the last version to require fixed length symbols and names.

Fortran 90 was a major revision, adding free source form, dynamic memory allocation, array operations, abstract data types, operator overloading, pointers, and modules to group related procedures and data together. Fortran 95 was a minor revision, adding features for parallel programming from the High Performance Fortran dialect, such as user-defined pure and elemental functions, and the forall construct. The most recent formal standard for the language, published in 2004, is known as Fortran 2003. It is an upwardly-compatible extension of Fortran 95, adding, among other things, support for IEEE floating-point arithmetic, exception handling, object-oriented programming, and improved interoperability with the C language. A comprehensive summary of the 2003 additions is at the ISO Fortran Working Group (WG5) web site, ftp://ftp.nag.co.uk/sc22wg5/N1551-N1600/N1579.pdf.

Features

Initially, the language relied on precise formatting of the source code and heavy use of statement numbers and goto statements. The ENTRY statement even allowed to pass the control into the middle of the subroutine being called. These quirks have been removed from newer versions of the language. Successive versions also introduced 'modern' programming concepts, such as source code comments and output of text, IF-THEN-ELSE (in FORTRAN 77), and parallel constructs, while still attempting to maintain Fortran's 'lean' profile and high performance. Among the most popular specialized Fortran-based languages were SAS, for generating statistical reports, and SIMSCRIPT, for simulating processes involving queuing. F is a clean subset of Fortran 95 that removes the unstructured features of Fortran, such as EQUIVALENCE.

Vendors of high performance scientific computers (Burroughs, CDC, Cray, Honeywell, IBM, Texas Instruments, UNIVAC...) added extensions to Fortran to make use of special hardware features such as: instruction cache, CPU pipeline , vector arrays, etc. For example, one of IBM's Fortran compilers (H Extended IUP) had a level of optimization which reordered the machine code instructions to keep several internal arithmetic units busy at the same time. Another example is CFD, a special 'version' of Fortran designed specifically for the ILLIAC IV supercomputer, running at NASA's Ames Research Center. These extensions have either disappeared over time or had elements incorporated into the main standard; the major remaining extension is OpenMP, which is a cross-platform extension for shared memory programming. One new extension, CoArray Fortran, is intended to promote parallel programming.

Syntax

As what was basically a first attempt at designing a high-level language, the language's syntax is sometimes regarded as arcane by programmers familiar with more recently developed languages such as C. Fortran has stayed abreast of such advances, however, and contemporary versions have attempted to supersede and deprecate such syntax in favor of more robust and transparent syntax. In deprecated forms of the language, it is difficult to write a lexical analyzer and one-character mistakes can lead to runtime errors rather than compilation errors. Contemporary constructs, such as free-form source, ameliorate such problems, but, as with any language, sound programming practices are the best way to avoid such errors.

One should also consider that the features of Fortran have been tuned to scientific and numerical work, as opposed to software development. For example, Fortran 95 has very short commands for performing mathematical operations on arrays which not only greatly improve program readability but also provide useful information to the compiler to enable it to vectorize operations. For these reasons, while Fortran is not often used outside scientific and engineering numerical work, it remains the language of choice for high performance numerical computing. It is also simple for non-programmers to learn how to write efficient code.

Since Fortran has been around for nearly fifty years, there is a vast body of Fortran in daily use throughout the scientific community (especially FORTRAN 77, the historically most important dialect). It is the primary language for some of the most intensive super-computing tasks, including weather and climate modeling.

Sample programs

The following programs can be compiled and run with any Fortran 90 or 95 compiler, such as GFortran [1]. Most modern Fortran compilers expect a file with .f95 or .f90 extension.

Hello world!

Here follows the Hello, world! example in the "classic" FORTRAN:

C       It was the first programming language
C       with the comments support!
        WRITE (6,7)
  7     FORMAT(15H Hello, world! )      
        STOP
        END

The program prints the Hello statement into output channel number six (on most machines, it was the terminal). The keyboard was usually connected to the channel five. The number 7 in the WRITE statement refers to the format line. This line can be placed anywhere in the program. The symbols 15H in the format line define the length of the message being printed in terms of Hollerith characters. The message text contains no bounding quotes. The recent FORTRAN versions accept quotes instead, besides the use of C-like format statements (but still support older notation). An updated version of the Hello, world! example reduces to:

  program HelloWorld
     !This is a comment
     write(*, '("Hello, world!")')
  end program HelloWorld

Cylinder area

This program calculates the area of a cylinder.

program cylinder

!!! Calculate the area of a cylinder.

!!! Declare variables and constants.
!!! constants=pi 
!!! variables=radius squared and height

  implicit none ! Require all variables to be declared -- Fortran 90 feature.

  integer :: ierr
  character :: yn
  real :: radius,height,area
  real, parameter :: pi = 3.14159

  interactive_loop: do

     ! Prompt the user for radius and 
     ! height and read them.

     write (*,*) 'Enter radius and height.'
     read (*,*,iostat=ierr) radius,height

     ! If radius and height could not
     ! be read from input, then restart 
     ! the loop.

     if (ierr /= 0) then
        write(*,*) 'Error, invalid input.'
        cycle interactive_loop
     end if

     ! Compute area. The ** means "raise to a power".

     area = 2*pi*(radius**2 + radius*height)

     ! Write the input variables (radius, height)
     ! and output (area) to the screen.

     write (*,'(1x,a7,f6.2,5x,a7,f6.2,5x,a5,f6.2)') &
          'radius=',radius,'height=',height,'area=',area

     yn = ' '
     yn_loop: do
        write(*,*) 'Perform another calculation? y[n]'
        read(*,'(a1)') yn
        if (yn=='y' .or. yn=='Y') exit yn_loop
        if (yn=='n' .or. yn=='N' .or. yn==' ') exit interactive_loop
     end do yn_loop

  end do interactive_loop

end program cylinder

Dynamic allocation and array operations

This program provides an example of two features in Fortran 90: dynamic memory allocation, and array operations. Note the absence of do loops and if/then loops. Also note the use of descriptive variable names and general code formatting that comport with contemporary computer programing style. The program performs some averaging on interactively entered data.

program average

!!! read in some numbers and take the average
!!! As written, if there are no data points (or no positive/negative points) 
!!!     an average of zero is returned.
!!! While this may not be expected behavior, it keeps this simple example simple.

  implicit none
  integer :: NumberOfPoints
  real, dimension(:), allocatable :: Points
  real :: AveragePoints=0., PositiveAverage=0., NegativeAverage=0.

  write (*,*) 'Input number of points to average:'
  read (*,*) NumberOfPoints

  allocate (Points(NumberOfPoints))

  write (*,*) 'Enter the Points to average:'
  read (*,*) Points

!!! take the average by summing Points and dividing by NumberOfPoints

  if (NumberOfPoints>0) AveragePoints = sum(Points)/NumberOfPoints

!!! now form average over positive and negative points only

  if (count(Points>0.)>0) PositiveAverage = sum(Points, Points>0.)/count(Points>0.)
  if (count(Points<0.)>0) NegativeAverage = sum(Points, Points<0.)/count(Points<0.)

  deallocate (Points)

!!! print result to terminal
  write (*,'(''Average = '', 1g12.4)') AveragePoints
  write (*,'(''Average of positive points = '', 1g12.4)') PositiveAverage
  write (*,'(''Average of negative points = '', 1g12.4)') NegativeAverage

end program average


Procedures

Modern Fortran features available for use with procedures, include deferred-shape and protected and optional arguments, as shown in the following example.

function GaussSparse(NumIter, Tol, b, A, X, ActualIter)

   !This function solves a system of equations (Ax = b) by using the Gauss-Jordan Method

   implicit none

   real GaussSparse

   !Input: its value cannot be modified from within the function
   integer, intent(in) :: NumIter
   real, intent(in) :: Tol
   real, intent(in), dimension(1:) :: b
   real, intent(in), dimension(1:,1:) :: A

   !Input/Output: its input value is used within the function, and can be modified
   real, intent(inout), dimension(1:) :: X

   !Outpu: its value is modified from within the function, only if the argument is required
   integer, optional, intent(out) :: ActualIter

   !Locals
   integer i, n, Iter
   real TolMax, Xk

   !Initialize values
   n = ubound(b, dim = 1)  !Size of the array, obtained by the use of the ubound intrinsic routine
   TolMax = 2. * Tol
   Iter = 0

   !Compute solution until convergence
   convergence_loop: do while (TolMax >= Tol.AND.Iter < NumIter); Iter = Iter + 1
      
      TolMax = -1. !Reset the tolerance value

      !Compute solution for the k-th iteration
      iteration_loop: do i = 1, n
         !Compute the current x-value
         Xk = (b(i) - sum(A(i,1:i-1) * X(1:i-1)) - sum(A(i,i+1:n) * X(i+1:n))) / A(i, i)

         !Compute the error of the solution
         TolMax = max((abs(X(i) - Xk)/(1. + abs(Xk))) ** 2, abs(A(i, i) * (X(i) - Xk)), TolMax)
         X(i) = Xk
      enddo iteration_loop
   enddo convergence_loop

   if (present(ActualIter)) ActualIter = Iter
   GaussSparse = TolMax

end function GaussSparse

If a return value is required only through arguments, a subroutine is preferred, as follows:

subroutine Swap_Real(a1, a2)

   implicit none

   !Input/Output
   real, intent(inout) :: a1(:), a2(:)

   !Locals
   integer :: lb(1), & !Lower bound
              ub(1)    !Upper bound
   integer i
   real a

   !Get bounds
   lb = lbound(a1)
   ub = ubound(a1)

   !Swap
   do i = lb(1), ub(1)
      a = a1(i)
      a1(i) = a2(i)
      a2(i) = a
   enddo

end subroutine Swap_Real

Modules

A module (programming) is program unit which contains both data and procedures. In Fortran, it only differs from the main program unit in that it contains no actual executable statements.

module GlobalModule

   !Reference to a pair of procedures included in a previously compiled 
   !module named PortabilityLibrary
   use PortabilityLibrary, only: GetLastError, &  !Generic procedure
                                 Date             !Specific procedure

   !Constants
   real, parameter :: zero = (0.D+00)
   real*8, parameter :: pi = (3.14159265358979)

   !Variables
   integer :: n, m, retint
   logical*2 :: status, retlog
   character(50) :: AppName

   !Arrays
   real, allocatable, dimension(:,:,:) :: a, b, c, d
   complex*8, allocatable, dimension(:) :: z

   !Structures
   type ijk
      integer i
      integer j
      integer k
   end type ijk

   type matrix
     integer m, n
     real, allocatable :: a(:,:)  !Fortran 2003 feature
   end type matrix


   !All the variables and procedures from this module can be accessed 
   !by other program units, except for AppName
   public
   private AppName

   !Procedure overload
   interface swap
      module procedure swap_Integer, swap_Real
   end interface swap

   interface GetLastError !This adds one more procedure to the generic procedure GetLastError
      module procedure GetLastError_GlobalModule
   end interface GetLastError

   !Operator overload
   interface operator(+)
      module procedure add_ijk
   end interface

   !Prototype for external procedure
   interface
      real function GaussSparse(NumIter, Tol, b, A, X)
         integer, intent(in) :: NumIter
         real, intent(in) :: Tol
         real, intent(in), dimension(1:) :: b
         real, intent(in), dimension(1:,1:) :: A
         real, intent(inout), dimension(1:) :: X
      end function GaussSparse
   end interface

   !Procedures included in the module
   contains

   !Internal function
   function add_ijk(ijk_1, ijk_2)
     type(ijk) add_ijk, ijk_1, ijk_2
     intent(in) :: ijk_1, ijk_2
     add_ijk = ijk(ijk_1%i + ijk_2%i, ijk_1%j + ijk_2%j, ijk_1%k + ijk_2%k)
   end function add_ijk
 
   !Include external files
   include 'Swap_Integer.f90'  !Comments SHOULDN'T be added here
   include 'Swap_Real.f90'
end module GlobalModule

Pointers And Targets

In Fortran the concept of pointer differs from that one conceived in C-like languages in that it does not store the memory adress of any other variable (unless it is defined as an integer, and a compiler-supplied function is used to do so, or the compiler provides a C-pointer feature). Instead, it serves whether as an alias for another variable (or part of it), or as an ordinary dynamically allocated variable. If an alias, it is said that its status is associated, and the variable to which it points must have either the pointer or target attribute. The following example illustrates the concept:

program Test

   !NOTE: Variable expressions in format statements (e.g., <m> or <n>), are compiler-dependant, 
   !      whereas array notation (e.g., [1,2,3]) is a Fortran 2003 feature.  

   use FunctionsModule, only: DoSomething  !This function performs any operation on the integer 
                                           !input and returns its integer result.

   implicit none

   integer, parameter :: m = 3, n = 3
   integer, pointer :: p(:)=>null(), q(:,:)=>null()
   integer, target :: A(:,:)
   integer ios = 0

   allocate(A(1:m, 1:n), q(1:m, 1:n), stat = ios)
   if (ios /= 0) stop
 
   !Assign the matrix
   !A = [[1   4   7]
   !     [2   5   8]
   !     [3   6   9]]
   A = reshape([(i, i = 1, m*n)], [m, n])
   q = A

   !p will be associated with the first column of A
   p => A(:, 1)

   !This operation on p has a direct effect on matrix A
   p = p ** 2

   !This will end the association between p and the first column of A
   nullify(p)

   !Matrix A becomes:
   !A = [[1  4  7  ]
   !     [4  5  8  ]
   !     [9  6  9  ]]
   write(*, '("Matrix A becomes:",/,"A = [",<m>("[",<n>(i1,2x),"]",/,)"]")') ((A(i, j), j = 1, n), i = 1, m)

   !Perform some array operation
   q = q + A   

   !Matrix q becomes:
   !q = [[ 2   8  14  ]
   !     [ 6  10  16  ]
   !     [12  12  18  ]]
   write(*, '("Matrix q becomes:",/,"q = [",<m>("[",<n>(i2,2x),"]",/,)"]")') ((q(i, j), j = 1, n), i = 1, m)

   !Use p as an ordinary array
   allocate (p(1:m*n), stat = ios)

   !Perform some array operation
   p = [((DoSomething(a(i, j) + b(i, j)), i = 1, m), j = 1, n)]

   write(*, '(<m*n>(i1,4x,"p[",i1,"] = ",i5))') (i, p(i), i = 1, m * n)

   deallocate(A, p, q, stat = ios)
   if (ios /= 0) stop

end program Test

Retro FORTRAN

A retro example of a FORTRAN IV (as it was called in 1968) program deck is available on the IBM 1130 page including the IBM 1130 DM2 JCL required for compilation and execution.

A curious feature common in early FORTRAN was the "3-way go to" statement (See GOTO). It was known as the "Arithmetic IF Statement". An example would resemble:

    IF (X - Y) 100, 200, 300

The 3 numbers are line numbers. If one translated this into a more modern version of FORTRAN, the logic of this would resemble:

  if (x - y < 0) goto 100
  if (x - y == 0) goto 200
  if (x - y > 0) goto 300 

Mentally one was often taught to view them as:

  if (x < y) goto 100
  if (x == y) goto 200
  if (x > y) goto 300     

For "greater than or equal" or "less than or equal", two goto targets would be the same. An alternative example that makes no use of the obsolete goto feature is:

  select case(x - y)
     case(:-1)
        !goto 100 code
     case(0)
        !goto 200 code
     case(1:)
        !goto 300 code
  end select

The standard FORTRAN joke

"GOD is REAL (unless declared INTEGER)." The joke works because, in the absence of an IMPLICIT declaration, variables beginning with the letters I through N were automatically considered to be integers, while A through H and O through Z were considered to be real numbers.

Another joke circa 1980 following the definition of FORTRAN 77 was "What will the language of the year 2000 look like? ... Nobody knows but it will be called FORTRAN."

References

General:

  • McCracken, Daniel D. (1961). A Guide to Fortran Programming. Wiley. {{cite book}}: Cite has empty unknown parameter: |coauthors= (help)
  • McCracken, Daniel D. (1965). A Guide to Fortran IV Programming. Wiley. {{cite book}}: Cite has empty unknown parameter: |coauthors= (help)
  • Metcalf, Michael (2004). Fortran 95/2003 Explained. Oxford University Press. {{cite book}}: Unknown parameter |coauthors= ignored (|author= suggested) (help)
  • Nyhoff, Larry (1995). FORTRAN 77 for Engineers and Scientists with an Introduction to FORTRAN 90 (4th Edition ed.). Prentice Hall. ISBN 013363003X. {{cite book}}: |edition= has extra text (help); Unknown parameter |coauthors= ignored (|author= suggested) (help)

Standards documents:

  • ANSI X3.198-1992 (R1997). Title: Programming Language "Fortran" Extended. Informally known as Fortran 90. Published by ANSI.
  • ISO/IEC 1539-1:1997. Title: Information technology - Programming languages - Fortran - Part 1: Base language. Informally known as Fortran 95. There are a further two parts to this standard. Part 1 has been formally adopted by ANSI.
  • ISO/IEC 1539-1:2004. Title: Information technology -- Programming languages -- Fortran -- Part 1: Base language. Informally known as Fortran 2003.

General

Program repositories

Proprietary compilers

Free software compilers

Online books

Template:Major programming languages small