The Queen's University of Belfast
Parallel Computer Centre

[Next] [Previous] [Top]

Program units


Program units

Topics

Programs structure

Illustrated definitions

The main program

Form

All programs have one main program:

PROGRAM [name]

[specification statements]

[executable statements]

...

[CONTAINS

internal procedures]

END [PROGRAM [name]]

STOP [label]

Procedures

Form

Procedures are a means of structuring a program and grouping together statements which perform well defined tasks.

procedure name [(argument list)]

[specification statements]

[executable statements]

...

[CONTAINS

internal procedures]

END procedure [name]

Subroutines vs Functions

CALL name [( argument list )]

result = name [( argument list )]

Actual and dummy arguments

Data may be shared between procedures through the referencing statement:

Subroutine example

REAL, DIMENSION(10) :: a, c

...

CALL swap( a,c )

SUBROUTINE swap( a,b )

REAL, DIMENSION(10) :: a, b, temp

temp = a

a = b

b = temp

END SUBROUTINE swap

Function example

REAL :: y,m,x,c

...

y = line( m,x,c )

FUNCTION line( m,x,const )

REAL :: line

REAL :: m, x, const

line = m*x + const

END FUNCTION line

Internal procedures

PROGRAM outer

REAL :: a, b, c

CALL inner( a )

...

CONTAINS

SUBROUTINE inner( a )

REAL :: a !argument

REAL :: b=1. !redefined

c = a + b !c host assoc

END SUBROUTINE inner

END PROGRAM outer

External procedures

PROGRAM first

REAL :: x

x = second()

...

END PROGRAM first

FUNCTION second()

REAL :: second

... !no host association

END FUNCTION second

Procedure variables

SAVE

REAL FUNCTION func1( a_new )

REAL :: a_new

REAL, SAVE :: a_old !saved

INTEGER :: counter=0 !saved

...

a_old = a_new

counter = counter+1

END FUNCTION func1

Interface blocks

Implicit and explicit

Interfaces occur between referencing and procedure statements.

The type, intent, etc. of actual and dummy arguments must match to allow compilation.

Declarations

Explicit interfaces may be provided as an aid to the compiler (and hence the programmer):

INTERFACE

interface statements

END INTERFACE

Example

PROGRAM count

INTERFACE

SUBROUTINE ties(score, nties)

REAL :: score(50)

INTEGER :: nties

END SUBROUTINE ties

END INTERFACE

REAL, DIMENSION(50):: data

...

CALL ties(data, n)

...

END PROGRAM count

SUBROUTINE ties(score, nties)

REAL :: score(50)

INTEGER :: nties

...

END SUBROUTINE ties

Procedure arguments

Assumed shape objects

Both dummy argument character strings and arrays may accept different sized actual arguments each time a procedure is called.

SUBROUTINE sub2(data1, data3, str)

REAL, DIMENSION(:) :: data1

INTEGER, DIMENSION(:,:,:) :: data3

CHARACTER(len=*) :: str

...

The intent attribute

SUBROUTINE invert(a, inverse, count)

REAL, INTENT(IN) :: a

REAL, INTENT(OUT) :: inverse

INTEGER, INTENT(INOUT) :: count

inverse = 1/a

count = count+1

END SUBROUTINE invert

Keyword arguments

SUBROUTINE sub2(a, b, stat)

INTEGER, INTENT(IN) :: a, b

INTEGER, INTENT(INOUT):: stat

...

END SUBROUTINE sub2

The following references are all legal:

CALL sub2( a=1, b=2, stat=x )

CALL sub2( 1, stat=x, b=2)

Optional arguments

SUBROUTINE sub1(a, b, c, d)

INTEGER, INTENT(INOUT) :: a, b

REAL, INTENT(IN), OPTIONAL :: c, d

...

END SUBROUTINE sub1

The following references are all legal:

CALL sub1( a, b )

CALL sub1( a, b, c, d )

CALL sub1( a, b, c )

PRESENT( name )

Procedures as arguments

External and module procedures may be passed as arguments to other procedures.

...

INTERFACE

REAL FUNCTION func( x )

REAL, INTENT(IN) ::x

END FUNCTION func

END INTERFACE

...

CALL sub1( a, b, func )

REAL FUNCTION func( x ) !external

REAL, INTENT(IN) :: x

func = 1/x

END FUNCTION func

Recursion

Recursive procedures

Recursive procedures reference themselves.

RECURSIVE FUNCTION factorial( n ) &

RESULT(res)

INTEGER, INTENT(IN) :: n

INTEGER :: res

