EQUIVALENCE
and COMMON
statements, and the BLOCK DATA
program unit,
are considered to be obsolescent (and reported as such when the -f2018 option is used).
ALLOCATABLE
or POINTER
attribute, and thus accept allocatable/pointer variables of any rank.
The syntax is as follows:
Real,Dimension(..) :: a, b Integer :: c(..)That declares three variables (which must be dummy arguments) to be assumed-rank.
The use of assumed-rank dummy arguments within Fortran is extremely limited; basically, the
intrinsic inquiry functions can be used, and there is a SELECT RANK
construct, but other
than that they may only appear as actual arguments to other procedures where they correspond to
another assumed-rank argument.
The main use of assumed rank is for advanced C interoperability (see later section).
Here is an extremely simple example of use within Fortran:
Program assumed_rank_example Real x(1,2),y(3,4,5,6,7) Call showrank(1.5) Call showrank(x) Call showrank(y) Contains Subroutine showrank(a) Real,Intent(In) :: a(..) Print *,'Rank is',Rank(a) End Subroutine End ProgramThat will produce the output
Rank is 0 Rank is 2 Rank is 5
TYPE(*)
type specifier can be used to declare scalar, assumed-size, and assumed-rank dummy arguments.
Such an argument is called assumed-type; the corresponding actual argument may be of any type.
It must not have the ALLOCATABLE
, CODIMENSION
, INTENT (OUT)
, POINTER
,
or VALUE
attribute.
An assumed-type variable is extremely limited in the ways it can be used directly in Fortran:
IS_CONTIGUOUS
, LBOUND
,
PRESENT
, SHAPE
, SIZE
, or UBOUND
;
C_LOC
(in the ISO_C_BINDING
intrinsic module}.
This is mostly useful for interoperating with C programs (see later section). Note that in a non-generic procedure reference, a scalar argument can be passed to an assumed-type argument that is an assumed-size array.
IMPLICIT NONE
statement can now have TYPE
and EXTERNAL
specifiers.
Its full syntax is now:
IMPLICIT NONE
[ (
[ implicit-none-specifier-list ] )
]
EXTERNAL
and TYPE
.
No keyword may appear more than once in the list.
If the list does not appear, or if TYPE
appears in the list, no other IMPLICIT
statement may appear
in the scoping unit.
The semantics of:
IMPLICIT NONE ()
IMPLICIT NONE (TYPE)
IMPLICIT NONE
If the keyword EXTERNAL
appears, a procedure with an implicit interface that is referenced
in the scoping unit must be given the EXTERNAL
attribute explicitly: that is, it must be
declared in an EXTERNAL
statement, in a type declaration statement that has the EXTERNAL
attribute,
or in a procedure declaration statement.
For example,
Subroutine sub(x) Implicit None (External) Integer f Print *,f(x) End Subroutinewill produce an error for the reference to the function
F
, because it does not have the EXTERNAL
attribute.
If the keyword EXTERNAL
appears and the keyword TYPE
does not appear, implicit typing is not disabled,
and other IMPLICIT
statements may appear in the scoping unit.
If both the keywords TYPE
and EXTERNAL
appear, both
implicit typing is disabled, and the EXTERNAL
attribute is required for implicit-interface procedures.
IMPORT
statement can appear in BLOCK
constructs and nested subprograms.
By default, such scoping units have access to all entities in the host scope by host association,
so by itself this is only useful as (compiler-checked) documentation.
For example,
Subroutine outer(x,y) Real,Intent(InOut) :: x, y(:) … Contains Subroutine inner Import :: x, y …
IMPORT,NONE
, IMPORT,ALL
, and IMPORT,ONLY
statements.
Like other IMPORT
statements, they can appear only in interface bodies, BLOCK
constructs, and
contained subprograms,
and appear in between USE
statements and other specification statements.
The IMPORT,NONE
statement specifies that no entities in the host scope are accessible by host association.
That is the default for interface bodies other than separate module procedure interfaces.
If an IMPORT,NONE
statement appears in a scoping unit, no other IMPORT
statement may appear.
For example, in
Subroutine outer(x,y) Real,Intent(InOut) :: x, y(:) … Contains Subroutine inner Import,None Implicit Integer (a-z) Read *,x Print *,x End Subroutine End Subroutinethe
X
in subroutine INNER
is not a reference to the X
in its host OUTER
,
but is an implicitly typed (Integer
) variable that is local to INNER
.
The IMPORT,ALL
statement specifies that all host entities are accessed.
That means that a declaration which would otherwise make a host entity inaccessible (so-called “shadowing”), is invalid.
For example, in
Subroutine outer(x,y) Real,Intent(InOut) :: x, y(:) … Contains Subroutine inner Import,All Integer,External :: y …the declaration of
Y
inside INNER
is invalid, and will produce a compilation error.
If an IMPORT,ALL
statement appears in a scoping unit, no other IMPORT
statement may appear.
The IMPORT,ONLY
statement specifies that only host entities named in IMPORT,ONLY
statements are
accessible by host association.
If an IMPORT,ONLY
statement appears in a scoping unit, all other IMPORT
statements must have the ONLY
keyword.
For example, in
Subroutine outer(x,y,z) Real,Intent(InOut) :: x, y(:),z … Contains Subroutine inner Import,Only:x,y z = x + ythe references to
X
and Y
in INNER
are references to the host (OUTER
) entities,
but the reference to Z
in INNER
is to an implicitly-typed local variable.