Transcript
Page 1: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Introduction to Fortran 90/95/2003NGSSC Cource : Programming in Science and Technology 2008Jonas Lindemann

Page 2: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

History

Page 3: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Fortran Development

First version 1954

FORTRAN 66FORTRAN 77

Fortran 90 – Backwards compatible

(The F programming language)Fortran 95

Fortran 2003, (2004)

Page 4: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Pascalprogram tpk(input,output);var i : integer;y : real;a : array [0..10] of real;

function f ( t : real) : real;beginf := sqrt(abs(t)) + 5*t*t*t

end;

beginfor i := 0 to 10 do read(a[i]);for i := 10 downto 0 dobeginy := f(a[i]);if y > 400 then writeln(i,' TOO LARGE')

else writeln(i,y);

end;end;

end.

Page 5: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

C#include <stdio.h>#include <stdlib.h>#include <math.h>

double f (double t){

double temp;temp = sqrt(fabs(t)) + 5*pow(t,3);return temp;

}

int main(){

int i;double y;double a[11];for ( i = 0; i <= 10; ++i)

scanf("%lf", &a[i]);for ( i = 10; i >= 0; i = i - 1 ) {

y = f(a[i]);if ( y > 400 ) {

printf(" %d",i); printf(" TOO LARGE\n");

}else {

printf(" %d",i); printf(" %lf",y); printf(" \n");

}}return 0;

}

Page 6: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

FORTRAN 0

DIMENSION A(11)READ A

2 DO 3,8,11 J=1,113 I=11-J

Y=SQRT(ABS(A(I+1)))+5*A(I+1)**3IF (400>=Y) 8,4

4 PRINT I,999.GOTO 2

8 PRINT I,Y11 STOP

Page 7: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

FORTRAN I

C FORTRAN I STYLEFUNF(T)=SQRTF(ABSF(T))+5.0*T**3DIMENSION A(11)

1 FORMAT(6F12.4)READ 1,ADO 10 J=1,11I=11-JY=FUNF(A(I+1))IF(400.0-Y)4,8,8

4 PRINT 5,I5 FORMAT(I10,10H TOO LARGE)

GOTO 108 PRINT 9,I,Y9 FORMAT(I10,F12.7)

10 CONTINUESTOP 52525

Page 8: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

FORTRAN IV eller Fortran 66

C FORTRAN IV STYLEDIMENSION A(11)FUN(T) = SQRT(ABS(T)) + 5.0*T**3READ (5,1) A

1 FORMAT(5F10.2)DO 10 J = 1, 11

I = 11 - JY = FUN(A(I+1))IF (400.0-Y) 4, 8, 8

4 WRITE (6,5) I5 FORMAT(I10, 10H TOO LARGE)

GO TO 108 WRITE(6,9) I, Y

FORMAT(I10, F12.6)10 CONTINUE

STOPEND

Page 9: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Fortran 77PROGRAM TPK

C FORTRAN 77 STYLEREAL A(0:10)READ (5,*) ADO 10 I = 10, 0, -1

Y = FUN(A(I))IF ( Y .LT. 400) THEN

WRITE(6,9) I, Y9 FORMAT(I10, F12.6)

ELSEWRITE (6,5) I

5 FORMAT(I10,' TOO LARGE')ENDIF

10 CONTINUEEND

REAL FUNCTION FUN(T)REAL TFUN = SQRT(ABS(T)) + 5.0*T**3END

Page 10: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Fortran 90/95program tpk! Fortran 90 styleimplicit noneinteger :: ireal :: yreal, dimension(0:10) :: Aread (*,*) Ado i = 10, 0, -1 ! Backwards

y = fun(A(I))if ( y < 400.0 ) then

write (*,*) i, yelse

write (*,*) i, ' Too large'end if

end docontains ! Local functionfunction fun(t)

real :: funreal, intent(in) :: tfun = sqrt(abs(t)) + 5.0*t**3

end function funend program tpk

Page 11: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Fprogram tpk! Fortran F styleimplicit noneinteger :: ireal :: yreal, dimension(0:10) :: Aread *, Ado i = 10, 0, -1 ! Backwards

y = fun(A(I))if ( y < 400.0 ) then

print *, i, yelse

print *, i, "Too large"end if

end docontains ! Local functionfunction fun(t) result(fun_result)

real :: fun_resultreal, intent(in) :: tfun_result = sqrt(abs(t)) + 5.0*t**3

end function funend program tpk

Page 12: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Language elements

Page 13: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Source form

Free form Fixed form

Source format Max 132 characters Code in positions 7‐72, linenumbers in position 2‐5

Comments ! anywhere on a line !, C or * at position 1

Continuation & at end of line character at position 6 on continuation line

Multiple statements per line

; between statements On statement per row

Page 14: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Example of Fortran 90/95 codeprogram example

implicit none

integer, parameter ::  ap=selected_real_kind(15,300)real(ap) :: x,yREAL(ap) :: K(20,20)

x = 6.0_ap   ! This is line comment

y =  &0.25_ap + &0.25_ap

write(*,*) x; write(*,*) ywrite(*,*) ap

call myproc(K)

stop

end program example

Page 15: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Variable names

Max 31 characters

Letters a‐z, A‐Z (not Å, Ä, Ö) Numbers 0‐9 

Underscore _ 

First character must be a letterLower case letters equivalent with upper caseletters 

Page 16: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Variabletypes

integer Integer

real Floating point

complex Complex numbers

logical Boolean variables

character Characters and strings

Page 17: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Variable declaration

integer :: i Scalar integer

real :: p Floating point scalar

integer, parameter :: a = 5 Integer constant

integer, dimension(10)  :: b Integer array with 10 elements

real :: C(10) Floating point array with 10 elements

