--- local: ---
As a general principle, this compiler will accept by default and without complaint many legacy features, extensions to the standard language, and features that have been deleted from the standard, so long as the recognition of those features would not cause a standard-conforming program to be rejected or misinterpreted.
Other non-standard features, which do conflict with the current standard specification of the Fortran programming language, are accepted if enabled by command-line options.
INTEGER
actual argument expressions (not variables!) are converted to the kinds of scalar INTEGER
dummy arguments when the interface is explicit and the kinds differ. This conversion allows the results of the intrinsics like SIZE
that (as mentioned below) may return non-default INTEGER
results by default to be passed. A warning is emitted when truncation is possible. These conversions are not applied in calls to non-intrinsic generic procedures.BLOCK DATA
subprograms so long as they contain no executable code, no internal subprograms, and allocate no storage outside a named COMMON
block. (C1415)character(11) :: buffer(3) character(10) :: quotes = '""""""""""' write(buffer,*,delim="QUOTE") quotes print "('>',a10,'<')", buffer end
COUNT=
and the COUNT_MAX=
optional arguments are present on the same call to the intrinsic subroutine SYSTEM_CLOCK
, we require that their types have the same integer kind, since the kind of these arguments is used to select the clock rate. In common with some other compilers, the clock rate varies from tenths of a second to nanoseconds depending on argument kind and platform support.CFI_section
, CFI_setpointer
or CFI_allocate
, the lower bound on that dimension will be set to 1 for consistency with the LBOUND()
intrinsic function.-2147483648_4
is, strictly speaking, a non-conforming literal constant on a machine with 32-bit two's-complement integers as kind 4, because the grammar of Fortran expressions parses it as a negation of a literal constant, not a negative literal constant. This compiler accepts it with a portability warning.loop
in loop: do j=1,n
are defined to be “local identifiers” and should be distinct in the “inclusive scope” -- i.e., not scoped by BLOCK
constructs. As most (but not all) compilers implement BLOCK
scoping of construct names, so does f18, with a portability warning.USE
statement can also be used as a non-global name in the same scope. This is not conforming, but it is useful and unambiguous.RANDOM_NUMBER
may not be an assumed-size array.NULL()
without MOLD=
is not allowed to be associated as an actual argument corresponding to an assumed-rank dummy argument; its rank in the called procedure would not be well-defined.FORALL
or DO CONCURRENT
is present in the enclosing scope, and the construct does not have an explicit type specification for its index variables, some weird restrictions in F'2023 subclause 19.4 paragraphs 6 & 8 should apply. Since this compiler properly scopes these names, violations of these restrictions elicit only portability warnings by default.MOD
and MODULO
for real arguments using expressions in terms of AINT
and FLOOR
. These definitions yield fairly poor results due to floating-point cancellation, and every Fortran compiler (including this one) uses better algorithms.PROCEDURE(), BIND(C) :: PROC
is not conforming, as there is no procedure interface. This compiler accepts it, since there is otherwise no way to declare an interoperable dummy procedure with an arbitrary interface like void (*)()
.PURE
functions are allowed to have dummy arguments that are neither INTENT(IN)
nor VALUE
, similar to PURE
subroutines, with a warning. This enables atomic memory operations to be naturally represented as PURE
functions, which allows their use in parallel constructs and DO CONCURRENT
.ASYNCHRONOUS
or VOLATILE
dummy argument, F‘2023 15.5.2.5 p31 notwithstanding. The effects of these attributes are scoped over the lifetime of the procedure reference, and they can by added by internal subprograms and BLOCK
constructs within the procedure. Further, a dummy argument can acquire the ASYNCHRONOUS
attribute implicitly simply appearing in an asynchronous data transfer statement, without the attribute being visible in the procedure’s explicit interface.USE
association with renaming, the name of the extended derived type’s parent component is the new name by which the base is known in the scope of the extended derived type, not the original. This interpretation has usability advantages and is what six other Fortran compilers do, but is not conforming now that J3 approved an “interp” in June 2024 to the contrary.<>
as synonym for .NE.
and /=
$
and @
as legal characters in names/values/
*
, e.g. REAL*4
DOUBLE COMPLEX
as a synonym for COMPLEX(KIND(0.D0))
-- but not when spelled TYPE(DOUBLECOMPLEX)
.STRUCTURE
, RECORD
, with ‘%FILL’; but UNION
, and MAP
are not yet supported throughout compilation, and elicit a “not yet implemented” message..field
BYTE
as synonym for INTEGER(KIND=1)
; but not when spelled TYPE(BYTE)
.Q
X
prefix/suffix as synonym for Z
on hexadecimal literalsB
, O
, Z
, and X
accepted as suffixes as well as prefixesL
in FORMAT statement%LOC
, %VAL
, and %REF
PROGRAM P()
FUNCTION F
POINTER(p,x)
and LOC()
intrinsic (with %LOC()
as an alias)IF
. (Which branch should NaN take? Fall through?)ASSIGN
statement, assigned GO TO
, and assigned formatPAUSE
statementNAMELIST
allowed in the execution part(x+y,z)
+
and -
before all primary expressions, e.g. x*-y
.NOT. .NOT.
acceptedNAME=
as synonym for FILE=
D
lines in fixed form as comments or debug codeCARRIAGECONTROL=
on the OPEN and INQUIRE statementsCONVERT=
on the OPEN and INQUIRE statementsDISPOSE=
on the OPEN and INQUIRE statements&
in column 1 in fixed form source is a variant form of continuation line.FORMAT
statements) are allowed on output.IAND(X'1',X'2')
, or as arguments of DIM
, MOD
, MODULO
, and SIGN
. Note that while other compilers may accept such usages, the type resolution of such BOZ literals usages is highly non portable).EXTENDEDTYPE(PARENTTYPE(1,2,3))
rather than EXTENDEDTYPE(1,2,3)
or EXTENDEDTYPE(PARENTTYPE=PARENTTYPE(1,2,3))
).+
operator, and defining the result type accordingly.POINTER
or ALLOCATABLE
and is INTENT(IN)
, we relax enforcement of some requirements on actual arguments that must otherwise hold true for definable arguments.POINTER
or ALLOCATABLE
actual argument to be associated with a compatible monomorphic dummy argument, as our implementation, like others, supports a reallocation that would change the dynamic typeLOGICAL
to INTEGER
and vice versa (but not other types) is allowed. The values are normalized to canonical .TRUE.
/.FALSE.
. The values are also normalized for assignments of LOGICAL(KIND=K1)
to LOGICAL(KIND=K2)
, when K1 != K2
.LOGICAL
with INTEGER
is allowed in DATA
statements and object initializers. The results are not normalized to canonical .TRUE.
/.FALSE.
. Static initialization of INTEGER
with LOGICAL
is also permitted.RETURN
statement may appear in a main program.COMMON
block variable is permitted to appear in a specification expression, such as an array bound, in a scope with IMPLICIT NONE(TYPE) if the name of the variable would have caused it to be implicitly typed as default INTEGER if IMPLICIT NONE(TYPE) were absent.CONTIGUOUS
attribute can be redundantly applied to simply contiguous objects, including scalars, with a portability warning.ALLOCATABLE
dummy arguments are distinguishing if an actual argument acceptable to one could not be passed to the other & vice versa because exactly one is polymorphic or exactly one is unlimited polymorphic).ERROR_UNIT
in the intrinsic ISO_FORTRAN_ENV
module.POINTER
component's type need not be a sequence type when the component appears in a derived type with SEQUENCE
. (This case should probably be an exception to constraint C740 in the standard.)NAMELIST
input will skip over NAMELIST
groups with other names, and will treat text before and between groups as if they were comment lines, even if not begun with !
.AND
, OR
, and XOR
are accepted as aliases for the standard intrinsic functions IAND
, IOR
, and IEOR
respectively.IMAG
is accepted as an alias for the generic intrinsic function AIMAG
.IZEXT
and JZEXT
are supported; ZEXT
has different behavior with various older compilers, so it is not supported.INTERFACE
can declare the interface of a procedure pointer even if it is not a dummy argument.NOPASS
type-bound procedure binding is required by C1529 to apply only to a scalar data-ref, but most compilers don't enforce it and the constraint is not necessary for a correct implementation.BIND(C)
procedure, or a logical component to a BIND(C)
derived type does not have to have KIND=C_BOOL
since it can be converted to/from _Bool
without loss of information.SOURCE=
or MOLD=
in ALLOCATE
may be distinct from the constant character length, if any, of an allocated object.IMPORT
from its host, it's an error only if the resolution is ambiguous.DATA
statement before its explicit type declaration under IMPLICIT NONE(TYPE)
.INCLUDE
lines can start in any column, can be preceded in fixed form source by a ‘0’ in column 6, can contain spaces between the letters of the word INCLUDE, and can have a numeric character literal kind prefix on the file name.INTRINSIC
functions are accepted for use in PROCEDURE
statements in generic interfaces, as in some other compilers.NULL()
pointer is treated as an unallocated allocatable when associated with an INTENT(IN)
allocatable dummy argument.READ(..., SIZE=n)
is accepted with NML=
and FMT=*
with a portability warning. The Fortran standard doesn't allow SIZE=
with formatted input modes that might require look-ahead, perhaps to ease implementations.INCLUDE
line or #include
directive has a continuation marker at the end of its last line in free form, Fortran line continuation works.NAMELIST
input group may omit its trailing /
character if it is followed by another NAMELIST
input group.NAMELIST
input group may begin with either &
or $
.MAX
and MIN
are converted when necessary to the type of the result. An OPTIONAL
, POINTER
, or ALLOCATABLE
argument after the first two cannot be converted, as it may not be present.+
or -
operator.BIND(C, NAME="...", CDEFINED)
signifies that the storage for an interoperable variable will be allocated outside of Fortran, probably by a C or C++ external definition.\U
..T.
, .F.
, .N.
, .A.
, .O.
, and .X.
[-flogical-abbreviations].XOR.
as a synonym for .NEQV.
[-fxor-operator]INTEGER
type is required by the standard to occupy the same amount of storage as the default REAL
type. Default REAL
is of course 32-bit IEEE-754 floating-point today. This legacy rule imposes an artificially small constraint in some cases where Fortran mandates that something have the default INTEGER
type: specifically, the results of references to the intrinsic functions SIZE
, STORAGE_SIZE
,LBOUND
, UBOUND
, SHAPE
, and the location reductions FINDLOC
, MAXLOC
, and MINLOC
in the absence of an explicit KIND=
actual argument. We return INTEGER(KIND=8)
by default in these cases when the -flarge-sizes
option is enabled. SIZEOF
and C_SIZEOF
always return INTEGER(KIND=8)
.IMPLICIT NONE
[-fimplicit-none-type-always]IMPLICIT NONE
and IMPLICIT NONE(TYPE)
[-fimplicit-none-type-never]PARAMETER pi=3.14
statement without parentheses [-falternative-parameter-statement].LG.
as synonym for .NE.
REDIMENSION
COMMON
ACCEPT
as synonym for READ *
TYPE
as synonym for PRINT
ARRAY
as synonym for DIMENSION
VIRTUAL
as synonym for DIMENSION
ENCODE
and DECODE
as synonyms for internal I/OIMPLICIT AUTOMATIC
, IMPLICIT STATIC
3.14159E
B
suffix on unquoted octal constantsZ
prefix on unquoted hexadecimal constants (dangerous)T
and F
as abbreviations for .TRUE.
and .FALSE.
in DATA (PGI/XLF).NOT.
, .AND.
, .OR.
, and .XOR.
.NCHARACTER
type and NC
Kanji character literalsPRIVATE
, or be intermixed with the component declarations.%LIST
, %NOLIST
, %EJECT
)INCLUDE
linesNULL()
actual argument corresponding to an ALLOCATABLE
dummy data objectELEMENTAL
procedures may not be passed as actual arguments, in accordance with the standard; some Fortran compilers permit such usage.CHARACTER::COS
and still get a real result from COS(3.14159)
, for example. f18 will complain when a generic intrinsic function's inferred result type does not match an explicit declaration. This message is a warning.DATA
statements; e.g., REAL, POINTER :: P => T(1:10:2)
. This Fortran 2008 feature might as well be viewed like an extension; no other compiler that we've tested can handle it yet.ASSOCIATE
or related construct is defined by a variable, it has the TARGET
attribute if the variable was a POINTER
or TARGET
. We read this to include the case of the variable being a pointer-valued function reference. No other Fortran compiler seems to handle this correctly for ASSOCIATE
, though NAG gets it right for SELECT TYPE
.INCLUDE
lines have been allowed to have a numeric kind parameter prefix on the file name. No other Fortran compiler supports them that I can find.SEQUENCE
derived type is required (F'2023 C745) to have at least one component. No compiler enforces this constraint; this compiler emits a warning.VALUE
assumed-length character dummy argument, which has been standard since F'2008. We accept this usage with an optional portability warning.ASYNCHRONOUS
attribute can be implied by usage in data transfer I/O statements. Only one other compiler supports this correctly. This compiler does, apart from objects in asynchronous NAMELIST I/O, for which an actual asynchronous runtime implementation seems unlikely.module module contains subroutine host(j) ! Although "m" never appears in the specification or executable ! parts of this subroutine, both of its contained subroutines ! might be accessing it via host association. integer, intent(in out) :: j call inner1(j) call inner2(j) contains subroutine inner1(n) integer(kind(m)), intent(in) :: n m = n + 1 end subroutine subroutine inner2(n) integer(kind(m)), intent(out) :: n n = m + 2 end subroutine end subroutine end module program demo use module integer :: k k = 0 call host(k) print *, k, " should be 3" end
Other Fortran compilers disagree in their interpretations of this example; some seem to treat the references to m
as if they were host associations to an implicitly typed variable (and print 3
), while others seem to treat them as references to implicitly typed local variables, and load uninitialized values.
In f18, we chose to emit an error message for this case since the standard is unclear, the usage is not portable, and the issue can be easily resolved by adding a declaration.
In subclause 7.5.6.2 of Fortran 2018 the standard defines a partial ordering of the final subroutine calls for finalizable objects, their non-parent components, and then their parent components. (The object is finalized, then the non-parent components of each element, and then the parent component.) Some have argued that the standard permits an implementation to finalize the parent component before finalizing an allocatable component in the context of deallocation, and the next revision of the language may codify this option. In the interest of avoiding needless confusion, this compiler implements what we believe to be the least surprising order of finalization. Specifically: all non-parent components are finalized before the parent, allocatable or not; all finalization takes place before any deallocation; and no object or subobject will be finalized more than once.
When RECL=
is set via the OPEN
statement for a sequential formatted input file, it functions as an effective maximum record length. Longer records, if any, will appear as if they had been truncated to the value of RECL=
. (Other compilers ignore RECL=
, signal an error, or apply effective truncation to some forms of input in this situation.) For sequential formatted output, RECL= serves as a limit on record lengths that raises an error when it is exceeded.
When a DATA
statement in a BLOCK
construct could be construed as either initializing a host-associated object or declaring a new local initialized object, f18 interprets the standard's classification of a DATA
statement as being a “declaration” rather than a “specification” construct, and notes that the BLOCK
construct is defined as localizing names that have specifications in the BLOCK
construct. So this example will elicit an error about multiple initialization:
subroutine subr integer n = 1 block data n/2/ end block end subroutine
Other Fortran compilers disagree with each other in their interpretations of this example. The precedent among the most commonly used compilers agrees with f18's interpretation: a DATA
statement without any other specification of the name refers to the host-associated object.
USE
-associated into a scope that also contains a generic interface of the same name but does not have the USE
-associated non-generic procedure as a specific procedure.module m1 contains subroutine foo(n) integer, intent(in) :: n end subroutine end module module m2 use m1, only: foo interface foo module procedure noargs end interface contains subroutine noargs end subroutine end module
This case elicits a warning from f18, as it should not be treated any differently than the same case with the non-generic procedure of the same name being defined in the same scope rather than being USE
-associated into it, which is explicitly non-conforming in the standard and not allowed by most other compilers. If the USE
-associated entity of the same name is not a procedure, most compilers disallow it as well.
Fortran 2018 19.3.4p1: “A component name has the scope of its derived-type definition. Outside the type definition, it may also appear ...” which seems to imply that within its derived-type definition, a component name is in its scope, and at least shadows any entity of the same name in the enclosing scope and might be read, thanks to the “also”, to mean that a “bare” reference to the name could be used in a specification inquiry. However, most other compilers do not allow a component to shadow exterior symbols, much less appear in specification inquiries, and there are application codes that expect exterior symbols whose names match components to be visible in a derived-type definition's default initialization expressions, and so f18 follows that precedent.
19.3.1p1 “Within its scope, a local identifier of an entity of class (1) or class (4) shall not be the same as a global identifier used in that scope...” is read so as to allow the name of a module, submodule, main program, or BLOCK DATA
subprogram to also be the name of an local entity in its scope, with a portability warning, since that global name is not actually capable of being “used” in its scope.
In the definition of the ASSOCIATED
intrinsic function (16.9.16), its optional second argument TARGET=
is required to be “allowable as the data-target or proc-target in a pointer assignment statement (10.2.2) in which POINTER is data-pointer-object or proc-pointer-object.” Some Fortran compilers interpret this to require that the first argument (POINTER=
) be a valid left-hand side for a pointer assignment statement -- in particular, it cannot be NULL()
, but also it is required to be modifiable. As there is no good reason to disallow (say) an INTENT(IN)
pointer here, or even NULL()
as a well-defined case that is always .FALSE.
, this compiler doesn't require the POINTER=
argument to be a valid left-hand side for a pointer assignment statement, and we emit a portability warning when it is not.
F18 allows a USE
statement to reference a module that is defined later in the same compilation unit, so long as mutual dependencies do not form a cycle. This feature forestalls any risk of such a USE
statement reading an obsolete module file from a previous compilation and then overwriting that file later.
F18 allows OPTIONAL
dummy arguments to interoperable procedures unless they are VALUE
(C865).
F18 processes the NAMELIST
group declarations in a scope after it has resolved all of the names in that scope. This means that names that appear before their local declarations do not resolve to host associated objects and do not elicit errors about improper redeclarations of implicitly typed entities.
Standard Fortran allows forward references to derived types, which can lead to ambiguity when combined with host association. Some Fortran compilers resolve the type name to the host type, others to the forward-referenced local type; this compiler diagnoses an error.
module m type ambiguous; integer n; end type contains subroutine s type(ambiguous), pointer :: ptr type ambiguous; real a; end type end end
When an intrinsic procedure appears in the specification part of a module only in function references, but not an explicit INTRINSIC
statement, its name is not brought into other scopes by a USE
statement.
The subclause on rounding in formatted I/O (13.7.2.3.8 in F'2023) only discusses rounding for decimal-to/from-binary conversions, omitting any mention of rounding for hexadecimal conversions. As other compilers do apply rounding, so does this one.
For real MAXVAL
, MINVAL
, MAXLOC
, and MINLOC
, NaN values are essentially ignored unless there are some unmasked array entries and all of them are NaNs.
When INDEX
is used as an unrestricted specific intrinsic function in the context of an actual procedure, as the explicit interface in a PROCEDURE
declaration statement, or as the target of a procedure pointer assignment, its interface has exactly two dummy arguments (STRING=
and SUBSTRING=
), and includes neither BACK=
nor KIND=
. This is how INDEX
as an unrestricted specific intrinsic function was documented in FORTRAN '77 and Fortran ‘90; later revisions of the standard deleted the argument information from the section on unrestricted specific intrinsic functions. At least one other compiler (XLF) seems to expect that the interface for INDEX
include an optional BACK=
argument, but it doesn’t actually work.
Allocatable components of array and structure constructors are deallocated after use without calling final subroutines. The standard does not specify when and how deallocation of array and structure constructors allocatable components should happen. All compilers free the memory after use, but the behavior when the allocatable component is a derived type with finalization differ, especially when dealing with nested array and structure constructors expressions. Some compilers call final routine for the allocatable components of each constructor sub-expressions, some call it only for the allocatable component of the top level constructor, and some only deallocate the memory. Deallocating only the memory offers the most flexibility when lowering such expressions, and it is not clear finalization is desirable in such context (Fortran interop 1.6.2 in F2018 standards require array and structure constructors not to be finalized, so it also makes sense not to finalize their allocatable components when releasing their storage).
F'2023 19.4 paragraph 5: “If integer-type-spec appears in data-implied-do or ac-implied-do-control it has the specified type and type parameters; otherwise it has the type and type parameters that it would have if it were the name of a variable in the innermost executable construct or scoping unit that includes the DATA statement or array constructor, and this type shall be integer type.” Reading “would have if it were” as being the subjunctive, this would mean that an untyped implied DO index variable should be implicitly typed according to the rules active in the enclosing scope. But all other Fortran compilers interpret the “would have if it were” as meaning “has if it is” -- i.e., if the name is visible in the enclosing scope, the type of that name is used as the type of the implied DO index. So this is an error, not a simple application of the default implicit typing rule:
character j print *, [(j,j=1,10)]
EXTENDS_TYPE_OF()
returns .TRUE.
if both of its arguments have the same type, a case that is technically implementation-defined.
ENCODING=
is not in the list of changeable modes on an I/O unit, but every Fortran compiler allows the encoding to be changed on an open unit.
A NAMELIST
input item that references a scalar element of a vector or contiguous array can be used as the initial element of a storage sequence. For example, “&GRP A(1)=1. 2. 3./” is treated as if had been “&GRP A(1:)=1. 2. 3./”.