Fortran Basics
Fortran Basics
Declaration: 6 6
−10 myint10
(minimum range)
integer myint
compiler barfs if KIND
double precision y
number unavailable
but beware constants
works OK, but not change only one line to
recommended convert all objects
implementation dependency encapsulation for re-use also
possible
©2006-8 LRZ 2
Fortran Type System:
Intrinsic types (2)
KINDS of reals
integer, parameter :: rk = selected_real_kind(12,100)
real(rk) :: y
:
y = 3.14_rk
character, dimension(20) :: line
character(len=20) :: line ! this is a scalar
line = 'give me a very long line' ; write(6, *) line
©2006-8 LRZ 5
Fortran Type System
Derived types (1)
©2006-8 LRZ 6
Fortran Type System
Derived types (2)
©2006-8 LRZ 7
Fortran Type System
Derived types (3)
Assignment
default is to copy all components -
type (body) :: earth
type (body), allocatable :: planets(:)
:
earth%mass = ...
: ! initialize all components
allocate(planets(8))
planets(3) = earth
nested derived types are treated recursively
see later slide
types with dynamic components need special attention
treated in a separate section of this talk
©2006-8 LRZ 8
Fortran Type System
Derived types (4)
©2006-8 LRZ 10
Manipulating array sections:
Vector subscripts and the cshift() intrinsic
Can be ... v
injective
many-one (as above) ... vs
Restrictions:
many-one not on left hand consistency of type and
side of an assignment shape required
actual subroutine can also specify an array
argument: dummy may not of integers as second
be intent(out|inout) argument
©2006-8 LRZ 11
What can we do with all this?
©2006-8 LRZ 12
Fortran Module concept:
Definition
©2006-8 LRZ 13
Fortran Module concept:
Example: Storage Pool (1)
module ocean
implicit none
real, private, save, allocatable :: ocean_t(:,:,:)
contains
subroutine ocean_init_t(n) temperature
integer, intent(in) :: n(3)
allocate(ocean_t(n(1),n(2),n(3))) ! check status etc.omitted
end subroutine ocean_init_t
subroutine ocean_set_t(i,j,k,val)
integer, intent(in) :: i,j,k
real, intent(in) :: val
ocean_t(i,j,k) = val
end subroutine ocean_set_t
! analogous: ocean_get_t() and further calls
end module ocean
©2006-8 LRZ 14
Fortran Module concept
Storage pool (2): Explanations
©2006-8 LRZ 15
Fortran Module concept: ocean
real :: x
myprog
:
call ocean_init_t((/34,34,22/))
ocean_t(3,6,2) = 1.4 ! will fail to compile
call ocean_set_t(3,6,2,1.4) ! this is OK
call ocean_set_t(3,6,2.0,1.4) ! will fail to compile
call ocean_get_t(3,6,2,x)
write(6, *) x ! will write 1.4 to unit 6
:
end program
©2006-8 LRZ 16
Fortran Module concept:
Using the module (2)
©2006-8 LRZ 17
Fortran Module concept:
A technical aspect
©2006-8 LRZ 18
Fortran Module concept:
Module procedures as methods (1)
module mod_foo function foo_create(this,...)
implicit none type(foo), ... :: this
private :
public :: foo_create, & end function foo_create
foo_destroy, & subroutine foo_destroy(...)
foo_xxx :
type, public :: foo end subroutine
private function foo_xxx(x) result(y)
integer :: len type(foo), ... :: x
real, ... :: stuff logical :: y
end type :
contains end function foo_xxx
! continued to the right end module foo
©2006-8 LRZ 19
Fortran Module concept:
Module procedures as methods (2)
©2006-8 LRZ 20
Fortran Module concept:
diagrammatic representation
class Foo2 : public Foo {
private:
type, public :: foo2 string name_;
private public:
! aggregation of foo Foo2() : name_(NULL) {};
type(foo) :: foo Foo2(int, float *, string &);
character(len=10) :: name virtual void print();
end type };
©2006-8 LRZ 21
Specifying intent:
Letting the compiler help you
©2006-8 LRZ 22
Interfaces (1)
©2006-8 LRZ 23
Interfaces (2): Overloading and generics
module mod_foo
Situation:
private
have (set of) various public :: create
types
: ! define public types foo, foo2
may be intrinsic or derived interface create
have a well-defined set module procedure &
of operations foo_create, foo2_create
working in the same manner for end interface
each member of the set contains
uniform usability desired function foo_create(x, ...)
type(foo) :: x
define a generic interface
:
overloads specific names
end function
allows to use a single
function foo2_create(x, ...)
method name for each
type(foo2) :: x
member of the set
:
e.g., static polymorphism (only
end function
object argument varies)
end module mod_foo
©2006-8 LRZ 24
Interfaces (3): Using generic calls
©2006-8 LRZ 25
Diagrammatic representation
for generic calls
mod_foo mod_3
create() create()
©2006-8 LRZ 26
Interfaces (4): Operator overloading
©2006-8 LRZ 28
Interfaces (6): Optional arguments cont'd
present() intrinsic
Client use:
logical function
require keyword call
type(par_type) :: param_def starting with first
: optional
param_def = ... ! set default
also for non-optionals coming
if (present(param)) then
param_def = param after first optional
! may need overloaded ! possible calls are:
! assignment call foo_calc(this)
end if call foo_calc(this, func=f, param=p)
call foo_calc(this, param=p, func=f)
function parameters call foo_calc(this, param=p)
may not reference at all if call foo_calc(this, func=f)
not present
undefined
can hand on non-present suggests programming style: all
need for check only optionals to the end of the
postponed argument list
©2006-8 LRZ 29
Concluding remarks on explicit interfaces
Recommendations
for software engineering
when using modules
defining a naming scheme
default attributes to choose
handling global variables
elimination of COMMON and EQUIVALENCE
function / subroutine arguments
©2006-8 LRZ 31
Recommendations:
Use a naming scheme (1)
Module:
defines internal name space for compiler
typical mangling: foo_MP_foo_create for method foo_create
name space separation mostly unavailable to client
same (global) name (type definition, object, module procedure) may occur multiple times,
but not be referenced via use association (only clauses and/or renaming can help –
see following slides)
compiler will refuse compilation or linking if this occurs
exceptions: generic interfaces / operator overloading
©2006-8 LRZ 33
Recommendations:
What to put into every module
module xyz blanket save statement
use .. ! whatever needed may use in module
implicit none declaration section
save values of uninitialized globals otherwise
private not guaranteed to be preserved if
... module not used by main program
end module xyz better alternative:
use xyz, only :
remove implicit typing
in main program, or
compiler enforces strong
typing save attribute on objects, or
blanket private initialize objects
sets default accessibility but not in subroutines
all exported entities need use save attribute ...
explicit public attribute and use with care
beware side effects e.g., in recursive
subroutines!
©2006-8 LRZ 34
Global objects (1)
Example: counting objects
add global variable count C++: static member variable
module mod_foo class Foo {
: public:
public :: ..., get_count Foo() : ...;
integer, private, save :: & Foo(int, float *);
count = 0 :
: protected:
contains static int count;
function foo_create(this,...) int len_;
: private:
count = count + 1 float *stuff_; };
end function foo_create
! destructor must decrement #include “Foo.h“
integer function get_count() int Foo::count = 0;
get_count = count
end function Foo::Foo() {
: count += 1;
end module }
// same with all other constr.
©2006-8 LRZ 35
Global variables (2) ... and don't forget to switch
Threading issues on OpenMP everywhere!
©2006-8 LRZ 36
Global variables (3)
migrating COMMON blocks
©2006-8 LRZ 37
Recommendations:
The EQUIVALENCE statement
transfer(source, mold[, size])
no explicit interface
module procedure
not as optimizable
©2006-8 LRZ 40
A case study:
Function arguments and threading (1)
©2006-8 LRZ 41
A case study:
Function arguments and threading (2)
Discrepancy:
interface required by vendor
real(dk) function arg_fun(x)
real(dk), intent(in) :: x
end function
subroutine user_fun(x, n, p, r)
real(dk), intent(in) :: x, p
integer, intent(in) :: n
real(dk), intent(out) :: r
end function
©2006-8 LRZ 42
A case study:
Function arguments and threading (3)
©2006-8 LRZ 43
A case study:
Function arguments and threading (4)
©2006-8 LRZ 44
Fortran pointers:
a contrast to C
©2006-8 LRZ 46
Fortran pointers:
definition variants
©2006-8 LRZ 47
Fortran pointers:
pointer assignment and allocation
©2006-8 LRZ 48
Notes (1): Some differences between
the pointer and allocatable attributes
subroutine do_stuff(...,r,...) subroutine do_stuff(...,r,...)
real, target :: r real, target :: r
: :
real, pointer :: a_loc(:) real, allocatable :: a_loc(:)
real, pointer :: s_loc ! real, allocatable :: s_loc
allocate(a_loc(...)) allocate(a_loc(...))
s_loc => r ! s_loc = r
: :
if (associated(a_loc)) then if (allocated(a_loc)) then
: :
end if end if
deallocate(a_loc) ! deallocate(a_loc)
end subroutine end subroutine
©2006-8 LRZ 49
Notes (2)
Pointers to arrays
„=“ assignment:
assume xx is a type with static components
could also be intrinsic type
type (xx), pointer :: p2
type (xx), target :: tt
:
Intel compiler:
p_xx => tt check pointer option
: should identify incorrect target
allocate(p2) assignments at run time
p2 = p_xx
target of p_xx is copied to target of p2
i.e. both left and right hand sides are dereferenced
both p_xx and p2 must be associated with a target
types with dynamic components: to be discussed later
©2006-8 LRZ 51
Fortran pointers:
handling subroutine arguments
Actual Dummy Argument
Argument object pointer target
usually by reference, pointer assoc. with
copy-in/copy-out dummy argument
object allowed, not allowed becomes undefined
no-alias assumption on return
©2006-8 LRZ 53
Derived data types
with dynamical components
Motivations:
In practice, the size of object (array) components is often
unknown at compile time
Want to implement information structures like lists and trees
may need to reference type recursively (or in a multiply recursive manner) within a type
definition
(potential) Issues:
memory management: prevent memory leaks
type :: cluster
type :: list_xx
integer :: num_bodies = 0
type(xx) :: xx
real, allocatable :: &
type(list_xx), pointer :: &
mass(:) ! must be array
next => null()
:
end type
end type
©2006-8 LRZ 54
Types with pointer components:
Assignment rules extended
Suppose we have
type(list_xx) :: l1, l2
type(xx) :: o_xx
o_xx = ...
l1%xx = o_xx
allocate(l1%next)
©2006-8 LRZ 55
Types with pointer components
Structure constructors
type(list_xx) :: l1
type(list_xx), target :: l2
l2 = list_xx(xx(...), null())
l1 = list_xx(xx(...), l2)
©2006-8 LRZ 56
Types with allocatable components:
Assignment rules extended
type(cluster) :: c1, c2 type(cluster) :: c1, c2
: :
c1%num_bodies = 5
allocate(c1%mass(5)) c1 = cluster(5, (/ ... /))
c1%mass = (/ ... /)
: :
c2 = c1 c2 = c1
©2006-8 LRZ 57
Further properties of
pointer vs. allocatable type components
auto-allocation no yes
©2006-8 LRZ 58
Allocating dynamic entities
within subroutines
Given the situation
program myprog
:
type(foo), allocatable :: f(:,:) pointer possible,
: but with performance issues
shape of allocatable typically generated within a subroutine
if values are to be read into array as well, a second subroutine
is needed. This is not very economical
allows following factory method:
subroutine alloc_foo_arr(f, unit)
type(foo), allocatable, intent(out) :: f(:,:)
integer, intent(in) :: unit
integer :: n, m
read(unit) :: n, m ! checks omitted
allocate(f(n, m), stat=...)
read(unit) :: f
end subroutine
©2006-8 LRZ 59
Rules for interfaces
using allocatable dummy arguments
©2006-8 LRZ 60
Some properties of functions (1)
Function result:
Assigning function results
is an object
is not a dummy argument type(foo) function foo_xx(...)
even if behaviour in some respects :
like an intent(out) argument end function foo_xx
:
exists temporarily only type(foo) :: res
until assignment to lhs of function res = foo_xx(...)
call completed
can be an object of any usually, standard
type assignment rules hold
can be an array beware validity of pointer
can be a pointer components
can be allocatable assignment may have
explicit interface been overloaded
needed for most of the lhs might even be different type
above than rhs
©2006-8 LRZ 61
Some properties of functions (2):
functions with pointer result
©2006-8 LRZ 62
Some properties of functions (3):
functions with allocatable result
©2006-8 LRZ 63