You are on page 1of 196

Large-scale simulations with Fortran 95: An object-based approach

Paul F. Dubois
PCMDI, Atmospheric Sciences Division
dubois1@llnl.gov

1 of 53
Lesson 1: Arrays and Modules

2 of 53
F o r tr a n 9 5 is a m o d e r n , ty p e -sa fe
la n g u a g e .
• D y n a m ic m e m o ry m a n a g e m e n t
• Ty p e -c h e c k e d p ro c e d u ra l in te rfa c e s
• S o p h is tic a te d s e t o f in trin s ic fu n c tio n s
• S c a la b le n a m e s p a c e m a n a g e m e n t
• U s e r-d e fin e d o b je c ts a n d o p e ra tio n s

3 of 53
M ig r a te to F o r tr a n 9 5 w ith o u t p a in .
• T h is 4 -le c tu re s e rie s w ill m ig ra te y o u .
• Yo u c a n m ig ra te y o u r e x is tin g c o d e a little
a t a tim e .
• C h a n g e y o u rs e lf o r y o u r c o d e a s m u c h o r a s
little a s y o u w a n t.

4 of 53
Yo u r life w ill g e t b e tte r.
• D e fin e y o u r o w n ty p e s a n d o p e ra tio n s .
• D a ta a lig n m e n t p ro b le m s d is a p p e a r w ith
m o d u le s .
• D y n a m ic m e m o ry m a n a g e m e n t is e a s y.
• P o rta b le (a n d e a s ily c h a n g e a b le ) p re c is io n
fo r re a l a n d c o m p le x v a ria b le s is a tta in a b le .

5 of 53
F o r tr a n 9 5 su p p o r ts o b je c t-b a s e d
p ro g r a m m in g .
• T h e re is s u ffic ie n t s u p p o rt fo r d e s ig n in g
y o u r o w n o b je c ts .
• G e n e ric in te rfa c e s p ro v id e fu n c tio n -
s ig n a tu re o v e rlo a d in g .
• It is n ’t fu lly O O (y e t) b u t it g o e s a lo n g w a y
to w a rd th e g o a ls o f O O P.

6 of 53
O u r “ u p g r a d e ” s tr a te g y is to o n ly le a r n th e
“ r ig h t w a y ” .
• N o la n g u a g e la w y e rs a llo w e d .
• M a n y fe a tu re s o m itte d .
• S u b tle p o in ts ig n o re d .
• In s h o rt, I’ll try to s tic k to th e s tu ff th a t
m a k e s a re a l d iffe re n c e .

7 of 53
C o u r s e -re la te d file s a re a v a ila b le a t
ftp -ic f.lln l.g o v /p u b /O B F 9 0 .
These slides
Example sources

8 of 53
If y o u w o u ld lik e a te x tb o o k , th e se a re
good.
• D ig ita l F o rtra n L a n g u a g e R e f. G u id e
(c o m e s w ith D ig ita l F o rtra n , a v a ila b le fo r
P C o r D E C ).
• E llis , P h ilip s , L a h e y, “ F o rtra n 9 0
P ro g ra m m in g G u id e ” , A d d is o n -W e s le y.
•C h a m b e rla n d , “ F o rtra n 9 0 : A re fe re n c e
g u id e ” , P re n tic e -H a ll
•A d a m s e t. a l, “ F o rtra n 9 5 H a n d b o o k ” , M IT
P re s s .

9 of 53
T h e fo llo w in g e x a m p le w ill n o t b e stu d ie d
in d e ta il. It is ju st h e re to fr ig h te n y o u in to
d o in g th e h o m e w o r k .
Is this Fortran? Yes!
program tryme !An old friend, now standard...
use example !Hmmm, must be a sort of include...
implicit none !Another old friend, now standard...
call init !This, I understand!
write(11, *) report(3) ! This too!
write(11, *) report() !Oh, dear...
end program tryme

10 of 53
module example
implicit none
private
public report, init
integer, dimension(10):: x
contains
function report (j) result(y)
integer, intent(in), optional:: j
integer, dimension(size(x)):: y

if (present(j)) then
y=j*x+2
else
y=x+2

11 o f 5 3
endif
end function report

subroutine init
integer i
x = (/ (i, i= 1, size(x)) /)
end subroutine init
end module example

12 of 53
F o r tr a n 7 7 ’s m a jo r w e a k n e ss w ith re s p e c t
to la r g e -s c a le p ro g r a m m in g is its p o o r
n a m e s c o p in g .
•T h e re a re o n ly tw o s c o p e s , lo c a l a n d g lo b a l.
•T h e g lo b a l s c o p e c o n ta in s a ll fu n c tio n n a m e s
a n d c o m m o n b lo c k s .
•L a b e le d c o m m o n b lo c k s le t y o u o n ly “ u s e ”
p a rt o f th e g lo b a l v a ria b le n a m e s b u t n a m e
c o n flic ts o c c u r b e tw e e n c o m m o n b lo c k s .
•T h e u s e r is re q u ire d to s e g re g a te v a ria b le s b y
ty p e in o rd e r to a c h ie v e c o rre c t d a ta
a lig n m e n t.

13 of 53
T h e se c o n d m a jo r w e a k n e ss o f F 7 7 is th e
p o o r fa c ility fo r d y n a m ic m e m o r y
m a n a g e m e n t.
The Cray “pointer” facility is dangerous and prone to
memory leaks.
The exact syntax and details of its operation are not de facto
standards.
But without it, no modern program is possible.

14 of 53
To d a y ’s le ss o n s o lv e s b o th th o s e p ro b le m s.
•M o d u le s p ro v id e s c a la b le n a m e s p a c e
c o n tro l.
•T h e a rra y fa c ilitie s in c lu d e c o m p le te s u p p o rt
fo r d y n a m ic m e m o ry m a n a g e m e n t.

15 of 53
M in i-le ss o n # 1 : R ip o u t th o s e c o m m o n
b lo c k s

16 of 53
R eplace co m m on b locks w ith
m o dules
C o m m o n b lo c k M o d u le
complex w module abc
real x, z complex w
integer y real x, z
common /abcc/ w integer y
common /abcr/ x, z end module abc
common /abci/ y ...
... use abc
#include “abc.h”

17 of 53
T h e m o d u le d e c la r a tio n c re a te s a n e w
n am e sp ace.
module m1
implicit none
real x, y(10)
end module m1

“Use association”
subroutine whatever
use m1 !makes all names in m1 available here
write(11, *) x, y
end subroutine whatever

18 of 53
subroutine whomever
use m1, only: x !makes only the name x available here
integer y
write(11, *) x, y
end subroutine whomever

You can even rename:


use m1, only: my_name_for_y => y
integer y ! no conflict with the y in m1

19 of 53
A r r a y s a re F 9 5 ’s b ig fo r te .
First, the way we were...
subroutine version77
real y(10)
real x(10)
common /mycom/ x
integer i
parameter(pi = 3.14159)

20 of 53
do 100 i = 1, 10
x(i) = i / 10.0
y(i) = sin(x(i) * pi)
100 continue
write(11, *) "Version 77"
write(11, *) (y(i), i = 1, 10)
end

21 of 53
W e u se a m o d u le to e s ta b lis h th e p re c is io n
o f o u r re a l v a r ia b le s.
module precision
implicit none
integer, parameter:: adequate =
selected_real_kind(6,35)
integer, parameter:: precise = selected_real_kind(14,99)
real(adequate), parameter:: pi = 3.14159_adequate
end module precision

We are assured that pi will be of a real type that has at least


six digits of precision and an exponent range of E-35 to
E+35.

22 of 53
T h e q u a lifie r o n th e re a l d e c la r a tio n is
c a lle d its “ k in d ” .
real(precise) x
real(kind=precise) x
The default “real” and “double” still exist but they have
unknown properties. These properties also apply to real and
double literal constants.

Note the underscore notation for ensuring that a literal has


the desired kind: 3.14159_adequate

Use kinds in conversion operators: real(24, adequate).

23 of 53
W e re p la c e th e c o m m o n b lo c k w ith a
m o d u le .
module mystuff
use precision
implicit none
real(adequate) x(10)
! there is more in this module, but we’ll see that later...
end module mystuff

24 of 53
subroutine version90
use mystuff
implicit none
integer i

do i = 1, 10
x(i) = i / 10.0
enddo
call version0
call version1
call version2
write(11, *) "Version 3"
write(11, *) version3(x)
call version4 (x, 10)

25 of 53
call version5 (x, 10)
call version6 (x(1), 10)
end