real :: K(20,20) Floating point array with 20 x 20 elements

Page 18: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Variable type parameters

integer(kind=4)   :: a integer(4)        :: b ! Short form

real(kind=8)      :: c real(8)           :: a ! Short form

character(len=20) :: textstringcharacter(20)     :: textstring2character(len=20, kind=1) :: textstring3     ! english stringcharacter(len=20, kind=kanji) :: textstring4 ! kanji string

integer and real typeparameters system 

dependent.

Page 19: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Determining appropriate type

selected_int_kind(r) returns the appropriatetype parameter to represent all integer values, n, in the range ‐10r < n < 10r

selected_real_kind(p,r) returns the appropriatetype parameter for representing a number with at least p decimal precsicion and decimal exponent range of at least r

Page 20: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Appropriate type ‐ example

integer, parameter :: rk = selected_real_kind(15,300)

integer, parameter :: ik = selected_real_kind(6)

real(kind=rk) :: xreal(rk) :: y

integer(kind=ik) :: zinteger(ik) :: c

Page 21: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

General type rule

Undeclared variables are defined as integer if the variable name starts with i,j,k,l,m,n, otherwisereal.

The implicit none directive forces declarationof all variables. Recommended.

Page 22: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Array storage

1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16

1 9

2 10

3 11

4 12

5 13

6 14

7 15

8 16

1 3

2 4

5 7

6 8

9 11

10 12

13 15

14 16

real :: A(16)

real :: A(8,2)

real :: A(2,8)

Page 23: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Character and strings

Declaration Description

Character :: ch Character

character, dimension(60) :: chv array of characters

character :: chv(60) array of characters

character(len=80) :: line character string

character :: line*80 character string

character(len=80), dimension(60) :: page array of strings

character(len=80) :: page(60) array of strings

Page 24: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Derived data types

type pointreal :: xreal :: yreal :: size

end type point

Type definition:

type(point) :: point ! Structure

Declaration statement:

Accessing structure member variables:

point%x = 1.0point%y = 2.0point%size = 4.0

Page 25: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Assignments

integer :: mm

integer, parameter :: ap = 8

real(kind=ap) :: pi

mm = 113

pi = 3.141592653589793_ap

m = 113

pi = 3.141592653589793

Python:

datatype parameter

Page 26: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Assignments

integer, parameter :: ap = & selected_real_kind(15,300)

real(kind=ap) :: K(20,20)

Element (5,6) is assigned a value of 5.0

All elements of K are assigned a value of 5.0

K(5,6) = 5.0_ap   

K = 5.0_ap

Page 27: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Assignments

integer, parameter :: ap = & selected_real_kind(15,300)

real(kind=ap) :: A(3,3)

Row 2 is assigned 1, 2, 3

Column 2 is assigned 4, 5, 6

A(2,:) = (/ 1.0_ap, 2.0_ap, 3.0_ap /)

A(:,2) = (/ 4.0_ap, 5.0_ap, 3.0_ap /)

Page 28: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Assignments

program pi_testinteger, parameter ::  &

ap = selected_real_kind(15,300)real(ap) pi1, pi2

pi1 = 3.141592653589793pi2 = 3.141592653589793_apwrite(*,*) ’pi1=', pi1write(*,*) ’pi2=', pi2stopend program pi_test

pi1=   3.14159274101257     pi2=   3.14159265358979

Page 29: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Assignments

logical :: flag

character(40) :: first_name

flag = .false.

first_name = ’Jan’

Page 30: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Defined and undefined variables

A variable is said to be undefined until it has been assigned a valuereal :: speed ! variable speed exists, but is undefined

An undefined variable must not be referencedWhen a variable is assigned a value it is considered definedspeed = 42.0 ! variable speed is definedIt can now be referenced by other expressions

An array is said to be defined when all elements have been assigned values

Page 31: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Arithmetic operators

** exponentiation

* Multiplication

/ Division

+ Áddition

‐ Subbtraction

Order of precedence

Page 32: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Unary operators

‐x or +x

Not allowed to follow directly after ordinaryoperator,  hence:x**‐y is illegal

x**(‐y) is ok

Page 33: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Expressions‐a+b+c

((‐a)+b)+c

Evaluated from left to right as:

a**b**c

a**(b**c)

Evaluated as:

Page 34: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Integer expressions

Results of divisions will be truncated towards 0

6/3 = 28/3 = 2‐8/3 = ‐2

A warning!

2**3 = 82**(‐3) = 1/(2**3) = 0

Page 35: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Mixed‐mode expressions

Numeric expressions with operands of differingdatatypes

Weaker of to datatypes will be coerced to the stronger oneResult will be of the stronger type

real :: ainteger :: ireal :: b

b = a*i

i coerced to real

Page 36: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Array expressions

Intrinsic operations can also apply to arrays

Same shape arrays are assumedOne or more operands can be scalarscalar values ”broadcast” to array operands

Order of array operations is not specified in the standardEnabling efficient execution on a vector or parallelcomputer

Page 37: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Array expressions examples

real, dimension(10,20) :: a, b

real, dimension(5) :: v

a/b          ! Array of shape (10,20), with elements a(i,j)/b(i,j)

v+1.         ! Array of shape (5), with elements v(i) + 1.0

5/v+a(1:5,5) ! Array of shape (5), with elements 5/v(i) + a(i,5)

a.eq.b ! .true. if a(i,j)==b(i,j) and .false. otherwise

Page 38: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Relational operators

Operator Meaning Python

< .lt. less than <

<= .le. less than or equal <=

== .eq. equal ==

/= .ne. not equal !=

> .gt. greater than >

>= .ge. greater than or equal >=

Page 39: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Logiska operatorer

Operator Meaning Python

.and. and and

.or. or or

