OPERATOR
generic has the VALUE
attribute, it is no longer required to have the INTENT(IN)
attribute.
For example,
INTERFACE OPERATOR(+) MODULE PROCEDURE logplus END INTERFACE ... PURE LOGICAL FUNCTION logplus(a,b) LOGICAL,VALUE :: a,b logplus = a.OR.b END FUNCTION
ASSIGNMENT
generic has the
VALUE
attribute, it is no longer required to have the INTENT(IN)
attribute.
For example,
INTERFACE ASSIGNMENT(=) MODULE PROCEDURE asgnli END INTERFACE ... PURE SUBROUTINE asgnli(a,b) LOGICAL,INTENT(OUT) :: a INTEGER,VALUE :: b DO WHILE (IAND(b,NOT(1))/=0) b = IEOR(IAND(b,1),SHIFTR(b,1)) END DO a = b/=0 ! Odd number of "1" bits. END SUBROUTINE
INTEGER FUNCTION factorial(n) RESULT(r) IF (n>1) THEN r = n*factorial(n-1) ELSE r = 1 END IF END FUNCTIONis valid, just as if it had been explicitly declared with the
RECURSIVE
keyword.
This does not apply to assumed-length character functions (where the result is declared with CHARACTER(LEN=*)
; these remain prohibited from being declared RECURSIVE
.
Note that procedures that are RECURSIVE
by default are excluded from the effects of the -save option, exactly as if they were explicitly declared RECURSIVE
.
RECURSIVE
or by default (when the -f2018 or -recursive options are specified).
For example,
ELEMENTAL RECURSIVE INTEGER FUNCTION factorial(n) RESULT(r) INTEGER,INTENT(IN) :: n IF (n>1) THEN r = n*factorial(n-1) ELSE r = 1 END IF END FUNCTIONmay be invoked with
PRINT *,factorial( [ 1,2,3,4,5 ] )to print the first five factorials.
NON_RECURSIVE
keyword explicitly declares that a procedure will not be called recursively.
For example,
NON_RECURSIVE INTEGER FUNCTION factorial(n) RESULT(r) r = 1 DO i=2,n r = r*i END DO END FUNCTION
In Fortran 2008 and older standards, procedures are non-recursive by default, so this keyword has no effect unless the -recursive or -f2018 is being used.
For example,
MODULE npa_example INTERFACE g MODULE PROCEDURE s1,s2 END INTERFACE CONTAINS SUBROUTINE s1(a) EXTERNAL a CALL a END SUBROUTINE SUBROUTINE s2(b,a) EXTERNAL b,a CALL b CALL a END SUBROUTINE END MODULE
This example does not conform to the Fortran 2008 rules for unambiguous generic procedures,
because the argument A
distinguishes by position but not by keyword,
the argument B
distinguish by keyword but not by position,
and the positional disambiguator (A
) does not appear earlier in the list than the keyword
disambiguator (B
).
GENERIC
statement provides a concise way of declaring generic interfaces.
It has the syntax:
GENERIC
[ , access-spec ] ::
generic-spec =>
procedure-name-list
PUBLIC
or PRIVATE
,
the generic-spec is a generic identifier (name, ASSIGNMENT(=)
,
OPERATOR(
op)
, or {READ
|WRITE
}(
{FORMATTED
|UNFORMATTED
})
),
and the procedure-name-list is a comma-separated list of named procedures.
The access-spec is only permitted if the GENERIC
statement is in the specification
part of a module.
Each named procedure in the list must have an explicit interface; that is, it must be an internal
procedure, module procedure, or be declared with an interface block or procedure declaration
statement that specifies an explicit interface.
Collectively, the procedures must satisfy the usual generic rules about all being functions or
all being subroutines, and being unambiguous.
Apart from the optional access-spec, the GENERIC
statement has the same effect as
INTERFACE generic-spec PROCEDURE procedure-name-list END INTERFACEThe only advantage is that it is a couple of lines shorter, and can declare the accessibility in the same line. This syntax is the same as for a generic-binding in a derived type definition, except that the list of names is of ordinary named procedures instead of type-bound procedures.
For example, the program
Module print_sqrt Private Generic,Public :: g => s1, s2 Contains Subroutine s1(x) Print '(F10.6)',Sqrt(x) End Subroutine Subroutine s2(n) Print '(I10)',Nint(Sqrt(Real(n))) End Subroutine End Module Program test Use print_sqrt Call g(2.0) Call g(127) End Programwill print
1.414214 11
USE
statement)
can be controlled by specifying that module name in a PUBLIC
or PRIVATE
statement,
overriding the default accessibility of other entities in the importing module.
For example, in
Module mymod Use Iso_Fortran_Env Real(real32) x Integer(int64) y Private Iso_Fortran_Env End Moduleall the entities in
ISO_FORTRAN_ENV
are by default PRIVATE
in module mymod
,
without needing to list them individually.
This new default accessibility can be overridden by an explicit PUBLIC
or PRIVATE
declaration.
Also, if an entity in a remote module (two or more USE
statements away) is accessed by more
than one intervening module, it is default PRIVATE
only if every route to the entity is
default PRIVATE
, and default PUBLIC
if any route is default PUBLIC
.
For example, in
Module remote Real a,b End Module Module route_one Use remote Private remote End Module Module route_two Use remote End Module Module my_module Use route_one Use route_two Private route_one End Modulethe variables
A
and B
in module REMOTE
are PUBLIC
in module MY_MODULE
,
because they are accessible via module ROUTE_TWO
which is default PUBLIC
.