26 of 53
W e d o n ’t n e e d a lo o p a n y m o re . A n d th e
c o m p ile r c a n p r in t th e a r r a y y.
subroutine version0
use mystuff
implicit none
real(adequate) y(10)

y = sin(x * pi)
write(11, *) "Version 0"
write(11, *) y
end subroutine version0

27 of 53
T h e re is n o n e e d to h a r d -w ire a r r a y siz e s.
subroutine version1
use mystuff
implicit none
real(adequate) y(size(x))

y = sin(x * pi)
write(11, *) "Version 1"
write(11, *) y
end subroutine version1

28 of 53
If y o u d o n 't k n o w th e r ig h t siz e o n e n tr y,
u s e a llo c a ta b le a r r a y s .
subroutine version2
use mystuff
implicit none
real(adequate), allocatable:: y(:)

allocate(y(size(x)))
y = sin(x * pi)
write(11, *) "Version 2"
write(11, *) y
end subroutine version2

29 of 53
U se th e sa m e m e th o d fo r a r g u m e n ts a n d
fu n c tio n re s u lts .
function version3 (x) result(y)
use precision
implicit none
real(adequate), intent(in):: x(:)
real(adequate) y(size(x))

y = sin(x * pi)
end function version3

30 of 53
S iz e s c a n a lso b e p ic k e d u p fro m fo r m a l
p a r a m e te r s o r m o d u le v a r ia b le s.
subroutine version4 (x, n)
use precision
implicit none
integer, intent(in):: n
real(adequate), intent(in):: x(n)
real(adequate) y(n)

y = sin(x * pi)
write(11, *) "Version 4"
write(11, *) y
end subroutine version4

31 of 53
T h e a ss u m e d -s iz e a r r a y is u se d fo r F 7 7 -
sty le a r g u m e n ts.
subroutine version5 (x, n)
use precision
implicit none
integer, intent(in):: n
real(adequate), intent(in):: x(*) ! assumed-size array
real(adequate) y(n)

! y = sin(x * pi) -- error


y = sin(x(1:n) * pi) ! o.k.
write(11, *) "Version 5"
write(11, *) y
end subroutine version5

32 of 53
subroutine version6 (x, n)
! Same as version 5, only called with x(1)
use precision
implicit none
integer, intent(in):: n
real(adequate), intent(in):: x(*) ! assumed-size array
real(adequate) y(n)

y = sin(x(1:n) * pi)
write(11, *) "Version 6"
write(11, *) y
end subroutine version6

33 of 53
A r r a y p o in te r s a re sim ila r to a llo c a ta b le
a r r a y s.
Array pointers have a rank but do not get a shape until they
are “pointed” at something with the => operator.

34 of 53
subroutine version7 (x)
use precision
implicit none
real(adequate), intent(in), target:: x(:)
real(adequate), pointer:: y(:), z(:)
integer n, m

n = lbound(x, 1)
m = ubound(x, 1)
y => x(n+1: m)
z => x(n: m - 1)
write(11, *), "Version 7"
write(11, *), z - y
end subroutine version7

35 of 53
W e h a v e le a r n e d th e re a re fo u r k in d s o f
a r r a y s.
1 . E x p lic it-s h a p e :
•S iz e e v a lu a b le a t c o m p ile tim e , s u c h a s
x (1 0 0 ). C a n b e in th e m a in p ro g ra m o r a
s u b p ro g ra m .
•S iz e e v a lu a b le o n e n try to a s u b p ro g ra m ,
s u c h a s x (n ). S h a p e is d e te rm in e d a t o n c e o n
e n try to th e s u b p ro g ra m .
2 . A s s u m e d -s h a p e : x (:), w h e re x is a fo rm a l
a rg u m e n t, a s s u m e s th e s h a p e o f th e a c tu a l
a rg u m e n t. S h a p e d e te rm in e d o n e n try to th e

36 of 53
s u b p ro g ra m . U s e th is w h e re y o u u s e d to u s e
x (* ). O K if m o re th a n o n e d im e n s io n , s u c h
a s y (:,:).
3 . D e fe rre d -s h a p e : x (:), w h e re x is a llo c a ta b le
o r h a s th e p o in te r a ttrib u te . T h e ra n k is
d e te rm in e d , b u t th e s h a p e w ill b e
d e te rm in e d la te r. O K if m o re th a n o n e
d im e n s io n . F 9 5 , b u t n o t F 9 0 , a llo w s a lo w e r
b o u n d , s u c h a s x (2 :).
4 . A s s u m e d s iz e : x (* ), w h e re x is a n
a rg u m e n t, a n d th e * is o n th e la s t d im e n s io n
o n ly. O n ly a n a d d re s s is a c tu a lly p a s s e d .
C a n b e u s e d fo r c o m p a tib ility w ith F o rtra n
77.

37 of 53
In all cases the rank is explicit and fixed.

38 of 53
R o u tin e s th a t h a v e th e “ m o d e r n ” a r r a y
a r g u m e n ts m u s t h a v e e x p lic it in te r fa c e s.
In other words, the compiler has to know, at the place where
it makes a call, what the signature of the callee looks like.
There are three ways to make an interface explicit, which
we will cover in a moment.

39 of 53
If a n in te r fa c e is e x p lic it w e g e t th e se
b e n e fits :
•A rg u m e n ts a n d re tu rn v a lu e s c a n b e a rra y -
v a lu e d .
•T h e c o m p ile r c h e c k s th e n u m b e rs a n d ty p e s
o f th e a rg u m e n ts in e a c h c a ll.
•T h e c o m p ile r p e rfo rm s ty p e c o n v e rs io n o n
a rg u m e n ts w h e re p o s s ib le .
•If a n a rg u m e n t h a s in te n t(in ), it c a n n o t b e
w ritte n .

40 of 53
W e n e e d to a d d in te r fa c e s to m o d u le
m y stu ff.
module mystuff
use precision
implicit none
real(adequate) x(10)
interface
function version3(x) result(y)
use precision
real(adequate), intent(in):: x(:)
real(adequate) y(size(x))
end function version3

41 of 53
subroutine version7(x)
use precision
real(adequate), intent(in):: x(:)
end subroutine version7
end interface
end module mystuff

Routines version3 and version7 had “modern” array


arguments, while version0, version1, and version2 had no
arguments, and the rest took assumed-size x(*) arguments.

42 of 53
T h e re a re th re e w a y s to m a k e a n
su b p ro g r a m ’s in te r fa c e e x p lic it.
1 . B y c o n ta in in g it in s id e th e ro u tin e th a t c a lls
it.
2 . B y c o n ta in in g it in a m o d u le .
3 . U s in g a n in te rfa c e b lo c k in a m o d u le .

43 of 53
module myfuns
use precision
implicit none
! interface to a function defined elsewhere
interface
function manipulate4(x)
use precision
real(adequate), intent(in):: x(:)
real(adequate) manipulate4(size(x))
end function manipulate4
end interface

contains

44 of 53
function manipulate3(x) result(s)
use precision
real(adequate) x(:)
real(adequate) s

s = sum(x)
end function manipulate3
end module myfuns

45 of 53
subroutine part2
use mystuff
use myfuns
implicit none
real(adequate) manipulate1, manipulate5
external manipulate1, manipulate5

write(11, *), "Manipulations"


write(11, *), manipulate1(x, size(x)), &
manipulate2(x), &
manipulate3(x)
write(11, *), manipulate4(x)
write(11, *), manipulate5()

46 of 53
contains

function manipulate2(x)
! explicit since contained in the calling routine
use precision
real(adequate), intent(in):: x(:)
integer manipulate2

manipulate2 = count(x > 0.3_adequate)


end function manipulate2

end subroutine part2

47 of 53
function manipulate1(x, n) result(w)
! implicit interface, new intrinsic dot_product
use precision
real(adequate), intent(in):: x(*)
real(adequate) w

w = dot_product(x(1:n), x(1:n))
end function manipulate1

48 of 53
function manipulate4(x) result(p_times_y)
! matrix multiply, etc.
use precision
real(adequate), intent(in):: x(:)
real(adequate) y(size(x)), z(size(x)), p(size(x), size(x))
real(adequate) p_times_y(size(x))
integer i, j, n
! array expressions
y = x**2 + 1.0
z=x/y
! scalar broadcast
p = 0.0
! sections
n = size(x)

49 of 53
do i = 1, n
p(i,:) = z * (1.0 / (1.0 + i))
enddo

p_times_y = matmul (p, y)

end function manipulate4

