IntroFortran Handout
IntroFortran Handout
Fortran as a language
– look and feel
– from code to program
Variables and operators
– declare, assign
– arrays
1 2
3 4
Short history of Fortran Short history of Fortran
John W. Backus et al (1954): The IBM Mathematical Fortran 2003 (2004): a major revision, adding e.g. object-
Formula Translating System oriented features, C-bindings
Early years development: Fortran II (1958), Fortran IV – ”Fortran 95/2003” is the current de facto standard
(1961), Fortran 66 & Basic Fortran (1966) The latest standard is Fortran 2008 (2010): a minor
Fortran 77 (1978) revision
Fortran 90 (1991) a major revision and Fortran 95 (1997) – Most notable addition: Fortran coarray syntax
a minor revision to it – Compiler support nearly complete
– The next revision: Fortran 2015
5 6
source code Compile and link in one go, execute the binary
(.f, .F, .f90, .F90) gfortran main.f90 -o foo
./foo
INCLUDE
files compiler output
In more complex cases (multiple sources)
compiler
(optional) – Compile each source code file (.f90) into an object file (.o)
modules
object code gfortran -c main.f90
gfortran -c sub.f90
(.o, .so)
– Link object files into a binary and execute the binary
libraries linker output gfortran -o foo main.o sub.o
linker
(.a, .so) (optional) ./foo
Variables
Variables must be declared at the
integer :: n0
beginning of the program or
procedure where they are used
real :: a, b
real :: r1=0.0 the intrinsic data types in Fortran are
VARIABLES complex :: c
integer, real, complex, character and
logical
complex :: imag_number=(0.1, 1.0)
They can also be given a value at
character(len=80) :: place
declaration (not recommended)
character(len=80) :: name='james bond'
11 12
Operators Arrays
Arithmetic operators
real :: x,y
integer, parameter :: m = 100, n = 500
integer :: i = 10
x = 2.0**(-i) !power function and negation precedence: first integer :: idx(m)
x = x*real(i) !multiplication and type change precedence: second real :: vector(0:n-1) By default, Fortran indexing starts
x = x/2.0 !division precedence: second real :: matrix(m, n)
from 1
i = i+1 !addition precedence: third character (len=80) :: screen (24)
i = i-1 !subtraction precedence: third
Relational operators ! or
< or .lt. !less than
<= or .le. !less than or equal to integer, dimension(m) :: idx
== or .eq. !equal to
real, dimension(0:n-1) :: vector
/= or .ne. !not equal to
> or .gt. !greater than real, dimension(m, n) :: matrix
>= or .ge. !greater than or equal to character(len=80), dimension(24) :: screen
Logical operators
.not. !logical negation precedence: first
.and. !logical conjunction precedence: second
.or. !logical inclusive disjunction precedence: third
13 14
Conditionals (if-else)
15 16
Conditionals example Loops
2
program placetest
implicit none Three loop formats available in Fortran
1
logical :: in_square1, in_square2
real :: x, y
– integer counter (fixed number of iterations)
write(*,*) ’give point coordinates x and y’ – condition controlled (do until condition is false)
read (*,*) x, y
in_square1 = (x >= 0. .and. x <= 2. .and. y >= 0. .and. y <= 2.) – explicit exit statement
in_square2 = (x >= 1. .and. x <= 3. .and. y >= 1. .and. y <= 3.)
if (in_square1 .and. in_square2) then ! inside both
write(*,*) ’point within both squares’ do {control clause}
else if (in_square1) then ! inside square 1 only ! execute something again and again until stopped
write(*,*) ’point inside square 1’ end do
else if (in_square2) then ! inside square 2 only
write(*,*) ’point inside square 2’ ! where the control clause (optional) is either of the form
else ! both are .false. ! i=init_value, max_value, increment
write(*,*) ’point outside both squares’ ! or a condition to execute while true
end if ! while (condition)
end program placetest
17 18
19 20
Labels example Select case
program gcd
integer :: i select case statements
! computes the greatest common divisor, Euclidean algorithm
logical :: is_prime,
implicit none
integer :: m, n, t
test_prime_number matches the entries of a
write(*,*)’ give positive integers m and n :’
...
list against the case index
read(*,*) m, n
write(*,*)’m:’, m,’ n:’, n – Only one found match is
Labels can be given to select case (i)
positive_check: if (m > 0 .and. n > 0) then allowed
main_algorithm: do while (n /= 0) control structures and used case (2,3,5,7)
t = mod(m,n) in conjunction with e.g. exit is_prime = .true. – Usually arguments are
case (1,4,6,8:10)
m = n and cycle statements
is_prime = .false.
character strings or
n = t integers
case default
end do main_algorithm
is_prime=test_prime_number(i)
write(*,*) ’greatest common divisor: ’,m
end select
– default branch if no
else
write(*,*) ’negative value entered’
match found
...
end if positive_check
end program gcd
21 22
Summary
23
Outline
Structured programming
Modules
Procedures: functions and subroutines
Interfaces
24 25
Structured programming based on program sub-units Modularity means dividing a program into minimally
(functions, subroutines and modules) enables dependent modules
– Testing and debugging separately – Enables division of the program into smaller self-contained
– Re-use of code units
– Improved readability Fortran modules enable
– Re-occurring tasks – Global definitions of procedures, variables and constants
– Compilation-time error checking
The key to success is in well defined data structures and
scoping, which lead to clean procedure interfaces – Hiding implementation details
– Grouping routines and data structures
– Defining generic procedures and custom operators
26 27
What are procedures? Procedure declarations
Procedure is block of code that can be called from other Subroutine Function
code.
Declaration: Declaration:
Calling code passes data to procedure via arguments
subroutine sub(arg1, arg2,...) [type] function func(arg1,
Fortran has two types of procedures: arg2,...) [result(val)]
[declarations]
subroutines and functions [statements] [declarations]
[statements]
Subroutines pass data back via arguments end subroutine sub
call mySubroutine(arg1_in, arg2_in, arg_out) end function func
28 29
30 31
INTENT keyword Local variables in procedures
subroutine foo(x, y, z) Declares how formal argument Local variables can be declared in the procedure
implicit none
is intended to be used for subroutine foo(x, y)
real, intent(in) :: x
real, intent(inout) :: y transferring a value implicit none
real, intent(out) :: z – IN: the value of the real, intent(in) :: x
real, intent(out) :: y
argument is read-only i.e.
x = 10 ! compilation error
y = 10 ! correct cannot be changed integer :: i ! Local variable
z = y * x ! correct – OUT: the value of the ...
end subroutine foo
argument must be provided
Local variables are not visible outside the procedure
– INOUT (the default)
Compiler uses INTENT for error By default, local variables do not retain their values
checking and optimization through successive calls of the procedure
Improves readability of code
32 33
36 37
38 39
Visibility of module objects Internal procedures
Variables and procedures in modules can be PRIVATE or Each program unit (program/subroutine/function) may
PUBLIC contain internal procedures
– PUBLIC = visible for all program units using the module
(the default) SUBROUTINE mySubroutine
...
– PRIVATE will hide the objects from other program units CALL myInternalSubroutine
...
REAL :: x, y CONTAINS
PRIVATE :: x SUBROUTINE myInternalSubroutine
PUBLIC :: y ...
! Or END SUBROUTINE myInternalSubroutine
REAL, PRIVATE :: x END SUBROUTINE mySubroutine
REAL, PUBLIC :: y
40 41
42 43
External procedures Interfaces
Declared in a separate program unit For external procedures, interfaces determine the type
– Referred to with the EXTERNAL keyword and properties of arguments and return values
– Compiled separately and linked to the final executable Defined by an INTERFACE block:
Avoid using them within a program, module procedures interface
provide much better compile time error checking interface-body
External procedures are often needed when using end interface
– procedures written with different programming language The interface-body matches the subprogram header
– library routines (e.g. BLAS and LAPACK libraries) – position, rank and type of arguments
– old F77 subroutines – return value type and rank (for functions)
44 45
46 47
Global data and global variables Summary
Global variables can be accessed from any program unit Procedural programming makes the code more readable
Module variables with SAVE attribute provide and easier to develop
controllable way to define and use global variables – Procedures encapsulate some piece of work that makes
MODULE commons sense and may be worth re-using elsewhere
INTEGER, PARAMETER :: r = 0.42
INTEGER, SAVE :: n, ntot Fortran uses functions and subroutines
REAL, SAVE :: abstol, reltol
END MODULE commons – Values of procedure arguments may be changed upon
– Explicit interface: type checking, limited scope calling the procedure
Generally, use of global variables is not recommended Fortran modules are used for modular programming and
data encapsulation
48 49
Outline
Fortran arrays
50 51
declaration
INTEGER, DIMENSION(M) :: idx
– Fortran supports up to 15 dimensions REAL, DIMENSION(0:N-1) :: vector
REAL, DIMENSION(1:M,N) :: matrix
CHARACTER(len=80), DIMENSION(24) :: screen
TYPE(my_own_type), DIMENSION(1:10) :: object
52 53
Arrays in modern Fortran Array initialization
INTEGER :: m = 3, n = 4, i, j Array syntax in modern Arrays can be initialized
REAL :: A(m,n), x(n), y(m)
Fortran enables a neat – element by element
! Array syntax (and fast) way to express
y=0.0 – copied from another array
do j = 1, n linear algebra operations
y(:) = y(:) + A(:,j)*x(j) 𝑁 – using single line data initialization statements
end do
𝑦 = 𝐴𝑥 = 𝑎𝑗 𝑥𝑗 ⟺ – using the FORALL and WHERE statements
! or, equivalently, with explicit
𝑗=1
! loops 𝑥1
y=0.0 𝑦1 𝑎11 𝑎12 𝑎13 𝑎14
𝑥2
do j = 1, n 𝑦2 = 𝑎21 𝑎22 𝑎23 𝑎24
𝑥3
do i = 1, m 𝑦3 𝑎31 𝑎32 𝑎33 𝑎34
𝑥4
y(i) = y(i) + A(i,j)*x(j)
end do
end do
54 55
56 57
Array sections Array sections
! set elements from 3 to n+8 to 0 Fortran array syntax ! Conforming size of 3-by-10 When copying array
sub_vector(3:n+8) = 0 LHS(1:3, 0:9)=RHS(-2:0, 20:29)
enables accessing a subset sections, both left and
! access a subblock of a matrix of an array in an intuitive ! Error: LHS 2-by-10, RHS 3-by-10 right hand sides of the
a(2:500,3:300:3) = 4.0 LHS(1:2, 0:9) = RHS(-2:0, 20:29)
way: array sections assignment statement
! set every third element from 1 to must have conforming
! 3*n+1 to 1
every_third(1:3*n+1:3) = 1 dimensions
! set block [i-1:i+1,j-2:j+2] to k
diag_block(i–1:i+1,j–2:j+2) = k
58 59
60 61
Summary
62
Outline
63 64
65 66
Dynamic memory allocation: example Array intrinsic functions
subroutine sub (m) When automatic arrays Array intrinsic functions are built-in functions which can
use some_module, only : n
integer, intent(in) :: m are being used, no explicit apply various operations on the whole array at once
integer :: idx(0:m–1)
allocate or As a result another array or just a scalar value is returned
real :: mat(m , n) deallocate is needed
! implementation omitted A subset selection through masking is also possible
end subroutine sub
– Operations are performed for those elements where
corresponding elements of the mask are .true.
– Masking and use of array (intrinsic) functions is often
accompanied with use of forall and where array
statements
67 68
69 70
Array intrinsic functions:
Array intrinsic functions: any, all
minval, maxval, minloc, maxloc
any(l_array [, dim]) returns a scalar value of minval(array [,dim] [, mask]) returns the
.true. if any value in l_array is .true. minimum value of a given array
[, along the specified dimension] and [, under mask]
all(l_array [, dim]) returns a scalar value of maxval is the same as minval, but returns the maximum
.true. if all values in l_array are .true. value of a given array
minloc(array [, mask]) returns a vector of location(s)
[, under mask], where the minimum value(s) is/are
found
maxloc similar to minloc, but for maximums
71 72
73 74
Array intrinsic functions: Array intrinsic functions: example
dot_product, matmul, transpose
dot_product(a_vec, b_vec) returns a scalar dot integer :: l, m, n
real :: a(l,m), b(m,n), c(l,n)
product of two vectors real :: a_tr(m,l)
real :: v1(n), v2(n), dotp
matmul(a_mat, b_mat) returns a matrix containing
matrix multiply of two matrices ! transpose a matrix
a_tr = transpose(a)
transpose(a_mat) returns a transposed matrix of the ! compute matrix-matrix product c=a*b
input matrix c = matmul(a, b)
! compute dot product (v1,v2)=v2^t*v1
dotp = dot_product(v1, v2)
75 76
Array control statements forall and where are integer :: j, ix(10000) integer :: j
... real :: a(100,100), b(100), c(100)
commonly used in the context of manipulating arrays where (ix < 0)
forall and where can provide masked assignment of ... ! fill in diagonal elements
elsewhere forall (j=1:100) a(j,j) = b(j)
values using efficient vector operations ...
end where ! fill in lower bi-diagonal matrix
forall (j=2:100) a(j,j-1) = c(j)
77 78
Pointers to arrays Pointers to arrays
The pointer attribute enables to create array (or scalar) A pointer can refer to an already allocated memory
aliasing variables region
– Pointer variables are usually employed to refer to another Initialized to point to nothing
integer, pointer :: p_x(:) => null()
array or an array section integer, target :: x(1000)
...
A pointer variable can also be a sole dynamic variable p_x => x Pointers provide a neat way for array
itself p_x => x(2 : 300) sections
p_x => x(1 : 1000 : 5)
– Not recommended; use the allocatable attribute ...
instead and employ pointer variables for aliasing only p_x(1) = 0
This would also change x(1) to 0
nullify(p_x)
Note for C programmers: a "pointer" has a different
meaning in C and Fortran Disconnects p_x from x
79 80
81 82
Summary
83
Outline
84 85
86 87
Output formatting: miscellaneous The I0 and G0 format descriptors
With complex numbers provide format for both real and Dynamic sizing of REAL and INTEGER valued output
imaginary parts: – I0 appeared in F03 and G0 was introduced in F08
complex :: z
write (*,'(f6.3,2x,f6.3)') z ! real & imaginary parts
Output fields are left justified with all the unnecessary
leading blanks (and precision for REAL valued variables)
Line break and whitespace:
removed
write (*,'(f6.3,/,f6.3)') x, y ! linebreak between x,y
write (*,'(i3,2x,f6.3)') i, x ! 2 spaces between i & x integer :: i = 12345
real (kind=4) :: sp = 1.23e0
It is possible that an edit descriptor will be repeated a real (kind=8) :: dp = 1.234567890d0
specified number of times write(*,fmt='("<i=",i0,", reals=",2(g0,1x),">")') i,sp,dp
write (*,'(5i8)') ivec(1:5) Output is <i=12345, reals=1.230000 1.234567890000000 >
write (*,'(4(i5,2x,f8.3))') (ivec(j),zvec(j),j=1,4)
88 89
Fortran provides several intrinsic functions for handling Often it is necessary to filter out data from a given
character strings, such as character string
– trim(string) - removes blank spaces from the end of – Or to pack values into a character string
string Fortran internal I/O with READ & WRITE becomes
– adjustl(string)/adjustr(string) - moves blank now handy
spaces from the beginning/end of the string to the
Actual files are not involved at all
end/beginning of it
– len(string) - length of a string
– index(string, substring) - returns the starting
position of a substring within a string
90 91
Internal I/O: examples Opening and closing files: basic concepts
character(len=13) :: cl1
character(len=60) :: cl2
Writing to or reading from a file is similar to writing onto
integer :: njobs, istep a terminal screen or reading from a keyboard
! extract a number from character string Differences
cl1 = 'time step# 10'
read(cl1,fmt='(10x,i3)') istep – File must be opened with an OPEN statement, in which the
unit number and (optionally) the file name are given
! write data to a character string
njobs = 2014 – Subsequent writes (or reads) must to refer to the given
write(cl2,'(a,i0)') 'the number of jobs completed = ', njobs unit number
– File should be closed at the end
92 93
The syntax is (the brackets [ ] indicate optional keywords The first parameter is the unit number
or arguments) The keyword unit= can be omitted
open([unit=]iu, file='name' [, options]) The unit numbers 0, 5 and 6 are predefined
close([unit=]iu [, options])
– 0 is output for standard (system) error messages
For example
– 5 is for standard (user) input
open(10, file= 'output.dat', status='new')
close(unit=10, status='keep') – 6 is for standard (user) output
– These units are opened by default and should not be re-
opened nor closed by the user
94 95
Opening and closing a file File opening options
The default input/output unit can be referred with a star: status: existence of a file
write(*, ...) – 'old', 'new', 'replace', 'scratch', 'unknown'
read(*, ...)
position: offset, where to start writing
– Note that these are not necessarily the same as the stdout
and stdin unit numbers 6 and 5 – 'append'
If the file name is omitted in the OPEN, the file name will action: file operation mode
based on unit number being opened, e.g. for unit=12 – 'write', 'read', 'readwrite'
this usually means the filename ’fort.12’ (on UNIX- form: text or binary file
systems) – 'formatted', 'unformatted'
96 97
access: direct or sequential file access Use inquire statement to find out information about
– 'direct', 'sequential', 'stream', – file existence
iostat: error indicator, (output) integer – file unit open status
– non-zero only upon an error – various file attributes
err: the fortran label number to jump upon an error The syntax has two forms, one based on file name, the
recl: record length, (input) integer other for unit number
inquire(file='name', options ...)
– for direct access files only
inquire(unit=iu, options ...)
– warning (check): may be in bytes or words
98 99
File opening: file properties File opening: file properties example
100 101
Writing to and reading from a file is done by giving the Text or formatted files are
corresponding unit number (iu) as a parameter : – Human readable
write(iu,*) str The star format (*) indicates list- – Portable i.e. machine independent
write(unit=iu, fmt=*) str directed output (i.e. programmer does
read(iu,*) str not choose the input/output styles) Binary or unformatted files are
read(unit=iu, fmt=*) str
– Machine readable only, generally not portable
Formats and other options can be used as needed – Much faster to access than formatted files
If keyword 'unit' is used, also the keyword 'fmt' must be – Suitable for large amount of data due to reduced file sizes
used – Internal data representation used for numbers, thus no
– Note: 'fmt' is applicable to formatted, text files only number conversion, no rounding of errors compared to
formatted data
102 103
Unformatted I/O Stream I/O
A binary file write adds extra record delimiters (hidden
Write to a sequential binary file from programmer) to the beginning and end of records
real :: rval
character(len=60) :: string In Fortran 2003 using access method 'stream' avoids this
open(10, file='foo.dat', form='unformatted') and implements a C-like approach
write(10) rval
write(10) string It is recommended to use stream I/O
close(10)
Create a stream (binary) file
No format descriptors allowed real :: dbheader(20), dbdata(300)
Reading similarly open(10,file='my_database.dat', access='stream')
write(10) dbheader
read(10) rval write(10) dbdata
read(10) string close(10)
Reading similarly
104 105
Summary
Input/Output formatting
Internal I/O
Files: communication between a program and the
outside world
– Opening and closing a file
– Data reading & writing
Use unformatted (stream) I/O for all except text files
106
Built-in data types in Fortran
107 108
Derived data type is a data structure composed of built- For real-world applications, using only intrinsic types is
in data types and possibly other derived data types often insufficient
– Equivalent to structs in C programming language It is beneficial to group the data together as larger
Derived type is defined in the variable declaration section objects
of programming unit – Code becomes easier to read and maintain
– Not visible to other programming units – Cleaner interfaces
– Unless defined in a module and used via the use clause, – Encapsulation of data
which is most often the preferred way Variables used in the same context should be grouped
together using modules and derived data types
109 110
Derived type declaration Derived type declaration
111 112
Derived types can contain other derived types as Array of Structures Structure of Arrays
components type point type point
type moleculetype real :: x, y, z real, allocatable :: x(:)
type(particletype), allocatable :: atoms(:) end type point real, allocatable :: y(:)
real :: mu real, allocatable :: z(:)
type(point), allocatable :: points
end type moleculetype end type point
... type(point) :: points
type solvent allocate(points(N))
type(moleculetype), allocatable :: fluid(:)
complex :: epsilon allocate(points%x(N), &
points%y(N), &
end type solvent
points%z(N))
Access as
beverage % fluid(1) % atoms(1) % x = 0.75
113 114
Data structures: memory layout Summary
Array of Structures Structure of Arrays Derived data types enables grouping of data to form
integer :: i, j integer :: i, j
logical objects
real :: dist(4,4) real :: dist(4,4)
do i = 1, 4 do i = 1, 4 A Fortran program becomes more readable and modular
do j = i, 4 do j = i, 4
dist(i,j) = sqrt( & dist(i,j) = sqrt( & with sensible use of derived data types
(points(i)%x-points(j)%x)**2 + (points%x(i)-points%x(j))**2 +
(points(i)%y-points(j)%y)**2 + (points%y(i)-points%y(j))**2 + Handling of complex data structures such as linked lists
(points(i)%z-points(j)%z)**2) (points%z(i)-points%z(j))**2)
end do end do or binary trees becomes more manageable with use of
end do Memory layout end do Memory layout
derived types
0 0
Enables the use of object oriented programming
concepts
points(i)%x points(i)%y points(i)%z points%x(:) points%y(:) points%z(:)
115 116
Outline
Generic procedures
Command line arguments
Environment variables
Executing commands
Useful features
117 118
Procedures which perform similar actions but for MODULE swapmod PROGRAM switch
IMPLICIT NONE USE swapmod
different data types can be defined as generic INTERFACE swap IMPLICIT NONE
procedures MODULE PROCEDURE swap_real, swap_char CHARACTER :: n,s
END INTERFACE REAL :: x,y
Procedures are called using the generic name and CONTAINS n = 'J'
SUBROUTINE swap_real(a, b) s = 'S'
compiler uses the correct procedure based on the REAL, INTENT(INOUT) :: a, b x=10
REAL :: temp y=20
argument number, type and dimensions temp = a; a = b; b = temp PRINT *,x,y
END SUBROUTINE PRINT *,n,s
– Compare with ”overloading” in C++ SUBROUTINE swap_char(a, b) CALL swap(n,s)
CHARACTER, INTENT(INOUT) :: a, b CALL swap(x,y)
Generic name is defined in INTERFACE section CHARACTER :: temp PRINT *,x,y
temp = a; a = b; b = temp PRINT *,n,s
END SUBROUTINE END PROGRAM
END MODULE swapmod
119 120
Overloading operators Operator overloading example
Parameters to a program are very often given to Access separate command line arguments
programs as command line arguments get_command_argument(number[,value][,length][,status])
– Input file(s), modify program behavior, etc. – number is of type integer and denotes which argument to
get
Fortran 2003 has a standardized method for reading
command line arguments – value is of type character string and contains the value of
the requested argument on return (optional)
– get_command_argument and
– length is of type integer and contains the length of the
command_argument_count
requested argument on return (optional)
To access the whole command line, use
– status is of type integer. On successful return status is
– get_command 0, -1 if value was too short to contain actual argument and
1 if argument could not be returned (optional)
123 124
Command line arguments … Command line input
125 126
Access the whole command line Besides command line arguments, environment variables
call get_command(command[,length][,status]) are a common way to modify program behaviour
– command is of type character string and contains the value Fortran 2003 has a standardized method for accessing
of the command line on return. values of environment variables
– length is of type integer and contains the length of the
command line on return (optional)
– status is of type integer. On successful return status is
0, -1 if value was too short to contain actual argument and
1 if argument could not be returned (optional)
127 128
Environment variables Environment variables: example
program environment
Access a value of an environment variable implicit none
call get_environment_variable(name,value[,length] character(len=256) :: enval
[,status][,trim_name]) integer:: len,stat
– name is of type character string and contains the name of the ! extract hostname
requested variable call get_environment_variable('hostname',enval,len,stat)
if (stat == 0) write (*,'(a,a)') 'host=', enval(1:len)
– value is of type character string and contains the value of the
requested variable ! extract user
call get_environment_variable('user',enval,len,stat)
– length is of type integer and contains the length of the if (stat == 0) write (*,'(a,a)') 'user=', enval(1:len)
requested variable on return (optional) end program environment
– status (optional)
– trim_name is of type logical and sets if trailing blanks are
allowed in variable names or not (optional)
129 130
133 134