xref: /llvm-project/flang/docs/Extensions.md (revision eb77f442b342a1bb234254e05759933bad9dfab1)
1<!--===- docs/Extensions.md
2
3   Part of the LLVM Project, under the Apache License v2.0 with LLVM Exceptions.
4   See https://llvm.org/LICENSE.txt for license information.
5   SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception
6
7-->
8
9# Fortran Extensions supported by Flang
10
11```{contents}
12---
13local:
14---
15```
16
17As a general principle, this compiler will accept by default and
18without complaint many legacy features, extensions to the standard
19language, and features that have been deleted from the standard,
20so long as the recognition of those features would not cause a
21standard-conforming program to be rejected or misinterpreted.
22
23Other non-standard features, which do conflict with the current
24standard specification of the Fortran programming language, are
25accepted if enabled by command-line options.
26
27## Intentional violations of the standard
28
29* Scalar `INTEGER` actual argument expressions (not variables!)
30  are converted to the kinds of scalar `INTEGER` dummy arguments
31  when the interface is explicit and the kinds differ.
32  This conversion allows the results of the intrinsics like
33  `SIZE` that (as mentioned below) may return non-default
34  `INTEGER` results by default to be passed.  A warning is
35  emitted when truncation is possible.  These conversions
36  are not applied in calls to non-intrinsic generic procedures.
37* We are not strict on the contents of `BLOCK DATA` subprograms
38  so long as they contain no executable code, no internal subprograms,
39  and allocate no storage outside a named `COMMON` block.  (C1415)
40* Delimited list-directed (and NAMELIST) character output is required
41  to emit contiguous doubled instances of the delimiter character
42  when it appears in the output value.  When fixed-size records
43  are being emitted, as is the case with internal output, this
44  is not possible when the problematic character falls on the last
45  position of a record.  No two other Fortran compilers do the same
46  thing in this situation so there is no good precedent to follow.
47  Because it seems least wrong, we emit one copy of the delimiter as
48  the last character of the current record and another as the first
49  character of the next record.  (The second-least-wrong alternative
50  might be to flag a runtime error, but that seems harsh since it's
51  not an explicit error in the standard, and the output may not have
52  to be usable later as input anyway.)
53  Consequently, the output is not suitable for use as list-directed or
54  NAMELIST input.  If a later standard were to clarify this case, this
55  behavior will change as needed to conform.
56```
57character(11) :: buffer(3)
58character(10) :: quotes = '""""""""""'
59write(buffer,*,delim="QUOTE") quotes
60print "('>',a10,'<')", buffer
61end
62```
63* The name of the control variable in an implied DO loop in an array
64  constructor or DATA statement has a scope over the value-list only,
65  not the bounds of the implied DO loop.  It is not advisable to use
66  an object of the same name as the index variable in a bounds
67  expression, but it will work, instead of being needlessly undefined.
68* If both the `COUNT=` and the `COUNT_MAX=` optional arguments are
69  present on the same call to the intrinsic subroutine `SYSTEM_CLOCK`,
70  we require that their types have the same integer kind, since the
71  kind of these arguments is used to select the clock rate.  In common
72  with some other compilers, the clock rate varies from tenths of a
73  second to nanoseconds depending on argument kind and platform support.
74* If a dimension of a descriptor has zero extent in a call to
75  `CFI_section`, `CFI_setpointer` or `CFI_allocate`, the lower
76  bound on that dimension will be set to 1 for consistency with
77  the `LBOUND()` intrinsic function.
78* `-2147483648_4` is, strictly speaking, a non-conforming literal
79  constant on a machine with 32-bit two's-complement integers as
80  kind 4, because the grammar of Fortran expressions parses it as a
81  negation of a literal constant, not a negative literal constant.
82  This compiler accepts it with a portability warning.
83* Construct names like `loop` in `loop: do j=1,n` are defined to
84  be "local identifiers" and should be distinct in the "inclusive
85  scope" -- i.e., not scoped by `BLOCK` constructs.
86  As most (but not all) compilers implement `BLOCK` scoping of construct
87  names, so does f18, with a portability warning.
88* 15.6.4 paragraph 2 prohibits an implicitly typed statement function
89  from sharing the same name as a symbol in its scope's host, if it
90  has one.
91  We accept this usage with a portability warning.
92* A module name from a `USE` statement can also be used as a
93  non-global name in the same scope.  This is not conforming,
94  but it is useful and unambiguous.
95* The argument to `RANDOM_NUMBER` may not be an assumed-size array.
96* `NULL()` without `MOLD=` is not allowed to be associated as an
97  actual argument corresponding to an assumed-rank dummy argument;
98  its rank in the called procedure would not be well-defined.
99* When an index variable of a `FORALL` or `DO CONCURRENT` is present
100  in the enclosing scope, and the construct does not have an explicit
101  type specification for its index variables, some weird restrictions
102  in F'2023 subclause 19.4 paragraphs 6 & 8 should apply.  Since this
103  compiler properly scopes these names, violations of these restrictions
104  elicit only portability warnings by default.
105* The standard defines the intrinsic functions `MOD` and `MODULO`
106  for real arguments using expressions in terms of `AINT` and `FLOOR`.
107  These definitions yield fairly poor results due to floating-point
108  cancellation, and every Fortran compiler (including this one)
109  uses better algorithms.
110* The rules for pairwise distinguishing the specific procedures of a
111  generic interface are inadequate, as admitted in note C.11.6 of F'2023.
112  Generic interfaces whose specific procedures can be easily proven by
113  hand to be pairwise distinct (i.e., no ambiguous reference is possible)
114  appear in real applications, but are still non-conforming under the
115  incomplete tests in F'2023 15.4.3.4.5.
116  These cases are compiled with optional portability warnings.
117* `PROCEDURE(), BIND(C) :: PROC` is not conforming, as there is no
118  procedure interface.  This compiler accepts it, since there is otherwise
119  no way to declare an interoperable dummy procedure with an arbitrary
120  interface like `void (*)()`.
121* `PURE` functions are allowed to have dummy arguments that are
122  neither `INTENT(IN)` nor `VALUE`, similar to `PURE` subroutines,
123  with a warning.
124  This enables atomic memory operations to be naturally represented
125  as `PURE` functions, which allows their use in parallel constructs
126  and `DO CONCURRENT`.
127* A non-definable actual argument, including the case of a vector
128  subscript, may be associated with an `ASYNCHRONOUS` or `VOLATILE`
129  dummy argument, F'2023 15.5.2.5 p31 notwithstanding.
130  The effects of these attributes are scoped over the lifetime of
131  the procedure reference, and they can by added by internal subprograms
132  and `BLOCK` constructs within the procedure.
133  Further, a dummy argument can acquire the `ASYNCHRONOUS` attribute
134  implicitly simply appearing in an asynchronous data transfer statement,
135  without the attribute being visible in the procedure's explicit
136  interface.
137* When the name of an extended derived type's base type is the
138  result of `USE` association with renaming, the name of the extended
139  derived type's parent component is the new name by which the base
140  is known in the scope of the extended derived type, not the original.
141  This interpretation has usability advantages and is what six other
142  Fortran compilers do, but is not conforming now that J3 approved an
143  "interp" in June 2024 to the contrary.
144* Arm has processors that allow a user to control what happens when an
145  arithmetic exception is signaled, as well as processors that do not
146  have this capability. An Arm executable will run on either type of
147  processor, so it is effectively unknown at compile time whether or
148  not this support will be available at runtime. The standard requires
149  that a call to intrinsic module procedure `IEEE_SUPPORT_HALTING` with
150  a constant argument has a compile time constant result in `constant
151  expression` and `specification expression` contexts. In compilations
152  where this information is not known at compile time, f18 generates code
153  to determine the absence or presence of this capability at runtime.
154  A call to `IEEE_SUPPORT_HALTING` in contexts that the standard requires
155  to be constant will generate a compilation error.
156
157## Extensions, deletions, and legacy features supported by default
158
159* Tabs in source
160* `<>` as synonym for `.NE.` and `/=`
161* `$` and `@` as legal characters in names
162* Initialization in type declaration statements using `/values/`
163* Saved variables without explicit or default initializers are zero initialized,
164  except for scalar variables from the main program that are not explicitly
165  initialized or marked with an explicit SAVE attribute (these variables may be
166  placed on the stack by flang and not zero initialized). It is not advised to
167  rely on this extension in new code.
168* In a saved entity of a type with a default initializer, components without default
169  values are zero initialized.
170* Kind specification with `*`, e.g. `REAL*4`
171* `DOUBLE COMPLEX` as a synonym for `COMPLEX(KIND(0.D0))` --
172  but not when spelled `TYPE(DOUBLECOMPLEX)`.
173* Signed complex literal constants
174* DEC `STRUCTURE`, `RECORD`, with '%FILL'; but `UNION`, and `MAP`
175  are not yet supported throughout compilation, and elicit a
176  "not yet implemented" message.
177* Structure field access with `.field`
178* `BYTE` as synonym for `INTEGER(KIND=1)`; but not when spelled `TYPE(BYTE)`.
179* When kind-param is used for REAL literals, allow a matching exponent letter
180* Quad precision REAL literals with `Q`
181* `X` prefix/suffix as synonym for `Z` on hexadecimal literals
182* `B`, `O`, `Z`, and `X` accepted as suffixes as well as prefixes
183* Support for using bare `L` in FORMAT statement
184* Triplets allowed in array constructors
185* `%LOC`, `%VAL`, and `%REF`
186* Leading comma allowed before I/O item list
187* Empty parentheses allowed in `PROGRAM P()`
188* Missing parentheses allowed in `FUNCTION F`
189* Cray based `POINTER(p,x)` and `LOC()` intrinsic (with `%LOC()` as
190  an alias)
191* Arithmetic `IF`.  (Which branch should NaN take? Fall through?)
192* `ASSIGN` statement, assigned `GO TO`, and assigned format
193* `PAUSE` statement
194* Hollerith literals and edit descriptors
195* `NAMELIST` allowed in the execution part
196* Omitted colons on type declaration statements with attributes
197* COMPLEX constructor expression, e.g. `(x+y,z)`
198* `+` and `-` before all primary expressions, e.g. `x*-y`
199* `.NOT. .NOT.` accepted
200* `NAME=` as synonym for `FILE=`
201* Data edit descriptors without width or other details
202* `D` lines in fixed form as comments or debug code
203* `CARRIAGECONTROL=` on the OPEN and INQUIRE statements
204* `CONVERT=` on the OPEN and INQUIRE statements
205* `DISPOSE=` on the OPEN and INQUIRE statements
206* Leading semicolons are ignored before any statement that
207  could have a label
208* The character `&` in column 1 in fixed form source is a variant form
209  of continuation line.
210* Character literals as elements of an array constructor without an explicit
211  type specifier need not have the same length; the longest literal determines
212  the length parameter of the implicit type, not the first.
213* Outside a character literal, a comment after a continuation marker (&)
214  need not begin with a comment marker (!).
215* Classic C-style /*comments*/ are skipped, so multi-language header
216  files are easier to write and use.
217* $ and \ edit descriptors are supported in FORMAT to suppress newline
218  output on user prompts.
219* Tabs in format strings (not `FORMAT` statements) are allowed on output.
220* REAL and DOUBLE PRECISION variable and bounds in DO loops
221* Integer literals without explicit kind specifiers that are out of range
222  for the default kind of INTEGER are assumed to have the least larger kind
223  that can hold them, if one exists.
224* BOZ literals can be used as INTEGER values in contexts where the type is
225  unambiguous: the right hand sides of assignments and initializations
226  of INTEGER entities, as actual arguments to a few intrinsic functions
227  (ACHAR, BTEST, CHAR), and as actual arguments of references to
228  procedures with explicit interfaces whose corresponding dummy
229  argument has a numeric type to which the BOZ literal may be
230  converted.  BOZ literals are interpreted as default INTEGER only
231  when they appear as the first items of array constructors with no
232  explicit type.  Otherwise, they generally cannot be used if the type would
233  not be known (e.g., `IAND(X'1',X'2')`, or as arguments of `DIM`, `MOD`,
234  `MODULO`, and `SIGN`. Note that while other compilers may accept such usages,
235  the type resolution of such BOZ literals usages is highly non portable).
236* BOZ literals can also be used as REAL values in some contexts where the
237  type is unambiguous, such as initializations of REAL parameters.
238* EQUIVALENCE of numeric and character sequences (a ubiquitous extension),
239  as well as of sequences of non-default kinds of numeric types
240  with each other.
241* Values for whole anonymous parent components in structure constructors
242  (e.g., `EXTENDEDTYPE(PARENTTYPE(1,2,3))` rather than `EXTENDEDTYPE(1,2,3)`
243   or `EXTENDEDTYPE(PARENTTYPE=PARENTTYPE(1,2,3))`).
244* Some intrinsic functions are specified in the standard as requiring the
245  same type and kind for their arguments (viz., ATAN with two arguments,
246  ATAN2, DIM, HYPOT, IAND, IEOR, IOR, MAX, MIN, MOD, and MODULO);
247  we allow distinct types to be used, promoting
248  the arguments as if they were operands to an intrinsic `+` operator,
249  and defining the result type accordingly.
250* DOUBLE COMPLEX intrinsics DREAL, DCMPLX, DCONJG, and DIMAG.
251* The DFLOAT intrinsic function.
252* INT_PTR_KIND intrinsic returns the kind of c_intptr_t.
253* Restricted specific conversion intrinsics FLOAT, SNGL, IDINT, IFIX, DREAL,
254  and DCMPLX accept arguments of any kind instead of only the default kind or
255  double precision kind. Their result kinds remain as specified.
256* Specific intrinsics AMAX0, AMAX1, AMIN0, AMIN1, DMAX1, DMIN1, MAX0, MAX1,
257  MIN0, and MIN1 accept more argument types than specified. They are replaced by
258  the related generics followed by conversions to the specified result types.
259* When a scalar CHARACTER actual argument of the same kind is known to
260  have a length shorter than the associated dummy argument, it is extended
261  on the right with blanks, similar to assignment.
262* When a dummy argument is `POINTER` or `ALLOCATABLE` and is `INTENT(IN)`, we
263  relax enforcement of some requirements on actual arguments that must otherwise
264  hold true for definable arguments.
265* We allow a limited polymorphic `POINTER` or `ALLOCATABLE` actual argument
266  to be associated with a compatible monomorphic dummy argument, as
267  our implementation, like others, supports a reallocation that would
268  change the dynamic type
269* Assignment of `LOGICAL` to `INTEGER` and vice versa (but not other types) is
270  allowed.  The values are normalized to canonical `.TRUE.`/`.FALSE.`.
271  The values are also normalized for assignments of `LOGICAL(KIND=K1)` to
272  `LOGICAL(KIND=K2)`, when `K1 != K2`.
273* Static initialization of `LOGICAL` with `INTEGER` is allowed in `DATA` statements
274  and object initializers.
275  The results are *not* normalized to canonical `.TRUE.`/`.FALSE.`.
276  Static initialization of `INTEGER` with `LOGICAL` is also permitted.
277* An effectively empty source file (no program unit) is accepted and
278  produces an empty relocatable output file.
279* A `RETURN` statement may appear in a main program.
280* DATA statement initialization is allowed for procedure pointers outside
281  structure constructors.
282* Nonstandard intrinsic functions: ISNAN, SIZEOF
283* A forward reference to a default INTEGER scalar dummy argument or
284  `COMMON` block variable is permitted to appear in a specification
285  expression, such as an array bound, in a scope with IMPLICIT NONE(TYPE)
286  if the name of the variable would have caused it to be implicitly typed
287  as default INTEGER if IMPLICIT NONE(TYPE) were absent.
288* OPEN(ACCESS='APPEND') is interpreted as OPEN(POSITION='APPEND')
289  to ease porting from Sun Fortran.
290* Intrinsic subroutines EXIT([status]) and ABORT()
291* The definition of simple contiguity in 9.5.4 applies only to arrays;
292  we also treat scalars as being trivially contiguous, so that they
293  can be used in contexts like data targets in pointer assignments
294  with bounds remapping.
295* The `CONTIGUOUS` attribute can be redundantly applied to simply
296  contiguous objects, including scalars, with a portability warning.
297* We support some combinations of specific procedures in generic
298  interfaces that a strict reading of the standard would preclude
299  when their calls must nonetheless be distinguishable.
300  Specifically, `ALLOCATABLE` dummy arguments are distinguishing
301  if an actual argument acceptable to one could not be passed to
302  the other & vice versa because exactly one is polymorphic or
303  exactly one is unlimited polymorphic).
304* External unit 0 is predefined and connected to the standard error output,
305  and defined as `ERROR_UNIT` in the intrinsic `ISO_FORTRAN_ENV` module.
306* Objects in blank COMMON may be initialized.
307* Initialization of COMMON blocks outside of BLOCK DATA subprograms.
308* Multiple specifications of the SAVE attribute on the same object
309  are allowed, with a warning.
310* Specific intrinsic functions BABS, IIABS, JIABS, KIABS, ZABS, and CDABS.
311* A `POINTER` component's type need not be a sequence type when
312  the component appears in a derived type with `SEQUENCE`.
313  (This case should probably be an exception to constraint C740 in
314  the standard.)
315* Format expressions that have type but are not character and not
316  integer scalars are accepted so long as they are simply contiguous.
317  This legacy extension supports pre-Fortran'77 usage in which
318  variables initialized in DATA statements with Hollerith literals
319  as modifiable formats.
320* At runtime, `NAMELIST` input will skip over `NAMELIST` groups
321  with other names, and will treat text before and between groups
322  as if they were comment lines, even if not begun with `!`.
323* Commas are required in FORMAT statements and character variables
324  only when they prevent ambiguity.
325* Legacy names `AND`, `OR`, and `XOR` are accepted as aliases for
326  the standard intrinsic functions `IAND`, `IOR`, and `IEOR`
327  respectively.
328* A digit count of d=0 is accepted in Ew.0, Dw.0, and Gw.0 output
329  editing if no nonzero scale factor (kP) is in effect.
330* The name `IMAG` is accepted as an alias for the generic intrinsic
331  function `AIMAG`.
332* The legacy extension intrinsic functions `IZEXT` and `JZEXT`
333  are supported; `ZEXT` has different behavior with various older
334  compilers, so it is not supported.
335* f18 doesn't impose a limit on the number of continuation lines
336  allowed for a single statement.
337* When a type-bound procedure declaration statement has neither interface
338  nor attributes, the "::" before the bindings is optional, even
339  if a binding has renaming with "=> proc".
340  The colons are not necessary for an unambiguous parse, C768
341  notwithstanding.
342* A type-bound procedure binding can be passed as an actual
343  argument corresponding to a dummy procedure and can be used as
344  the target of a procedure pointer assignment statement.
345* An explicit `INTERFACE` can declare the interface of a
346  procedure pointer even if it is not a dummy argument.
347* A `NOPASS` type-bound procedure binding is required by C1529
348  to apply only to a scalar data-ref, but most compilers don't
349  enforce it and the constraint is not necessary for a correct
350  implementation.
351* A label may follow a semicolon in fixed form source.
352* A logical dummy argument to a `BIND(C)` procedure, or a logical
353  component to a `BIND(C)` derived type does not have to have
354  `KIND=C_BOOL` since it can be converted to/from `_Bool` without
355  loss of information.
356* The character length of the `SOURCE=` or `MOLD=` in `ALLOCATE`
357  may be distinct from the constant character length, if any,
358  of an allocated object.
359* When a name is brought into a scope by multiple ways,
360  such as USE-association as well as an `IMPORT` from its host,
361  it's an error only if the resolution is ambiguous.
362* An entity may appear in a `DATA` statement before its explicit
363  type declaration under `IMPLICIT NONE(TYPE)`.
364* `INCLUDE` lines can start in any column, can be preceded in
365  fixed form source by a '0' in column 6, can contain spaces
366  between the letters of the word INCLUDE, and can have a
367  numeric character literal kind prefix on the file name.
368* Intrinsic procedures SIND, COSD, TAND and ATAND. Constant folding
369  is currently not supported for these procedures but this is planned.
370* When a pair of quotation marks in a character literal are split
371  by a line continuation in free form, the second quotation mark
372  may appear at the beginning of the continuation line without an
373  ampersand, althought one is required by the standard.
374* Unrestricted `INTRINSIC` functions are accepted for use in
375  `PROCEDURE` statements in generic interfaces, as in some other
376  compilers.
377* A `NULL()` pointer is treated as an unallocated allocatable
378  when associated with an `INTENT(IN)` allocatable dummy argument.
379* `READ(..., SIZE=n)` is accepted with `NML=` and `FMT=*` with
380  a portability warning.
381  The Fortran standard doesn't allow `SIZE=` with formatted input
382  modes that might require look-ahead, perhaps to ease implementations.
383* When a file included via an `INCLUDE` line or `#include` directive
384  has a continuation marker at the end of its last line in free form,
385  Fortran line continuation works.
386* A `NAMELIST` input group may omit its trailing `/` character if
387  it is followed by another `NAMELIST` input group.
388* A `NAMELIST` input group may begin with either `&` or `$`.
389* A comma in a fixed-width numeric input field terminates the
390  field rather than signaling an invalid character error.
391* Arguments to the intrinsic functions `MAX` and `MIN` are converted
392  when necessary to the type of the result.
393  An `OPTIONAL`, `POINTER`, or `ALLOCATABLE` argument after
394  the first two cannot be converted, as it may not be present.
395* A derived type that meets (most of) the requirements of an interoperable
396  derived type can be used as such where an interoperable type is
397  required, with warnings, even if it lacks the BIND(C) attribute.
398* A "mult-operand" in an expression can be preceded by a unary
399  `+` or `-` operator.
400* `BIND(C, NAME="...", CDEFINED)` signifies that the storage for an
401  interoperable variable will be allocated outside of Fortran,
402  probably by a C or C++ external definition.
403* An automatic data object may be declared in the specification part
404  of the main program.
405* A local data object may appear in a specification expression, even
406  when it is not a dummy argument or in COMMON, so long as it is
407  has the SAVE attribute and was initialized.
408* `PRINT namelistname` is accepted and interpreted as
409  `WRITE(*,NML=namelistname)`, a near-universal extension.
410* A character length specifier in a component or entity declaration
411  is accepted before an array specification (`ch*3(2)`) as well
412  as afterwards.
413* A zero field width is allowed for logical formatted output (`L0`).
414
415### Extensions supported when enabled by options
416
417* C-style backslash escape sequences in quoted CHARACTER literals
418  (but not Hollerith) [-fbackslash], including Unicode escapes
419  with `\U`.
420* Logical abbreviations `.T.`, `.F.`, `.N.`, `.A.`, `.O.`, and `.X.`
421  [-flogical-abbreviations]
422* `.XOR.` as a synonym for `.NEQV.` [-fxor-operator]
423* The default `INTEGER` type is required by the standard to occupy
424  the same amount of storage as the default `REAL` type.  Default
425  `REAL` is of course 32-bit IEEE-754 floating-point today.  This legacy
426  rule imposes an artificially small constraint in some cases
427  where Fortran mandates that something have the default `INTEGER`
428  type: specifically, the results of references to the intrinsic functions
429  `SIZE`, `STORAGE_SIZE`,`LBOUND`, `UBOUND`, `SHAPE`, and the location reductions
430  `FINDLOC`, `MAXLOC`, and `MINLOC` in the absence of an explicit
431  `KIND=` actual argument.  We return `INTEGER(KIND=8)` by default in
432  these cases when the `-flarge-sizes` option is enabled.
433  `SIZEOF` and `C_SIZEOF` always return `INTEGER(KIND=8)`.
434* Treat each specification-part like is has `IMPLICIT NONE`
435  [-fimplicit-none-type-always]
436* Ignore occurrences of `IMPLICIT NONE` and `IMPLICIT NONE(TYPE)`
437  [-fimplicit-none-type-never]
438* Old-style `PARAMETER pi=3.14` statement without parentheses
439  [-falternative-parameter-statement]
440* `UNSIGNED` type (-funsigned)
441
442### Extensions and legacy features deliberately not supported
443
444* `.LG.` as synonym for `.NE.`
445* `REDIMENSION`
446* Allocatable `COMMON`
447* Expressions in formats
448* `ACCEPT` as synonym for `READ *`
449* `TYPE` as synonym for `PRINT`
450* `ARRAY` as synonym for `DIMENSION`
451* `VIRTUAL` as synonym for `DIMENSION`
452* `ENCODE` and `DECODE` as synonyms for internal I/O
453* `IMPLICIT AUTOMATIC`, `IMPLICIT STATIC`
454* Default exponent of zero, e.g. `3.14159E`
455* Characters in defined operators that are neither letters nor digits
456* `B` suffix on unquoted octal constants
457* `Z` prefix on unquoted hexadecimal constants (dangerous)
458* `T` and `F` as abbreviations for `.TRUE.` and `.FALSE.` in DATA (PGI/XLF)
459* Use of host FORMAT labels in internal subprograms (PGI-only feature)
460* ALLOCATE(TYPE(derived)::...) as variant of correct ALLOCATE(derived::...) (PGI only)
461* Defining an explicit interface for a subprogram within itself (PGI only)
462* USE association of a procedure interface within that same procedure's definition
463* NULL() as a structure constructor expression for an ALLOCATABLE component (PGI).
464* Conversion of LOGICAL to INTEGER in expressions.
465* Use of INTEGER data with the intrinsic logical operators `.NOT.`, `.AND.`, `.OR.`,
466  and `.XOR.`.
467* IF (integer expression) THEN ... END IF  (PGI/Intel)
468* Comparison of LOGICAL with ==/.EQ. rather than .EQV. (also .NEQV.) (PGI/Intel)
469* Procedure pointers in COMMON blocks (PGI/Intel)
470* Underindexing multi-dimensional arrays (e.g., A(1) rather than A(1,1)) (PGI only)
471* Legacy PGI `NCHARACTER` type and `NC` Kanji character literals
472* Using non-integer expressions for array bounds (e.g., REAL A(3.14159)) (PGI/Intel)
473* Mixing INTEGER types as operands to bit intrinsics (e.g., IAND); only two
474  compilers support it, and they disagree on sign extension.
475* Module & program names that conflict with an object inside the unit (PGI only).
476* When the same name is brought into scope via USE association from
477  multiple modules, the name must refer to a generic interface; PGI
478  allows a name to be a procedure from one module and a generic interface
479  from another.
480* Type parameter declarations must come first in a derived type definition;
481  some compilers allow them to follow `PRIVATE`, or be intermixed with the
482  component declarations.
483* Wrong argument types in calls to specific intrinsics that have different names than the
484  related generics. Some accepted exceptions are listed above in the allowed extensions.
485  PGI, Intel, and XLF support this in ways that are not numerically equivalent.
486  PGI converts the arguments while Intel and XLF replace the specific by the related generic.
487* VMS listing control directives (`%LIST`, `%NOLIST`, `%EJECT`)
488* Continuation lines on `INCLUDE` lines
489* `NULL()` actual argument corresponding to an `ALLOCATABLE` dummy data object
490* User (non-intrinsic) `ELEMENTAL` procedures may not be passed as actual
491  arguments, in accordance with the standard; some Fortran compilers
492  permit such usage.
493* Constraint C1406, which prohibits the same module name from being used
494  in a scope for both an intrinsic and a non-intrinsic module, is implemented
495  as a portability warning only, not a hard error.
496* IBM @PROCESS directive is accepted but ignored.
497
498## Preprocessing behavior
499
500* The preprocessor is always run, whatever the filename extension may be.
501* We respect Fortran comments in macro actual arguments (like GNU, Intel, NAG;
502  unlike PGI and XLF) on the principle that macro calls should be treated
503  like function references.  Fortran's line continuation methods also work.
504
505## Standard features not silently accepted
506
507* Fortran explicitly ignores type declaration statements when they
508  attempt to type the name of a generic intrinsic function (8.2 p3).
509  One can declare `CHARACTER::COS` and still get a real result
510  from `COS(3.14159)`, for example.  f18 will complain when a
511  generic intrinsic function's inferred result type does not
512  match an explicit declaration.  This message is a warning.
513
514## Standard features that might as well not be
515
516* f18 supports designators with constant expressions, properly
517  constrained, as initial data targets for data pointers in
518  initializers of variable and component declarations and in
519  `DATA` statements; e.g., `REAL, POINTER :: P => T(1:10:2)`.
520  This Fortran 2008 feature might as well be viewed like an
521  extension; no other compiler that we've tested can handle
522  it yet.
523* According to 11.1.3.3p1, if a selector of an `ASSOCIATE` or
524  related construct is defined by a variable, it has the `TARGET`
525  attribute if the variable was a `POINTER` or `TARGET`.
526  We read this to include the case of the variable being a
527  pointer-valued function reference.
528  No other Fortran compiler seems to handle this correctly for
529  `ASSOCIATE`, though NAG gets it right for `SELECT TYPE`.
530* The standard doesn't explicitly require that a named constant that
531  appears as part of a complex-literal-constant be a scalar, but
532  most compilers emit an error when an array appears.
533  f18 supports them with a portability warning.
534* f18 does not enforce a blanket prohibition against generic
535  interfaces containing a mixture of functions and subroutines.
536  We allow both to appear, unlike several other Fortran compilers.
537  This is especially desirable when two generics of the same
538  name are combined due to USE association and the mixture may
539  be inadvertent.
540* Since Fortran 90, `INCLUDE` lines have been allowed to have
541  a numeric kind parameter prefix on the file name.  No other
542  Fortran compiler supports them that I can find.
543* A `SEQUENCE` derived type is required (F'2023 C745) to have
544  at least one component.  No compiler enforces this constraint;
545  this compiler emits a warning.
546* Many compilers disallow a `VALUE` assumed-length character dummy
547  argument, which has been standard since F'2008.
548  We accept this usage with an optional portability warning.
549* The `ASYNCHRONOUS` attribute can be implied by usage in data
550  transfer I/O statements.  Only one other compiler supports this
551  correctly.  This compiler does, apart from objects in asynchronous
552  NAMELIST I/O, for which an actual asynchronous runtime implementation
553  seems unlikely.
554
555## Behavior in cases where the standard is ambiguous or indefinite
556
557* When an inner procedure of a subprogram uses the value or an attribute
558  of an undeclared name in a specification expression and that name does
559  not appear in the host, it is not clear in the standard whether that
560  name is an implicitly typed local variable of the inner procedure or a
561  host association with an implicitly typed local variable of the host.
562  For example:
563```
564module module
565 contains
566  subroutine host(j)
567    ! Although "m" never appears in the specification or executable
568    ! parts of this subroutine, both of its contained subroutines
569    ! might be accessing it via host association.
570    integer, intent(in out) :: j
571    call inner1(j)
572    call inner2(j)
573   contains
574    subroutine inner1(n)
575      integer(kind(m)), intent(in) :: n
576      m = n + 1
577    end subroutine
578    subroutine inner2(n)
579      integer(kind(m)), intent(out) :: n
580      n = m + 2
581    end subroutine
582  end subroutine
583end module
584
585program demo
586  use module
587  integer :: k
588  k = 0
589  call host(k)
590  print *, k, " should be 3"
591end
592
593```
594
595  Other Fortran compilers disagree in their interpretations of this example;
596  some seem to treat the references to `m` as if they were host associations
597  to an implicitly typed variable (and print `3`), while others seem to
598  treat them as references to implicitly typed local variables, and
599  load uninitialized values.
600
601  In f18, we chose to emit an error message for this case since the standard
602  is unclear, the usage is not portable, and the issue can be easily resolved
603  by adding a declaration.
604
605* In subclause 7.5.6.2 of Fortran 2018 the standard defines a partial ordering
606  of the final subroutine calls for finalizable objects, their non-parent
607  components, and then their parent components.
608  (The object is finalized, then the non-parent components of each element,
609  and then the parent component.)
610  Some have argued that the standard permits an implementation
611  to finalize the parent component before finalizing an allocatable component in
612  the context of deallocation, and the next revision of the language may codify
613  this option.
614  In the interest of avoiding needless confusion, this compiler implements what
615  we believe to be the least surprising order of finalization.
616  Specifically: all non-parent components are finalized before
617  the parent, allocatable or not;
618  all finalization takes place before any deallocation;
619  and no object or subobject will be finalized more than once.
620
621* When `RECL=` is set via the `OPEN` statement for a sequential formatted input
622  file, it functions as an effective maximum record length.
623  Longer records, if any, will appear as if they had been truncated to
624  the value of `RECL=`.
625  (Other compilers ignore `RECL=`, signal an error, or apply effective truncation
626  to some forms of input in this situation.)
627  For sequential formatted output, RECL= serves as a limit on record lengths
628  that raises an error when it is exceeded.
629
630* When a `DATA` statement in a `BLOCK` construct could be construed as
631  either initializing a host-associated object or declaring a new local
632  initialized object, f18 interprets the standard's classification of
633  a `DATA` statement as being a "declaration" rather than a "specification"
634  construct, and notes that the `BLOCK` construct is defined as localizing
635  names that have specifications in the `BLOCK` construct.
636  So this example will elicit an error about multiple initialization:
637```
638subroutine subr
639  integer n = 1
640  block
641    data n/2/
642  end block
643end subroutine
644```
645
646  Other Fortran compilers disagree with each other in their interpretations
647  of this example.
648  The precedent among the most commonly used compilers
649  agrees with f18's interpretation: a `DATA` statement without any other
650  specification of the name refers to the host-associated object.
651
652* Many Fortran compilers allow a non-generic procedure to be `USE`-associated
653  into a scope that also contains a generic interface of the same name
654  but does not have the `USE`-associated non-generic procedure as a
655  specific procedure.
656```
657module m1
658 contains
659  subroutine foo(n)
660    integer, intent(in) :: n
661  end subroutine
662end module
663
664module m2
665  use m1, only: foo
666  interface foo
667    module procedure noargs
668  end interface
669 contains
670  subroutine noargs
671  end subroutine
672end module
673```
674
675  This case elicits a warning from f18, as it should not be treated
676  any differently than the same case with the non-generic procedure of
677  the same name being defined in the same scope rather than being
678  `USE`-associated into it, which is explicitly non-conforming in the
679  standard and not allowed by most other compilers.
680  If the `USE`-associated entity of the same name is not a procedure,
681  most compilers disallow it as well.
682
683* Fortran 2018 19.3.4p1: "A component name has the scope of its derived-type
684  definition.  Outside the type definition, it may also appear ..." which
685  seems to imply that within its derived-type definition, a component
686  name is in its scope, and at least shadows any entity of the same name
687  in the enclosing scope and might be read, thanks to the "also", to mean
688  that a "bare" reference to the name could be used in a specification inquiry.
689  However, most other compilers do not allow a component to shadow exterior
690  symbols, much less appear in specification inquiries, and there are
691  application codes that expect exterior symbols whose names match
692  components to be visible in a derived-type definition's default initialization
693  expressions, and so f18 follows that precedent.
694
695* 19.3.1p1 "Within its scope, a local identifier of an entity of class (1)
696  or class (4) shall not be the same as a global identifier used in that scope..."
697  is read so as to allow the name of a module, submodule, main program,
698  or `BLOCK DATA` subprogram to also be the name of an local entity in its
699  scope, with a portability warning, since that global name is not actually
700  capable of being "used" in its scope.
701
702* In the definition of the `ASSOCIATED` intrinsic function (16.9.16), its optional
703  second argument `TARGET=` is required to be "allowable as the data-target or
704  proc-target in a pointer assignment statement (10.2.2) in which POINTER is
705  data-pointer-object or proc-pointer-object."  Some Fortran compilers
706  interpret this to require that the first argument (`POINTER=`) be a valid
707  left-hand side for a pointer assignment statement -- in particular, it
708  cannot be `NULL()`, but also it is required to be modifiable.
709  As there is  no good reason to disallow (say) an `INTENT(IN)` pointer here,
710  or even `NULL()` as a well-defined case that is always `.FALSE.`,
711  this compiler doesn't require the `POINTER=` argument to be a valid
712  left-hand side for a pointer assignment statement, and we emit a
713  portability warning when it is not.
714
715* F18 allows a `USE` statement to reference a module that is defined later
716  in the same compilation unit, so long as mutual dependencies do not form
717  a cycle.
718  This feature forestalls any risk of such a `USE` statement reading an
719  obsolete module file from a previous compilation and then overwriting
720  that file later.
721
722* F18 allows `OPTIONAL` dummy arguments to interoperable procedures
723  unless they are `VALUE` (C865).
724
725* F18 processes the `NAMELIST` group declarations in a scope after it
726  has resolved all of the names in that scope.  This means that names
727  that appear before their local declarations do not resolve to host
728  associated objects and do not elicit errors about improper redeclarations
729  of implicitly typed entities.
730
731* Standard Fortran allows forward references to derived types, which
732  can lead to ambiguity when combined with host association.
733  Some Fortran compilers resolve the type name to the host type,
734  others to the forward-referenced local type; this compiler diagnoses
735  an error.
736```
737module m
738  type ambiguous; integer n; end type
739 contains
740  subroutine s
741    type(ambiguous), pointer :: ptr
742    type ambiguous; real a; end type
743  end
744end
745```
746
747* When an intrinsic procedure appears in the specification part of a module
748  only in function references, but not an explicit `INTRINSIC` statement,
749  its name is not brought into other scopes by a `USE` statement.
750
751* The subclause on rounding in formatted I/O (13.7.2.3.8 in F'2023)
752  only discusses rounding for decimal-to/from-binary conversions,
753  omitting any mention of rounding for hexadecimal conversions.
754  As other compilers do apply rounding, so does this one.
755
756* For real `MAXVAL`, `MINVAL`, `MAXLOC`, and `MINLOC`, NaN values are
757  essentially ignored unless there are some unmasked array entries and
758  *all* of them are NaNs.
759
760* When `INDEX` is used as an unrestricted specific intrinsic function
761  in the context of an actual procedure, as the explicit interface in
762  a `PROCEDURE` declaration statement, or as the target of a procedure
763  pointer assignment, its interface has exactly two dummy arguments
764  (`STRING=` and `SUBSTRING=`), and includes neither `BACK=` nor
765  `KIND=`.
766  This is how `INDEX` as an unrestricted specific intrinsic function was
767  documented in FORTRAN '77 and Fortran '90; later revisions of the
768  standard deleted the argument information from the section on
769  unrestricted specific intrinsic functions.
770  At least one other compiler (XLF) seems to expect that the interface for
771  `INDEX` include an optional `BACK=` argument, but it doesn't actually
772  work.
773
774* Allocatable components of array and structure constructors are deallocated
775  after use without calling final subroutines.
776  The standard does not specify when and how deallocation of array and structure
777  constructors allocatable components should happen. All compilers free the
778  memory after use, but the behavior when the allocatable component is a derived
779  type with finalization differ, especially when dealing with nested array and
780  structure constructors expressions. Some compilers call final routine for the
781  allocatable components of each constructor sub-expressions, some call it only
782  for the allocatable component of the top level constructor, and some only
783  deallocate the memory. Deallocating only the memory offers the most
784  flexibility when lowering such expressions, and it is not clear finalization
785  is desirable in such context (Fortran interop 1.6.2 in F2018 standards require
786  array and structure constructors not to be finalized, so it also makes sense
787  not to finalize their allocatable components when releasing their storage).
788
789* F'2023 19.4 paragraph 5: "If integer-type-spec appears in data-implied-do or
790  ac-implied-do-control it has the specified type and type parameters; otherwise
791  it has the type and type parameters that it would have if it were the name of
792  a variable in the innermost executable construct or scoping unit that includes
793  the DATA statement or array constructor, and this type shall be integer type."
794  Reading "would have if it were" as being the subjunctive, this would mean that
795  an untyped implied DO index variable should be implicitly typed according to
796  the rules active in the enclosing scope.  But all other Fortran compilers interpret
797  the "would have if it were" as meaning "has if it is" -- i.e., if the name
798  is visible in the enclosing scope, the type of that name is used as the
799  type of the implied DO index.  So this is an error, not a simple application
800  of the default implicit typing rule:
801```
802character j
803print *, [(j,j=1,10)]
804```
805
806* The Fortran standard doesn't mention integer overflow explicitly. In many cases,
807  however, integer overflow makes programs non-conforming.
808  F18 follows other widely-used Fortran compilers. Specifically, f18 assumes
809  integer overflow never occurs in address calculations and increment of
810  do-variable unless the option `-fwrapv` is enabled.
811
812## De Facto Standard Features
813
814* `EXTENDS_TYPE_OF()` returns `.TRUE.` if both of its arguments have the
815  same type, a case that is technically implementation-defined.
816
817* `ENCODING=` is not in the list of changeable modes on an I/O unit,
818  but every Fortran compiler allows the encoding to be changed on an
819  open unit.
820
821* A `NAMELIST` input item that references a scalar element of a vector
822  or contiguous array can be used as the initial element of a storage
823  sequence.  For example, "&GRP A(1)=1. 2. 3./" is treated as if had been
824  "&GRP A(1:)=1. 2. 3./".
825