50 of 53
M in i-le ss o n # 2 : Yo u c a n a d d e x p lic it
in te r fa c e s to y o u r e x istin g p ro g r a m n o w .
Add a module to each “physics package” and in it declare
explicit interfaces to the functions in that package.
In each routine that implements or calls one of the
functions, add a use statement.
Compile everything with f90 or f95.

51 of 53
H om ew ork
If you’re going to just sit there, you’ll have more fun at a
movie.
1 . W rite a n d d e m o th is fu n c tio n :
function stats(x), where x is a one-dimensional real array.
Return value is a real array y containing the following
items:
y(1) = mean of x
y(2) = percentage of the array actually greater than the
mean
y(3) = variance (average the squares of the differences
between each element and the mean).
Use a kind for the arrays.

52 of 53
2 . W rite a n d d e m o a fu n c tio n w h ic h re tu rn s
th e o u te r p ro d u c t o f tw o v e c to rs g iv e n a s
a rg u m e n ts .
If x and y are vectors, the outer product w is defined as
having elements w(i,j) = x(i)*y(j)).
3 . G o rip o u t a c o m m o n b lo c k in o n e o f y o u r
co d es. F eel g o o d ?

53 of 53
Lesson 2: Modules and Derived Types
Paul F. Dubois
X-Division
dubois1@llnl.gov

54 of 106
F o r tr a n 9 0 /9 5 a re s ig n ific a n tly d iffe re n t
th a n F o r tr a n 7 7 .

55 of 106
In th e fir st le ss o n , w e c o n c e n tr a te d o n
m o d u le s a n d a r r a y s .
Modules are the replacement for common blocks, and they
can hold both data and functions.
We learned that F95 has an array language similar to that in
Matlab or Basis, and that arrays can now be passed as self-
contained arguments and returned from functions.

56 of 106
To re c e iv e th is a n d m a n y o th e r b e n e fits w e
m u s t m a k e th e in te r fa c e to a su b p ro g r a m
e x p lic it.
There are three ways to do that:
•P u ttin g th e s u b p ro g ra m in a m o d u le , o r
•P u ttin g a n in te rfa c e d e c la ra tio n fo r it in a
m o d u le , a n d
•U s e ’in g th a t m o d u le w h e re a p p ro p ria te

57 of 106
A n sw e r s to th e h o m e w o r k
1. Write and demo this function:
function stats(x)
x is a one-dimensional real array. (Use a kind for the
array).
return value is a real array y containing the following
items:
y(1) = mean of x
y(2) = percentage of the array actually greater than the
mean
y(3) = variance (average the squares of the differences
between each element and the mean).

58 of 106
2. Write and demo a function which returns the outer
product of two vectors given as arguments. (If x and y are
vectors, the outer product w is defined as having elements
w(i,j) = x(i) * y(j)).
3. Go rip out a common block in one of your codes. Feel
good?

59 of 106
module hw1
use precision
implicit none
contains

function stats(x) result(y)


real(adequate), intent(in), dimension(:):: x
real(adequate) y(3), mean

mean = sum(x) / size(x)


y(1) = mean
y(2) = real (count (x > mean), adequate) / size(x)
y(3) = sum ((x - mean)**2) / size(x)
end function stats

60 of 106
function outer (x, y) result(z)
real(adequate), intent(in):: x(:), y(:)
real(adequate) z(size(x), size(y))
integer i

do i = 1, size(x)
z(i, :) = x(i) * y
enddo
end function outer

end module hw1

61 of 106
program test1
use hw1
implicit none

real(adequate) x(5), y(5)

x = (/ 1., 2., 3., 4., 5. /)


y = 10 * x

print *, stats(x)
print *, outer(x, y)
end program test1

62 of 106
In th is le s so n w e w ill le a r n m o re a b o u t
m o d u le s a n d th e n le a r n h o w to d e fin e o u r
o w n d a ta ty p e s .
Each of these ideas is important on their own.
Together, they enable an object-based approach to Fortran
programming.

63 of 106
M o d u le s fill se v e r a l n e e d s .
1 . P ro v id e a re p la c e m e n t fo r c o m m o n /in c lu d e .
2 . A llo w d e fin in g o f u s e r-d e fin e d ty p e s a n d
o p e ra to rs .
3 . P e rm it th e c o n s tru c tio n o f s e lf-c o n ta in e d
s o ftw a re lib ra rie s .
4 . P ro v id e a m e a n s fo r d a ta a b s tra c tio n .

64 of 106
Yo u h a v e p re c is e c o n tro l o v e r th e n a m e s in
a m o d u le .
module mod1
use precision
private ! makes names private by default
real(adequate),public:: x, z
real(adequate) y
public adequate, precise, display
contains

65 of 106
subroutine display(label)
character(len=*),intent(in),optional:: label
if(present(label)) then
write(11, *), label
endif
write(11, *) x, y, z
end subroutine display
end module mod1

66 of 106
subroutine example1
use mod1
implicit none
integer y !does not conflict with the private y in mod1
x=3
y=2
call display ("example1")
end subroutine example1

67 of 106
A lw a y s b e g in a m o d u le w ith a n y u se
sta te m e n ts fo llo w e d b y im p lic it n o n e .
module mod2
use mod1
! left out the implicit none, trouble follows...
private

public y ! creates a new variable y of default type real


! it doesn't succeed in making mod1::y public
end module mod2

68 of 106
subroutine example2
use mod2
implicit none
! real x does not compile, x still public
x = 9.0
y = 7.0
call display("example2")
end subroutine example2

69 of 106
It is ju st a m a tte r o f s ty le a s to w h ic h
d e fa u lt y o u u se a n d w h ic h m e th o d o f
d e c la r in g n o n -d e fa u lts .
I personally favor default private, and a separate “public”
statement. This requires an affirmative step to make things
public and also makes a nice visible list of the public names.

70 of 106
module foo
implicit none
private
public x, y, z, w
real, dimension(:), allocatable:: x, y, z, w
real, dimension(:), allocatable:: a_temporary
contains
function hidden
...
allocate(a_temporary(size(x)))
...
deallocate(a_temporary)
end module foo

71 of 106
D e fin in g y o u r o w n ty p e s a n d th e o p e r a tio n s
th e y s u p p o r t is th e k e y to sp e c ia liz in g
F o r tr a n fo r y o u r a p p lic a tio n a re a .
A data type comprises:
•a n a m e fo r th e ty p e
•th e s e t o f v a lu e s th e in s ta n c e s o f th e ty p e c a n
assu m e
•th e s e t o f o p e ra tio n s th e ty p e s u p p o rts
•a fo rm fo r w ritin g c o n s ta n ts o f th a t ty p e

72 of 106
T h e n a tiv e ty p e s in a la n g u a g e h a v e n a m e s ,
v a lu e s, o p e r a tio n s , a n d c o n s ta n ts th a t a re
a lre a d y d e te r m in e d .
•N a m e : in te g e r
•Va lu e s : p o s itiv e a n d n e g a tiv e in te g e rs w ith in
s o m e p ro c e s s o r-d e p e n d e n t b o u n d s .
•O p e ra tio n s : p lu s , m in u s , tim e s , d iv id e , ...
•C o n s ta n t fo rm : 1 2 3 , 4 5 6 _ m y k in d

73 of 106
T h e d e r iv e d -ty p e d e c la r a tio n is sim p ly th e
ty p e n a m e w ith a lis t o f th e d e sire d
c o m p o n e n ts .
module mod3
use precision
implicit none
public

type atom
real(adequate) mass
integer charge
end type atom

end module mod3

74 of 106
ty p e (a to m ) n o w is a ty p e w e c a n u s e in th e
sa m e w a y w e u se “ in te g e r ” .
subroutine example3
use mod3
implicit none
type(atom) h, he, hep
type(atom), parameter:: omm = atom(16.0, -2)

75 of 106
h = atom ( 1.0, 0)
he = atom (omm%mass/4, 0)
hep = he
hep%charge = 1
write(11, *) "h ", h
write(11, *) "he ", he
write(11, *) "hep ", hep
end subroutine example3

76 of 106
T h is e x a m p le illu str a te s a ll th e m a in fa c ts
a b o u t d e r iv e d ty p e s.
•To a c c e s s a c o m p o n e n t v a lu e , w e u s e th e %
o p e ra to r. (To o b a d it is n ’t a p e rio d , b u t
F o rtra n h a d to liv e w ith .lt., .tru e ., e tc .).
•A s s ig n m e n t is e q u iv a le n t to a s e rie s o f
a s s ig n m e n t s ta te m e n ts o f e a c h
c o rre s p o n d in g c o m p o n e n t v a lu e .
•T h e ty p e n a m e a ls o b e c o m e s th e
“ c o n s tru c to r” fo r b o th c o n s ta n t a n d
tra n s ie n t v a lu e s .