.not. not not

Page 40: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Control constructs

Page 41: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

If‐statements

if (x>1000) thenx = 1000

end if

if (x>1000) x = 1000

if x>1000:x = 1000

Fortran Python

Page 42: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

If‐statements

if (x>1000) theny = 100

else y = 200

end if

if x>1000:y = 100

else:y = 200

Fortran Python

Page 43: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

If‐statements

if (x>1000) theny = 10

else if (x<0) theny = 20

elsey = 30

end if

if x>1000:y = 10

elif x<0:y = 20

else:y = 30

Fortran Python

Page 44: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

case‐statements

select case (display_mode)case (0)...case (1)...case default...end select

Page 45: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

case‐statements

select case (number)case (:‐1)...case (0)...case (1:)...case default...end select

case(low:high) low <= number <= high

case(:high) number <= high

case(low:high) <=> low <= number

‐1 1

(:‐1) (1:)

0

(0)

default

Page 46: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

do‐statements (loops)

do i = 1, 10j = j + i

end do

do i = 2, 30, 4j = j + i

end do

start‐value end‐value

start‐value end‐value

step

1 2 3 4 5 6 7 8 9 10

2 6 10 14 18 22 26 30

loop‐variable is not allowed to be modified in do‐statement

Page 47: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

do‐statements (loops)

do i=1,1000:if (x>50) thenexit

else if (x<20) thencycle

end if:

end do:

Exit do‐statement and execute next executablestatement after loop.

Continue to next iteration

Page 48: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Program units and procedures

Page 49: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Main program

[program program‐name][specification statements][executable statements]

[containsinternal‐subprograms]

end [program [program‐name]]

A Fortran program contains only onemain program.

The end‐statement signals the end of the program‐unit and also terminatesthe program execution.

Page 50: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

The stop‐statement

Stops program execution

Can be used in all program units”Well‐behaved” programs returns control to the main program, so stop‐statements should appearin the main program

A stop‐statement can contain stop codesNumber or strings

Page 51: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Subprograms

External subprogramsPlaced in separate source files. Implicit interface.

Can be implemented in other languages

Internal subprogramssubprograms contained inside program units, externalsubprograms and in module subprograms

Module subprogramsubprogram contained in a module

Page 52: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

External subprogram

subroutine statement[specification statements][executable statements]

