[flang] Accept polymorphic component element in storage_size
[llvm-project.git] / flang / docs / Extensions.md
blobc9793f89836ec811fb22332d68beec06db2b0381
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 ```eval_rst
12 .. contents::
13    :local:
14 ```
16 As a general principle, this compiler will accept by default and
17 without complaint many legacy features, extensions to the standard
18 language, and features that have been deleted from the standard,
19 so long as the recognition of those features would not cause a
20 standard-conforming program to be rejected or misinterpreted.
22 Other non-standard features, which do conflict with the current
23 standard specification of the Fortran programming language, are
24 accepted if enabled by command-line options.
26 ## Intentional violations of the standard
28 * Scalar `INTEGER` actual argument expressions (not variables!)
29   are converted to the kinds of scalar `INTEGER` dummy arguments
30   when the interface is explicit and the kinds differ.
31   This conversion allows the results of the intrinsics like
32   `SIZE` that (as mentioned below) may return non-default
33   `INTEGER` results by default to be passed.  A warning is
34   emitted when truncation is possible.  These conversions
35   are not applied in calls to non-intrinsic generic procedures.
36 * We are not strict on the contents of `BLOCK DATA` subprograms
37   so long as they contain no executable code, no internal subprograms,
38   and allocate no storage outside a named `COMMON` block.  (C1415)
39 * Delimited list-directed (and NAMELIST) character output is required
40   to emit contiguous doubled instances of the delimiter character
41   when it appears in the output value.  When fixed-size records
42   are being emitted, as is the case with internal output, this
43   is not possible when the problematic character falls on the last
44   position of a record.  No two other Fortran compilers do the same
45   thing in this situation so there is no good precedent to follow.
46   Because it seems least wrong, we emit one copy of the delimiter as
47   the last character of the current record and another as the first
48   character of the next record.  (The second-least-wrong alternative
49   might be to flag a runtime error, but that seems harsh since it's
50   not an explicit error in the standard, and the output may not have
51   to be usable later as input anyway.)
52   Consequently, the output is not suitable for use as list-directed or
53   NAMELIST input.  If a later standard were to clarify this case, this
54   behavior will change as needed to conform.
55 ```
56 character(11) :: buffer(3)
57 character(10) :: quotes = '""""""""""'
58 write(buffer,*,delim="QUOTE") quotes
59 print "('>',a10,'<')", buffer
60 end
61 ```
62 * The name of the control variable in an implied DO loop in an array
63   constructor or DATA statement has a scope over the value-list only,
64   not the bounds of the implied DO loop.  It is not advisable to use
65   an object of the same name as the index variable in a bounds
66   expression, but it will work, instead of being needlessly undefined.
67 * If both the `COUNT=` and the `COUNT_MAX=` optional arguments are
68   present on the same call to the intrinsic subroutine `SYSTEM_CLOCK`,
69   we require that their types have the same integer kind, since the
70   kind of these arguments is used to select the clock rate.  In common
71   with some other compilers, the clock rate varies from tenths of a
72   second to nanoseconds depending on argument kind and platform support.
73 * If a dimension of a descriptor has zero extent in a call to
74   `CFI_section`, `CFI_setpointer` or `CFI_allocate`, the lower
75   bound on that dimension will be set to 1 for consistency with
76   the `LBOUND()` intrinsic function.
77 * `-2147483648_4` is, strictly speaking, a non-conforming literal
78   constant on a machine with 32-bit two's-complement integers as
79   kind 4, because the grammar of Fortran expressions parses it as a
80   negation of a literal constant, not a negative literal constant.
81   This compiler accepts it with a portability warning.
82 * Construct names like `loop` in `loop: do j=1,n` are defined to
83   be "local identifiers" and should be distinct in the "inclusive
84   scope" -- i.e., not scoped by `BLOCK` constructs.
85   As most (but not all) compilers implement `BLOCK` scoping of construct
86   names, so does f18, with a portability warning.
88 ## Extensions, deletions, and legacy features supported by default
90 * Tabs in source
91 * `<>` as synonym for `.NE.` and `/=`
92 * `$` and `@` as legal characters in names
93 * Initialization in type declaration statements using `/values/`
94 * Kind specification with `*`, e.g. `REAL*4`
95 * `DOUBLE COMPLEX` as a synonym for `COMPLEX(KIND(0.D0))` --
96   but not when spelled `TYPE(DOUBLECOMPLEX)`.
97 * Signed complex literal constants
98 * DEC `STRUCTURE`, `RECORD`, with '%FILL'; but `UNION`, and `MAP`
99   are not yet supported throughout compilation, and elicit a
100   "not yet implemented" message.
101 * Structure field access with `.field`
102 * `BYTE` as synonym for `INTEGER(KIND=1)`; but not when spelled `TYPE(BYTE)`.
103 * When kind-param is used for REAL literals, allow a matching exponent letter
104 * Quad precision REAL literals with `Q`
105 * `X` prefix/suffix as synonym for `Z` on hexadecimal literals
106 * `B`, `O`, `Z`, and `X` accepted as suffixes as well as prefixes
107 * Triplets allowed in array constructors
108 * `%LOC`, `%VAL`, and `%REF`
109 * Leading comma allowed before I/O item list
110 * Empty parentheses allowed in `PROGRAM P()`
111 * Missing parentheses allowed in `FUNCTION F`
112 * Cray based `POINTER(p,x)` and `LOC()` intrinsic (with `%LOC()` as
113   an alias)
114 * Arithmetic `IF`.  (Which branch should NaN take? Fall through?)
115 * `ASSIGN` statement, assigned `GO TO`, and assigned format
116 * `PAUSE` statement
117 * Hollerith literals and edit descriptors
118 * `NAMELIST` allowed in the execution part
119 * Omitted colons on type declaration statements with attributes
120 * COMPLEX constructor expression, e.g. `(x+y,z)`
121 * `+` and `-` before all primary expressions, e.g. `x*-y`
122 * `.NOT. .NOT.` accepted
123 * `NAME=` as synonym for `FILE=`
124 * Data edit descriptors without width or other details
125 * `D` lines in fixed form as comments or debug code
126 * `CARRIAGECONTROL=` on the OPEN and INQUIRE statements
127 * `CONVERT=` on the OPEN and INQUIRE statements
128 * `DISPOSE=` on the OPEN and INQUIRE statements
129 * Leading semicolons are ignored before any statement that
130   could have a label
131 * The character `&` in column 1 in fixed form source is a variant form
132   of continuation line.
133 * Character literals as elements of an array constructor without an explicit
134   type specifier need not have the same length; the longest literal determines
135   the length parameter of the implicit type, not the first.
136 * Outside a character literal, a comment after a continuation marker (&)
137   need not begin with a comment marker (!).
138 * Classic C-style /*comments*/ are skipped, so multi-language header
139   files are easier to write and use.
140 * $ and \ edit descriptors are supported in FORMAT to suppress newline
141   output on user prompts.
142 * Tabs in format strings (not `FORMAT` statements) are allowed on output.
143 * REAL and DOUBLE PRECISION variable and bounds in DO loops
144 * Integer literals without explicit kind specifiers that are out of range
145   for the default kind of INTEGER are assumed to have the least larger kind
146   that can hold them, if one exists.
147 * BOZ literals can be used as INTEGER values in contexts where the type is
148   unambiguous: the right hand sides of assignments and initializations
149   of INTEGER entities, as actual arguments to a few intrinsic functions
150   (ACHAR, BTEST, CHAR), and as actual arguments of references to
151   procedures with explicit interfaces whose corresponding dummy
152   argument has a numeric type to which the BOZ literal may be
153   converted.  BOZ literals are interpreted as default INTEGER only
154   when they appear as the first items of array constructors with no
155   explicit type.  Otherwise, they generally cannot be used if the type would
156   not be known (e.g., `IAND(X'1',X'2')`).
157 * BOZ literals can also be used as REAL values in some contexts where the
158   type is unambiguous, such as initializations of REAL parameters.
159 * EQUIVALENCE of numeric and character sequences (a ubiquitous extension),
160   as well as of sequences of non-default kinds of numeric types
161   with each other.
162 * Values for whole anonymous parent components in structure constructors
163   (e.g., `EXTENDEDTYPE(PARENTTYPE(1,2,3))` rather than `EXTENDEDTYPE(1,2,3)`
164    or `EXTENDEDTYPE(PARENTTYPE=PARENTTYPE(1,2,3))`).
165 * Some intrinsic functions are specified in the standard as requiring the
166   same type and kind for their arguments (viz., ATAN with two arguments,
167   ATAN2, DIM, HYPOT, MAX, MIN, MOD, and MODULO);
168   we allow distinct types to be used, promoting
169   the arguments as if they were operands to an intrinsic `+` operator,
170   and defining the result type accordingly.
171 * DOUBLE COMPLEX intrinsics DREAL, DCMPLX, DCONJG, and DIMAG.
172 * The DFLOAT intrinsic function.
173 * INT_PTR_KIND intrinsic returns the kind of c_intptr_t.
174 * Restricted specific conversion intrinsics FLOAT, SNGL, IDINT, IFIX, DREAL,
175   and DCMPLX accept arguments of any kind instead of only the default kind or
176   double precision kind. Their result kinds remain as specified.
177 * Specific intrinsics AMAX0, AMAX1, AMIN0, AMIN1, DMAX1, DMIN1, MAX0, MAX1,
178   MIN0, and MIN1 accept more argument types than specified. They are replaced by
179   the related generics followed by conversions to the specified result types.
180 * When a scalar CHARACTER actual argument of the same kind is known to
181   have a length shorter than the associated dummy argument, it is extended
182   on the right with blanks, similar to assignment.
183 * When a dummy argument is `POINTER` or `ALLOCATABLE` and is `INTENT(IN)`, we
184   relax enforcement of some requirements on actual arguments that must otherwise
185   hold true for definable arguments.
186 * Assignment of `LOGICAL` to `INTEGER` and vice versa (but not other types) is
187   allowed.  The values are normalized.
188 * Static initialization of `LOGICAL` with `INTEGER` is allowed in `DATA` statements
189   and object initializers.
190   The results are *not* normalized to canonical `.TRUE.`/`.FALSE.`.
191   Static initialization of `INTEGER` with `LOGICAL` is also permitted.
192 * An effectively empty source file (no program unit) is accepted and
193   produces an empty relocatable output file.
194 * A `RETURN` statement may appear in a main program.
195 * DATA statement initialization is allowed for procedure pointers outside
196   structure constructors.
197 * Nonstandard intrinsic functions: ISNAN, SIZEOF
198 * A forward reference to a default INTEGER scalar dummy argument is
199   permitted to appear in a specification expression, such as an array
200   bound, in a scope with IMPLICIT NONE(TYPE) if the name
201   of the dummy argument would have caused it to be implicitly typed
202   as default INTEGER if IMPLICIT NONE(TYPE) were absent.
203 * OPEN(ACCESS='APPEND') is interpreted as OPEN(POSITION='APPEND')
204   to ease porting from Sun Fortran.
205 * Intrinsic subroutines EXIT([status]) and ABORT()
206 * The definition of simple contiguity in 9.5.4 applies only to arrays;
207   we also treat scalars as being trivially contiguous, so that they
208   can be used in contexts like data targets in pointer assignments
209   with bounds remapping.
210 * We support some combinations of specific procedures in generic
211   interfaces that a strict reading of the standard would preclude
212   when their calls must nonetheless be distinguishable.
213   Specifically, `ALLOCATABLE` dummy arguments are distinguishing
214   if an actual argument acceptable to one could not be passed to
215   the other & vice versa because exactly one is polymorphic or
216   exactly one is unlimited polymorphic).
217 * External unit 0 is predefined and connected to the standard error output,
218   and defined as `ERROR_UNIT` in the intrinsic `ISO_FORTRAN_ENV` module.
219 * Objects in blank COMMON may be initialized.
220 * Initialization of COMMON blocks outside of BLOCK DATA subprograms.
221 * Multiple specifications of the SAVE attribute on the same object
222   are allowed, with a warning.
223 * Specific intrinsic functions BABS, IIABS, JIABS, KIABS, ZABS, and CDABS.
224 * A `POINTER` component's type need not be a sequence type when
225   the component appears in a derived type with `SEQUENCE`.
226   (This case should probably be an exception to constraint C740 in
227   the standard.)
228 * Format expressions that have type but are not character and not
229   integer scalars are accepted so long as they are simply contiguous.
230   This legacy extension supports pre-Fortran'77 usage in which
231   variables initialized in DATA statements with Hollerith literals
232   as modifiable formats.
233 * At runtime, `NAMELIST` input will skip over `NAMELIST` groups
234   with other names, and will treat text before and between groups
235   as if they were comment lines, even if not begun with `!`.
236 * Commas are required in FORMAT statements and character variables
237   only when they prevent ambiguity.
238 * Legacy names `AND`, `OR`, and `XOR` are accepted as aliases for
239   the standard intrinsic functions `IAND`, `IOR`, and `IEOR`
240   respectively.
241 * A digit count of d=0 is accepted in Ew.0, Dw.0, and Gw.0 output
242   editing if no nonzero scale factor (kP) is in effect.
243 * The name `IMAG` is accepted as an alias for the generic intrinsic
244   function `AIMAG`.
245 * The legacy extension intrinsic functions `IZEXT` and `JZEXT`
246   are supported; `ZEXT` has different behavior with various older
247   compilers, so it is not supported.
248 * f18 doesn't impose a limit on the number of continuation lines
249   allowed for a single statement.
250 * When a type-bound procedure declaration statement has neither interface
251   nor attributes, the "::" before the bindings is optional, even
252   if a binding has renaming with "=> proc".
253   The colons are not necessary for an unambiguous parse, C768
254   notwithstanding.
255 * A type-bound procedure binding can be passed as an actual
256   argument corresponding to a dummy procedure and can be used as
257   the target of a procedure pointer assignment statement.
258 * An explicit `INTERFACE` can declare the interface of a
259   procedure pointer even if it is not a dummy argument.
260 * A `NOPASS` type-bound procedure binding is required by C1529
261   to apply only to a scalar data-ref, but most compilers don't
262   enforce it and the constraint is not necessary for a correct
263   implementation.
264 * A label may follow a semicolon in fixed form source.
266 ### Extensions supported when enabled by options
268 * C-style backslash escape sequences in quoted CHARACTER literals
269   (but not Hollerith) [-fbackslash]
270 * Logical abbreviations `.T.`, `.F.`, `.N.`, `.A.`, `.O.`, and `.X.`
271   [-flogical-abbreviations]
272 * `.XOR.` as a synonym for `.NEQV.` [-fxor-operator]
273 * The default `INTEGER` type is required by the standard to occupy
274   the same amount of storage as the default `REAL` type.  Default
275   `REAL` is of course 32-bit IEEE-754 floating-point today.  This legacy
276   rule imposes an artificially small constraint in some cases
277   where Fortran mandates that something have the default `INTEGER`
278   type: specifically, the results of references to the intrinsic functions
279   `SIZE`, `STORAGE_SIZE`,`LBOUND`, `UBOUND`, `SHAPE`, and the location reductions
280   `FINDLOC`, `MAXLOC`, and `MINLOC` in the absence of an explicit
281   `KIND=` actual argument.  We return `INTEGER(KIND=8)` by default in
282   these cases when the `-flarge-sizes` option is enabled.
283   `SIZEOF` and `C_SIZEOF` always return `INTEGER(KIND=8)`.
284 * Treat each specification-part like is has `IMPLICIT NONE`
285   [-fimplicit-none-type-always]
286 * Ignore occurrences of `IMPLICIT NONE` and `IMPLICIT NONE(TYPE)`
287   [-fimplicit-none-type-never]
288 * Old-style `PARAMETER pi=3.14` statement without parentheses
289   [-falternative-parameter-statement]
291 ### Extensions and legacy features deliberately not supported
293 * `.LG.` as synonym for `.NE.`
294 * `REDIMENSION`
295 * Allocatable `COMMON`
296 * Expressions in formats
297 * `ACCEPT` as synonym for `READ *`
298 * `TYPE` as synonym for `PRINT`
299 * `ARRAY` as synonym for `DIMENSION`
300 * `VIRTUAL` as synonym for `DIMENSION`
301 * `ENCODE` and `DECODE` as synonyms for internal I/O
302 * `IMPLICIT AUTOMATIC`, `IMPLICIT STATIC`
303 * Default exponent of zero, e.g. `3.14159E`
304 * Characters in defined operators that are neither letters nor digits
305 * `B` suffix on unquoted octal constants
306 * `Z` prefix on unquoted hexadecimal constants (dangerous)
307 * `T` and `F` as abbreviations for `.TRUE.` and `.FALSE.` in DATA (PGI/XLF)
308 * Use of host FORMAT labels in internal subprograms (PGI-only feature)
309 * ALLOCATE(TYPE(derived)::...) as variant of correct ALLOCATE(derived::...) (PGI only)
310 * Defining an explicit interface for a subprogram within itself (PGI only)
311 * USE association of a procedure interface within that same procedure's definition
312 * NULL() as a structure constructor expression for an ALLOCATABLE component (PGI).
313 * Conversion of LOGICAL to INTEGER in expressions.
314 * Use of INTEGER data with the intrinsic logical operators `.NOT.`, `.AND.`, `.OR.`,
315   and `.XOR.`.
316 * IF (integer expression) THEN ... END IF  (PGI/Intel)
317 * Comparison of LOGICAL with ==/.EQ. rather than .EQV. (also .NEQV.) (PGI/Intel)
318 * Procedure pointers in COMMON blocks (PGI/Intel)
319 * Underindexing multi-dimensional arrays (e.g., A(1) rather than A(1,1)) (PGI only)
320 * Legacy PGI `NCHARACTER` type and `NC` Kanji character literals
321 * Using non-integer expressions for array bounds (e.g., REAL A(3.14159)) (PGI/Intel)
322 * Mixing INTEGER types as operands to bit intrinsics (e.g., IAND); only two
323   compilers support it, and they disagree on sign extension.
324 * Module & program names that conflict with an object inside the unit (PGI only).
325 * When the same name is brought into scope via USE association from
326   multiple modules, the name must refer to a generic interface; PGI
327   allows a name to be a procedure from one module and a generic interface
328   from another.
329 * Type parameter declarations must come first in a derived type definition;
330   some compilers allow them to follow `PRIVATE`, or be intermixed with the
331   component declarations.
332 * Wrong argument types in calls to specific intrinsics that have different names than the
333   related generics. Some accepted exceptions are listed above in the allowed extensions.
334   PGI, Intel, and XLF support this in ways that are not numerically equivalent.
335   PGI converts the arguments while Intel and XLF replace the specific by the related generic.
336 * VMS listing control directives (`%LIST`, `%NOLIST`, `%EJECT`)
337 * Continuation lines on `INCLUDE` lines
338 * `NULL()` actual argument corresponding to an `ALLOCATABLE` dummy data object
339 * User (non-intrinsic) `ELEMENTAL` procedures may not be passed as actual
340   arguments, in accordance with the standard; some Fortran compilers
341   permit such usage.
343 ## Preprocessing behavior
345 * The preprocessor is always run, whatever the filename extension may be.
346 * We respect Fortran comments in macro actual arguments (like GNU, Intel, NAG;
347   unlike PGI and XLF) on the principle that macro calls should be treated
348   like function references.  Fortran's line continuation methods also work.
350 ## Standard features not silently accepted
352 * Fortran explicitly ignores type declaration statements when they
353   attempt to type the name of a generic intrinsic function (8.2 p3).
354   One can declare `CHARACTER::COS` and still get a real result
355   from `COS(3.14159)`, for example.  f18 will complain when a
356   generic intrinsic function's inferred result type does not
357   match an explicit declaration.  This message is a warning.
359 ## Standard features that might as well not be
361 * f18 supports designators with constant expressions, properly
362   constrained, as initial data targets for data pointers in
363   initializers of variable and component declarations and in
364   `DATA` statements; e.g., `REAL, POINTER :: P => T(1:10:2)`.
365   This Fortran 2008 feature might as well be viewed like an
366   extension; no other compiler that we've tested can handle
367   it yet.
368 * According to 11.1.3.3p1, if a selector of an `ASSOCIATE` or
369   related construct is defined by a variable, it has the `TARGET`
370   attribute if the variable was a `POINTER` or `TARGET`.
371   We read this to include the case of the variable being a
372   pointer-valued function reference.
373   No other Fortran compiler seems to handle this correctly for
374   `ASSOCIATE`, though NAG gets it right for `SELECT TYPE`.
375 * The standard doesn't explicitly require that a named constant that
376   appears as part of a complex-literal-constant be a scalar, but
377   most compilers emit an error when an array appears.
378   f18 supports them with a portability warning.
379 * f18 does not enforce a blanket prohibition against generic
380   interfaces containing a mixture of functions and subroutines.
381   Apart from some contexts in which the standard requires all of
382   a particular generic interface to have only all functions or
383   all subroutines as its specific procedures, we allow both to
384   appear, unlike several other Fortran compilers.
385   This is especially desirable when two generics of the same
386   name are combined due to USE association and the mixture may
387   be inadvertent.
389 ## Behavior in cases where the standard is ambiguous or indefinite
391 * When an inner procedure of a subprogram uses the value or an attribute
392   of an undeclared name in a specification expression and that name does
393   not appear in the host, it is not clear in the standard whether that
394   name is an implicitly typed local variable of the inner procedure or a
395   host association with an implicitly typed local variable of the host.
396   For example:
398 module module
399  contains
400   subroutine host(j)
401     ! Although "m" never appears in the specification or executable
402     ! parts of this subroutine, both of its contained subroutines
403     ! might be accessing it via host association.
404     integer, intent(in out) :: j
405     call inner1(j)
406     call inner2(j)
407    contains
408     subroutine inner1(n)
409       integer(kind(m)), intent(in) :: n
410       m = n + 1
411     end subroutine
412     subroutine inner2(n)
413       integer(kind(m)), intent(out) :: n
414       n = m + 2
415     end subroutine
416   end subroutine
417 end module
419 program demo
420   use module
421   integer :: k
422   k = 0
423   call host(k)
424   print *, k, " should be 3"
429   Other Fortran compilers disagree in their interpretations of this example;
430   some seem to treat the references to `m` as if they were host associations
431   to an implicitly typed variable (and print `3`), while others seem to
432   treat them as references to implicitly typed local variabless, and
433   load uninitialized values.
435   In f18, we chose to emit an error message for this case since the standard
436   is unclear, the usage is not portable, and the issue can be easily resolved
437   by adding a declaration.
439 * In subclause 7.5.6.2 of Fortran 2018 the standard defines a partial ordering
440   of the final subroutine calls for finalizable objects, their non-parent
441   components, and then their parent components.
442   (The object is finalized, then the non-parent components of each element,
443   and then the parent component.)
444   Some have argued that the standard permits an implementation
445   to finalize the parent component before finalizing an allocatable component in
446   the context of deallocation, and the next revision of the language may codify
447   this option.
448   In the interest of avoiding needless confusion, this compiler implements what
449   we believe to be the least surprising order of finalization.
450   Specifically: all non-parent components are finalized before
451   the parent, allocatable or not;
452   all finalization takes place before any deallocation;
453   and no object or subobject will be finalized more than once.
455 * When `RECL=` is set via the `OPEN` statement for a sequential formatted input
456   file, it functions as an effective maximum record length.
457   Longer records, if any, will appear as if they had been truncated to
458   the value of `RECL=`.
459   (Other compilers ignore `RECL=`, signal an error, or apply effective truncation
460   to some forms of input in this situation.)
461   For sequential formatted output, RECL= serves as a limit on record lengths
462   that raises an error when it is exceeded.
464 * When a `DATA` statement in a `BLOCK` construct could be construed as
465   either initializing a host-associated object or declaring a new local
466   initialized object, f18 interprets the standard's classification of
467   a `DATA` statement as being a "declaration" rather than a "specification"
468   construct, and notes that the `BLOCK` construct is defined as localizing
469   names that have specifications in the `BLOCK` construct.
470   So this example will elicit an error about multiple initialization:
472 subroutine subr
473   integer n = 1
474   block
475     data n/2/
476   end block
477 end subroutine
480   Other Fortran compilers disagree with each other in their interpretations
481   of this example.
482   The precedent among the most commonly used compilers
483   agrees with f18's interpretation: a `DATA` statement without any other
484   specification of the name refers to the host-associated object.
486 * Many Fortran compilers allow a non-generic procedure to be `USE`-associated
487   into a scope that also contains a generic interface of the same name
488   but does not have the `USE`-associated non-generic procedure as a
489   specific procedure.
491 module m1
492  contains
493   subroutine foo(n)
494     integer, intent(in) :: n
495   end subroutine
496 end module
498 module m2
499   use m1, only: foo
500   interface foo
501     module procedure noargs
502   end interface
503  contains
504   subroutine noargs
505   end subroutine
506 end module
509   This case elicits a warning from f18, as it should not be treated
510   any differently than the same case with the non-generic procedure of
511   the same name being defined in the same scope rather than being
512   `USE`-associated into it, which is explicitly non-conforming in the
513   standard and not allowed by most other compilers.
514   If the `USE`-associated entity of the same name is not a procedure,
515   most compilers disallow it as well.
517 * Fortran 2018 19.3.4p1: "A component name has the scope of its derived-type
518   definition.  Outside the type definition, it may also appear ..." which
519   seems to imply that within its derived-type definition, a component
520   name is in its scope, and at least shadows any entity of the same name
521   in the enclosing scope and might be read, thanks to the "also", to mean
522   that a "bare" reference to the name could be used in a specification inquiry.
523   However, most other compilers do not allow a component to shadow exterior
524   symbols, much less appear in specification inquiries, and there are
525   application codes that expect exterior symbols whose names match
526   components to be visible in a derived-type definition's default initialization
527   expressions, and so f18 follows that precedent.
529 * 19.3.1p1 "Within its scope, a local identifier of an entity of class (1)
530   or class (4) shall not be the same as a global identifier used in that scope..."
531   is read so as to allow the name of a module, submodule, main program,
532   or `BLOCK DATA` subprogram to also be the name of an local entity in its
533   scope, with a portability warning, since that global name is not actually
534   capable of being "used" in its scope.
536 * In the definition of the `ASSOCIATED` intrinsic function (16.9.16), its optional
537   second argument `TARGET=` is required to be "allowable as the data-target or
538   proc-target in a pointer assignment statement (10.2.2) in which POINTER is
539   data-pointer-object or proc-pointer-object."  Some Fortran compilers
540   interpret this to require that the first argument (`POINTER=`) be a valid
541   left-hand side for a pointer assignment statement -- in particular, it
542   cannot be `NULL()`, but also it is required to be modifiable.
543   As there is  no good reason to disallow (say) an `INTENT(IN)` pointer here,
544   or even `NULL()` as a well-defined case that is always `.FALSE.`,
545   this compiler doesn't require the `POINTER=` argument to be a valid
546   left-hand side for a pointer assignment statement, and we emit a
547   portability warning when it is not.
549 * F18 allows a `USE` statement to reference a module that is defined later
550   in the same compilation unit, so long as mutual dependencies do not form
551   a cycle.
552   This feature forestalls any risk of such a `USE` statement reading an
553   obsolete module file from a previous compilation and then overwriting
554   that file later.
556 ## De Facto Standard Features
558 * `EXTENDS_TYPE_OF()` returns `.TRUE.` if both of its arguments have the
559   same type, a case that is technically implementation-defined.