77 of 106
T h e ty p e d e c la r a tio n d e fin e s th re e o f th e
fo u r p ro p e r tie s o f th e ty p e .
1 . N a m e : th e n a m e g iv e n in th e d e c la ra tio n
2 . Va lu e s : th e s e t p ro d u c t o f th e v a lu e s
p o s s ib le fo r e a c h c o m p o n e n t.
3 . O p e ra tio n s : O th e r o p e ra tio n s m a y b e
d e fin e d , b u t th e ty p e d e c la ra tio n d o e s n ’t d o
it.
4 . T h e n a m e o f th e ty p e b e c o m e s th e n a m e
u s e d to fo rm c o n s ta n ts o f th a t ty p e . T h e
a rg u m e n t lis t m u s t lis t o n e a p p ro p ria te
v a lu e fo r e a c h c o m p o n e n t.

78 of 106
To d is c u ss w h a t h a p p e n s w h e n a
c o m p o n e n t is a p o in te r, w e m u st d ig re s s
a n d le a r n a little m o re a b o u t p o in te r s.
•P o in te rs c a n b e “ a s s o c ia te d ” w ith s o m e
ta rg e t, o r “ d is a s s o c ia te d ” . Yo u c a n te s t
w h e th e r a p o in te r is a s s o c ia te d o r n o t, o r
a s s o c ia te d to a c e rta in ta rg e t, w ith th e
in trin s ic fu n c tio n a s s o c ia te d .

79 of 106
T h e re a re tw o “ a ss ig n m e n t” o p e r a to r s fo r
p o in te r s:
1 . R e g u la r a s s ig n m e n t s ta te m e n t: th e _ p o in te r
= s o m e _ v a lu e
T h is a s s ig n s s o m e _ v a lu e to th e o b je c t to
w h ic h th e _ p o in te r is c u rre n tly “ a s s o c ia te d ” ,
c a lle d its “ ta rg e t” .
2 . P o in te r a s s ig n m e n t s ta te m e n t: th e _ p o in te r
= > s o m e _ ta rg e t
T h is c h a n g e s th e a s s o c ia tio n o f th e _ p o in te r
to s o m e _ ta rg e t. O r, if s o m e _ ta rg e t is a
p o in te r a ls o , th e _ p o in te r is a s s o c ia te d to its
ta rg e t.

80 of 106
If a d e r iv e d ty p e h a s a p o in te r c o m p o n e n t,
th e n o r m a l “ a ss ig n m e n t” o p e r a to r d o e s
p o in te r a s sig n m e n t o n c o m p o n e n ts w h ic h
a re p o in te r s .
subroutine example3a
use precision

type curve
real(adequate), dimension(:), pointer:: x, y
end type curve

real(adequate), target:: x(4) = (/ (i, i=1, 4) /)


real(adequate), target:: y(4), z(4)
real(adequate), pointer:: zp(:)

81 of 106
type(curve) my_curve

y = x**2
zp => z ! pointer assignment, zp now associated with z
zp = y ! assignment, z now has same values as y
write(11, *) "z ", z

my_curve = curve(x, y)
! due to pointer components, cannot simply write *
write(11, *) "mycurve%x ", my_curve%x
write(11, *) "mycurve%y ", my_curve%y
end subroutine example3a

82 of 106
T h e ty p e n a m e is a ls o u s e d to c re a te n e w
in s ta n c e s o f th e ty p e a t r u n tim e .
So what happened when we said my_curve = curve (x, y)?
1 . T h e c u rv e (x , y ) c o n s tru c ts a te m p o ra ry
o b je c t T o f ty p e c u rv e . It in itia liz e s th e x
c o m p o n e n t b y p o in te r a s s ig n m e n t to x . It
in itia liz e s th e y c o m p o n e n t b y p o in te r
a s s ig n m e n t to y.
2 . T h e a s s ig n m e n t s ta te m e n t d o e s
m y _ c u rv e % x = > T % x . B u t T % x is a ls o a
p o in te r, s o m y _ c u rv e % x is a s s o c ia te d w ith
its ta rg e t, n a m e ly x .

83 of 106
3 . L ik e w is e , m y _ c u rv e % y e n d s u p a s s o c ia te d
w ith y.
Object-oriented persons will note that this is the only
constructor for the derived type, and that there is no
destructor.

84 of 106
U se d s e p a r a te ly, w e s e e th a t m o d u le s a n d
d e r iv e d ty p e s e a c h h a v e s o m e a sp e c t o f
c la ss e s .
Modules can contain both data and functions, and do
information hiding. But there is only one instance of the
data in a module.
Derived types have a constructor that can be used as a
cookie cutter to produce instances, but they do not contain
methods.
Derived types do have the possibility of hiding all or part of
their data but you lose some conveniences if you do so.

85 of 106
It is p o s sib le to h a v e a p u b lic ty p e w h o se
c o m p o n e n ts a re p r iv a te .
module mod4
use precision
implicit none
public

type atom
private
real(adequate) mass
integer charge
end type atom

contains

86 of 106
You give up the ability to use the “constructor”

atom (amass, acharge)

outside of the module, since presumably nobody else knows


anymore what is inside of an atom.

Likewise, the compiler can no longer write such objects for


you using data-directed i/o.

87 of 106
W e n e e d to p u t ro u tin e s in to th e m o d u le to
re tr ie v e a n d m a n ip u la te th e c o m p o n e n ts.
This is reminiscent of C++’s common paradigm of private
components and public accessors.

88 of 106
subroutine atom_new (a, name)
character*(*), intent(in):: name
type(atom), intent(out):: a
select case(name)
case("H")
a = atom(1.0, 0)
case("He")
a = atom(4.0, 0)
case("C")
a = atom(12.0, 0)
case default
stop "Illegal atom creation attempted."
end select
end subroutine atom_new

89 of 106
function atom_mass (a)
real(adequate) atom_mass
type(atom), intent(in):: a
atom_mass = a%mass
end function atom_mass

90 of 106
N o te th e c o n v e n tio n o f h a v in g th e fir s t
a r g u m e n t b e th e a to m to b e o p e r a te d u p o n .
function atom_charge (a)
real(adequate) atom_charge
type(atom), intent(in):: a
atom_charge = a%charge
end function atom_charge
function atom_as_string (a)
type(atom), intent(in):: a
character*(32) atom_as_string
write (atom_as_string, 100) a%mass, a%charge
100 format("atom( ", e14.4, ", ", i2, ")")
end function atom_as_string

91 of 106
subroutine set_atom_mass (a, m)
type(atom), intent(inout):: a
real(adequate), intent(in):: m
a%mass = m
end subroutine set_atom_mass
subroutine set_atom_charge (a, c)
type(atom), intent(inout):: a
integer, intent(in):: c
a%charge = c
end subroutine set_atom_charge
end module mod4

92 of 106
N o w w e c a n c re a te a n d m a n ip u la te o u r
a to m s w ith th e a c c e ss o r fu n c tio n s.
subroutine example4
use mod4
type(atom) a1, a2, a3
call atom_new(a1, "H")
call atom_new(a2, "He")
call atom_new(a3, "He")
call set_atom_charge(a3, -1)
! write(11, *) a1 (no good, type(a) has private
components)
write(11, *) "atom_mass(a3) ", atom_mass(a3)
write(11, *) "a3 ", trim(atom_as_string(a3))
end subroutine example4

93 of 106
G e n e r ic in te r fa c e s c a n b e sp e c ifie d to a llo w
y o u to tre a t m a n y d iffe re n t ty p e s in a
sim ila r m a n n e r.
subroutine example5
use atoms
use molecules
type(atom) a1, a2, a3
type(molecule) m1, m2, m3

call new(a1, "H")


call new(a2, "He")
call new(a3, "He")
call set_charge(a3, -1)

94 of 106
call new(m1, "O2")
call new(m2, "CH4")
call new(m3, "H2O")
call set_charge(m3, 0)

write(11, *) "mass(m2) ", mass(m2)


write(11, *) "a3 ", trim(as_string(a3))
write(11, *) "m3 ", trim(as_string(m3))
end subroutine example5

95 of 106
To d o th is w e a d d in te r fa c e sta te m e n ts fo r
e a c h n e w g e n e r ic fu n c tio n n a m e w e w a n t.
module atoms
use precision
implicit none
private

