Modern Programming Languages: Fortran90/95/2003/2008
Modern Programming Languages: Fortran90/95/2003/2008
Why we need modern languages (Fortran/C++) How to write code in modern Fortran
Lars Koesterke
Texas Advanced Computing Center The University of Texas at Austin
March 5, 2012
Modern Programming Languages: Fortran90/95/2003/2008
This is an Intermediate Class
You You
know already one computer language understand the very basic concepts:
What is a variable, an assignment, function call, etc.? Why do I have to compile my code? What is an executable?
You (may) already know some Fortran You are curious about what comes next What are the choices? How to proceed from old Fortran (or C), to much more modern
languages like Fortran2003/2008 (and C++)?
Modern Programming Languages: Fortran90/95/2003/2008 Outline
Outline Motivation
Modern Fortran
Object-Oriented Programming: (Very) Short Version
Modern Programming Languages: Fortran90/95/2003/2008 Motivation
Why do we (have to) learn advanced languages?
Basic features (BASIC)
Variables Data containers for Integers, Reals, Characters ,Logicals
Arrays: Vectors ,Matrices
Basic operators arithmetic (+, , *, /) logical, lexical, etc. Control constructs if/else-if, case/switch, goto, ... Loops do/for, while/repeat, etc. I/O All languages provide sophisticated mechanisms for I/O
(ASCII, binary, streams): Not covered! Is that enough to write code? My answer: No!
Subprograms: subroutines and functions
they enable us to repeat operations on dierent data and to avoid code replication
Modern Programming Languages: Fortran90/95/2003/2008 Motivation
Starting with: Fortran77
basic language (BASIC): allows to write 500 lines of code w/ subprograms: we can do much, much better
Old Fortran (Fortran77) provides only the absolute Minimum! And these languages (Fortran77 and C) have aws:
Fortran77: No dynamic memory allocation (on the heap) common blocks, equivalence statements
old & obsolete constructs clunky style, missing blanks old (legacy) code is usually cluttered C: Call by value, no multidimensional arrays
Pointer (de)referencing everywhere, for no good reason
Fortran77 and C are simple languages and they are (kind-of) easy to learn
7
Modern Programming Languages: Fortran90/95/2003/2008 Motivation
If Fortran77 and C are so simple,
Why is it then so dicult to write good code?
Is simple really better?
Using a language allows us to express our thoughts (on a computer) A more sophisticated language allows for more complex thoughts I argue: Fortran77 and plain C are (way) too simple Basics + 1 plus the aws are not enough! We need better tools!
The basics without aws Language has to provide new (awless) features User has to avoid old (awed) features more language elements to get organized
= Fortran90/95/2003 and C++
Modern Programming Languages: Fortran90/95/2003/2008 Motivation
So, these languages (Fortran77 and C) are easy to learn?
... are you kiddin ? They are not!
We want to get our science done! Not learn languages! How easy/dicult is it really to learn Fortran77 and C? The concepts are easy: Variables, Arrays, Operators, If, Do, Subroutines/Functions
I/O Syntax Rules & regulations, the ne print Conquering math, developing algorithms, the environment: OS, compiler, hardware, queues, etc.
I/O details print to screen read/write from/to les from ASCII to binary from basic to ecient to parallel
parallel computing: MPI, OpenMP, CUDA, ... ... and the aws = simple things will be complicated
Invest some time now, gain big later!
Remember: so far, we have only the Basics + Functions/Subroutines
11
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Overview
Modern Fortran starts here!
Modern style Free format Attributes implicit none do, exit, cycle, case Single and double precision Fixing the aws Allocatable arrays Structures, derived types Module-oriented Programming internal subprograms private, public, protected contains use Explicit interfaces Optional arguments & intent Formula translation Array syntax, where and forall statement Extended & user-dened operators Functions: elemental, inquiry, mathematical Odds and Ends Fortran pointers (References) Command line arguments Environment variables Preprocessor Interoperability with C (binding) Performance considerations Object oriented programming
13
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Style
Free Format
Statement may start at the rst column (0132 characters) Exclamation mark (!) starts a comment (not in literal strings) Blanks are signicant: Not allowed in keywords or variables Continuation with an ampersand (&) as the last character Mulitple statements in one line separated by a semicolon (;)
Style example
program style print *, This statement starts in column 1 i = 5; j = 7 ! Two statements in one line ! Comment with an exclamation mark i = & ! Line with continuation j * j + j end
15
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Style
Blanks, blank lines, and comments
Use blanks, blank lines, and comments freely Use indentation
Good
program square ! This program calculates ... implicit none real :: x, x2 x = 5. x2 = x * x if (x == 13.) print *, Lucky end
Bad
program square x=5. x2=x*x if(x.eq.13)print*,Lucky end
17
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Style
Good
program square ! This program calculates ... implicit none integer :: i real :: x, x2 do i=1, 20 x = real(i) x2 = x * x if (x == 13.) print *, Lucky enddo end
Bad
program square do 100 i=1,20 x=i x2=x*x if(x.eq.13)print*,... continue end
100
19
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Style
Attributes Style example
program style integer real real, parameter real, dimension(100) real, dimension(:,:), allocatable
General form
:: :: :: :: ::
i, j x pi = 3.1415 array dyn_array_2d
integer :: name real, <attributes> :: name
attributes are:
parameter, dimension, allocatable, intent, pointer, target, optional, private, public, value, bind, etc.
21
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Style
Implicit none
Implicit type declaration
program implicit implicit none ! use to disable the default
Default type of undeclared variables:
All variables starting with the letter i, j, k, l, m, n are integers All other variables are real variables
Turn default o with: implicit none Strongly recommended (may not be right for everybody, though)
23
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Style
Loops: do, while, repeat do-Loop
do i=1, 100, 8 ! No label ! loop-variable, start, increment ... enddo
while-Loop
i = 0 do if (i > 20) exit i = i + 1 enddo
repeat-Loop
i = 0 do i = i + 1 if (i > 20) exit enddo
Use the exit statement to jump out of a loop
25
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Style
Loops: exit and cycle Exit anywhere
do i=1, 100 x = real(i) y = sin(x) if (i > 20) exit z = cos(x) enddo
exit: Exit a loop cycle: Skip to the end of a loop Put exit or cycle anywhere in the loop body Works with loops with bounds or without bounds
Skip a loop iteration
do i=1, 100 x = real(i) y = sin(x) if (i > 20) cycle z = cos(x) enddo
27
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Style
Nested loops: exit and cycle Exit Outer Loop
outer: do j=1, 100 inner: do i=1, 100 x = real(i) y = sin(x) if (i > 20) exit outer z = cos(x) enddo inner enddo outer
Skip an outer loop iteration
outer: do j=1, 100 inner: do i=1, 100 x = real(i) y = sin(x) if (i > 20) cycle outer z = cos(x) enddo inner enddo outer
Constructs (do, if, case, where, etc.) may have names exit: Exit a nested loop cycle: Skip to the end of an outer loop Put exit or cycle anywhere in the loop body Works with loops with bounds or without bounds
29
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Style
Case
integer :: temp_c ! Temperature in Celsius! select case (temp_c) case (:-1) write (*,*) Below freezing case (0) write (*,*) Freezing point case (1:20) write (*,*) It is cool case (21:33) write (*,*) It is warm case (34:) write (*,*) This is Texas! end select
case takes ranges (or one
element)
works also with characters read the ne-print
31
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Style
Variables of dierent kind values
integer :: i, my_kind real :: r ! ! ! ! ! ! Selection based on precision prints 4 4 (most compilers) select a real that has 15 significant digits prints 8
print *, kind(i), kind(r) my_kind = selected_real_kind(15) print *, my_kind
integer, parameter :: k9 = selected_real_kind(9) real(kind=k9) :: r r = 2._k9; print *, sqrt(r) ! prints 1.41421356237309
33
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Style
Variables of dierent kind values: The sloppy way
There are only 2(3) kinds of reals: 4-byte, 8-byte (and 16-byte) The kind-numbers are 4, 8, and 16 (most compilers!) Kind number may not be byte number! Selection based on the number of bytes :: :: :: :: :: x8 y8 x4 i4 i8 ! ! ! ! ! Real with 8 bytes (double precision) same, but not completely safe Real with 4 bytes (single precision) Integer single precision Integer double precision
real*8 real(kind=8) real*4 integer*4 integer*8
x8 = 3.1415_8 i8 = 6_8
! Literal constant in double precision ! same for an integer
real*8, real*4: works well with MPI Real8 and MPI Real4
35
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Style
Variables of dierent kind values
Do not use double in your denition double refers to something; its double of what? double precision, dble(...) Select appropriate precision at compile time: ifort -r4, ifort -r8 Compiler ag also elevates the unnamed constants :: x8, y8 :: x4, y4 :: i ! 3.1415 is an unnamed constant ! with -r8: 8 bytes ! Old style, using dble ! New style using the kind parameter
real*8 real*4 integer y8 = 3.1415
x4 = real(i) x8 = dble(i) x8 = real(i, kind=8)
37
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Fixing the Flaws
Fixing the Flaws
Allocatable arrays
exible size allocated on the heap The size of the stack is severely limited (default: 2 GB) Remedies are problematic (Intel: -mcmodel=medium -intel-shared) Always allocate large arrays on the heap! Large arrays always have to be allocatable (heap) arrays, even if you do not need the exibility to avoid problems with the limited size of the stack
Structures and derived types
Organize your data Compound dierent variables into one type
39
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Fixing the Flaws
Allocatable Arrays
Variables live on the heap (vs. stack for scalars and static arrays) Declaration and allocation in 2 steps Declare an array as allocatable,
use colons (:) as placeholders
allocate/deallocate in the executable part Allocation takes time. Do not allocate too often.
program alloc_array real, dimension(:), allocatable :: x_1d real, dimension(:,:), allocatable :: x_2d ... read n, m allocate(x_1d(n), x_2d(n,m), stat=ierror) if (ierror /= 0) stop error ... deallocate(x)
! Attribute ! allocatable
! Check the ! error status! ! optional
41
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Fixing the Flaws
Structures and Derived Types
Declaration species a list of items (Derived Type) A Structure (a variable of a derived type) can hold variables of simple type (real, integer, character, logical, complex) arrays: static and allocatable other derived types A structure can be allocatable
program struct type my_struct ! Declaration of a Derived Type integer :: i real :: r real*8 :: r8 real, dimension(100,100) :: array_s ! stack real, dimension(:), allocatable :: array_h ! heap type(other_struct), dimension(5) :: os ! structure end type my_struct
43
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Fixing the Flaws
Declaration of a Structure
Variables of Derived Type program 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
45
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Fixing the Flaws
Example: Structures
program people type person character(len=10) real character(len=6) end type person we(1)%name = you%name we(2) = you :: name :: age :: eid ! Old style ! name, age, eid: arrays call do_this(name,age,eid) ! Reduce parameter list ! to one structure call do_this_smart(we)
type(person) :: you type(person), dimension(10) :: we you%name = John Doe ! Use (%) you%age = 34.2 ! to access you%eid = jd3456 ! elements
Need more data =
add a component to the derived type
47
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Module-oriented Programming
From Functions to Modules
Lets step back for a second: Why do we use Subprograms (Functions/Subroutines)? Subroutines and Functions serve mainly 3 purposes:
Re-use code blocks Repeat operations on dierent datasets
call do this(data1) call do this(data2) call do this(data3)
Hide local variables, so that the names can be re-used
subroutine do this(data) integer :: i, j ! Local variables, real :: x, y, z ! not accessible outside of the ! subprogram
49
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Module-oriented Programming
Modules are another, more exible tool to Hide Content
Modules may contain all kind of things
Derived Type declarations Variables and Arrays, etc. Parameters (named constants) Variables Arrays Structures Subprograms Subroutines, Functions other Modules Objects
Fortran 2008: Modules may contain Submodules. Will make using Modules even nicer. (Not implemented in Intel 12, yet)
51
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Module-oriented Programming
Example: Constants and Variables
module mad_science real, parameter :: pi = 3. & c = 3.e8 & e = 2.7 real :: r end module mad_science program go_mad ! make the content of module available use mad_science r = 2. print *, Area = , pi * r**2 end program
53
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Module-oriented Programming
Example: Type Declarations
module mad_science real, parameter :: pi = 3. & c = 3.e8 & e = 2.7 real :: r type scientist character(len=10) :: name logical :: mad real :: height end type scientist end module mad_science
55
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Module-oriented Programming
Example: Subroutines and Functions
Subprograms after the contains statement
module mad_science real, parameter :: pi = 3. type scientist character(len=10) :: name real :: height logical :: mad end type scientist contains subroutine set_mad(s) type(scientist) :: s s%mad = .true. end subroutine end module mad_science
program go_mad use mad_science type(scientist) :: you type(scientist), & dimension(10) :: we you%name = John Doe call set_mad(you) we(1) = you we%mad = .true. you%height = 5. area = you%height * pi
57
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Module-oriented Programming
Example: Public, Private Subroutine
module mad_science private public :: set_mad contains subroutine reset(s) s%name = undef s%mad = .false. subroutine set_mad(s) type(scientist) :: s call reset(s) s%mad = .true.
A module becomes accessible when
the module is used
Even more control: public and
private components
Default is public: all public content
can be used from the outside of the module, i.e. by subprograms that use the module
private items are only accessible
from within the module
Example: subroutine reset is only
accessible by subroutine set mad
59
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Module-oriented Programming
Example: Public, Private Variables
module mad_science private public :: swap real, dimension(100) :: scratch contains subroutine swap(x, y) real, dimension(100) :: x, y scratch(1:100) = x(1:100) x(1:100) = y(1:100) y(1:100) = scratch(1:100)
Default: public Private items not visible outside
of the module
private array scratch not
accessible from outside of the module
Keywords private or public can
stand alone, or be an attribute
61
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Module-oriented Programming
Example: Protected Variables
module mad_science real, parameter :: pi = 3. & c = 3.e8 & e = 2.7 integer, protected :: n real, dimension(:), private & allocatable :: scratch contains subroutine alloc() n = ... ! n defined in the module allocate (scratch(n))
protected variables are visible
on the outside
protected variables cannot be
modied outside the module
protected variables may be
modied inside of the module
variable n is set in the module
subroutine alloc n is visible to all subprograms that use the module
n cannot by changed outside of
the module
63
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Module-oriented Programming
Example: Rename Components of a Module
module mad_science real, parameter :: pi = 3. end module program t use mad_science, mad_pi => pi real, parameter :: pi = 3.1415 print *, mad_pi = , mad_pi print *, pi = , pi end program
Use module mad science change the name of pi (so that
you can declare your own and correct pi)
mad pi => pi: Refer to pi from
the module as mad pi
renaming works with function
names, too
prints mad pi = 3 prints pi = 3.1415
65
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Module-oriented Programming
Interfaces: Implicit = Explicit
Implicit interface: matching positions
subroutine s(a, b, c, n, ...) ... call s(x, y, z, m, ...)
The subroutine may be compiled separately (separate le)
from the other routine(s) or the main program that calls the subroutine
The position is the only information available
67
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Module-oriented Programming
Interfaces: Implicit = Explicit
Explicit interface which does not solely rely on positional information
module my_module contains subroutine s(a, b, c, n, ...) ... subroutine upper_level use my_module call s(x, y, z, m, ...)
Modules have to be compiled rst Compilation of a module results in a .mod le At compile time (Subr. upper level), the (content of the) module
(my module) is known through the .mod le (my module.mod)
Benets: Allows consistency check by the compiler Assumed-shape arrays, optional parameters, etc.
69
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Module-oriented Programming
Passing an array
Traditional scheme: Shapes of the actual and the dummy array
(may) have to agree integer, parameter :: n = 100 real, dimension(n) :: x call sub(x, n) subroutine sub(y, m) integer :: m real, dimension(m) :: y
You can, of course, play some games here The shape and the size do not have to match, but you have to
explicitly declare the shape and size in the subroutine
71
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Module-oriented Programming
Passing Assumed-shape arrays
module my_module contains subroutine sub(x) real, dimension(:) :: x print *, size(x) ! prints 100 subroutine upper_level ! calls the subroutine sub use my_module real, dimension(100) :: y call sub(y)
Variable y is declared as an array in subroutine upper level The subroutine (sub), knows the shape of the array
73
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Module-oriented Programming
Example: Assumed-shape and Automatic Arrays
subroutine swap(a, b) :: a, b real, dimension(:) real, dimension(size(a)) :: work ! Scratch array ! work is an automatic array on the Stack work = a ! uses Array syntax a = b ! Inquire with b = work ! lbound, ubound end subroutine swap ! shape, size
swap has to be in a module (explicit interface) calling routine has to use the module containing the subroutine swap No need to communicate the shape of the array size(a) returns the size of a, used to determine the size of work Automatic array work appears and disappears automatically
75
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Module-oriented Programming
Intent: In, Out, InOut
Formalize if a parameter is Input: intent(in) Output: intent(in) Both: intent(inout)
subroutine calc(result, a, b, c, d) ! This routine calculates ... ! Input: a, b, c ! Output: result ! d is scratch data: Input and Output real, intent(out) :: result real, intent(in) :: a, b, c ! Default real, intent(inout) :: d
You would put this information in the comment anyway. Improves maintainability Compiler will check for misuse
77
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Module-oriented Programming
Optional Arguments
Optional arguments require an explicit interface Optional arguments may not be changed, if they are not passed
module my_module subroutine calc(a, b, c, d) real :: a, b, c real, optional :: d real :: start if (present(d)) then start = d d = d_new else start = 0. endif
subroutine upper_level use my_module call calc( 1., 2., 3., 4.) call calc( 1., 2., 3.) call calc(a=1., b=2., c=3., d=4.) call calc(b=2., d=4., a=1., c=3.) call calc( 1., 2., 3., d=4.) call calc( 1., 2., d=4., c=3)
Positional arguments rst, then keyword arguments
79
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Module-oriented Programming
Optional Arguments
Optional arguments require an explicit interface Optional arguments may not be changed, if they are not passed
module my_module subroutine calc(a, b, c, d) real :: a, b, c real, optional :: d real :: start if (present(d)) then start = d d = d_new else start = 0. endif
subroutine upper_level use my_module call calc( 1., 2., 3., 4.) call calc( 1., 2., 3.) call calc(a=1., b=2., c=3., d=4.) call calc(b=2., d=4., a=1., c=3.) call calc( 1., 2., 3., d=4.) call calc( 1., 2., d=4., c=3)
Positional arguments rst, then keyword arguments
BREAK!
79
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Complaints Department
This just in from the Complaints Department
Isnt it really easy to screw up in these advanced languages
(Fortran2003 and C++)?
If modern Fortran is so much like C++,
Do I have to write Object-Oriented code in Fortran?
Isnt C++ (supposed to be) quite ugly? Will my Fortran code be
ugly, too? C++ does this name-mangling. Thats hideous! Does Fortran do the same?
There are so many features, do I need to master all of them to write
good code? Im new to Fortran. How much of the old stu do I need to know?
What is the bare minimum to get started?
81
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Complaints Department
A more complex language can create more confusion! We all deal with that every day ...
83
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Complaints Department
A more complex language can create more confusion! We all deal with that every day ...
... because as we know, there are known knowns; there are things we know we know. We also know there are known unknowns; that is to say, we know there are some things we do not know. But there are also unknown unknowns, the ones we dont know we dont know ... some politician Perfectly valid point, but the presentation is lacking
83
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Complaints Department
Do I have to write Object-Oriented code?
No, but you have to learn (sooner or later) how to write module-oriented code. Writing Object-Oriented code for access control is actually pretty nice! If your problem/algorithm requires, you may add Object-Oriented code exploiting Polymorphism (supported in Fortran2003 & 2008). Learn later, how to write Object-Oriented code in Fortran without performance penalty; Access control only.
85
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Complaints Department
Isnt C++ code (supposed to be) ugly? Will my Fortran2003 code be ugly, too?
Write clean code Clean code is not ugly (in any language: C++ and/or modern Fortran)
Use blanks, blank lines, indentation Comment your code Use modern constructs Use the language in a clear, unambiguous manner
87
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Complaints Department
C++ does name-mangling Does Fortran do the same?
Its not a bug, it is a feature!
It protects against misuse The objects (.o les) in your library (.a les) contain protected
names
If you do it right, name mangling causes no problems (see also
chapter on Interoperability with C )
89
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Complaints Department
There are so many features. Do I have to master all of them?
Here is how you get started:
Do not use common blocks or equivalence statements! If you nd yourself in a situation where you think they are needed, please revisit the modern constructs Use Heap arrays: allocate and deallocate (2 slides) Use structures to organzie your data (3 slides)
= Heap arrays + structures: There is Absolutely! no need for common blocks and equivalence statements
Use Modules: start writing module-oriented code (2 slides)
91
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Complaints Department
Here is how you get started: contd Use Modules: start writing module-oriented code What to put in a Module:
1. Constants (parameters) 2. Derived type declarations avoid repeating parameter and derived type denitions. Sometimes physical constants are put in an include le. This should be done using a module. 3. Variables (probably not?) 4. Functions and Subroutines, move on by using the public, private and protected attributes 5. Write Object-Oriented code without performance penalty 6. Use Inheritance and Polymorphism with care
What about learning old Fortran (F77 and older)?
Dont bother, if you dont have to Learn how to read code, assume that the code works correctly
93
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Formula zzzTranslation
Formula Translation
Array syntax where construct forall construct Case study: Stencil Update User dened Operators Elemental Functions Inquiry Functions Odds and Ends
95
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Formula zzzTranslation
Simple Array Syntax
real :: x real, dimension(10) :: a, b real, dimension(10,10) :: c, d a c a(1:10) a(2:3) a(1:10) a c a(1:3) = = = = = = = = b d b(1:10) b(4:5) c(1:10,2) x x b(1:5:2) ! a(1) = b(1) ! a(2) = b(3) ! a(3) = b(5)
Variables on the left and the
right have to be conformable
Number of Elements have to
agree
Scalars are conformable, too Strides can be used, too
97
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Formula zzzTranslation
Array constructor
real, dimension(4) :: x = [ 1., 2., 3. real, dimension(4) :: y, z y = [ -1., 0., 1., 2. ] ! z(1:4) = [ (sqrt(real(i)), i=1, 4) ] ! ! real, dimension(:), & allocatable :: x ... x = [ 1, 2, 3 ] print *, size(x) x = [ 4, 5 ] print *, size(x) 4. ] Array constructor with implicit loop
prints 3 prints 2
99
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Formula zzzTranslation
Derived Type constructor
type person real :: age character(len=8) :: name integer :: ssn end type person type(person) :: you you = [ 17., John Doe, 123456789 ]
101
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Formula zzzTranslation
Arrays as Indices
real, dimension(5) :: & a = [ 1, 3, 5, 7, 9 ] integer, dimension(2) :: & i = [ 2, 4 ] print *, a(i)
Variable i is an array (vector) a(i) is [ a(i(1)), a(i(2)), ... ]
prints 3. 7.
103
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Formula zzzTranslation
where statement
real, dimension(4) :: & x = [ -1, 0, 1, 2 ] & a = [ 5, 6, 7, 8 ] ... where (x < 0) a = -1. end where where (x /= 0) a = 1. / a elsewhere a = 0. end where
arrays must have the same
shape
code block executes when
condition is true
code block can contain Array assignments other where constructs forall constructs
105
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Formula zzzTranslation
where statement
real :: v real, dimension(100,100) :: x ... call random_number(v) ! scalar call random_number(x) ! array where (x < 0.5) x = 0. end where
Distinction between scalar and
array vanishes call to random number() Subroutine random number accepts scalars and arrays see also slides on elemental functions
107
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Formula zzzTranslation
any statement
integer, parameter :: n = 100 real, dimension(n,n) :: a, b, c1, c2 c1 = my_matmul(a, b) ! home-grown function c2 = matmul(a, b) ! built-in function if (any(abs(c1 - c2) > 1.e-4)) then print *, There are significant differences endif
matmul (also dot product) is provided by the compiler abs(c1 - c2): Array syntax any returns one logical
109
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Formula zzzTranslation
Example: Stencil Update
Ai = (Ai1 + Ai+1 )/2.
real, dimension(n) :: v real :: t1, t2 ... t2 = v(1) do i=2, n-1 t1 = v(i) v(i) = 0.5 * (t2 + v(i+1)) t2 = t1 enddo
111
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Formula zzzTranslation
Example: Stencil Update
Ai = (Ai1 + Ai+1 )/2.
real, dimension(n) :: v real :: t1, t2 ... t2 = v(1) do i=2, n-1 t1 = v(i) v(i) = 0.5 * (t2 + v(i+1)) t2 = t1 enddo v(2:n-1) = 0.5 * (v(1:n-2) + v(3:n))
Traditional scheme requires scalar variables Array syntax: Evaluate RHS, then copy the result
111
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Formula zzzTranslation
Stencil Update
Ai,j = (Ai1,j + Ai+1,j + Ai,j1 + Ai,j+1 )/4.
real, dimension(n,n) :: a, b do j=2, n-1 do i=2, n-1 b(i,j) = 0.25 * (a(i-1,j) + a(i+1,j) + a(i,j-1) + a(i,j+1)) enddo enddo do j=2, n-1 do i=2, n-1 a(i,j) = b(i,j) enddo enddo
Two copies required: b = f(a); a = b
113
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Formula zzzTranslation
Stencil Update
Ai,j = (Ai1,j + Ai+1,j + Ai,j1 + Ai,j+1 )/4.
a(2:n-1,2:n-1) = 0.25 * (a(1:n-2,2:n) + a(3:n,2:n) + a(2:n,1:n-2) + a(2:n,3:n))
No copy required (done internally)
115
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Formula zzzTranslation
Stencil Update
Ai,j = (Ai1,j + Ai+1,j + Ai,j1 + Ai,j+1 )/4.
a(2:n-1,2:n-1) = 0.25 * (a(1:n-2,2:n) + a(3:n,2:n) + a(2:n,1:n-2) + a(2:n,3:n))
No copy required (done internally)
Now with the forall construct forall (i=2:n-1, j=2:n-1) & a(i,j) = 0.25 * (a(i-1,j) + a(i+1,j) + a(i,j-1) + a(i,j+1))
Fortran statement looks exactly like the original formula
115
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Formula zzzTranslation
Detached Explicit Interfaces
Enables User-dened Operators and Generic Subprograms The interface can be detached from the routine Only the interface may reside in the module (like in a C header le) Comes in handy, when a large number of people (n>1) work on one project
module my_interfaces interface subroutine swap(a, b) real, dimension(:) :: a, b real, dimension(size(a)) :: work end subroutine end interface
! Scratch array
Any subprogram that calls swap has to use the module my interfaces
117
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Formula zzzTranslation
Generic Interfaces Function/Subroutine Overload
Motivation: Write code that allows to swap two variables of type real and two variables of type integer Subroutine 1: swap real() Subroutine 2: swap integer() program p_swap module mod_swap use mod_swap contains real :: a, b subroutine swap_real(x, y) integer :: i1, i2 real :: x, y, t t = x; x = y; y = t ! Get a, b, i1 and i2 from end subroutine ! somewhere call swap_real(a, b) subroutine swap_integer(i, j) call swap_integer(i1, i2) real :: i, j, k k = i; i = j; j = k end program end subroutine end module
119
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Formula zzzTranslation
Generic Interfaces Function/Subroutine Overload
Add a generic interface (swap) to both routines swap with real arguments swap real swap with integer arguments swap integer
module mod_swap public swap private swap_real, swap_integer interface swap module procedure & swap_real, swap_integer end interface contains
subroutine swap_real(x, y) real :: x, y, t t = x; x = y; y = t end subroutine subroutine swap_integer(i, j) real :: i, j, k k = i; i = j; j = k end subroutine end module
121
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Formula zzzTranslation
Generic Interfaces Function/Subroutine Overload
module mod_swap public swap private swap_real, swap_integer interface swap module procedure & swap_real, swap_integer end interface contains ... program p_swap use mod_swap call swap(a, b) ! swap_real call swap(i1, i2) ! swap_integer call swap_real(a, b) ! Does NOT ! compile! end program
Interface swap is public Inner workings (swap real,
swap integer) are private
User of module mod swap cannot
access/mess-up inner routines
123
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Formula zzzTranslation
Generic Interfaces Function/Subroutine Overload
Anything distinguishable works real, integer, real(8), ... Only one argument may dier
module mod_swap public swap private swap_real, swap_real8 interface swap module procedure & swap_real, swap_real8 end interface contains
subroutine swap_real(x, y) real :: x, y, t t = x; x = y; y = t end subroutine subroutine swap_real8(x, y) real(8) :: x, y, t t = x; x = y; y = t end subroutine end module
125
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Formula zzzTranslation
User-dened Operators
module operator public :: operator(.lpl.) private :: log plus log interface operator(.lpl.) module procedure log plus log end interface contains function log plus log(x, y) & result(lpl result) real, intent(in) :: x, y real :: lpl result lpl_result = log(x) + log(y) end function end module program op use operator print *, 2. .lpl. 3. end program
prints 1.791759 .lpl. is the new operator
(dened public)
rest of the denition is private interface function log plus log .lpl. is dened as
log(x) + log(y)
log(2.) + log(3.) = 1.791759
127
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Formula zzzTranslation
Elemental Functions
module e_fct elemental function sqr(x) & result(sqr_result) real, intent(in) :: x real :: sqr_result sqr_result = x * x end function end module program example use e_fct real :: x = 1.5 real, dimension(2) :: a = & [ 2.5, 3.5 ] print *, x = , sqr(x) print *, a = , sqr(a) end program
Write function for scalars add elemental routine will also accept arrays
prints a = 2.25 prints x = 6.25 12.25 allows to extend array syntax to
more operations
129
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Formula zzzTranslation
where/any in combination with elemental functions
module e_fct elemental function log_sqr(x) & result(ls_result) real, intent(in) :: x real :: ls_result ls_result = log(sqr(x)) end function end module subroutine example(x, y) use e_fct real, dimension(100) :: x, y where (log_sqr(x) < 0.5) y = x * x end where if (any(log_sqr(x) > 10.)) then print *, ... something ... endif end program
Put an elemental function in a
module
Use elemental function with
where and any
131
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Formula zzzTranslation
Inquiry Functions
digits(x):
number of signicant digits with 1 + <> 1
epsilon(x): smallest
huge(x): largest number maxexponent/minexponent: largest/smallest exponent tiny(x): smallest positive number (that is not 0.) ubound, lbound, size, shape, ... input unit, output unit, error unit le storage size (Good when you use the Intel compiler!) character storage size, numeric storage size etc.
133
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Formula zzzTranslation
Mathematical Functions
sin, cos, tan, etc. New in Fortran 2008: Bessel fct., Error-fct., Gamma-fct., etc.
135
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Odds and Ends
Fortran pointers (Aliases)
integer, parameter :: n = 1000 real, dimension(n*n), target :: data real, dimension(:), pointer :: ptr, diag real, dimension(:), allocatable, & pointer :: ptr_alloc ... ptr => data diag => data(1: :1001) ! start, end, stride allocate(ptr_alloc(100))
Pointer association : Pointing to Pointer is of the same type as the target Target has the target attribute (needed for optimization) Pointers can have memory allocated by themselves (ptr alloc in C) Pointers are useful to create linked lists (not covered here)
137
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Odds and Ends
Fortran pointers (Aliases)
integer, parameter :: n = 5 real, dimension(n,n), target :: data real, dimension(:), pointer :: row, col ... row => data(4,:) ! 4th row col => data(:,2) ! 2nd column print *, row, col ! Use pointer like a variable
Pointers col and row are pointing to a column/row of the 2-dim
array data
Memory is not contiguous for row When you pass row to a subroutine, a copy-in/copy-out may be
necessary
What is => used for? Referencing and de-referencing is automatic,
so a special symbol is needed for pointing
139
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Odds and Ends
Fortran pointers (Aliases)
real, dimension(100), target :: array1, array2, temp real, dimension(:), pointer :: p1, p2, ptmp ... temp = array1 ! Copy the whole array 3 times array1 = array2 ! Very costly! array2 = temp ... p1 => array1 ! use 2 pointers to point p2 => array2 ! to data ... ptmp => p1 ! Move the Pointers p1 => p2 ! Very cheap! p2 => ptmp
Later, use the pointers as of they were normal variables
141
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Odds and Ends
Command Line Arguments
! Function: returns ! number of arguments call get_command argument(number, value, length, status) ! input: number ! output: value, length, status ! (all optional) call get_command(command, length, status) ! output: command, length, status Example: ./a.out option X character(len=16) :: command call get_command(command) print command ! prints: ./a.out option X command_argument_count()
143
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Odds and Ends
Environment Variables
call get_environment_variable(name, value) ! Input : name ! Output: value character(len=16) :: value call get_environment_variable(SHELL, value) print value ! prints /bin/bash
145
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Odds and Ends
Fortran Preprocessor
same as in C (#ifdef, #ifndef, #else, #endif) compile with -fpp use option -D<variable> to set variable to true Example: ifort -Dmacro t.f
#ifdef macro x = y #else x = z #endif
147
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Odds and Ends
Interoperability with C (Name Mangling)
Variables, Functions and Subroutines, etc., that appear in modules
have mangled names
This enables hiding the components from misuse No naming convention for the mangled names
file t.f module operator real :: x contains subroutine s() return end subroutine end
compile with: ifort -c t.f result is t.o nm t.o prints this: (nm is a Unix command) T _operator_mp_s_ C operator_mp_x_
149
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Odds and Ends
Give Objects (in object le) a specic Name
Use intrinsic module (iso c binding) to use pass strings (not shown
here)
file t.f module operator real, bind(C) :: x contains subroutine s() & bind(C, name=_s) return end subroutine end
compile with: ifort -c t.f result is t.o nm t.o prints this: T _s C _x
151
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Odds and Ends
Use C-compatible variable types
Use variables of a special kind c oat, c double, c int, c ptr, etc. works with characters, too
module operator real, bind(C) :: x type, bind(C) :: c_comp real(c_float) :: data integer(c_int) :: i type(c_ptr) :: ptr end type contains subroutine s() & bind(C, name=_s)
Arrays: Fortran: real(c float) :: x(5,6,7) C: float y[7][6][5]
153
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran Odds and Ends
Not Covered
Floating-point Exception Handling Linked-Lists, Binary Trees Recursion I/O (Stream Data Access) Object-Oriented Programming, but see introduction in the next
chapter
155
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran History
History of Fortran
History of Programming Languages
1954 1960 1965 1970 1975 1980 1985 1990 1995 2000 2001 2002 2003 2004
1986
For more than half of the fifty years computer programmers have been writing code, OReilly has provided developers with comprehensive, in-depth technical information. Weve kept pace with rapidly changing technologies as new languages have emerged, developed, and matured. Whether you want to learn something new or need answers to tough technical questions, youll find what you need in OReilly books and on the OReilly Network. This timeline includes fifty of the more than 2500 documented programming languages. It is based on an original diagram created by ric Lvnez (www.levenez.com), augmented with suggestions from OReilly authors, friends, and conference attendees. For information and discussion on this poster, go to www.oreilly.com/go/languageposter.
1990
1990
1991
1991
1993
1994
1995
1996
1996
1997
1997
2000
2001
2001
2003
2003
2004
www.oreilly.com
2004 OReilly Media, Inc. OReilly logo is a registered trademark of OReilly Media, Inc. All other trademarks are property of their respective owners. part#30417
Fortran started in 1954; the rst line in the diagram.
157
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran History
Fortran 90+: 90, 95, 2003, 2008
Modern, ecient, and appropriate for
Number Crunching and High Performance Computing
Upgrades every few years: 90, 95, 2003, 2008, ... Major upgrade every other release: 90, 2003 Easy switch: F90 is fully compatible with F77
Where are we now?
F2003 fully supported by Cray, IBM, PGI and Intel compilers F2008 is partially supported
159
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran The Future
Performance Considerations and Object-Oriented Programming
(Most of the) Language elements shown in this class do not have
(any/severe) performance implications
Most of the module-oriented programming handles access Some array syntax may! be done better in explicit loops, if more than one statement can be grouped into one loop Pointers that have non-contiguous elements in memory may! require a copy in/out, when passed to a subprogram Compiler can warn you (Intel: -check arg temp created) Use pointers (references) and non-contigous data with care Fortran allows for an Object-Oriented Programming style Access control, really a great concept! Type extension, Polymorphic entities Use with care (may be slower), but use these features if your algorithm requires and the implemenation benets from it
161
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran The Future
Functions, Modules, Objects
Use Functions and Subroutines to hide local Data Use Modules to hide Data, Functions and Subroutines Use Objects to hide Data and expose Methods
163
Modern Programming Languages: Fortran90/95/2003/2008 Modern Fortran The Future
Book Recommendations
Fortran 95/2003 for Scientists and Engineers by Chapman
Very! verbose, with many examples. Guides the programmer nicely towards a good programming style. (International/cheaper edition available) modern fortran explained by Metcalf, Reid and Cohen Good to learn new features; more complete than the Guide (4), but a very few times a bit confusing. Covers Fortran 2008 The Fortran 2003 Handbook by Adams, Brainerd, et al. Complete syntax and Reference Guide to Fortran 2003 Programming by Walter S. Brainerd Good to learn the new features, clever examples Some Guidance is denitely needed The same task may be accomplished in several ways What to use When?
165
Modern Programming Languages: Fortran90/95/2003/2008 Object-Oriented Programming: (Very) Short Version Modularity and Object Orientation
How long does it take to Debug Code?
Defect density r per 1000 lines Number of lines in code: Assume a chronological listing of code, where redundant occurrences
are removed
A bug appears on average at line number /2 (in the middle) Bug must be located in preceding lines /2 1, again on
average at line number 1 (/2 1) (again, in the middle) 2 Code contains r bugs
(r ) 1 (/2 1) 2 lines have to be inspected 2 Defect rate is independent of Modularity (8-24 per 1000
lines, according to studies)
Something better than Modularity is needed
167
Modern Programming Languages: Fortran90/95/2003/2008 Object-Oriented Programming: (Very) Short Version Modularity and Object Orientation
From Modules to Objects: Global Variables
In debugging, most time is spent locating the bug, not xing it
Lets assume that your code iterates to nd a solution and that the
problem occurs in the 2nd iteration Almost all your code has been executed at least once, probably except the routines for the nal output If your code employs: Global Variables
the bug can be anywhere in your lines of code in any routine you may have overwritten a global variable the debug-time will be proportional to 2 for all bugs
169
Modern Programming Languages: Fortran90/95/2003/2008 Object-Oriented Programming: (Very) Short Version Modularity and Object Orientation
From Modules to Objects: Modules
Lets assume that you have created several modules, and that you
have bundled subroutines needed for a specic task in these modules
Example: Module read data contains routines that read input into array inp Module calc 1 takes inp and calculates some temporary data d1 Module calc 2 takes inp and d1 and calculates the result r
If Bugs appear in Module calc 2
Bugs may be located in the same module and the search time is
then proportional to 2 2 calc but the bugs may come from changes you made in the other 2 modules 2 2 best case: search time proportional to 2 read data + calc 1 + calc 2 2 worst case w/ side eects: search time again proportional to
171
Modern Programming Languages: Fortran90/95/2003/2008 Object-Oriented Programming: (Very) Short Version Modularity and Object Orientation
From Modules to Objects:
Modules (Modularity) create a barrier that is somewhat porous Lets make the barrier (almost) impenetrable:
Objects and Object-Oriented programming
Content in one Object is completely shielded from content in
another Object Bugs appear in Object calc 2 your search time is proportional to 2 2 calc
What are Objects and what do they contain?
173
Modern Programming Languages: Fortran90/95/2003/2008 Object-Oriented Programming: (Very) Short Version Modularity and Object Orientation
Object-Oriented Programming: Concept
Object-oriented code will still contain data (arrays, structures) and
subprograms (subroutines, functions), but we need new names for these if they reside in an object Objects add functions/subroutines to a Derived Type
The data in a Derived Type is called a Field The subprograms are called Methods Methods operate on the Fields Only the Methods are visible from the outside The data (elds) are not visible An Object is an instance of a Class (or a Derived Type); Examples:
real :: a type(class_a) :: object_a
! a is an instantiation of real ! object a is an instantiation ! of the class a
175
Modern Programming Languages: Fortran90/95/2003/2008 Object-Oriented Programming: (Very) Short Version Modularity and Object Orientation
Object-Oriented Programming: Nomenclature
All languages use their own words There is usually no 1-to-1 translation between Fortran and C++,
but the table provides a guideline
Table: OOP Nomenclature Fortran Derived type / Class Component Class Type-bound procedure Parent type Extended type Module C++ Class Data member Dynamic Polymorphism Virtual Member function Base class Subclass Namespace General Abstract data type Attribute or Field Method Parent class Child class Package
from Scientic Software Design by Rouson, Xia, Xu, Table 2.1
177
Modern Programming Languages: Fortran90/95/2003/2008 Object-Oriented Programming: (Very) Short Version Modularity and Object Orientation
Object-Oriented Programming: Advantages
Data in a class is shielded / hidden Methods are exposed Code becomes reusable: Never replicate code! Code becomes extensible: Inheritance Debug (search) time scales with number of lines in code in object
The three (four) pillars of Object-Oriented Programming (OOP) 1. 2. 3. 4. Data encapsulation & data hiding Polymorphism Inheritance Operator overloading
Polymorphism comes in 2 avors; Ill only touch on one, which is somtimes called static or procedural polymorphism
179
Modern Programming Languages: Fortran90/95/2003/2008 Object-Oriented Programming: (Very) Short Version Modularity and Object Orientation
Summary of OO Concept
Objects contain (have the properties):
Data Instance Variables or Fields Subr./Fct. Instance Methods Polymorphism/Inheritance Reusability and Extensibility
Data is only accessible through the methods OO-speak: Call of a Subr. (instance method) Sending a Message A Class is a blueprint for a Object
type(data) :: structure containing variables type(data plus fct) :: object containing variables and functions class(data plus fct) :: with dynamic polymorphism
Classes are organized in Hierarchies and can inherit
instance variables and methods from higher level classes
An object can have many forms (polymorphism), depending on
context
181
Modern Programming Languages: Fortran90/95/2003/2008 Object-Oriented Programming: (Very) Short Version Modularity and Object Orientation
Example of an Object in Fortran 2003
module my_mod private public :: person type :: person character(8), private :: name integer, private :: iage contains procedure :: set procedure :: print end type person contains Private and public components subroutine set(this, & name, iage) class(person) :: this character(len=*) :: name integer :: iage this%name = name this%iage = iage write (0,*) set end subroutine subroutine print(this) class(person) :: this write (0,*) this%name, & this%iage end subroutine end module
183
Modern Programming Languages: Fortran90/95/2003/2008 Object-Oriented Programming: (Very) Short Version Modularity and Object Orientation
How to use the Class dened in my mod
program op use my_mod type(person) :: you type(person), dimension(5) :: we ! Allowed call you%set(J. Doe, 25) call you%print ! Not allowed call set(...) call print(...) write (0,*) name is , you%name we(1) = you end
185
Declare object as a type without
dynamic polymorphism: No performance implications
Access to the data only through
approved public methods Note: you%set called with 2 arguments, but Subroutine has 3 arguments
Modern Programming Languages: Fortran90/95/2003/2008 Object-Oriented Programming: (Very) Short Version Modularity and Object Orientation
How is a method called?
! Definition (with 3 arguments) subroutine set(this, & name, iage) class(person) :: this character(len=*) :: name integer :: iage this%name = name this%iage = iage write (0,*) set end subroutine ! Call side (with 2 arguments) call you%set(J. Doe, 25)
you%set is called with 2
arguments,but Subroutine has 3 arguments
The you on the call side,
becomes the rst argument (this) on the denition side
187
Modern Programming Languages: Fortran90/95/2003/2008 Object-Oriented Programming: (Very) Short Version Modularity and Object Orientation
Encapsulation and Code Replication
All data in your objects is hidden Only the methods are exposed The denition of all data and all methods are in one module Code is never replicated It always means the same when you code: call you%print If you change the meaning of you%print, the meaning changes
everywhere
There will be only one method in your code that prints the elds of
a particular object, i.e. you%print
189
Modern Programming Languages: Fortran90/95/2003/2008 Object-Oriented Programming: (Very) Short Version Modularity and Object Orientation
Inheritance: Avoid Code Replication
module mod_line private public :: line type :: line real, private :: x1, y1, & x2, y2 contains procedure :: print_coord end type contains subroutine print_coord(this) class(line) :: this write (0,*) Start : , x1, y1 write (0,*) End : , x2, y2 end subroutine end module
Module conains the class line Data:
start and end points
Method:
Print start and end points
191
Modern Programming Languages: Fortran90/95/2003/2008 Object-Oriented Programming: (Very) Short Version Modularity and Object Orientation
Inheritance: Extend an existing class
module mod_line private public :: line, color_line type :: line real, private :: x1, y1, & x2, y2 contains procedure :: print_coord end type type, extends(line) :: & color_line integer, dimension(3), & private :: rgb contains procedure :: print_color end type color_line
Class color line extends class line color line inherits the data
x1, y1, x2, y2
and the method print coord Additions: rgb and print color
193
Modern Programming Languages: Fortran90/95/2003/2008 Object-Oriented Programming: (Very) Short Version Modularity and Object Orientation
Inheritance: Extend an existing class
program main use mod_line type(line) :: l1 type(color_line) :: l2 call l1%print_coord call l2%print_color ! Inherited Method call l2%print_coord ! Invalid call l1%print_color
l1%print coord and
l2%print coord invoke the same subroutine
Object l2 contains the same data
and methods as l1
l2%print color is an additional
method unique to object l2
195