[flang][runtime] Extension: allow a comma to terminate a fixed input … (#76768)
[llvm-project.git] / flang / docs / Extensions.md
blob986890714417036468f0627e86f77c8c0f6068a2
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 -->
9 # Fortran Extensions supported by Flang
11 ```{contents}
12 ---
13 local:
14 ---
15 ```
17 As a general principle, this compiler will accept by default and
18 without complaint many legacy features, extensions to the standard
19 language, and features that have been deleted from the standard,
20 so long as the recognition of those features would not cause a
21 standard-conforming program to be rejected or misinterpreted.
23 Other non-standard features, which do conflict with the current
24 standard specification of the Fortran programming language, are
25 accepted if enabled by command-line options.
27 ## Intentional violations of the standard
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 ```
57 character(11) :: buffer(3)
58 character(10) :: quotes = '""""""""""'
59 write(buffer,*,delim="QUOTE") quotes
60 print "('>',a10,'<')", buffer
61 end
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.
100 ## Extensions, deletions, and legacy features supported by default
102 * Tabs in source
103 * `<>` as synonym for `.NE.` and `/=`
104 * `$` and `@` as legal characters in names
105 * Initialization in type declaration statements using `/values/`
106 * Saved variables without explicit or default initializers are zero initialized.
107 * In a saved entity of a type with a default initializer, components without default
108   values are zero initialized.
109 * Kind specification with `*`, e.g. `REAL*4`
110 * `DOUBLE COMPLEX` as a synonym for `COMPLEX(KIND(0.D0))` --
111   but not when spelled `TYPE(DOUBLECOMPLEX)`.
112 * Signed complex literal constants
113 * DEC `STRUCTURE`, `RECORD`, with '%FILL'; but `UNION`, and `MAP`
114   are not yet supported throughout compilation, and elicit a
115   "not yet implemented" message.
116 * Structure field access with `.field`
117 * `BYTE` as synonym for `INTEGER(KIND=1)`; but not when spelled `TYPE(BYTE)`.
118 * When kind-param is used for REAL literals, allow a matching exponent letter
119 * Quad precision REAL literals with `Q`
120 * `X` prefix/suffix as synonym for `Z` on hexadecimal literals
121 * `B`, `O`, `Z`, and `X` accepted as suffixes as well as prefixes
122 * Support for using bare `L` in FORMAT statement
123 * Triplets allowed in array constructors
124 * `%LOC`, `%VAL`, and `%REF`
125 * Leading comma allowed before I/O item list
126 * Empty parentheses allowed in `PROGRAM P()`
127 * Missing parentheses allowed in `FUNCTION F`
128 * Cray based `POINTER(p,x)` and `LOC()` intrinsic (with `%LOC()` as
129   an alias)
130 * Arithmetic `IF`.  (Which branch should NaN take? Fall through?)
131 * `ASSIGN` statement, assigned `GO TO`, and assigned format
132 * `PAUSE` statement
133 * Hollerith literals and edit descriptors
134 * `NAMELIST` allowed in the execution part
135 * Omitted colons on type declaration statements with attributes
136 * COMPLEX constructor expression, e.g. `(x+y,z)`
137 * `+` and `-` before all primary expressions, e.g. `x*-y`
138 * `.NOT. .NOT.` accepted
139 * `NAME=` as synonym for `FILE=`
140 * Data edit descriptors without width or other details
141 * `D` lines in fixed form as comments or debug code
142 * `CARRIAGECONTROL=` on the OPEN and INQUIRE statements
143 * `CONVERT=` on the OPEN and INQUIRE statements
144 * `DISPOSE=` on the OPEN and INQUIRE statements
145 * Leading semicolons are ignored before any statement that
146   could have a label
147 * The character `&` in column 1 in fixed form source is a variant form
148   of continuation line.
149 * Character literals as elements of an array constructor without an explicit
150   type specifier need not have the same length; the longest literal determines
151   the length parameter of the implicit type, not the first.
152 * Outside a character literal, a comment after a continuation marker (&)
153   need not begin with a comment marker (!).
154 * Classic C-style /*comments*/ are skipped, so multi-language header
155   files are easier to write and use.
156 * $ and \ edit descriptors are supported in FORMAT to suppress newline
157   output on user prompts.
158 * Tabs in format strings (not `FORMAT` statements) are allowed on output.
159 * REAL and DOUBLE PRECISION variable and bounds in DO loops
160 * Integer literals without explicit kind specifiers that are out of range
161   for the default kind of INTEGER are assumed to have the least larger kind
162   that can hold them, if one exists.
163 * BOZ literals can be used as INTEGER values in contexts where the type is
164   unambiguous: the right hand sides of assignments and initializations
165   of INTEGER entities, as actual arguments to a few intrinsic functions
166   (ACHAR, BTEST, CHAR), and as actual arguments of references to
167   procedures with explicit interfaces whose corresponding dummy
168   argument has a numeric type to which the BOZ literal may be
169   converted.  BOZ literals are interpreted as default INTEGER only
170   when they appear as the first items of array constructors with no
171   explicit type.  Otherwise, they generally cannot be used if the type would
172   not be known (e.g., `IAND(X'1',X'2')`).
173 * BOZ literals can also be used as REAL values in some contexts where the
174   type is unambiguous, such as initializations of REAL parameters.
175 * EQUIVALENCE of numeric and character sequences (a ubiquitous extension),
176   as well as of sequences of non-default kinds of numeric types
177   with each other.
178 * Values for whole anonymous parent components in structure constructors
179   (e.g., `EXTENDEDTYPE(PARENTTYPE(1,2,3))` rather than `EXTENDEDTYPE(1,2,3)`
180    or `EXTENDEDTYPE(PARENTTYPE=PARENTTYPE(1,2,3))`).
181 * Some intrinsic functions are specified in the standard as requiring the
182   same type and kind for their arguments (viz., ATAN with two arguments,
183   ATAN2, DIM, HYPOT, IAND, IEOR, IOR, MAX, MIN, MOD, and MODULO);
184   we allow distinct types to be used, promoting
185   the arguments as if they were operands to an intrinsic `+` operator,
186   and defining the result type accordingly.
187 * DOUBLE COMPLEX intrinsics DREAL, DCMPLX, DCONJG, and DIMAG.
188 * The DFLOAT intrinsic function.
189 * INT_PTR_KIND intrinsic returns the kind of c_intptr_t.
190 * Restricted specific conversion intrinsics FLOAT, SNGL, IDINT, IFIX, DREAL,
191   and DCMPLX accept arguments of any kind instead of only the default kind or
192   double precision kind. Their result kinds remain as specified.
193 * Specific intrinsics AMAX0, AMAX1, AMIN0, AMIN1, DMAX1, DMIN1, MAX0, MAX1,
194   MIN0, and MIN1 accept more argument types than specified. They are replaced by
195   the related generics followed by conversions to the specified result types.
196 * When a scalar CHARACTER actual argument of the same kind is known to
197   have a length shorter than the associated dummy argument, it is extended
198   on the right with blanks, similar to assignment.
199 * When a dummy argument is `POINTER` or `ALLOCATABLE` and is `INTENT(IN)`, we
200   relax enforcement of some requirements on actual arguments that must otherwise
201   hold true for definable arguments.
202 * Assignment of `LOGICAL` to `INTEGER` and vice versa (but not other types) is
203   allowed.  The values are normalized to canonical `.TRUE.`/`.FALSE.`.
204   The values are also normalized for assignments of `LOGICAL(KIND=K1)` to
205   `LOGICAL(KIND=K2)`, when `K1 != K2`.
206 * Static initialization of `LOGICAL` with `INTEGER` is allowed in `DATA` statements
207   and object initializers.
208   The results are *not* normalized to canonical `.TRUE.`/`.FALSE.`.
209   Static initialization of `INTEGER` with `LOGICAL` is also permitted.
210 * An effectively empty source file (no program unit) is accepted and
211   produces an empty relocatable output file.
212 * A `RETURN` statement may appear in a main program.
213 * DATA statement initialization is allowed for procedure pointers outside
214   structure constructors.
215 * Nonstandard intrinsic functions: ISNAN, SIZEOF
216 * A forward reference to a default INTEGER scalar dummy argument or
217   `COMMON` block variable is permitted to appear in a specification
218   expression, such as an array bound, in a scope with IMPLICIT NONE(TYPE)
219   if the name of the variable would have caused it to be implicitly typed
220   as default INTEGER if IMPLICIT NONE(TYPE) were absent.
221 * OPEN(ACCESS='APPEND') is interpreted as OPEN(POSITION='APPEND')
222   to ease porting from Sun Fortran.
223 * Intrinsic subroutines EXIT([status]) and ABORT()
224 * The definition of simple contiguity in 9.5.4 applies only to arrays;
225   we also treat scalars as being trivially contiguous, so that they
226   can be used in contexts like data targets in pointer assignments
227   with bounds remapping.
228 * The `CONTIGUOUS` attribute can be redundantly applied to simply
229   contiguous objects, including scalars, with a portability warning.
230 * We support some combinations of specific procedures in generic
231   interfaces that a strict reading of the standard would preclude
232   when their calls must nonetheless be distinguishable.
233   Specifically, `ALLOCATABLE` dummy arguments are distinguishing
234   if an actual argument acceptable to one could not be passed to
235   the other & vice versa because exactly one is polymorphic or
236   exactly one is unlimited polymorphic).
237 * External unit 0 is predefined and connected to the standard error output,
238   and defined as `ERROR_UNIT` in the intrinsic `ISO_FORTRAN_ENV` module.
239 * Objects in blank COMMON may be initialized.
240 * Initialization of COMMON blocks outside of BLOCK DATA subprograms.
241 * Multiple specifications of the SAVE attribute on the same object
242   are allowed, with a warning.
243 * Specific intrinsic functions BABS, IIABS, JIABS, KIABS, ZABS, and CDABS.
244 * A `POINTER` component's type need not be a sequence type when
245   the component appears in a derived type with `SEQUENCE`.
246   (This case should probably be an exception to constraint C740 in
247   the standard.)
248 * Format expressions that have type but are not character and not
249   integer scalars are accepted so long as they are simply contiguous.
250   This legacy extension supports pre-Fortran'77 usage in which
251   variables initialized in DATA statements with Hollerith literals
252   as modifiable formats.
253 * At runtime, `NAMELIST` input will skip over `NAMELIST` groups
254   with other names, and will treat text before and between groups
255   as if they were comment lines, even if not begun with `!`.
256 * Commas are required in FORMAT statements and character variables
257   only when they prevent ambiguity.
258 * Legacy names `AND`, `OR`, and `XOR` are accepted as aliases for
259   the standard intrinsic functions `IAND`, `IOR`, and `IEOR`
260   respectively.
261 * A digit count of d=0 is accepted in Ew.0, Dw.0, and Gw.0 output
262   editing if no nonzero scale factor (kP) is in effect.
263 * The name `IMAG` is accepted as an alias for the generic intrinsic
264   function `AIMAG`.
265 * The legacy extension intrinsic functions `IZEXT` and `JZEXT`
266   are supported; `ZEXT` has different behavior with various older
267   compilers, so it is not supported.
268 * f18 doesn't impose a limit on the number of continuation lines
269   allowed for a single statement.
270 * When a type-bound procedure declaration statement has neither interface
271   nor attributes, the "::" before the bindings is optional, even
272   if a binding has renaming with "=> proc".
273   The colons are not necessary for an unambiguous parse, C768
274   notwithstanding.
275 * A type-bound procedure binding can be passed as an actual
276   argument corresponding to a dummy procedure and can be used as
277   the target of a procedure pointer assignment statement.
278 * An explicit `INTERFACE` can declare the interface of a
279   procedure pointer even if it is not a dummy argument.
280 * A `NOPASS` type-bound procedure binding is required by C1529
281   to apply only to a scalar data-ref, but most compilers don't
282   enforce it and the constraint is not necessary for a correct
283   implementation.
284 * A label may follow a semicolon in fixed form source.
285 * A scalar logical dummy argument to a `BIND(C)` procedure does
286   not have to have `KIND=C_BOOL` since it can be converted to/from
287   `_Bool` without loss of information.
288 * The character length of the `SOURCE=` or `MOLD=` in `ALLOCATE`
289   may be distinct from the constant character length, if any,
290   of an allocated object.
291 * When a name is brought into a scope by multiple ways,
292   such as USE-association as well as an `IMPORT` from its host,
293   it's an error only if the resolution is ambiguous.
294 * An entity may appear in a `DATA` statement before its explicit
295   type declaration under `IMPLICIT NONE(TYPE)`.
296 * `INCLUDE` lines can start in any column, can be preceded in
297   fixed form source by a '0' in column 6, can contain spaces
298   between the letters of the word INCLUDE, and can have a
299   numeric character literal kind prefix on the file name.
300 * Intrinsic procedures TAND and ATAND. Constant folding is currently
301   not supported for these procedures but this is planned.
302 * When a pair of quotation marks in a character literal are split
303   by a line continuation in free form, the second quotation mark
304   may appear at the beginning of the continuation line without an
305   ampersand, althought one is required by the standard.
306 * Unrestricted `INTRINSIC` functions are accepted for use in
307   `PROCEDURE` statements in generic interfaces, as in some other
308   compilers.
309 * A `NULL()` pointer is treated as an unallocated allocatable
310   when associated with an `INTENT(IN)` allocatable dummy argument.
311 * `READ(..., SIZE=n)` is accepted with `NML=` and `FMT=*` with
312   a portability warning.
313   The Fortran standard doesn't allow `SIZE=` with formatted input
314   modes that might require look-ahead, perhaps to ease implementations.
315 * When a file included via an `INCLUDE` line or `#include` directive
316   has a continuation marker at the end of its last line in free form,
317   Fortran line continuation works.
318 * A `NAMELIST` input group may omit its trailing `/` character if
319   it is followed by another `NAMELIST` input group.
320 * A `NAMELIST` input group may begin with either `&` or `$`.
321 * A comma in a fixed-width numeric input field terminates the
322   field rather than signaling an invalid character error.
324 ### Extensions supported when enabled by options
326 * C-style backslash escape sequences in quoted CHARACTER literals
327   (but not Hollerith) [-fbackslash], including Unicode escapes
328   with `\U`.
329 * Logical abbreviations `.T.`, `.F.`, `.N.`, `.A.`, `.O.`, and `.X.`
330   [-flogical-abbreviations]
331 * `.XOR.` as a synonym for `.NEQV.` [-fxor-operator]
332 * The default `INTEGER` type is required by the standard to occupy
333   the same amount of storage as the default `REAL` type.  Default
334   `REAL` is of course 32-bit IEEE-754 floating-point today.  This legacy
335   rule imposes an artificially small constraint in some cases
336   where Fortran mandates that something have the default `INTEGER`
337   type: specifically, the results of references to the intrinsic functions
338   `SIZE`, `STORAGE_SIZE`,`LBOUND`, `UBOUND`, `SHAPE`, and the location reductions
339   `FINDLOC`, `MAXLOC`, and `MINLOC` in the absence of an explicit
340   `KIND=` actual argument.  We return `INTEGER(KIND=8)` by default in
341   these cases when the `-flarge-sizes` option is enabled.
342   `SIZEOF` and `C_SIZEOF` always return `INTEGER(KIND=8)`.
343 * Treat each specification-part like is has `IMPLICIT NONE`
344   [-fimplicit-none-type-always]
345 * Ignore occurrences of `IMPLICIT NONE` and `IMPLICIT NONE(TYPE)`
346   [-fimplicit-none-type-never]
347 * Old-style `PARAMETER pi=3.14` statement without parentheses
348   [-falternative-parameter-statement]
350 ### Extensions and legacy features deliberately not supported
352 * `.LG.` as synonym for `.NE.`
353 * `REDIMENSION`
354 * Allocatable `COMMON`
355 * Expressions in formats
356 * `ACCEPT` as synonym for `READ *`
357 * `TYPE` as synonym for `PRINT`
358 * `ARRAY` as synonym for `DIMENSION`
359 * `VIRTUAL` as synonym for `DIMENSION`
360 * `ENCODE` and `DECODE` as synonyms for internal I/O
361 * `IMPLICIT AUTOMATIC`, `IMPLICIT STATIC`
362 * Default exponent of zero, e.g. `3.14159E`
363 * Characters in defined operators that are neither letters nor digits
364 * `B` suffix on unquoted octal constants
365 * `Z` prefix on unquoted hexadecimal constants (dangerous)
366 * `T` and `F` as abbreviations for `.TRUE.` and `.FALSE.` in DATA (PGI/XLF)
367 * Use of host FORMAT labels in internal subprograms (PGI-only feature)
368 * ALLOCATE(TYPE(derived)::...) as variant of correct ALLOCATE(derived::...) (PGI only)
369 * Defining an explicit interface for a subprogram within itself (PGI only)
370 * USE association of a procedure interface within that same procedure's definition
371 * NULL() as a structure constructor expression for an ALLOCATABLE component (PGI).
372 * Conversion of LOGICAL to INTEGER in expressions.
373 * Use of INTEGER data with the intrinsic logical operators `.NOT.`, `.AND.`, `.OR.`,
374   and `.XOR.`.
375 * IF (integer expression) THEN ... END IF  (PGI/Intel)
376 * Comparison of LOGICAL with ==/.EQ. rather than .EQV. (also .NEQV.) (PGI/Intel)
377 * Procedure pointers in COMMON blocks (PGI/Intel)
378 * Underindexing multi-dimensional arrays (e.g., A(1) rather than A(1,1)) (PGI only)
379 * Legacy PGI `NCHARACTER` type and `NC` Kanji character literals
380 * Using non-integer expressions for array bounds (e.g., REAL A(3.14159)) (PGI/Intel)
381 * Mixing INTEGER types as operands to bit intrinsics (e.g., IAND); only two
382   compilers support it, and they disagree on sign extension.
383 * Module & program names that conflict with an object inside the unit (PGI only).
384 * When the same name is brought into scope via USE association from
385   multiple modules, the name must refer to a generic interface; PGI
386   allows a name to be a procedure from one module and a generic interface
387   from another.
388 * Type parameter declarations must come first in a derived type definition;
389   some compilers allow them to follow `PRIVATE`, or be intermixed with the
390   component declarations.
391 * Wrong argument types in calls to specific intrinsics that have different names than the
392   related generics. Some accepted exceptions are listed above in the allowed extensions.
393   PGI, Intel, and XLF support this in ways that are not numerically equivalent.
394   PGI converts the arguments while Intel and XLF replace the specific by the related generic.
395 * VMS listing control directives (`%LIST`, `%NOLIST`, `%EJECT`)
396 * Continuation lines on `INCLUDE` lines
397 * `NULL()` actual argument corresponding to an `ALLOCATABLE` dummy data object
398 * User (non-intrinsic) `ELEMENTAL` procedures may not be passed as actual
399   arguments, in accordance with the standard; some Fortran compilers
400   permit such usage.
401 * Constraint C1406, which prohibits the same module name from being used
402   in a scope for both an intrinsic and a non-intrinsic module, is implemented
403   as a portability warning only, not a hard error.
404 * IBM @PROCESS directive is accepted but ignored.
406 ## Preprocessing behavior
408 * The preprocessor is always run, whatever the filename extension may be.
409 * We respect Fortran comments in macro actual arguments (like GNU, Intel, NAG;
410   unlike PGI and XLF) on the principle that macro calls should be treated
411   like function references.  Fortran's line continuation methods also work.
413 ## Standard features not silently accepted
415 * Fortran explicitly ignores type declaration statements when they
416   attempt to type the name of a generic intrinsic function (8.2 p3).
417   One can declare `CHARACTER::COS` and still get a real result
418   from `COS(3.14159)`, for example.  f18 will complain when a
419   generic intrinsic function's inferred result type does not
420   match an explicit declaration.  This message is a warning.
422 ## Standard features that might as well not be
424 * f18 supports designators with constant expressions, properly
425   constrained, as initial data targets for data pointers in
426   initializers of variable and component declarations and in
427   `DATA` statements; e.g., `REAL, POINTER :: P => T(1:10:2)`.
428   This Fortran 2008 feature might as well be viewed like an
429   extension; no other compiler that we've tested can handle
430   it yet.
431 * According to 11.1.3.3p1, if a selector of an `ASSOCIATE` or
432   related construct is defined by a variable, it has the `TARGET`
433   attribute if the variable was a `POINTER` or `TARGET`.
434   We read this to include the case of the variable being a
435   pointer-valued function reference.
436   No other Fortran compiler seems to handle this correctly for
437   `ASSOCIATE`, though NAG gets it right for `SELECT TYPE`.
438 * The standard doesn't explicitly require that a named constant that
439   appears as part of a complex-literal-constant be a scalar, but
440   most compilers emit an error when an array appears.
441   f18 supports them with a portability warning.
442 * f18 does not enforce a blanket prohibition against generic
443   interfaces containing a mixture of functions and subroutines.
444   Apart from some contexts in which the standard requires all of
445   a particular generic interface to have only all functions or
446   all subroutines as its specific procedures, we allow both to
447   appear, unlike several other Fortran compilers.
448   This is especially desirable when two generics of the same
449   name are combined due to USE association and the mixture may
450   be inadvertent.
451 * Since Fortran 90, `INCLUDE` lines have been allowed to have
452   a numeric kind parameter prefix on the file name.  No other
453   Fortran compiler supports them that I can find.
454 * A `SEQUENCE` derived type is required (F'2023 C745) to have
455   at least one component.  No compiler enforces this constraint;
456   this compiler emits a warning.
458 ## Behavior in cases where the standard is ambiguous or indefinite
460 * When an inner procedure of a subprogram uses the value or an attribute
461   of an undeclared name in a specification expression and that name does
462   not appear in the host, it is not clear in the standard whether that
463   name is an implicitly typed local variable of the inner procedure or a
464   host association with an implicitly typed local variable of the host.
465   For example:
467 module module
468  contains
469   subroutine host(j)
470     ! Although "m" never appears in the specification or executable
471     ! parts of this subroutine, both of its contained subroutines
472     ! might be accessing it via host association.
473     integer, intent(in out) :: j
474     call inner1(j)
475     call inner2(j)
476    contains
477     subroutine inner1(n)
478       integer(kind(m)), intent(in) :: n
479       m = n + 1
480     end subroutine
481     subroutine inner2(n)
482       integer(kind(m)), intent(out) :: n
483       n = m + 2
484     end subroutine
485   end subroutine
486 end module
488 program demo
489   use module
490   integer :: k
491   k = 0
492   call host(k)
493   print *, k, " should be 3"
498   Other Fortran compilers disagree in their interpretations of this example;
499   some seem to treat the references to `m` as if they were host associations
500   to an implicitly typed variable (and print `3`), while others seem to
501   treat them as references to implicitly typed local variables, and
502   load uninitialized values.
504   In f18, we chose to emit an error message for this case since the standard
505   is unclear, the usage is not portable, and the issue can be easily resolved
506   by adding a declaration.
508 * In subclause 7.5.6.2 of Fortran 2018 the standard defines a partial ordering
509   of the final subroutine calls for finalizable objects, their non-parent
510   components, and then their parent components.
511   (The object is finalized, then the non-parent components of each element,
512   and then the parent component.)
513   Some have argued that the standard permits an implementation
514   to finalize the parent component before finalizing an allocatable component in
515   the context of deallocation, and the next revision of the language may codify
516   this option.
517   In the interest of avoiding needless confusion, this compiler implements what
518   we believe to be the least surprising order of finalization.
519   Specifically: all non-parent components are finalized before
520   the parent, allocatable or not;
521   all finalization takes place before any deallocation;
522   and no object or subobject will be finalized more than once.
524 * When `RECL=` is set via the `OPEN` statement for a sequential formatted input
525   file, it functions as an effective maximum record length.
526   Longer records, if any, will appear as if they had been truncated to
527   the value of `RECL=`.
528   (Other compilers ignore `RECL=`, signal an error, or apply effective truncation
529   to some forms of input in this situation.)
530   For sequential formatted output, RECL= serves as a limit on record lengths
531   that raises an error when it is exceeded.
533 * When a `DATA` statement in a `BLOCK` construct could be construed as
534   either initializing a host-associated object or declaring a new local
535   initialized object, f18 interprets the standard's classification of
536   a `DATA` statement as being a "declaration" rather than a "specification"
537   construct, and notes that the `BLOCK` construct is defined as localizing
538   names that have specifications in the `BLOCK` construct.
539   So this example will elicit an error about multiple initialization:
541 subroutine subr
542   integer n = 1
543   block
544     data n/2/
545   end block
546 end subroutine
549   Other Fortran compilers disagree with each other in their interpretations
550   of this example.
551   The precedent among the most commonly used compilers
552   agrees with f18's interpretation: a `DATA` statement without any other
553   specification of the name refers to the host-associated object.
555 * Many Fortran compilers allow a non-generic procedure to be `USE`-associated
556   into a scope that also contains a generic interface of the same name
557   but does not have the `USE`-associated non-generic procedure as a
558   specific procedure.
560 module m1
561  contains
562   subroutine foo(n)
563     integer, intent(in) :: n
564   end subroutine
565 end module
567 module m2
568   use m1, only: foo
569   interface foo
570     module procedure noargs
571   end interface
572  contains
573   subroutine noargs
574   end subroutine
575 end module
578   This case elicits a warning from f18, as it should not be treated
579   any differently than the same case with the non-generic procedure of
580   the same name being defined in the same scope rather than being
581   `USE`-associated into it, which is explicitly non-conforming in the
582   standard and not allowed by most other compilers.
583   If the `USE`-associated entity of the same name is not a procedure,
584   most compilers disallow it as well.
586 * Fortran 2018 19.3.4p1: "A component name has the scope of its derived-type
587   definition.  Outside the type definition, it may also appear ..." which
588   seems to imply that within its derived-type definition, a component
589   name is in its scope, and at least shadows any entity of the same name
590   in the enclosing scope and might be read, thanks to the "also", to mean
591   that a "bare" reference to the name could be used in a specification inquiry.
592   However, most other compilers do not allow a component to shadow exterior
593   symbols, much less appear in specification inquiries, and there are
594   application codes that expect exterior symbols whose names match
595   components to be visible in a derived-type definition's default initialization
596   expressions, and so f18 follows that precedent.
598 * 19.3.1p1 "Within its scope, a local identifier of an entity of class (1)
599   or class (4) shall not be the same as a global identifier used in that scope..."
600   is read so as to allow the name of a module, submodule, main program,
601   or `BLOCK DATA` subprogram to also be the name of an local entity in its
602   scope, with a portability warning, since that global name is not actually
603   capable of being "used" in its scope.
605 * In the definition of the `ASSOCIATED` intrinsic function (16.9.16), its optional
606   second argument `TARGET=` is required to be "allowable as the data-target or
607   proc-target in a pointer assignment statement (10.2.2) in which POINTER is
608   data-pointer-object or proc-pointer-object."  Some Fortran compilers
609   interpret this to require that the first argument (`POINTER=`) be a valid
610   left-hand side for a pointer assignment statement -- in particular, it
611   cannot be `NULL()`, but also it is required to be modifiable.
612   As there is  no good reason to disallow (say) an `INTENT(IN)` pointer here,
613   or even `NULL()` as a well-defined case that is always `.FALSE.`,
614   this compiler doesn't require the `POINTER=` argument to be a valid
615   left-hand side for a pointer assignment statement, and we emit a
616   portability warning when it is not.
618 * F18 allows a `USE` statement to reference a module that is defined later
619   in the same compilation unit, so long as mutual dependencies do not form
620   a cycle.
621   This feature forestalls any risk of such a `USE` statement reading an
622   obsolete module file from a previous compilation and then overwriting
623   that file later.
625 * F18 allows `OPTIONAL` dummy arguments to interoperable procedures
626   unless they are `VALUE` (C865).
628 * F18 processes the `NAMELIST` group declarations in a scope after it
629   has resolved all of the names in that scope.  This means that names
630   that appear before their local declarations do not resolve to host
631   associated objects and do not elicit errors about improper redeclarations
632   of implicitly typed entities.
634 * Standard Fortran allows forward references to derived types, which
635   can lead to ambiguity when combined with host association.
636   Some Fortran compilers resolve the type name to the host type,
637   others to the forward-referenced local type; this compiler diagnoses
638   an error.
640 module m
641   type ambiguous; integer n; end type
642  contains
643   subroutine s
644     type(ambiguous), pointer :: ptr
645     type ambiguous; real a; end type
646   end
650 * When an intrinsic procedure appears in the specification part of a module
651   only in function references, but not an explicit `INTRINSIC` statement,
652   its name is not brought into other scopes by a `USE` statement.
654 * Should hexadecimal floating-point input editing apply any rounding?
655   F'2023 subclause 13.7.2.3.8 only discusses rounding in the context of
656   decimal-to-binary conversion; it would seem to not apply, and so
657   we don't round.  This seems to be how the Intel Fortran compilers
658   behave.
660 ## De Facto Standard Features
662 * `EXTENDS_TYPE_OF()` returns `.TRUE.` if both of its arguments have the
663   same type, a case that is technically implementation-defined.
665 * `ENCODING=` is not in the list of changeable modes on an I/O unit,
666   but every Fortran compiler allows the encoding to be changed on an
667   open unit.
669 * A `NAMELIST` input item that references a scalar element of a vector
670   or contiguous array can be used as the initial element of a storage
671   sequence.  For example, "&GRP A(1)=1. 2. 3./" is treated as if had been
672   "&GRP A(1:)=1. 2. 3./".