type atom
private
real(adequate) mass
integer charge
end type atom

public atom, mass, charge, set_mass, set_charge, new, &

96 of 106
as_string

interface new
module procedure atom_new
end interface new

interface mass
module procedure atom_mass
end interface mass

97 of 106
interface charge
module procedure atom_charge
end interface charge

interface set_mass
module procedure set_atom_mass
end interface set_mass

interface set_charge
module procedure set_atom_charge
end interface set_charge

interface as_string
module procedure atom_as_string

98 of 106
end interface as_string

contains

subroutine atom_new (a, name)


...
... the rest as it was before...
...
end module atoms

99 of 106
M o d u le m o le c u le s is v e r y s im ila r.
module molecules
use precision
implicit none
private

type molecule
private
real(adequate) mass
integer charge
integer number_of_elements, number_of_atoms
end type molecule

100 of
public molecule, mass, charge, set_mass, &
set_charge, new, as_string

interface new
module procedure molecule_new
end interface new

interface mass
module procedure molecule_mass
end interface mass
...

101 of
T h e re a re p ro s a n d c o n s to u s in g th is
“ p r iv a te c o m p o n e n t” sty le .
Pro: better locality. For example,
•if y o u h a v e a to m (m , c ) a ll o v e r th e c o d e , a n d
y o u g e t a n e w c o m p o n e n t, th o s e re fe re n c e s
m u s t b e a ll c h a n g e d . Yo u h a v e m o re
fle x ib ility if th e re a re o n e o r m o re
“ c o n s tru c to rs ” th a t y o u w rite , p o s s ib ly
u s in g k e y w o rd o r o p tio n a l a rg u m e n ts .

102 of
•O O p ro g ra m m e rs h a v e le a rn e d th a t if a c lie n t
c a n R E A D a c o m p o n e n t d ire c tly th e y c a n
W R IT E it, p o s s ib ly c re a tin g a n o b je c t th a t
n o lo n g e r h a s a v a lid v a lu e .

In fa c t, a .b o n th e le ft s id e o f a n a s s ig n m e n t
o p e ra to r is a re d fla g to a n e x p e rie n c e d O O
p ro g ra m m e r.

103 of
C o n : ta k e s m o re w o r k .
Besides, writing a%b = c is nice and clear and I never make
mistakes. And I can do the generic functions whether or not
the components are private. Anyway, I don’t trust the
compiler to do those accessors efficiently.

104 of
H om ew ork
Write a program with a user-defined type “point” that has x,
y, z components. Write another user-defined type
“quadrilateral” that has a component “vertices” that is an
array of 4 points. (For simplicity, make everything public).
Try creating and manipulating some quadrilaterals and
arrays of quadrilaterals.
If q is an array of quadrilaterals,
q(1)%vertices(1)%x
is the x’th coordinate of the first vertex of the first
quadrilateral in q.

105 of
But can you do q(1)%vertices%x, q(1)%vertices(2:3)%x,
q(2:4)%vertices%x?
Just how cool is this?
And what about
integer:: iv(3) = (/ 1, 2, 4 /)
real:: integer x(20)
What about:
x(iv)?
q(1)%vertices(iv)?

106 of
107 of
Lesson 3: Types and objects

Paul F. Dubois
X-Division
dubois1@llnl.gov

108 of
In o u r fir s t tw o le ss o n s , w e h a v e
c o n c e n tr a te d o n a r r a y s, m o d u le s , a n d
d e r iv e d ty p e s.
It is the combination of types and modules that allows us to
work in a style I will call “object-based”.
The homework should have helped you get a feel for
creating and working with derived types.

109 of
M in i-le ss o n # 3 : G iv e e a c h c o m p o n e n t in a
d e r iv e d ty p e a d e fa u lt in itia l v a lu e .
type particle
type(point):: location = point(0.0, 0.0, 0.0)
type(point):: momentum = point(0.0, 0.0, 0.0)
real(adequate):: mass = 1.0
real(adequate):: charge = 0.0
end type particle

The default initial value can be over-ridden by an explicit


one.
You must use the “entity-oriented” form of declaration with
the two colons.

11 0 o f 1 5 1
W e w ish to im p le m en t an
“a b strac t d ata typ e ”, in
w h ich n o “ille g al” o b jec ts
o f th is typ e ca n ev er b e
m ad e.
Initializing each instance properly is an important part of
this.

111 o f 1 5 1
M o d u le s a n d d e r iv e d ty p e s e a c h h a v e s o m e
a sp e c t o f c la ss e s.
Modules can contain both data and functions, and do
information hiding. But there is only one instance of the
data in a module.
Derived types have a constructor that can be used as a
cookie cutter to produce instances, but they do not contain
methods.
Derived types do have the possibility of hiding all or part of
their data but you lose some conveniences if you do so.
=> The secret is to combine the two.

11 2 o f 1 5 1
M in i-le ss o n # 4 : U s e a m o d u le to m o d e l
sin g le to n s.
A singleton is a class which has exactly one instance.
So, if you have some data which should exist exactly once
in your application, package it into a module, together with
the functions whose exclusive purpose is to manipulate that
data.
Then think out what you want the public interface to look
like.

11 3 o f 1 5 1
T h e g e n e r ic in te r fa c e c a p a b ility is m u c h
m o re p o w e r fu l th a n w e h a v e s e e n so fa r.
We used it to define a single name that could be applied to
objects of varied types. You can also use it to:
•d e fin e o p e ra to rs s u c h a s + a n d * ;
•a d d n e w o p e ra to rs s u c h a s .d o t., .in te g ra te .,
o r .in v e rs e ., o f y o u r o w n c h o o s in g ;
•ta k e o v e r th e a s s ig n m e n t o p e ra to r;
•e v e n e x te n d th e m e a n in g o f in trin s ic n a m e s
s u c h a s s q rt

11 4 o f 1 5 1
H e re is a m o d u le im p le m e n tin g a 3 -D p o in t
o b je c t.
module points
use precision
private
public dot, sqrt, norm
public operator(+), operator(-), operator(*), operator(/)

type,public:: point
real(adequate):: x = 0.0
real(adequate):: y = 0.0
real(adequate):: z = 0.0
end type point

11 5 o f 1 5 1
We’ve defined a new type named “point”. We’ve given
every component a default value so there won’t be any
uninitialized points.

Note the alternate syntax used for giving type(point) the


attribute “public”.

11 6 o f 1 5 1
N o w w e d e fin e th e b a s ic a r ith m e tic
o p e r a to r s to im p le m e n t v e c to r a r ith m e tic
o n p o in ts .
We supply three versions of each so that we can do
point+point, point+real, real+point, for convenient
operations such as translation and scaling.

interface operator(+)
module procedure point_add, point_add_s, point_s_add
end interface

11 7 o f 1 5 1
interface operator(-)
module procedure point_subtract, point_subtract_s, &
point_s_subtract, point_negate
end interface

interface operator(*)
module procedure point_multiply, point_multiply_s, &
point_s_multiply
end interface

interface operator(/)
module procedure point_divide, point_divide_s, &
point_s_divide
end interface

11 8 o f 1 5 1
M o d u le p ro c e d u re s d o th e re a l w o r k .
function point_add (a, b) result(r)
type(point), intent(in):: a, b
type(point):: r
r%x = a%x + b%x
r%y = a%y + b%y
r%z = a%z + b%z
end function point_add

function point_add_s (a, b) result(r)


type(point), intent(in):: a
real(adequate), intent(in):: b
type(point):: r

11 9 o f 1 5 1
r%x = a%x + b
r%y = a%y + b
r%z = a%z + b
end function point_add_s

function point_s_add (a, b) result(r)


type(point), intent(in):: b
real(adequate), intent(in):: a
type(point):: r
r%x = a + b%x
r%y = a + b%y
r%z = a + b%z
end function point_s_add
These are all in the procedure part of the module “points”.

120 of
T h e c o m p ile r c h o o se s a n a p p ro p r ia te
fu n c tio n b a s e d o n sig n a tu re .
type(point) x, y, z
z = x + y !actually does z = point_add(x, y)
z = x + 1.0 !actually does z = point_add_s(x, 1.0)
z = 1.0 + x !actually does z = point_s_add(1.0, x)

121 of
W e a lso d e fin e a g e n e r ic “ n o r m ” fu n c tio n ,
a b in a r y o p e r a to r fo r d o t p ro d u c t, a n d a n
e le m e n t-w ise s q u a re ro o t.
Users can write norm(v), v .dot. w, and sqrt(v). And yes,
sqrt(2.0) still works!

