Introduction to Fortran
Ed Kornkven
PHYS F693
Spring 2004
Resources
• http://www.csl.mtu.edu/cs2911/www/FortranReview.htm
– The source of these notes - some bugs
• http://www.fortran.com/fortran/tutorials.html
– List of Fortran Tutorials
– The Manchester Computer Centre materials are a
nice set of notes but unfortunately in PostScript
format
• Fortran 90 for Engineers and Scientists, Larry Nyhoff and
Sanford Leestma, Prentice-Hall, 1997
1
Source Form
• Max. line length of 132 characters
• Case insensitive
• Identifiers
– Begin with alpha
– Contain alphanumeric and underscore
– Max. length of 31 characters
• Exclamation begins comment
Source Form (cont.)
• Ampersand (&) at end of line
indicates continuation
• Semicolon separates multiple
statements on a line
• Statement labels are integers
2
Source Form (cont.)
PROGRAM name
! Exclamation mark indicates comment
IMPLICIT NONE ! Don’t implicitly declare variables
! declarations follow and must precede use
:
CONTAINS
! Internal subroutines and functions follow
:
END PROGRAM name
Prototype Code
PROGRAM main
IMPLICIT NONE
REAL :: a=6.0, b=30.34, c=98.98
REAL :: mainsum
mainsum = add()
CONTAINS
FUNCTION add()
REAL :: add ! a,b,c defined in 'main'
add = a + b + c
END FUNCTION add
END PROGRAM main
3
Declaration of Primitive Types
INTEGER :: i, j = 2
! do not forget the double :: without spaces
REAL :: a, b, c = 1.2
LOGICAL, PARAMETER :: debug = .true.
! Parameter indicates a constant
CHARACTER(20) :: name = "John"
IMPLICIT NONE ! always use
Assignment Statement
• variable = expression
I = 3**2
J = MOD(15, 2)
A = 'Quotes delineate character literal'
B = "Can also use double quotes.”
4
Operators and Their Priority
Arithmetic
Operator Symbol Associativity
Exponentiation ** Right-to_left
Multiplication
*/ Left-to-right
and division
Addition and
+- Left-to-right
subtraction
Some Intrinsic Functions
RETURN
FUNCTION DESCRIPTION ARG TYPE TYPE
ABS(x) Absolute value of x INTEGER INTEGER
REAL REAL
SQRT(x) Square root of x REAL REAL
SIN(x) Sine of x radians REAL REAL
COS(x) Cosine of x radians REAL REAL
TAN(x) Tangent of x radians REAL REAL
EXP(x) ex REAL REAL
LOG(x) REAL REAL
5
Conversion Functions
RETURN
FUNCTION DESCRIPTION ARG TYPE TYPE
INT(x) Integer part of x REAL INTEGER
NINT(x) Nearest integer to x REAL INTEGER
Greatest integer < or =
FLOOR(x) REAL INTEGER
to x
FRACTION(x) Fractional part of x REAL INTEGER
REAL(x) Converts x to REAL INTEGER REAL
MAX(x1,.., xn) Max of x1,.. xn INTEGER INTEGER
REAL REAL
MIN(x1,.., xn) Min of x1,.. xn INTEGER INTEGER
REAL REAL
MOD(x,y) x - INT( x/y) * y INTEGER INTEGER
Input/Output
• READ(integer_unit_number, format-format_line)
– Fortran “unit number” functions like a file
descriptor in C
– Formats are powerful and complex like they are in
C
• READ(*,*) a, b, c ! asterisks for default values
– Traditional default unit numbers are
• 5 = stdin
• 6 = stdout
• PRINT format,
• PRINT *, 'hi’
– Shortcut for WRITE(*,*)
6
Input/Output
• Full treatment of I/O is important for
scientific computing but not possible
here -- e.g.:
– Binary and text files
– Sequential and direct access
– On-the-fly conversions between different binary
formats
– Setting record lengths, block sizes, etc.
– Special instructions for asynchronous I/O
Logical Operators and
Precedence
TYPE OPERATOR ASSOCIATIVITY
Relational < <= > >= == /=
(old style) .LT. .LE. .GT. None
.GE. .EQ. .NE.
Logical .NOT. Right-to-left
.AND. Left-to-right
.OR. Left-to-right
.EQV. .NEQV. Left-to-right
7
IF Statements
• Single line form • Else-if form
IF ( logical-expr ) statement IF ( logical-expression )
THEN
• Multiple statement form statements
IF ( logical-expr ) THEN ELSE IF (logical-expression)
statements THEN
END IF statements
ELSE IF (logical-expression)
• If-else form THEN
IF ( logical-expr ) THEN statements
statements ELSE
ELSE statements
statements END IF
END IF
Selection
• SELECT CASE Statement
SELECT CASE (selector)
CASE (label-list-1)
statements-1
CASE (label-list-2)
statements-2
CASE (label-list-3)
statements-3
...........
CASE (label-list-n)
statements-n
CASE DEFAULT
statements-DEFAULT
END CASE
8
SELECT Labels
• A label has one of the following four
forms:
Label Meaning
:x all values less or equal x
x: all values greater or equal to x
x:y all values in the range of x and y
x the values of x itself
SELECT Example
SELECT CASE(index)
CASE(:0)
print *, "index is equal or less then zero"
CASE(1: maxIndex)
print *, "index is in range"
CASE( int(maxIndex/2) )
print *, "index is at mean"
CASE(maxIndex+1:)
print *, "index is greater the max"
END CASE
9
Iteration
• General DO-Loop w/ EXIT • Counting Loop
DO DO var=init-val ,final-val ,step-size
Statements-1 Statements
END DO
IF (Logical-Expr) EXIT
Statements-2
• Default step-size is 1
END DO
DO var=initial-value, final-value
Statements
• Nested DO-loop: END DO
Outer: DO
IF (expression-1) EXIT Outer • CYCLE: jump up to the top
Statements-1
of loop and increment (like
Inner: DO
IF (expression-2) EXIT Inner continue in C)
Statements-2
END DO Inner
Statements-3
END DO Outer
Iteration Examples
• Classic example • Another example
Sum = 0 READ(*,*) N
DO Count = 1, N Factorial = 1
READ*, Input DO I = 1, N
Sum = Sum + Input Factorial = Factorial * I
END DO END DO
Average = REAL(Sum) / REAL(N)
10
Obsolescent/Redundant
Loops
• Redundant WHILE loop
• Fortran 77 DO loops
DO WHILE(logical-expr)
DO 100 I=1, N statements
statements END DO
100 CONTINUE
• Equivalent to
DO
IF (logical_expr) EXIT
statements
END DO
Subprograms
• Subroutines • Functions
– Conceptually return a
– Don’t return a value
value, don’t modify
except by modifying arguments; but this is not
arguments enforced!
– Therefore, not typed and – Typed by return value; must
not declared be declared
– Arguments are passed – Arguments are passed by
by reference reference
– Invoked by CALL – Assign return value to
statement function name
– Invoked by name reference
11
Subroutine Example
SUBROUTINE swap(a,b)
IMPLICIT NONE ! Good habit
INTEGER, INTENT(INOUT):: a, b ! INTENT is optional
INTEGER:: tmp ! local
tmp = a
a = b
b = tmp
END SUBROUTINE swap
! Call with:
CALL swap(x,y) ! Call by reference!
Function Example
REAL FUNCTION fact(k)
IMPLICIT NONE
INTEGER, INTENT (IN) :: k
REAL :: f
INTEGER :: i
IF (k .lt. 1) THEN
fact = 0.0
ELSE
f = 1.0
DO i = 1, k
f = f * i
END DO
fact = f
END IF
END FUNCTION fact
12
More Fun With Functions
• Look, Ma! Fortran can do recursion!
– Just declare the routine to be recursive and
specify the result value
RECURSIVE REAL FUNCTION fact3(k) RESULT (fact)
IMPLICIT NONE
INTEGER, INTENT (IN) :: k
IF (k .lt. 1) THEN
fact = 0.0
ELSE IF (k .eq. 1) THEN
fact = 1.0
ELSE
fact = k * fact3(k-1)
END IF
END FUNCTION fact3
More Fun With Functions
• By default, variables declared inside a
subprogram have
– Local scope
– “Automatic” lifetime
• A local variable can be given a “static”
lifetime by either
– Initializing it
INTEGER :: keeper = 0
– Or giving it the SAVE attribute when declaring it
INTEGER, SAVE :: keeper
13
Expressions & Assignments
• Data types
– Implicit typing rules
• Operators
• Library functions
• Assignments
1-D Arrays
• Syntax
– type, DIMENSION ( extent ) :: name-1, name-2, ...
– type, DIMENSION( lower : upper) :: list-array-names
• Array operands and operators
– Initialization
A = (/ 1, 2, 3 /)
– Array expressions and assignments
A=B+C ! These operations are done
A = B * 3.14 ! element-wise
14
Array Example
REAL FUNCTION fact(k)
INTEGER, INTENT (IN) :: k
INTEGER, PARAMETER :: N = 8
REAL :: f ! Don’t use “fact” on RHS!
REAL :: precmp(N)=(/1.0,2.0,6.0,24.0,120.0,720.0,5040.0,40320.0/)
IF (k .lt. 1) THEN
fact = 0.0
ELSE IF (k .le. N) THEN
fact = precmp(k)
ELSE
f = precmp(N)
DO i = N+1, k
f = f * i
END DO
fact = f
END IF
END FUNCTION fact
Some Array Functions
FUNCTION RETURNS
MAXVAL(A) Maximum value in array A
MINVAL(A) Minimum value in array A
One Dimensional array of one
MAXLOC(A) element containing the location of
the largest element
One Dimensional array of one
MINLOC(A)
element containing the location of
the smallest element
SIZE(A) Number of elements in A
SUM(A) Sum of the elements in A
PRODUCT(A) Product of the elements in A
15
Dynamic Array Allocation
• Syntax
– type, DIMENSION(:), ALLOCATABLE :: list-of-array-names
– ALLOCATE(list, STAT = status-variable)
– DEALLOCATE( list, STAT= status-variable)
Dynamic Array Allocation
• Example
PROGRAM main
INTEGER, DIMENSION(:), ALLOCATABLE :: A
INTEGER :: aStatus, N
WRITE(*, '(1X, A)', ADVANCE = "NO") "Enter array size: "
READ *, N ! Try 1 billion on your PC!
ALLOCATE( A(N), STAT = aStatus )
IF (aStatus /= 0) STOP "*** Not enough memory ***"
PRINT*, ‘Array allocated with size ‘, N
DEALLOCATE(A)
PRINT*, ‘Array deallocated…’
END PROGRAM main
16
Multidimensional Arrays
• Syntax
– type, DIMENSION( dim1,dim2,…) :: list-array-names
– type, DIMENSION(:,:,…), ALLOCATABLE :: list-array-names
– ALLOCATE(array-name( lower1: upper1, lower2: upper2) ,
STAT = status)
• Examples
– INTEGER, DIMENSION(100,200) :: a
– INTEGER, DIMENSION(:,:), ALLOCATABLE :: a
Multidimensional Arrays
• Column-major ordering
– Suppose we have the declaration
INTEGER, DIMENSION(100,200) :: a
– The usual way of viewing a 2-D array reference is
• A(row,column) - first dimension is “rows”, second is “columns”
– Of course, computer memory is 1-D. How is virtual 2-
D array mapped to real memory?
• In Fortran, it is in column-major order -- I.e., column-by-column
• NB: C is row-major order!
– Yes, there are situations in which we care!
• Certain performance situations
• Interfacing Fortran and C
17
Multi-D Array Functions
FUNCTION RETURNS
Array of one less dimension containing the
MAXVAL(A,D) maximum values in array A along dimension D. If D
is omitted, maximum of the entire array is returned.
MINVAL(A,D) Like MAXVAL() but for minima
One Dimensional array of one element containing
MAXLOC(A)
the location of the largest element
MINLOC(A)
Like MAXLOC() but for smallest element
SIZE(A) Number of elements in A
Multi-D Array Fns (cont.)
FUNCTION RETURNS
Array of one less dimension containing the sums of
the elements of A along dimension D. If D is
SUM(A,D) omitted, the sum of the elements of the entire array
is returned.
Array of one less dimension containing the products
of the elements of A along dimension D. If D is
PRODUCT(A)
omitted, the product of the elements of the entire
array is returned.
Matrix product of A and B (provided result is
MATMUL(A,B)
defined)
18
Modules
• Modules - used to package
together
– Type declarations
– Subprograms
– Data type definitions
• Forms a library that can be used
in other program units
Module Syntax
• Module definition
MODULE module-name
IMPLICIT NONE
specification part
PUBLIC :: Name-1, Name-2, ... , Name-n
PRIVATE :: Name-1, Name-2, ... , Name-n
CONTAINS
internal-functions
END MODULE
• Module use - use the USE to use
USE module-name
19
New Fortran Features That
We Can’t Cover
• Pointers
• User-defined types and operations
• INTERFACE blocks
• KIND
• Others -- can you say “C++”?
Obsolescent & Redundant
Features
• Arithmetic IF
• PARAMETER
• DATA
• GO TO
• Computed GO TO
• COMMON blocks
• EQUIVALENCE
20
NEC/Cray SX-6
Architecture Overview
SX-6 Architecture
21
SX-6 Overview
• SX-6 Node
– 8 CPUs
– 64 GB Memory
• Performance
– 64 GFLOPS per
Node
• SUPER-UX
operating system
– 32- and 64-bit IEEE
SX-6 Programming
Environment
Fortran 90 √
C++ / C
SX-6
√
HPF √
Languages / Co-array Fortran
Programming UPC
Models Auto par. √
OpenMP √
MPI √
MPI-2 √ ("almost all")
SHMEM
22
CPU Performance Overview
SX-6 SV1ex X1
Vector pipes 8 2 8
Vector regs. 8 x 256 x 64 8 x 64 x 64 128 x 64 x 64
Clock (mHz) 500 500 800
Peak perf.
8 2 12.8
(GFLOPS)
Mem. BW
31.9 3.6 34.1
(GB/sec)
Earth Simulator - 40 TFlops
• 640 SX-6 cabinets
• x 8 Pes each
• = 40960 GFLOPS
• > combined 5
nearest competitors
“Real Performance”?
• SC 2002 Gordon Bell prize winner
• Sustained rates exceeding 25 TFLOPS
23
Compiling on SX-6
• Gateway machine
– rimegate.arsc.edu
– An SGI front end
– Fast compiles using SX cross-compilers
• SX-6
– rime.arsc.edu
– Limited disk space, no backups
• http://www.arsc.edu/support/howtos/usingsx6.html
Compiling on SX-6 (cont.)
• Summary
– Give Fortran source files a suffix of .f90
– Rime compile: f90 file.f90
– Rimegate compile: sxf90 file.f90
– Execute (must be on Rime!): ./a.out
– For compiler options: man {sx}f90
– NQS batch system
24
Compiling on SX-6 (cont.)
• Important compiler options
– -ew : 64-bit
– -Wf,”-pvctl fullmsg -L fmtlist” : listing details
– -pi : automatic inlining
SX-6 Source File Name
Defaults
Fixed Format Free Format
Preprocessor .f90
Invoked .f
.ftn
Preprocessor .F90
Not Invoked .F
.FTN
25