For example,
SUBROUTINE mysub(coeffs)
REAL,INTENT(IN) :: coeffs(0:) ! Coefficients of polynomial.
REAL integral
integral = integrate(myfunc,0.0,1.0) ! Integrate from 0.0 to 1.0.
PRINT *,'Integral =',integral
CONTAINS
REAL FUNCTION myfunc(x) RESULT(y)
REAL,INTENT(IN) :: x
INTEGER i
y = coeffs(UBOUND(coeffs,1))
DO i=UBOUND(coeffs,1)-1,0,-1
y = y*x + coeffs(i)
END DO
END FUNCTION
END SUBROUTINE
Impure Elemental Integer Function checked_addition(a,b) Result(c)
Integer,Intent(In) :: a,b
If (a>0 .And. b>0) Then
If (b>Huge(c)-a) Stop 'Positive Integer Overflow'
Else If (a<0 .And. b<0) Then
If ((a+Huge(c))+b<0) Stop 'Negative Integer Overflow'
End If
c = a + b
End Function
When an argument is an array, an impure elemental procedure is applied to each
element in array element order (unlike a pure elemental procedure, which has no
specified order).
An impure elemental procedure cannot be referenced in a context that requires a
procedure to be pure, e.g. within a FORALL construct.
Impure elemental procedures are probably most useful for debugging (because i/o is allowed) and as final procedures.
PURE SUBROUTINE s(a,b)
REAL,INTENT(OUT) :: a
REAL,VALUE :: b
a = b
END SUBROUTINE
Note however that the second argument of a defined assignment subroutine, and all arguments of a defined operator function, are still required to have the INTENT(IN) attribute even if they have the VALUE attribute.
SUBROUTINE sub() BIND(C,NAME='one')
PRINT *,'one'
END SUBROUTINE
SUBROUTINE sub() BIND(C,NAME='two')
PRINT *,'two'
END SUBROUTINE
PROGRAM test
INTERFACE
SUBROUTINE one() BIND(C)
END SUBROUTINE
SUBROUTINE two() BIND(C)
END SUBROUTINE
END INTERFACE
CALL one
CALL two
END PROGRAM
The effect is that a copy is made of the actual argument, and the dummy argument is associated with the copy; any changes to the dummy argument do not affect the actual argument. For example,
PROGRAM value_example_2008
INTEGER :: a(3) = [ 1,2,3 ]
CALL s('Hello?',a)
PRINT '(7X,3I6)',a
CONTAINS
SUBROUTINE s(string,j)
CHARACTER(*),VALUE :: string
INTEGER,VALUE :: j(:)
string(LEN(string):) = '!'
j = j + 1
PRINT '(7X,A,3I6)',string,j
END SUBROUTINE
END PROGRAM
will produce the output
Hello! 2 3 4
1 2 3
A “separate module procedure” is a procedure whose interface is declared in the module specification part, but whose definition may provided either in the module itself, or in a submodule of that module. The interface of a separate module procedure is declared by using the MODULE keyword in the prefix of the interface body. For example,
INTERFACE
MODULE RECURSIVE SUBROUTINE sub(x,y)
REAL,INTENT(INOUT) :: x,y
END SUBROUTINE
END INTERFACE
An important aspect of the interface for a separate module procedure is that, unlike any other
interface body, it accesses the module by host association without the need for an IMPORT
statement.
For example,
INTEGER,PARAMETER :: wp = SELECTED_REAL_KIND(15)
INTERFACE
MODULE REAL(wp) FUNCTION f(a,b)
REAL(wp) a,b
END FUNCTION
END INTERFACE
The eventual definition of the separate module procedure, whether in the module itself or in a submodule,
must have exactly the same characteristics, the same names for the dummy arguments, the same name for the result variable (if a function), the same binding-name (if it uses BIND(C)), and be
RECURSIVE if and only if the interface is declared so.
There are two ways to achieve this:
...
CONTAINS
MODULE REAL(wp) FUNCTION f(a,b)
REAL(wp)a,b
f = a**2 - b**3
END FUNCTION
...
CONTAINS
MODULE PROCEDURE sub
! Arguments A and B, their characteristics, and that this is a recursive
! subroutine, are all taken from the interface declaration.
IF (a>b) THEN
CALL sub(b,-ABS(a))
ELSE
a = b**2 - a
END IF
END PROCEDURE
submodule-stmt
declaration-part
[ CONTAINS
module-subprogram-part ]
END [ SUBMODULE [ submodule-name ] ]
The initial submodule-stmt has the form
SUBMODULE ( module-name [ : parent-submodule-name ] ) submodule-name
where module-name is the name of a module with one or more separate module procedures,
parent-submodule-name (if present) is the name of another submodule of that module,
and submodule-name is the name of the submodule being defined.
The submodules of a module thus form a tree structure, with successive submodules being able
to extend others; however, the name of a submodule is unique within that module.
This structure is to facilitate creation of internal infrastructure (types, constants, and
procedures) that can be used by multiple submodules,
without having to put all the infrastructure inside the module itself.
The submodule being defined accesses its parent module or submodule by host association; for entities from the module, this includes access to PRIVATE entities. Any local entity it declares in the declaration-part will therefore block access to an entity in the host that has the same name.
The entities (variables, types, procedures) declared by the submodule are local to that submodule, with the sole exception of separate module procedures that are declared in the ancestor module and defined in the submodule. No procedure is allowed to have a binding name, again, except in the case of a separate module procedure, where the binding name must be the same as in the interface.
For example,
MODULE mymod
INTERFACE
MODULE INTEGER FUNCTION next_number() RESULT(r)
END FUNCTION
MODULE SUBROUTINE reset()
END SUBROUTINE
END INTERFACE
END MODULE
SUBMODULE (mymod) variables
INTEGER :: next = 1
END SUBMODULE
SUBMODULE (mymod:variables) functions
CONTAINS
MODULE PROCEDURE next_number
r = next
next = next + 1
END PROCEDURE
END SUBMODULE
SUBMODULE (mymod:variables) subroutines
CONTAINS
MODULE SUBROUTINE reset()
PRINT *,'Resetting'
next = 1
END SUBROUTINE
END SUBMODULE
PROGRAM demo
USE mymod
PRINT *,'Hello',next_number()
PRINT *,'Hello again',next_number()
CALL reset
PRINT *,'Hello last',next_number()
END PROGRAM
Submodule information for use by other submodules is stored by the NAG Fortran Compiler in files named module.submodule.sub, in a format similar to that of .mod files. The -nomod option, which suppresses creation of .mod files, also suppresses creation of .sub files.