-
An empty internal subprogram part, module subprogram part or type-bound
procedure part is now permitted following a CONTAINS statement.
In the case of the type-bound procedure part, an ineffectual PRIVATE
statement may appear following the unnecessary CONTAINS statement.
-
[6.0]
An internal procedure can be passed as an actual argument or assigned to a
procedure pointer.
When the internal procedure is invoked via the dummy argument or procedure
pointer, it can access the local variables of its host procedure.
In the case of procedure pointer assignment, the pointer is only valid until
the host procedure returns (since the local variables cease to exist at that
point).
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
-
The rules used for generic resolution and for checking that procedures in a
generic are unambiguous have been extended.
The extra rules are that
-
a dummy procedure is distinguishable from a dummy variable;
-
an ALLOCATABLE dummy variable is distinguishable from a POINTER
dummy variable that does not have INTENT(IN).
-
[6.0]
A disassociated pointer, or an unallocated allocatable variable, may be passed
as an actual argument to an optional nonallocatable nonpointer dummy argument.
This is treated as if the actual argument were not present.
-
[5.3.1]
Impure elemental procedures can be defined using the IMPURE keyword.
An impure elemental procedure has the restrictions that apply to elementality
(e.g. all arguments must be scalar) but does not have any of the “pure”
restrictions. This means that an impure elemental procedure may have side
effects and can contain input/output and STOP statements.
For example,
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.
-
[6.0]
If an argument of a pure procedure has the VALUE attribute it does not
need any INTENT attribute.
For example,
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.
-
[5.3.1]
The FUNCTION or SUBROUTINE keyword on the END statement for an
internal or module subprogram is now optional (when the subprogram name does not
appear).
Previously these keywords were only optional for external subprograms.
-
ENTRY statements are regarded as obsolescent.
-
[1.0]
A line in the program is no longer prohibited from beginning with a semi-colon.
-
[6.2] The name of an external procedure with a binding label is now considered
to be a local identifier only, and not a global identifier.
That means that code like the following is now standard-conforming:
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
-
[6.2]
An internal procedure is permitted to have the BIND(C) attribute,
as long as it does not have a NAME= specifier.
Such a procedure is interoperable with C, but does not have a binding label
(as if it were specified with NAME='').
-
[6.2]
A dummy argument with the VALUE attribute is permitted to be an array,
and is permitted to be of type CHARACTER with length non-constant and/or
not equal to one.
(It is still not permitted to have the ALLOCATABLE or POINTER
attributes, and is not permitted to be a coarray.)
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