PROGRAM [name]
[specification statements]
[executable statements]
...
[CONTAINS
internal procedures]
END [PROGRAM [name]]
CONTAINS
statement,
STOP
statement:
STOP [label]
procedure name [(argument list)]
[specification statements]
[executable statements]
...
[CONTAINS
internal procedures]
END procedure [name]
procedure
may be:
CALL
statement:
CALL name [( argument list )]
result = name [( argument list )]
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
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
CONTAINS
statement.
CONTAINS
statement).
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
a
is passed by argument.
b
is redefined within the subroutine.
c
is common to both through host association.
PROGRAM first
REAL :: x
x = second()
...
END PROGRAM first
FUNCTION second()
REAL :: second
... !no host association
END FUNCTION second
SAVE
(statement, or attribute).
SAVE
attribute.
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
SAVE
dummy arguments or function results.
The type, intent, etc. of actual and dummy arguments must match to allow compilation.
INTERFACE
interface statements
END INTERFACE
interface statements
consist of a partial copy of the procedure:
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
SUBROUTINE sub2(data1, data3, str)
REAL, DIMENSION(:) :: data1
INTEGER, DIMENSION(:,:,:) :: data3
CHARACTER(len=*) :: str
...
INTENT
attribute:
INTENT(IN)
the dummy argument must not be redefined in the procedure.
INTENT(OUT)
the dummy argument must not read in a value but must be set by the procedure.
INTENT(INOUT)
the dummy argument must be read in and redefined by the procedure.
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
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)
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 )
...
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
RESULT
clause is needed when a function references itself (its own name is unavailable),
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
SQRT(x)
returns the square root of x
:
SQRT()
if x
is real,
DSQRT()
if x is double precision,
CSQRT()
if x
is complex.
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
iswap
and rswap
to be referenced by the same generic name, swap
.
a
and b
are integer then iswap
is used.
a
and b
are real then rswap
is used.
MODULE name
[definitions]
...
[CONTAINS
module procedures]
END [MODULE [name]]
USE name
MODULE global
REAL, DIMENSION(100) :: a, b, c
INTEGER :: list(100)
LOGICAL :: test
END MODULE global
global
:
USE global
a
and c
:
USE global, ONLY: a, c
test
, but referenced as state
:
USE global, state => test
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
USE
that module.i.e. all entities are public by default.
PUBLIC
and PRIVATE
(statement or attribute).
MODULE data
PRIVATE !set default
REAL, PUBLIC :: a !public
REAL :: b !private
...
END MODULE data
INTERFACE generic_name
MODULE PROCEDURE name_list
END INTERFACE
Where name_list
are the procedures to be referred to by the generic_name
.
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
Such extended operators are `overloaded'.
INTERFACE OPERATOR( operator )
interface_block
END INTERFACE
INTENT(IN)
arguments.
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
.name.
INTERFACE OPERATOR( .name. )
interface_block
END INTERFACE
INTENT(IN)
arguments.
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
INTERFACE ASSIGNMENT( = )
interface_block
END INTERFACE
INTENT(OUT)
or INTENT(INOUT)
,
INTENT(IN)
.
A scoping unit is one of the following:
USE
the module.
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