interface norm
module procedure point_norm
end interface

interface operator(.dot.)
module procedure point_dot
end interface

122 of
interface sqrt
module procedure point_sqrt
end interface

123 of
W e liste d in th e in te r fa c e fo r e a c h o p e r a to r
th e fu n c tio n s th a t th e c o m p ile r c o u ld u se to
d o th e jo b .
The functions were all in the module itself so all we had to
do was list them as “module procedures”.
We could also use functions defined elsewhere by putting
interface specifications for them into the interface blocks.
In the “contains” section of the module we put the actual
“worker” routines. These are all private to the module.

124 of
It is a ls o h e lp fu l to a d d u n a r y m in u s to th e
su b tr a c t in te r fa c e .
function point_negate (a) result(r)
type(point), intent(in):: a
type(point):: r

r%x = -a%x
r%y = -a%y
r%z = -a%z
end function point_negate

125 of
N o w w e d o th e n o r m , .d o t., a n d s q r t.
function point_norm(self) result(r)
type(point),intent(in):: self
real(adequate) r
r = sqrt(self%x**2 + self%y**2 + self%z**2)
end function point_norm

126 of
function point_dot(a, b) result(r)
type(point), intent(in):: a, b
real(adequate):: r
real(precise):: s
s = real(a%x, precise) * b%x + &
real(a%y, precise) * b%y + &
real(a%z, precise) * b%z
r = real(s, adequate)
end function point_dot

127 of
function point_sqrt(a) result(r)
type(point), intent(in):: a
type(point):: r
r%x = sqrt(a%x)
r%y = sqrt(a%y)
r%z = sqrt(a%z)
end function point_sqrt
end module points

128 of
L e t’s te st-d r iv e m o d u le p o in ts .
type(point), parameter:: origin = point(0.0, 0.0, 0.0)
type(point), parameter:: e1 = point(1.0, 0.0, 0.0)
type(point), parameter:: e2 = point(0.0, 1.0, 0.0)
type(point), parameter:: e3 = point(0.0, 0.0, 1.0)
type(point) x1, x2
x1 = 3.0 * e1 + 4.0 * e2 + 5.0 * e3
x2 = -4.0 * x1 - (2.0_adequate * e2) + e3
write(11, *) "x1 ", x1
write(11, *) "x2 ", x2
write(11, *) "norm(x1)", norm(x1)
write(11, *) "sqrt(x1)", sqrt(x1)
write(11, *) "dot product", x1 .dot. x2

129 of
N o te th a t k in d c o n v e r s io n w a s p e r fo r m e d ,
b u t ty p e c o n v e r sio n w o n ’t b e .
x1 = 3.0 * e1 + 4.0 * e2 + 5.0 * e3 !ok
x1 = 3.0 * e1 + 4.0 * e2 + 5 * e3 !doesn’t compile

Naturally, you could define two more “handlers” so that


each operation would work with integers.

130 of
S u p p o se w e w a n t to re p re s e n t p o in ts o n th e
u n it c irc le , a n d to b e a b le to a sk fo r th e ir x ,
y, a n d th e ta c o o r d in a te s.
However, we always want 0.0 <= theta < 2.0 * pi
We also want to be able to add and subtract angles from
such points, and to create the points from real numbers
representing the angle.

131 of
H e re is h o w w e a re g o in g to u s e e n titie s o f
ty p e u c p o in t.
type(point) a
type(ucpoint) r1, r2

r1 = pi / 4.0_adequate
r2 = -r1 + pi / 12.0_adequate
write (11, *) "r1 ", x (r1), y (r1), theta (r1)
write (11, *) "r2 ", x (r2), y (r2), theta (r2)
write (11, *) "r3 ", theta (as_ucpoint (-0.3 * pi))
a = point(x(r1), y(r1), 0.0)
write (11, *) "a ", a

132 of
module ucpoints !points on the unit circle
use precision
private
public ucpoint, as_ucpoint
public operator(+), operator(-), assignment(=)
public x, y, theta

type ucpoint
private
real(adequate):: theta = 0.0
end type ucpoint

133 of
interface assignment(=)
module procedure ucpoint_set
end interface

interface operator(+)
module procedure ucpoint_add_s, ucpoint_s_add
end interface

interface operator(-)
module procedure ucpoint_subtract_s, &
ucpoint_s_subtract, ucpoint_negate
end interface

134 of
N o w in th e p ro c e d u re p a r t o f th e m o d u le
w e d e fin e th e s e o p e r a to r s.
contains
function as_ucpoint(r) result(p)
real(adequate), intent(in):: r
type(ucpoint) p
p=r
end function as_ucpoint

function x(p)
type(ucpoint), intent(in):: p
real(adequate) x
x = cos(p%theta)
end function x

135 of
function y(p)
type(ucpoint), intent(in):: p
real(adequate) y
y = sin(p%theta)
end function y

function theta(p)
type(ucpoint), intent(in):: p
real(adequate) r
theta = p%theta
end function theta

136 of
To d e fin e th e a s sig n m e n t o p e r a to r w e
su p p ly a su b ro u tin e .
You can have multiple assignment handlers with different
signatures for the second argument.
subroutine ucpoint_set (p, r)
type(ucpoint), intent(out):: p
real(adequate), intent(in):: r
p%theta = modulo(r, 2.0_adequate * pi)
end subroutine ucpoint_set
Note that the intent of p must be out or inout. The intent of r
must be in.
The statement p = r will be handled by a call ucpoint_set(p,
r).

137 of
B y u s in g o u r o w n a s sig n m e n t o p e r a to r, w e
c a n in s u re th a t th e ta is a lw a y s in th e
d e sire d r a n g e .
function ucpoint_add_s (a, b) result(p)
type(ucpoint), intent(in):: a
real(adequate), intent(in):: b
type(ucpoint):: p

p = a%theta + b
end function ucpoint_add_s

Note that the assignment is really ucpoint_set (p, a%theta +


b).

138 of
T h u s, u cp o in t_s et m a ke s
su re o n ly leg a l u c p o in ts
ca n b e crea te d .
If each point is born correct, and each (public) operation
keeps it correct, it is always correct.

139 of
F o r tr a n 9 5 ’s d e r iv e d ty p e s c o m p a re
u n fa v o r a b ly to C + + ’s.

C om p arison of d erived types in F95


and C ++
N et
E ffe c t
fo r F 9 0 A re a o f c o n c e r n
v s.
C++
M in u s T h e re a re n o p ro v is io n s
fo r d e s tru c to rs .

M in u s T h e re is o n ly th e o n e
“o ffic ia l” c o n s tru c to r.

140 of
C om p arison of d erived types in F95
and C ++
N et
E ffe c t
fo r F 9 0 A re a o f c o n c e r n
v s.
C++
S lig h t P lu s T h e re is n o a u to m a tic s ig -
n a tu re m a tc h in g o r
im p lic it c o n v e rs io n s .

Huge N o in h e rita n c e in F o rtra n


M in u s 95

Huge N o p a ra m e te riz e d ty p e s
M in u s in F 9 5

H u g e P lu s Ty p e s a fe ty

141 of
C om p arison of d erived types in F95
and C ++
N et
E ffe c t
fo r F 9 0 A re a o f c o n c e r n
v s.
C++
H u g e P lu s In te ra c tio n o f a rra y fa c ility
w ith d e riv e d ty p e s .

H u g e P lu s E a s e o f le a rn in g to u s e
d e riv e d ty p e s c o rre c tly.

142 of
T h e jo b o f a d e str u c to r is to re le a se a n y
a ss e ts a c q u ire d b y a n o b je c t d u r in g its
life tim e .
module curves !points on the unit circle
use precision
private
public curve
public length, segment, create, destroy
public get_x, get_y

type curve
private
real(adequate), pointer:: x(:) => Null()
real(adequate), pointer:: y(:) => Null()

143 of
end type curve

interface create
module procedure curve_create
end interface create

interface destroy
module procedure curve_destroy
end interface destroy

interface length
module procedure curve_length
end interface length

144 of
D e fin e a ss ig n m e n t o f o n e c u r v e to a n o th e r
so th a t it m a k e s a c o p y.
interface assignment(=)
module procedure curve_set_curve
end interface

145 of
T h e c o n str u c to r a n d d e s tr u c to r a n d
a ss ig n m e n t o p e r a to r w o r k to g e th e r to
a v o id m e m o r y le a k s .
subroutine curve_create(c, x, y)
real(adequate), intent(in):: x(:), y(:)
type(curve), intent(inout):: c
if(size(x) /= size(y)) then
stop "curve assignment: incorrect sizes"
endif
call curve_destroy(c)
allocate(c%x(size(x)))
allocate(c%y(size(y)))
c%x = x
c%y = y