IF( n==1 ) THEN

res = 1

ELSE

res = n*factorial( n-1 )

END IF

END FUNCTION factorial

Generic procedures

A `generic interface' block allows several procedures to be referenced by the same name.

Example

INTERFACE swap

SUBROUTINE iswap( a, b )

INTEGER, INTENT(INOUT) :: a, b

END SUBROUTINE iswap

SUBROUTINE rswap( a, b )

REAL, INTENT(INOUT) :: a, b

END SUBROUTINE rswap

END INTERFACE

Modules

Specification

MODULE name

[definitions]

...

[CONTAINS

module procedures]

END [MODULE [name]]

USE name

Global data

MODULE global

REAL, DIMENSION(100) :: a, b, c

INTEGER :: list(100)

LOGICAL :: test

END MODULE global

USE global

USE global, ONLY: a, c

USE global, state => test

Module procedures

MODULE cartesian

TYPE point

REAL :: x, y

END TYPE point

CONTAINS

SUBROUTINE swap( p1, p2 )

TYPE(point), INTENT(INOUT):: p1

TYPE(point), INTENT(INOUT):: p2

TYPE(point) :: tmp

tmp = p1

p1 = p2

p2 = tmp

END SUBROUTINE swap

END MODULE cartesian

PUBLIC and PRIVATE

All entities in a module are accessible to program units which USE that module.

i.e. all entities are public by default.

MODULE data

PRIVATE !set default

REAL, PUBLIC :: a !public

REAL :: b !private

...

END MODULE data

Generic procedures

MODULE cartesian

TYPE point

REAL :: x, y

END TYPE point

INTERFACE swap

MODULE PROCEDURE pointswap, &

iswap, rswap

END INTERFACE

CONTAINS

SUBROUTINE pointswap( a, b )

TYPE(point) :: a, b

...

END SUBROUTINE pointswap

!subroutines iswap and rswap

END MODULE cartesian

Overloading operators

Intrinsic operators (+, -, ...) may be extended to cover new operations on existing and derived data types.

Such extended operators are `overloaded'.

INTERFACE OPERATOR( operator )

interface_block

END INTERFACE

Example

MODULE strings

INTERFACE OPERATOR ( / )

MODULE PROCEDURE num

END INTERFACE

CONTAINS

INTEGER FUNCTION num( s, c )

CHARACTER(len=*), INTENT(IN) :: s

CHARACTER, INTENT(IN) :: c

num = 0

DO i=1,LEN( s )

IF( s(i:i)==c ) num=num+1

END DO

END FUNCTION num

END MODULE strings

USE strings

...

i = `hello world'/'o' !i=2

Defining operators

New operators may be defined to cover new operations on existing and derived data types.

.name.

INTERFACE OPERATOR( .name. )

interface_block

END INTERFACE

Example

MODULE cartesian

TYPE point

REAL :: x, y

END TYPE point

INTERFACE OPERATOR ( .DIST. )

MODULE PROCEDURE dist

END INTERFACE

CONTAINS

REAL FUNCTION dist( a, b )

TYPE(point) INTENT(IN) :: a, b

dist = SQRT( (a%x-b%x)**2 + &

(a%y-b%y)**2 )

END SUBROUTINE dist

END MODULE cartesian

To make use of the .DIST. operator:

USE cartesian

TYPE(point) :: a, b

distance = a .DIST. b

Assignment overloading

The assignment operator (=) may be overloaded to apply to derived data types.

INTERFACE ASSIGNMENT( = )

interface_block

END INTERFACE

Scope

Scoping units

The scope of an entity is that part of a program within which a name or label is unique.

A scoping unit is one of the following:

Labels and names

Example

MODULE scope1 !scope 1

... !scope 1

CONTAINS !scope 1

SUBROUTINE scope2 () !scope 2

TYPE scope3 !scope 3

... !scope 3

END TYPE scope3 !scope 3

INTERFACE !scope 3

... !scope 4

END INTERFACE !scope 3

REAL :: a, b !scope 3

10 ... !scope 3

CONTAINS !scope 2

FUNCTION scope5() !scope 5

REAL :: b !scope 5

b = a+1 !scope 5

10 ... !scope 5

END FUNCTION !scope 5

END SUBROUTINE !scope 2

END MODULE !scope 1


[Next] [Previous] [Top]
All documents are the responsibility of, and copyright, © their authors and do not represent the views of The Parallel Computer Centre, nor of The Queen's University of Belfast.
Maintained by Alan Rea, email A.Rea@qub.ac.uk
Generated with CERN WebMaker