[contains[internal subprograms]

end [subroutine [subroutines‐name]]

function statement[specification statements][executable statements]

[contains[internal subprograms]

end [subroutine [subroutines‐name]]

Page 53: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

External subprogram ‐ Example

subroutine myproc(a, B, C)integer, intent(in) :: areal, dimension(:,:) intent(in) :: Breal, dimension(:), intent(out) :: C

:

returnend subroutine myproc

Page 54: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Calling external subprogram

program maininteger, parameter :: areal :: B(a,a)real :: C(a)

:

call myproc(a,B,C)

:

end program main

Page 55: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Modules

Packagesglobal data

derived types and associated operations

subprograms

interface blocks

namelist definitions

Package everything associated with some kind of taskinterval arithmetic

FEM elements of a certain type …

Page 56: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Modulesmodule module‐name

[specification statements][contains

module‐subprograms]end [module [program‐name]]

module constantsinteger, parameter :: &

ik6 = selected_int_kind(6)end module constants

:use constants

integer(ik6) :: myint

Page 57: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Modulermodule truss

integer ...real, private ...:public :: bar2e:

contains

subroutine bar2e(...)...return

end subroutine bar2e:end module truss

variables and subprogramscan be made private and public using the public and private attributes.

Page 58: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Moduler

program mainuse truss:call bar2e:

end program main

All public variables, subprograms and datatypesfrom truss now available in program unit

Page 59: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Arguments of procedures

Paramters passed as referenceChanging a parameter in a subroutine affects variable in calling routine

Quicker subroutine calls

Undesired “sideeffects”

Declaration of parametersDon’t have to be the same as the calling routine

Last dimension can be left out for arrays.

Page 60: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Subroutines exampleprogram sub_declaration1

real(8), dimension(4,4) :: Ainteger, dimension(3) :: v

A = 0.0_8v = 0

call dowork(A,4,4,v,3)

print *, A(4,4)print *, v(3)

end program sub_declaration1 

subroutine dowork(A,rows,cols,v,elements)

integer :: rows, cols, elementsreal(8), dimension(rows*cols) :: Ainteger, dimension(elements)  :: v

A = 42.0_8v = 42

return

end subroutine dowork

Page 61: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Subroutine interfaces

2 flavorsexternal/implicit interfaceInternal/explicit interface

Implicit (Fortran 77)Separately compiled .f90‐filesCompiler does not have all information

Explicit (Fortran 9x / 200x)Declared in modules, program contain‐section or with interface declarationCompiler has all information on the subroutine interface

Page 62: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Subroutines and Fortran 90/95/2003

Arrays and vectors can be declared with  (:,:) or (:) dimensions 

The explicit interface gives the compiler all information to determine the sizes of the parametersShorter subroutine parameter lists

Actual dimensions of the arrays can be queried using the size(array, dimension) function.

Page 63: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Example – Implicit interfaceprogram test

real(8), dimension(20,30) :: A

A = 0.0_8

call mysub(A, 20, 30)

end program testsubroutine mysub(A,rows,cols)

integer :: rows, colsreal(8), dimension(rows,cols) :: A

A = 42.0_8

print *, 'rows = ', size(A,1)print *, 'cols = ', size(A,2)

return

end subroutine mysub

Page 64: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Example (Module)

module utils

contains

subroutine mysub2(A)

real(8), dimension(:,:) :: A

A = 42.0_8

print *, 'rows = ', size(A,1)print *, 'cols = ', size(A,2)

return

end subroutine mysub2

end module utils

program test

use utils

real(8), dimension(20,30) :: A

A = 0.0_8

call mysub2(A)

end program test

Assumed shape array

Page 65: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Example – Internal subprogramprogram test

real(8), dimension(20,30) :: A

A = 0.0_8

call mysub3(A)

contains 

subroutine mysub3(A)

real(8), dimension(:,:) :: A

A = 42.0_8

print *, 'rows = ', size(A,1)print *, 'cols = ', size(A,2)

end subroutine mysub3

end program test

Assumed shape array

Page 66: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Example – Explicit interfaceprogram test

interface subroutine mysub4(A)

real(8), dimension(:,:) :: Aend subroutine mysub4

end interface

real(8), dimension(20,30) :: A

A = 0.0_8

call mysub4(A)

end program test

subroutine mysub4(A)

real(8), dimension(:,:) :: A

A = 42.0_8

print *, 'rows = ', size(A,1)print *, 'cols = ', size(A,2)

return

end subroutine mysub4

Assumed shape array

Page 67: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Automatic fields

Temporary fields in subroutines

Created on the stackMust fit in the stack

Page 68: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Automatic fields

program automatic_arrays

real(8), dimension(20,30) :: A

call mysub(A)

contains

subroutine mysub(A)

real(8), dimension(:,:) :: Ainteger, dimension(size(A,1),size(A,2)) :: B

B = 0

print *, "rows = ", size(B,1)print *, "cols = ", size(B,2)

end subroutine mysub

end program automatic_arrays

Page 69: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Array features

Page 70: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Allocatable arrays

Size of arrays not always known at compile timeDeclared using the allocatable attributeThe array rank is defined at declarations, but bounds undefined until array has been allocatedAllocate‐statements used to allocate the array”Work arrays” where used in Fortran 77 as a replacement for allocatable arraysDeallocated with deallocate‐statementAllocatable arrays automatically deallocated when returning from a function or subroutine

Page 71: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Allocatable arrays

real, dimension(:), allocatable :: f

real, dimension(:,:), allocatable :: K

allocate(f(20))

allocate(K(20,20))

deallocate(f)

deallocate(K)

deallocate(f, K)

or

allocate(f(20), K(20,20))

Page 72: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Where‐statement

Often desired to perform operations on only certain elements of an array

where (logical‐array‐expr) array‐variable = expr

where (logical‐array‐expr)array‐assignments

end where

where (logical‐array‐expr)array‐assignments

elsewherearray‐assignments

end where

Page 73: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Where‐statement example

where (a>0.0) a = 1.0/a

where (pressure <= 1.0)pressure = pressure + inc_pressuretemp = temp + 5.0

elsewhereraining = .true.

end where

where (a>0.0) a = log(a)

function is only called when condition is fulfilled.

a, pressure, temp are arrays

Page 74: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

forall‐statement

In do‐loops the processor must each succesive iteration in order and after each otherPerformance penalties (especially on parallel machines)

forall‐statement a replacement when operations can be executed in any orderArray assignments expressed with indices

Page 75: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

forall‐statement

do i=1,na(i,i) = 2.0 * x(i)

end do

forall(i=1:n) a(i,i) = 2.0 * x(i)

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

forall(i=1:n, j=1:n, y(i,j)/=0.) x(i,j) = 1.0/y(i,j)

Masking condition

Risk of dividing by zero

Page 76: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Pure procedures

Using functions with side‐effects in forall can affect performance and resultspure functions must be used in forall‐statementsA procedure in Fortran in considered pure 

if it does not alter any dummy argumentdoes not alter any part of a variable accessed by host or use associationcontains no local variable with save attributeperforms no operations on external filescontains no stop statement

pure attribute used to indicate pure function

Page 77: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Elemental procedures

Subroutines operating on elements of arrays

Elemental subroutines must be pure (defined automatically)

elemental subroutine swap(a, b)real, intent(inout) :: a, breal :: work

work = aa = bb = work

end subroutine swap

:

real, dimension(20,20) :: areal, dimension(20,20) :: b

call swap(a,b)

Page 78: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Array subobjects

Used to extract fields/arrays from other arrays

Can be used as parameters in subroutine callsCompare Matlab’s index notation

Page 79: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Array subobject exampleprogram array_subobjects

integer, dimension(5,10) :: Ainteger :: i, j

do i=1,5do j=1,10

A(i,j) = (i‐1)*10 + jend do

end do

print *, "Entire array:"call writeArray(A)

print *, "A(1, 5:10)"call writeVector(A(1, 5:10))

print *, "A(1:5, 5:10)"call writeArray(A(1:5, 5:10))

print *, "A(1:5, 5:10)"call writeArray(A(1:5, 5:10))

print *, "A((/1,3/), (/2,4/))"call writeArray(A( (/1,3/), (/2,4/) ))

Page 80: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Array subobjects exampleEntire array:1 2 3 4 5 6 7 8 9 1011 12 13 14 15 16 17 18 19 2021 22 23 24 25 26 27 28 29 3031 32 33 34 35 36 37 38 39 4041 42 43 44 45 46 47 48 49 50A(1, 5:10)5 6 7 8 9 10A(1:5, 5:10)5 6 7 8 9 1015 16 17 18 19 2025 26 27 28 29 3035 36 37 38 39 4045 46 47 48 49 50A(1:5, 5:10)5 6 7 8 9 1015 16 17 18 19 2025 26 27 28 29 3035 36 37 38 39 4045 46 47 48 49 50A((/1,3/), (/2,4/))2 422 24

Page 81: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Intrinsic procedures

Page 82: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Intrinsic procedures (builtin...)

Elemental procedures

Inquiry functionsReturns properties of the arguments that does not depend on their values, kind, range etc...

Transformational functionsHas array arguments and returns arrays depending on all elements of the input arrays

Non‐elemental subroutines

Page 83: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Elemental functions

abs(x) absolute value of x

int(x) converts x to integere, truncates towards 0

nint(x) returns integer, nearest to x

real(x) converts to floating point value

...

sin(x) returns the sine of x

sqrt(x) returns the square root of x

atan2(y,x) returns the arc tangent for pairs of reals

... converts to floating point value

Routines that may convert

Mathematical functions

Page 84: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Vector and matrix multiplication

Matrix multiplicationmatmul(A,B), where A and B are matrices

Scalarproductdot_product(a,b), where a and b are vectors

Page 85: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Vector and matrix multiplication

program matrix_multiply

real(8), dimension(4,4) :: Areal(8), dimension(4,8) :: Breal(8), dimension(4,8) :: C

call randomMatrix(A)call randomMatrix(B)call randomMatrix(C)

C = matmul(A,B)

print *, "A = "call writeArray(A)print *, "B = "call writeArray(B)print *, "C = "call writeArray(C)

end program matrix_multiply

Page 86: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Vector and matrix multiplication

A =.984    .700    .275    .661.810    .910    .304    .484.985    .347    .548    .614.971    .882    .129    .929B =

.763    .534    .711E‐01.404    .731    .636    .879    .689

.786    .231    .238    .951    .621    .528    .733    .588E‐01

.466    .302    .209    .294    .598    .461    .911    .343

.690E‐01.619    .305    .326E‐01.438    .202    .617    .851C =

1.48    1.18    .496    1.17    1.61    1.26    2.04    1.381.51    1.03    .486    1.30    1.55    1.23    1.96    1.131.32    1.15    .455    .909    1.53    1.19    2.00    1.411.56    1.34    .589    1.30    1.74    1.33    2.19    1.56

Page 87: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Reduction routines

allTrue if all element = .true.

anyTrue if any element = .true.

maxval/minvalMax/min value in the field

productProduct of all elements in the field

sumSum of all elements in the field

Page 88: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Reduction functions

print *, 'Product of A = ', product(A)print *, 'Sum of A     = ', sum(A)print *, 'Max of A     = ', maxval(A)print *, 'Min of A     = ', minval(A)

A =.984    .700    .275    .661.810    .910    .304    .484.985    .347    .548    .614.971    .882    .129    .929...Product of A =  0.00016095765496870103Sum of A     =  10.534961942117661Max of A     =  0.9853920286986977Min of A     =  0.12899155798368156

Page 89: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Information functions

lboundReturns lower field index 

uboundReturn upper field index

shapeReturns the matrix shape in an array [rows, columns]

sizeReturns the size of matrix in a specific  dimension

Page 90: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Input and output

Page 91: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Reading and writing files

One row for each READ/WRITE‐statement

Fortran automatically converts text in a file to typed variable valuesSeveral variables can be read in the same statement using a comman separated list of variables

To handle a large number of values on a row an implicit loop can be used

Page 92: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Example

! Read 8 floating point values from unit ir

read(ir,*) a(1), a(2), a(3), a(4), a(5), a(6), a(7), a(8)

! or perhaps even better...

read(ir,*) (a(i), i=1,8)

! Same procedure for writing

write(iw,*) (a(i), i=1,8)

Page 93: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Formatted IO

Second parameter in the WRITE statement defines the output format

* represents the default format which often displays at full precisionA format parameter is a string describing the output format

The format is defined using format codes

Page 94: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Formatted IO

Common codesA[n] – character string with the width n

I[n] – integer with the width n

G[m.n] – floating point value with width m and n decimals

Format codes can be repeated by giving a integer in front of the code“(6I5)” = 6 integers with the width 5

Page 95: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Exampleprogram format_print

real(8), dimension(3) :: ainteger, dimension(4) :: binteger :: i, j

! Write table header

a = (/ 1.0, 2.0, 3.0 /)b = (/ 4, 5, 6, 7 /)

write(*, '(3A8,4A5)') 'aaaaaaaa', &'bbbbbbbb', 'cccccccc', 'ddddd', 'eeeee', 'fffff', &'ggggg‘

! Write table

do j=1,10write(*, '(3G8.3,4I5)') (a(i),i=1,3), (b(i), i=1,4)

end do

end program format_print

Page 96: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Example

aaaaaaaabbbbbbbbccccccccdddddeeeeefffffggggg1.00    2.00    3.00        4    5    6    71.00    2.00    3.00        4    5    6    71.00    2.00    3.00        4    5    6    71.00    2.00    3.00        4    5    6    71.00    2.00    3.00        4    5    6    71.00    2.00    3.00        4    5    6    71.00    2.00    3.00        4    5    6    71.00    2.00    3.00        4    5    6    71.00    2.00    3.00        4    5    6    71.00    2.00    3.00        4    5    6    7

Page 97: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

“Dynamic” format codes

Format strings are static strings

How to create a format code that can handle dynamic number of valuesWRITE can use a character string as a “file”

Page 98: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Examplesubroutine writeArray(A)

real(8), dimension(:,:) :: Ainteger :: rows, cols, i, jcharacter(255) :: fmt

rows = size(A,1)cols = size(A,2)

write(fmt, '(A,I1,A)') '(',cols, 'G8.3)'  

do i=1,rowsprint fmt, (A(i,j), j=1,cols)

end do

return

end subroutine writeArray

String that will contain final format codes.

Write to fmt string using a write statement ”colsG8.3”.

Use the fmt string as a format string when printing the array.

Page 99: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Reading

read(*,*) Aread(5,*) A

integer, parameter :: ir=15

open(unit=ir, file=’example.dat’)read(ir,*) Aclose(unit=ir)

Keyboard

File

Please see, Metcalf for more parameters for the open‐statement

Page 100: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Writing

write(*,*) Awrite(6,*) Awrite(*,’ (TR1,A,G15.6)’) ’A = ’, A

integer, parameter :: iw=16

open(unit=iw, file=’example.dat’)write(iw, ’(A,G15.6)’) Aclose(unit=iw)

Screen

File

Please see, Metcalf for more parameters for the open‐statement

Page 101: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Code structuring

Page 102: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Structuring of projects

For smaller project modularisation not necessary 

For larger project it is a must to be able to maintain the codeIn Fortran 95 the key to modularisation is the module

Modules should be used to group related subroutines and data 

Page 103: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Code structuring

inputdata outputdatafem solve

utils

program

Page 104: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Example code

program stress

use inputdatause outputdatause femuse solve

.

.

end program stress

module fem 

use utils

.

.

end module fem

module utils

.

.

end module utils

Page 105: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Using the Photran IDE

Page 106: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Selecting workspace

A workspace is a directorycontaining settings for the enviroment and a set of development projects.

Page 107: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Welcome screen

Click here

Page 108: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Workbench screen

File/New/other…

Page 109: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Create a Fortran project

Click Next

Page 110: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Select project type and name

1

2

3

Click Finish

Page 111: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Switch to Fortran Perspective

Page 112: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Workbench with empty project

Page 113: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Adding a Fortran source fileFile/New/Other…

Click Next

Page 114: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Name source file

Click Finish

Enter name of sourcefile

Page 115: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Makefile generation with pymkmf

Select the source directoryusing the browse button.

Click ”Generate” to create a Makefile for source files.

Page 116: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Refreshing project tree

Right click and select ”Refresh” to display the generatedMakefile

Page 117: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Building the projectRight click and select ”BuildProject” to start the buildprocess.

Page 118: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Running the project

Click to run project

Click Ok

Page 119: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Program output

Page 120: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Debugging with Photran

Page 121: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Special FX

Page 122: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Procedures as arguments

procedures in Fortran 95 can take procedures as arguments

Properties of “dummy” procedure arguments must agreeThe procedure type is declared in the specification part

Internal procedures can’t be used

Page 123: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Procedures as argumentsmodule utils

implicit none

contains

real(8) function myfunc(x)

real(8), intent(in) :: x

myfunc = sin(x)

end function myfunc

subroutine tabulate(startInterval, endInterval, step, func)

real(8), intent(in) :: startInterval, endInterval, stepreal(8) :: x

interface real(8) function func(x)

real(8), intent(in) :: xend function func

end interface

x = startIntervaldo while (x<endInterval) 

print *, x, func(x)x = x + step

end do

returnend subroutine tabulate

end module utils

Declaration of  function interface. Function used as argument must havethe same interface

Page 124: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Procedures as arguments

program procedures_as_arguments

use utils

implicit none

call tabulate(0.0_8, 3.14_8, 0.1_8, myfunc)

end program procedures_as_arguments

Page 125: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Procedures as arguments0.0000000000000000        0.0000000000000000     0.10000000000000001       9.98334166468281548E‐0020.20000000000000001       0.19866933079506122     0.30000000000000004       0.29552020666133960     0.40000000000000002       0.38941834230865052     0.50000000000000000       0.47942553860420301     0.59999999999999998       0.56464247339503537     0.69999999999999996       0.64421768723769102     0.79999999999999993       0.71735609089952268     0.89999999999999991       0.78332690962748330     0.99999999999999989       0.84147098480789639     1.0999999999999999       0.89120736006143531     1.2000000000000000       0.93203908596722629     1.3000000000000000       0.96355818541719296     1.4000000000000001       0.98544972998846025     1.5000000000000002       0.99749498660405445     1.6000000000000003       0.99957360304150511     1.7000000000000004       0.99166481045246857     1.8000000000000005       0.97384763087819504     1.9000000000000006       0.94630008768741425     2.0000000000000004       0.90929742682568149     2.1000000000000005       0.86320936664887349     2.2000000000000006       0.80849640381958987     2.3000000000000007       0.74570521217671970     2.4000000000000008       0.67546318055115029     2.5000000000000009       0.59847214410395577     2.6000000000000010       0.51550137182146338     2.7000000000000011       0.42737988023382895     2.8000000000000012       0.33498815015590383     2.9000000000000012       0.23924932921398112     3.0000000000000013       0.14112000805986591     3.1000000000000014       4.15806624332891589E‐002

Page 126: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Keyword and optional arguments

Many procedures have long argument listsAll arguments not needed

Procedural arguments in Fortran can be given the attribute optionalreal, optional :: a

Optional arguments can be omitted in the procedure callPresence of an argument can be tested with the present function.

Arguments can be specified with keywords

Page 127: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Keyword and optional arguments

subroutine order_icecream(number, flavor, topping)

integer :: numberinteger, optional :: flavorinteger, optional :: topping

print *, number, 'icecreams ordered.'

if (present(flavor)) thenprint *, 'Flavor is ', flavor

elseprint *, 'No flavor was given.'

end if

if (present(topping)) thenprint *, 'Topping is ', topping

elseprint *, 'No topping was given.'

end if

end subroutine order_icecream

call order_icecream(2)call order_icecream(2, 1)call order_icecream(4, 4, 2)call order_icecream(4, topping=3)

Page 128: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Overloading

Procedure call to different procedures depending on datatype

Declare an interface with procedural interfaces for all used datatypesExplicit interfaces (modules) can use a simpler form module procedure procedure‐name‐list

Page 129: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Overloadingmodule special

interface funcmodule procedure ifunc, rfunc

end interface

contains

integer function ifunc(x)

integer, intent(in) :: xifunc = x * 42

end function ifunc

real(8) function rfunc(x)

real(8), intent(in) :: xrfunc = x / 42.0_8

end function rfunc

end module special 

program overloading

use special

implicit none

integer :: a = 42real(8) :: b = 42.0_8

a = func(a)b = func(b)

print *, aprint *, b 

end program overloading

17641.00000000000000000 

Page 130: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Operator overloading

Define operations on derived types

Vector / Matrix operationsinterface operator(operator) used to define a function implementing the operations for this operator

Function has the formtype(derived‐type‐name) function‐name(operand1, operand2)

Page 131: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Operator overloading

module vector_operations

type vectorreal(8) :: components(3)

end type vector

interface operator(+)module procedure vector_plus_vector

end interface

contains

type(vector) function vector_plus_vector(v1, v2)

type(vector), intent(in) :: v1, v2vector_plus_vector%components = v1%components + v2%components

end function vector_plus_vector

end module vector_operations

Page 132: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Operator overloading

program operator_overloading

use vector_operations

implicit none

type(vector) :: v1type(vector) :: v2type(vector) :: v

v1%components = (/1.0, 0.0, 0.0/)v2%components = (/0.0, 1.0, 0.0/)

v = v1 + v2

print *, v

end program operator_overloading

1.00000000000000000       1.00000000000000000        0.0000000000000000

Page 133: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Public and private attributes

Control visibility of variables and functions

Hide module implementation detailsPrevent side effects in modules

Visibility of variables controlled by private and public attributes

procedure visibility controlled by private access‐list

public is the default for all module variables and procedures

Page 134: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Public and private 

module mymodule

implicit none

integer, public :: visibleinteger, private :: invisible

private privatefuncpublic publicfunc

contains

subroutine privatefunc

print *, 'This function can only be called from within a module.'

end subroutine privatefunc

subroutine publicfunc

call privatefunc

end subroutine publicfunc

end module mymodule

Page 135: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Public and privateprogram private_entities

use mymodule

implicit none

call publicfunc

end program private_entities

This function can only be called from within a module.

program private_entities

use mymodule

implicit none

call privatefunc

end program private_entities

make all gfortran ‐g ‐fbounds‐check ‐Wall ‐Wtabs ‐c main.f90gfortran ‐o private_entities mymodule.o main.omain.o: In function `private_entities':D:\edu\lunarc\sciprog\workspace\private_entities/main.f90:7: undefined reference to `privatefunc_'collect2: ld returned 1 exit statusmake: *** [private_entities] Error 1

Page 136: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Pointers

Pointer = reference to a variable

Strictly typedPointer targets must have target attributeFor compiler optimisation

Enables the return of allocatable arrays from procedures

nullify(pointer) disassociates pointer from target=> operator is used to associated a pointer with a target

Page 137: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Pointersprogram pointers

implicit none

integer, allocatable, dimension(:,:), target :: Ainteger, dimension(:,:), pointer :: B, C

allocate(A(20,20))

B => A

print *, size(B,1), size(B,2)

call createArray(C)

print *, size(C,1), size(C,2)

deallocate(C)

B => null()

B(1,1) = 0 ! Dangerous!

contains

subroutine createArray(D)

integer, dimension(:,:), pointer :: D

allocate(D(10,10))

end subroutine createArray

end program pointers

B points to A

B can be queried just like a normal array

An unassociatedpointer can be passedto a subroutine and be returned as an allocated array

Page 138: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Advanced I/O

Page 139: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

List directed I/O

Fortran uses a specific format for reading and writing variables to files

Variables output from write(*,*) are separated with space/blanksComplex numbers surrounded by ( )

Strings must be enclosed in ‘ ‘ or “ “ when output

Reading variables require the same format

Page 140: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

List directed I/Oprogram list_io

implicit none

integer, parameter :: ir = 15integer, parameter :: iw = 16

integer :: a = 42real :: b = 42.0 * 42.0character(len=20) :: string = 'Hello, string!'logical :: topping = .true.complex :: c = (1.0,2.0)

open(unit=iw, file='list.txt', status='replace')write(iw,*) a, b, '"',string,'"', topping, cclose(unit=iw)

open(unit=ir, file='list.txt', status='old')read(ir,*) a, b, string, topping, cclose(unit=ir)

print *, aprint *, bprint *, toppingprint *, c

end program list_io

42   1764.0000     "Hello, string!      " F ( 1.00000000    ,  2.0000000    )

.true. and .false. canalso be used as input for logical variables

Page 141: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Namelist I/O

Reading list of named values

Value names defined in a namelistInput must consist of lists of named value pairs separated with comma& name = value, name = value /

Can contain arraysname = 1,2,3,4,5 

Fortran can also write named values

Page 142: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Namelist I/O

program namelist_io

implicit none

integer, parameter :: ir = 15integer, parameter :: iw = 16integer :: no_of_eggs, litres_of_milk, kilos_of_butter, list(5)namelist /food/ no_of_eggs, litres_of_milk, kilos_of_butter, list

list = 0

open(unit=ir, file='food.txt', status='old')read(ir, nml=food)close(unit=ir)

print *, no_of_eggs, litres_of_milk, kilos_of_butter

open(unit=iw, file='food2.txt', status='new')write(iw, nml=food)close(unit=iw)

end program namelist_io

namelist definedvariables to be read from file

namelist definedvariables to be writtento file.

Page 143: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Namelist I/O

&food litres_of_milk=5, no_of_eggs=12, kilos_of_butter=42, list=1,2,3,4,5 /

&FOODNO_OF_EGGS=         12,LITRES_OF_MILK=          5,KILOS_OF_BUTTER=         42,LIST=          1,          2,          3,          4,          5,/

food.txt:

food2.txt:

writing namelistalways producesuppercase variable names

Page 144: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Unformatted I/O

Writing data using a textual representation not efficient in all cases

No format needed, binary outputread(unit=xx) a

write(unit=xx) b

Output from unformatted I/O often system dependent

Scratchfiles and temporary files

Page 145: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Direct access files 

Used when a random access pattern is needed

File consists of a set of equal sized recordsAny record in the file can be accessed randomly

If the record is changed data cannot be read back from file

Size of a record can be found using inquire(iolength=variable‐name) recordLength

Page 146: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Direct access files / unformatted IOprogram unformatted_io

implicit none

type accountcharacter(len=40) :: account_holderreal :: balance

end type account

integer, parameter :: iw = 15type(account) :: accountAtype(account) :: accountBinteger :: recordSize

inquire(iolength=recordSize) accountA

print *, 'Record size =',recordSize

accountA%account_holder = 'Olle'accountA%balance = 400

accountB%account_holder = 'Janne'accountB%balance = 800

open(unit=iw, file='bank.dat', access='direct', recl=recordSize, status='replace')write(iw, rec=1) accountAwrite(iw, rec=2) accountBclose(unit=iw)

end program unformatted_io

Derived datatypesgood candidates for storing as records in a random access file

Inquire for the required record length

access=’direct’ createsa direct access file.

The rec attributedetermines the location to store/read the record

Page 147: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

File positioning

File pointer – Invisible cursor in the file

backspace unitMove file pointer back 1 record

rewind unitMove file pointer to beginning of file

endfile unit Move file pointer to the end of the file.

Page 148: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Error handling in file operations

open, close, read and write have an err attribute that can be set to a specific label to jump to when an error occurs

Well behaved programs should implement error handling when reading and writing files

Page 149: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Error handling in file operationsprogram error_handling

implicit none

integer, parameter :: ir = 15integer :: a 

open(unit=ir, file='test.txt', status='old', err=99)read(ir,*,err=99) aclose(unit=ir,err=99)

stop

99  print *, 'An error occured reading the file.'

end program error_handling

Page 150: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Fortran 2003 extensions

Page 151: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Allocatable array extensions

Remove the need for pointers to use allocatablearrays as dummy arguments

Inefficient 

Page 152: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Allocatable dummy argumentsprogram allocatable_dummy

implicit none

real, allocatable :: A(:,:)

call createArray(A)

print *, size(A,1), size(A,2)

deallocate(A)

contains

subroutine createArray(A)

real, allocatable, intent(out) :: A(:,:)

allocate(A(20,20))

end subroutine createArray

end program allocatable_dummy

A pointer dummy argument was neededto implement this i Fortran 95

Page 153: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Allocatable functions

program allocatable_function

implicit none

real :: A(20)

A = createVector(20)print *, size(A,1)

contains

function createVector(n)

real, allocatable, dimension(:) :: createVectorinteger, intent(in) :: n

allocate(createVector(n))

end function createVector

end program allocatable_function

Vector allocated in function will be automaticallydeallocated when it has been used.

Page 154: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Allocatable components

type stackinteger :: indexinteger, allocatable :: content(:)

end type stack

Pointers used in Fortran 95, but no automaticdeallocation available

Page 155: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Submodules

The Fortran 95 module concept adequate for moderate size projects

Difficult to modularize modules themselvesDividing modules into several modulesexposes internal structure

nameclashes

Changes to module features require recompilation of all files using this module

Page 156: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Submodules

Separation of module intoInterface – defined in the module

Body – defined in submodule

Page 157: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Submodulesmodule points

type pointreal :: x, y

end type point

interface real module function point_dist(a, b)

type(point), intent(in) :: a, bend function point_dist

end interfaceend module points

submodule (points) points_a

contains

real module function point_dist(a,b)type(point), intent(in) :: a, bpoint_dist = sqrt((a%x‐b%x)**2+(a%y‐b%y)**2)

end function point_dist

end submodule points_a

Not available in gfortran yet.

Page 158: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

C interoperability

No clear definitions existed between Fortran 95 and the C language

C/Fortran programming is importantInterfacing with C libraries

C user interface application interfacing with Fortran code

New intrinsic module, iso_c_binding, includedContains definitions of all the C datatypes mapped to Fortran types

Page 159: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

C interoperability

program c_interop

use iso_c_binding

implicit none

integer(c_int) :: areal(c_float) :: breal(c_double) :: c

a = 42b = 42.0_c_floatc = 84.0_c_double

print *, a, b, c

end program c_interop

Page 160: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

C interoperability

Fortran always passes all variables by reference

In C scalar arguments are often passed by valueArgument value is copied to procedure

The variable attribute value is added for compatibility with C code

Enables direct linking with C

Page 161: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Object‐oriented programming 

module mytype_module

type mytypereal :: myvalue(4) = 0.0

containsprocedure :: write => write_mytypeprocedure :: reset 

end type mytype

private :: write_mytype, reset

contains

subroutine write_mytype(this, unit)class(mytype) :: thisinteger, optional :: unitif (present(unit)) then

write(unit,*) this%myvalueelse

print *, this%myvalueend if

end subroutine write_mytype

subroutine reset(variable)class(mytype) :: variablevariable%myvalue = 0.0

end subroutine reset

end module mytype_module

class(mtype) :: x

call x%write(6)call x%reset

Not available in gfortran yet.

Page 162: Introduction to Fortran 90/95/2003 -  · PDF fileIntroduction to Fortran 90/95/2003 ... First version 1954 FORTRAN 66 ... computer. Array expressions examples

Access to computing environment

get_environment_variable(…)Query environment variables

command_argument_count()Retrieve the number of command line arguments

get_command_argument(…)Retrieve specific command line argument


Top Related