146 of
end subroutine curve_create

subroutine curve_set_curve(p, q)
type(curve), intent(inout):: p
type(curve), intent(in):: q
call curve_create (p, q%x, q%y)
end subroutine curve_set_curve

147 of
T h e d e str u c to r u se s th e “ a s so c ia te d ”
fu n c tio n to se e if m e m o r y h a s b e e n
a llo c a te d in th is c u r v e .
subroutine curve_destroy(p)
type(curve), intent(inout):: p
if(associated(p%x)) then
deallocate(p%x)
deallocate(p%y)
endif
end subroutine curve_destroy
end module curves

148 of
M e m o r y in te g r ity th e n d e p e n d s o n a
p ro g r a m m e r c o n v e n tio n to d e s tro y e a c h
ite m th a t is c re a te d .
subroutine try_curves
use precision
use curves
implicit none
type(curve) c1, c2, c3
real(adequate) xx(4), yy(4)
xx = (/ 1., 2., 3., 4. /)
yy = xx**2 + 1
call create(c1, xx, yy)
call create(c2, xx, yy / 2.)
write(11, *) "y(c2) ", y(c2)

149 of
... some coding which may or may not use c3....
call destroy(c1)
call destroy(c2)
call destroy(c3)
end subroutine try_curves

150 of
H om ew ork
A tic-tac-toe board consists of a 3 by 3 matrix. Each entry
can either be empty, an X, or an O. Create a tic-tac-toe
board object which is sufficiently rich to support writing a
tic-tac-toe game. In the game, users can “undo” moves right
back to the start. The board class should refuse to make
illegal moves and return an error flag if so requested.
There is no “right” answer.
How robust you make the input procedure is up to you.

151 of
152 of
Lesson 4: New features

Paul F. Dubois
X-Division
dubois1@llnl.gov

153 of
To c o m p le te o u r “ u p g r a d e ” to F 9 5 , th is
w e e k w e ’ll c o v e r s o m e o f th e n e w fe a tu re s
o f th e la n g u a g e .
Scaling considerations
More about working with arrays
Looping and control statements
More intrinsic functions
What’s still missing?
Caution: today’s example is strongly F95, not just F90.
You’ll have to comment out quite a few things to get it to
compile F90.

154 of
T h e e n v e lo p e , p le a s e ...
(The contest was won by George Zimmerman).

155 of
T h e m o d u le is th e k e y to h a p p in e s s, b u t
th e re a re p ro b le m s fo r la r g e p ro g r a m s .
The module is what remembers information between files.
So clearly the compiler must remember some information
about each module it encounters.
Typically, this is done by creating a module_name.mod file.
(Not universal, not standard).
When the compiler sees a “use” statement, it looks for the
.mod file.

156 of
M o d u le u s e m u s t fo r m a n a c y c lic d ire c te d
grap h .
Depending on the situation, you may decide to separate data
from functions.

module a_data
...
end module a_data
module b_data
...
end module b_data
module a
use a_data

157 of
use b_data
contains
functions that manipulate a_data
but sometimes need b_data
end module a_data

Similarly for b.

158 of
M in i-le ss o n # 5 : O n e m o d u le , o n e file
Often the module contains one type and implements an
object.
You can put module statements in a file with other program
units, but don’t.

159 of
F 9 5 su p p o r ts “ g o -to -le ss ” lo o p s.
x = (/ (i, i=1, n) /)
y = sqrt(x**2/3.0)
The old way to find a maximum...
t = x(1)
k=1
do i = 2, n
if(x(i) > t) then
t = x(i)
k=i
endif
enddo

160 of
New way #1...
t = x(1)
k=1
do i = 2, n
if(x(i) <= t) cycle
t = x(i)
k=i
enddo
New way #2...
t = maxval(x)
k = maxloc(x, 1)

161 of
T h e w o r d e x it n o w m e a n s to le a v e a lo o p ,
n o t th e p ro g r a m !
t = 12.0
k=0
do i = 1, n
if(x(i) == t) then
k=i
exit
endif
enddo

162 of
T h e d o w h ile lo o p is o fte n u se d fo r ite r a tiv e
p ro c e ss e s .
k=0
do while(k /= 0)
if(x(i) == t) k = i
end do

163 of
T h e k e y w o r d c y c le m e a n s to b e g in th e n e x t
lo o p ite r a tio n im m e d ia te ly.
This fragment finds the sum of elements of an array y
within the data range of another array, x.

w1 = minval (x)
w2 = maxval (x)
t = 0.0
do j = 1, n
if (y(j) > w2) cycle
if (w1 <= y(j)) then
t = t + y(j)
endif
enddo

164 of
write(11, *) "Sum of y elements within x range is ", t

165 of
A la b e l c a n b e u s e d to c o n tro l b e h a v io r in
n e ste d lo o p s .
outer: do i=1, n
inner: do j = 1, m
...
if (...) exit outer
enddo
enddo

However, loops of any sort are not fun to write.

F95 to the rescue!

166 of
M a s k e d a ss ig n m e n t e lim in a te s th e n e e d fo r
m a n y lo o p s.
where (w1 <= y .and. y <= w2)
z=y
elsewhere
z = 0.0
end where
write(11, *) "Same thing, without a loop ", sum(z)

167 of
T h e w h e re c o n str u c t a lso h a s a o n e -
sta te m e n t fo r m .
logical cond(size(y))
...
z = 0.0
cond = w1 <= y .and. y <=w2
where (cond) z = y
write(11, *) "Same thing, using where statement ", sum(z)

You might calculate cond separately like this if, for


example, you were going to use it several times. Otherwise,
it would be fine to just say

where(w1 <= y .and. y <= w2) z = y

168 of
Ve c to r iz a tio n u se d to b e p o ss ib le o n ly fo r
lo o p s u s in g in tr in s ic fu n c tio n s.
do i =1, n
x(i) = sqrt(y(i)) !vectorizes
x(i) = f(y(i)) !doesn’t
enddo

Now we face the same inequity with the array syntax:


x = sqrt(y) !ok
x(1) = f(y(1))
x = vector_version_of_f(y)

169 of
Generic interfaces would work so that you could just write
f(y) but you would have to write a separate function for
each rank of array.

170 of
If f is d e c la re d “ e le m e n ta l” , f(x ) w ill w o r k
o n a n y a r r a y.
elemental function f(x)
real(adequate), intent(in):: x
real(adequate):: f
f = sqrt(x / 3.0)
end function f

where(cond)
z = f(x)
elsewhere
z = 0.0
endwhere

171 of
write(11, *) "Same thing, using elemental function ",
sum(z)

x = x - 4.0 ! make some values negative


w1 = 0.0
cond = w1 <= y .and. y <= w2
where(cond)
z = f(x)
elsewhere
z = 0.0
endwhere
write(11, *) "f(x) not evaluated at bad points ", sum(z)

172 of
L o o p s a n d fu n c tio n s d isg u is e in fo r m a tio n
y o u m a y h a v e a b o u t p a r a lle lis m .
Two new facilities are provided.
•Yo u c a n d e c la re a fu n c tio n “ p u re ” to in d ic a te
it h a s n o s id e e ffe c ts .
•T h e fo ra ll c o n s tru c t e x p re s s e s p a ra lle l lo o p s
c o m p a c tly a n d c le a rly.

173 of
T h e fo r a ll s ta te m e n t a lso c o m e s in tw o
fla v o r s.
integer c(6)

forall(i=1:6) c(i) = 3 - i

forall(i=1:6)
c(i) = 3 - i
end forall

174 of
M u ltip le d im e n s io n s re p la c e n e ste d lo o p
c o n str u c ts .
integer, parameter:: n= 5, m = 6
integer a(n, m), b(n, m)

forall(i=1:n, j=1:m) a(i,j) = 10 * i + j

forall(i=1:n, j=1:m)
a(i, j) = 10 * i + j
b(i, j) = x(i) - y(j)
end forall

175 of
M a s k e d a s sig n m e n t is a lso su p p o r te d .
b=0
forall(i=1:n, j=1:m, a(i,j) > 22) b(i,j) = 1.0

176 of
N a m e list is n o w s ta n d a r d iz e d .
You declare a namelist group to contain a group of variables
that you wish to read or write as a group.

namelist /ab/ a, b

•T h e “ a b ” is c a lle d th e “ g ro u p n a m e ” .
•It c a n b e u s e d fo r in p u t o r o u tp u t.
•It ra n re a d w h a t it w ro te .
•W h a t it w ro te m ig h t b e u g ly.

177 of
Yo u u s e th e N M L k e y w o r d in a re a d o r
w r ite sta te m e n t in ste a d o f a fo r m a t.
forall(i=1:n, j=1:m)
a(i,j) = i + j
b(i,j) = i - j
end forall
write(11, NML=ab)

Here is what it wrote.


&AB
A = 11, 21, 31, 41, 12, 22, 32, 42, 13,
23, 33, 43, 14, 24, 34, 44, 15, 25, 35,
45,
B = 2*0, 2*1, 2*0, 2*1, 0, 3*1, 0, 3*1, 0, 3*1
/

178 of
Yo u c a n c a ll fu n c tio n s u sin g k e y w o r d s .
subroutine go(x, y, z)
call go(1, 2, 3)
call go(1, z=4, y=2)
call go(x=1, z=2, y=3)
To do this, subroutine go must have an explicit interface.

179 of
T h e re a re s o m e in te re s tin g a r r a y -o r ie n te d
in tr in s ic fu n c tio n s .
spread is used to replicate parts of arrays to make larger
dimensional versions.

a = 10 * spread(iotan, dim=2, ncopies=m) + &


spread(iotam, dim=1, ncopies=n)
is the same as:
forall(i=1:m, j=1:n) a(i,j) = 10 * i + j

We could have done our outer product with spread.

180 of
H e re a re s o m e o th e r a r r a y fu n c tio n s y o u
m ig h t w a n t to e x p lo re .
•c s h ift -- c irc u la r s h ift
•e o s h ift -- e n d -o ff s h ift
•m a tm u l -- m a trix m u ltip ly
•d o t_ p ro d u c t
•c o u n t -- c o u n tin g tru e e le m e n ts in lo g ic a l
e x p re s s io n s
•m e rg e (tru e _ s o u rc e , fa ls e _ s o u rc e , m a s k )
•p a c k (a rra y, m a s k ) -- c o m p re s s

181 of
T h e re sh a p e fu n c tio n is in c re d ib ly
p o w e r fu l.
Use it for reshaping and reordering subscripts.

reshape(source, shape, pad, order)

reshape( iota(6), (/ 2, 3 /)) is the matrix


135
246

reshape( iota(6), (/ 2, 4 /), (/ 0, 0 /), (/ 2, 1 /))


1234
5600

182 of
R e s h a p e c a n b e u s e d to m a k e a n a r r a y o n e -
d im e n s io n a l
real(adequate) a(n,m), z(n*m)
z = reshape(a, (/ size(a) /))

You can also do it with transfer(a,a). The transfer function is


extremely powerful, non-portable, and fun.

“I shouldn’t tell you about this...” -- Jeanne Martin

I deny ever telling you about it.

183 of
M o s t o f th e in q u ir y o p e r a to r s o n a r r a y s a re
a b le to ta k e a n e x tr a a r g u m e n t in d ic a tin g a
d im e n s io n .
shape(a) 4 5

Sum up columns
sum(a,1) 14 18 22 26 30

Sum up rows
sum(a,2) 20 25 30 35

Sum up array
sum(a) 110

184 of
A lso , m o s t o f th e sc a la r in tr in sic s a re
e le m e n ta l, so y o u c a n u se th e m o n a r r a y s .
•s q rt, e x p , c o s , ...
•d im (x , y ) -- x - y b u t flo o re d a t z e ro
•ra n d o m _ n u m b e r(z )

185 of
S o w h y d id n ’t I w a n t to le a r n F 9 0 b e fo re ?
•S tu p id ity
•N o c o m p ile rs
•N o p e rfo rm a n c e
but more seriously
•N o in h e rita n c e
•N o p o ly m o rp h is m / d y n a m ic b in d in g
•N o g a rb a g e c o lle c tio n
•N o e x c e p tio n h a n d lin g

186 of
•N o g e n e ric ty p e s
•N o c o m m a n d lin e a rg u m e n ts
•N o s ig n a l h a n d lin g
•N o s trin g s

187 of
T h e str in g fa c ilitie s in F 9 5 a re s till
m a ss iv e ly a n n o y in g .
character(len=32):: s = “hello”
character(len=32):: t = “ world”
character(len=32):: greeting
greeting = s // ' ' // t !Not...sets greeting to “hello”
greeting = trim(s) // ' '
greeting(len(trim(s)) + 1: ) = t !Just shoot me...
You can’t even write a function that returns a variably sized
string such as a file name with no trailing blanks, I thought.
(I was wrong, as we shall see.)

188 of
H e y ! I d e a ! I c a n w r ite m y o w n str in g ty p e !

type string
character(len=1), pointer:: storage(1)
integer capacity
integer length
end type string

and go ahead and make a string object out of it.

Hey! Wait! If this is such a great idea, why didn’t ISO do it?

189 of
A c tu a lly, IS O d id d o it.
They made a separate standard for it and never mention it
out loud.
I had to ask Jeanne Martin for it, and she didn’t even have a
copy.

MODULE ISO_VARYING_STRING

! Written by J.L.Schonfelder
! Incorporating suggestions by C.Tanasescu, C.Weber, J.Wagener and W.Walter,
! and corrections due to L.Moss, M.Cohen, P.Griffiths, B.T.Smith
! and many other members of the committee ISO/IEC JTC1/SC22/WG5

! Version produced (??-Jul-94)

!-----------------------------------------------------------------------------!
! This module defines the interface and one possible implementation for a !
! dynamic length character string facility in Fortran 90. The Fortran 90 !
! language is defined by the standard ISO/IEC 1539 : 1991. !
! The publicly accessible interface defined by this module is conformant !

190 of
! with the auxilliary standard, ISO/IEC 1539-2 : 1994. !
! The detailed implementation may be considered as an informal definition of !
! the required semantics, and may also be used as a guide to the production !
! of a portable implementation. !
! N.B. Although every care has been taken to produce valid Fortran code in !
! construction of this module no guarantee is given or implied that this !
! code will work correctly without error on any specific processor, nor !
! is this implementation intended to be in any way optimal either in use !
! of storage or CPU cycles. !
!-----------------------------------------------------------------------------!

Gosh, how reassuring...

191 of
In d e e d , v a r y in g str in g se e m s to b e
so m e th in g lik e w h a t I im a g in e d .
TYPE VARYING_STRING
PRIVATE
CHARACTER,DIMENSION(:),POINTER :: chars
ENDTYPE VARYING_STRING
...
PUBLIC :: VARYING_STRING,VAR_STR,CHAR,LEN,GET,PUT,PUT_LINE,INSERT,REPLACE,
SPLIT,REMOVE,REPEAT,EXTRACT,INDEX,SCAN,VERIFY,LLT,LLE,LGE,LGT,
ASSIGNMENT(=),OPERATOR(//),OPERATOR(==),OPERATOR(/=),OPERATOR(<),
OPERATOR(<=),OPERATOR(>=),OPERATOR(>),LEN_TRIM,TRIM,IACHAR,ICHAR,
ADJUSTL,ADJUSTR

192 of
L e t’s ta k e it fo r a te st d r iv e .
subroutine try_string
! try the ISO varying_string
use iso_varying_string
implicit none
type(varying_string) s, t, u
s = "hello"
t = "world"
u = s // var_str(" ") // t
write(11, *) char(u)
end subroutine try_string

...and it nicely writes out “hello world”.

193 of
T h e str in g th a t is p r in te d tu r n e d o u t n o t to
h a v e a n y o b n o x io u s p a d d in g o n th e e n d .
Indeed, the source for the char() operator teaches us how:

FUNCTION s_to_c(string)
type(VARYING_STRING),INTENT(IN) :: string
CHARACTER(LEN=SIZE(string%chars)) :: s_to_c
! returns the characters of string as an automatically
! sized character
INTEGER :: lc
lc=SIZE(string%chars)
DO i=1,lc
s_to_c(i:i) = string%chars(i)

194 of
ENDDO
ENDFUNCTION s_to_c

Remember how we couldn’t do real(kind(x)) for an


argument x?
That doesn’t apply here as it is simply a matter of how much
automatic storage is needed.

195 of
H o w y o u g o n n a k e e p ‘e m , d o w n o n th e
fa r m ...
Now that you have looked over, and seen the promised land,
I’m sure you’ll get there.
I hope you have enjoyed your upgrade experience.
There is no support number.

-- Paul

196 of

You might also like