1 <!--===- docs/Extensions.md
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
9 # Fortran Extensions supported by Flang
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.
57 character(11) :: buffer(3)
58 character(10) :: quotes = '""""""""""'
59 write(buffer,*,delim="QUOTE") quotes
60 print "('>',a10,'<')", buffer
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
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,
124 This enables atomic memory operations to be naturally represented
125 as `PURE` functions, which allows their use in parallel constructs
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
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.
145 ## Extensions, deletions, and legacy features supported by default
148 * `<>` as synonym for `.NE.` and `/=`
149 * `$` and `@` as legal characters in names
150 * Initialization in type declaration statements using `/values/`
151 * Saved variables without explicit or default initializers are zero initialized.
152 * In a saved entity of a type with a default initializer, components without default
153 values are zero initialized.
154 * Kind specification with `*`, e.g. `REAL*4`
155 * `DOUBLE COMPLEX` as a synonym for `COMPLEX(KIND(0.D0))` --
156 but not when spelled `TYPE(DOUBLECOMPLEX)`.
157 * Signed complex literal constants
158 * DEC `STRUCTURE`, `RECORD`, with '%FILL'; but `UNION`, and `MAP`
159 are not yet supported throughout compilation, and elicit a
160 "not yet implemented" message.
161 * Structure field access with `.field`
162 * `BYTE` as synonym for `INTEGER(KIND=1)`; but not when spelled `TYPE(BYTE)`.
163 * When kind-param is used for REAL literals, allow a matching exponent letter
164 * Quad precision REAL literals with `Q`
165 * `X` prefix/suffix as synonym for `Z` on hexadecimal literals
166 * `B`, `O`, `Z`, and `X` accepted as suffixes as well as prefixes
167 * Support for using bare `L` in FORMAT statement
168 * Triplets allowed in array constructors
169 * `%LOC`, `%VAL`, and `%REF`
170 * Leading comma allowed before I/O item list
171 * Empty parentheses allowed in `PROGRAM P()`
172 * Missing parentheses allowed in `FUNCTION F`
173 * Cray based `POINTER(p,x)` and `LOC()` intrinsic (with `%LOC()` as
175 * Arithmetic `IF`. (Which branch should NaN take? Fall through?)
176 * `ASSIGN` statement, assigned `GO TO`, and assigned format
178 * Hollerith literals and edit descriptors
179 * `NAMELIST` allowed in the execution part
180 * Omitted colons on type declaration statements with attributes
181 * COMPLEX constructor expression, e.g. `(x+y,z)`
182 * `+` and `-` before all primary expressions, e.g. `x*-y`
183 * `.NOT. .NOT.` accepted
184 * `NAME=` as synonym for `FILE=`
185 * Data edit descriptors without width or other details
186 * `D` lines in fixed form as comments or debug code
187 * `CARRIAGECONTROL=` on the OPEN and INQUIRE statements
188 * `CONVERT=` on the OPEN and INQUIRE statements
189 * `DISPOSE=` on the OPEN and INQUIRE statements
190 * Leading semicolons are ignored before any statement that
192 * The character `&` in column 1 in fixed form source is a variant form
193 of continuation line.
194 * Character literals as elements of an array constructor without an explicit
195 type specifier need not have the same length; the longest literal determines
196 the length parameter of the implicit type, not the first.
197 * Outside a character literal, a comment after a continuation marker (&)
198 need not begin with a comment marker (!).
199 * Classic C-style /*comments*/ are skipped, so multi-language header
200 files are easier to write and use.
201 * $ and \ edit descriptors are supported in FORMAT to suppress newline
202 output on user prompts.
203 * Tabs in format strings (not `FORMAT` statements) are allowed on output.
204 * REAL and DOUBLE PRECISION variable and bounds in DO loops
205 * Integer literals without explicit kind specifiers that are out of range
206 for the default kind of INTEGER are assumed to have the least larger kind
207 that can hold them, if one exists.
208 * BOZ literals can be used as INTEGER values in contexts where the type is
209 unambiguous: the right hand sides of assignments and initializations
210 of INTEGER entities, as actual arguments to a few intrinsic functions
211 (ACHAR, BTEST, CHAR), and as actual arguments of references to
212 procedures with explicit interfaces whose corresponding dummy
213 argument has a numeric type to which the BOZ literal may be
214 converted. BOZ literals are interpreted as default INTEGER only
215 when they appear as the first items of array constructors with no
216 explicit type. Otherwise, they generally cannot be used if the type would
217 not be known (e.g., `IAND(X'1',X'2')`, or as arguments of `DIM`, `MOD`,
218 `MODULO`, and `SIGN`. Note that while other compilers may accept such usages,
219 the type resolution of such BOZ literals usages is highly non portable).
220 * BOZ literals can also be used as REAL values in some contexts where the
221 type is unambiguous, such as initializations of REAL parameters.
222 * EQUIVALENCE of numeric and character sequences (a ubiquitous extension),
223 as well as of sequences of non-default kinds of numeric types
225 * Values for whole anonymous parent components in structure constructors
226 (e.g., `EXTENDEDTYPE(PARENTTYPE(1,2,3))` rather than `EXTENDEDTYPE(1,2,3)`
227 or `EXTENDEDTYPE(PARENTTYPE=PARENTTYPE(1,2,3))`).
228 * Some intrinsic functions are specified in the standard as requiring the
229 same type and kind for their arguments (viz., ATAN with two arguments,
230 ATAN2, DIM, HYPOT, IAND, IEOR, IOR, MAX, MIN, MOD, and MODULO);
231 we allow distinct types to be used, promoting
232 the arguments as if they were operands to an intrinsic `+` operator,
233 and defining the result type accordingly.
234 * DOUBLE COMPLEX intrinsics DREAL, DCMPLX, DCONJG, and DIMAG.
235 * The DFLOAT intrinsic function.
236 * INT_PTR_KIND intrinsic returns the kind of c_intptr_t.
237 * Restricted specific conversion intrinsics FLOAT, SNGL, IDINT, IFIX, DREAL,
238 and DCMPLX accept arguments of any kind instead of only the default kind or
239 double precision kind. Their result kinds remain as specified.
240 * Specific intrinsics AMAX0, AMAX1, AMIN0, AMIN1, DMAX1, DMIN1, MAX0, MAX1,
241 MIN0, and MIN1 accept more argument types than specified. They are replaced by
242 the related generics followed by conversions to the specified result types.
243 * When a scalar CHARACTER actual argument of the same kind is known to
244 have a length shorter than the associated dummy argument, it is extended
245 on the right with blanks, similar to assignment.
246 * When a dummy argument is `POINTER` or `ALLOCATABLE` and is `INTENT(IN)`, we
247 relax enforcement of some requirements on actual arguments that must otherwise
248 hold true for definable arguments.
249 * We allow a limited polymorphic `POINTER` or `ALLOCATABLE` actual argument
250 to be associated with a compatible monomorphic dummy argument, as
251 our implementation, like others, supports a reallocation that would
252 change the dynamic type
253 * Assignment of `LOGICAL` to `INTEGER` and vice versa (but not other types) is
254 allowed. The values are normalized to canonical `.TRUE.`/`.FALSE.`.
255 The values are also normalized for assignments of `LOGICAL(KIND=K1)` to
256 `LOGICAL(KIND=K2)`, when `K1 != K2`.
257 * Static initialization of `LOGICAL` with `INTEGER` is allowed in `DATA` statements
258 and object initializers.
259 The results are *not* normalized to canonical `.TRUE.`/`.FALSE.`.
260 Static initialization of `INTEGER` with `LOGICAL` is also permitted.
261 * An effectively empty source file (no program unit) is accepted and
262 produces an empty relocatable output file.
263 * A `RETURN` statement may appear in a main program.
264 * DATA statement initialization is allowed for procedure pointers outside
265 structure constructors.
266 * Nonstandard intrinsic functions: ISNAN, SIZEOF
267 * A forward reference to a default INTEGER scalar dummy argument or
268 `COMMON` block variable is permitted to appear in a specification
269 expression, such as an array bound, in a scope with IMPLICIT NONE(TYPE)
270 if the name of the variable would have caused it to be implicitly typed
271 as default INTEGER if IMPLICIT NONE(TYPE) were absent.
272 * OPEN(ACCESS='APPEND') is interpreted as OPEN(POSITION='APPEND')
273 to ease porting from Sun Fortran.
274 * Intrinsic subroutines EXIT([status]) and ABORT()
275 * The definition of simple contiguity in 9.5.4 applies only to arrays;
276 we also treat scalars as being trivially contiguous, so that they
277 can be used in contexts like data targets in pointer assignments
278 with bounds remapping.
279 * The `CONTIGUOUS` attribute can be redundantly applied to simply
280 contiguous objects, including scalars, with a portability warning.
281 * We support some combinations of specific procedures in generic
282 interfaces that a strict reading of the standard would preclude
283 when their calls must nonetheless be distinguishable.
284 Specifically, `ALLOCATABLE` dummy arguments are distinguishing
285 if an actual argument acceptable to one could not be passed to
286 the other & vice versa because exactly one is polymorphic or
287 exactly one is unlimited polymorphic).
288 * External unit 0 is predefined and connected to the standard error output,
289 and defined as `ERROR_UNIT` in the intrinsic `ISO_FORTRAN_ENV` module.
290 * Objects in blank COMMON may be initialized.
291 * Initialization of COMMON blocks outside of BLOCK DATA subprograms.
292 * Multiple specifications of the SAVE attribute on the same object
293 are allowed, with a warning.
294 * Specific intrinsic functions BABS, IIABS, JIABS, KIABS, ZABS, and CDABS.
295 * A `POINTER` component's type need not be a sequence type when
296 the component appears in a derived type with `SEQUENCE`.
297 (This case should probably be an exception to constraint C740 in
299 * Format expressions that have type but are not character and not
300 integer scalars are accepted so long as they are simply contiguous.
301 This legacy extension supports pre-Fortran'77 usage in which
302 variables initialized in DATA statements with Hollerith literals
303 as modifiable formats.
304 * At runtime, `NAMELIST` input will skip over `NAMELIST` groups
305 with other names, and will treat text before and between groups
306 as if they were comment lines, even if not begun with `!`.
307 * Commas are required in FORMAT statements and character variables
308 only when they prevent ambiguity.
309 * Legacy names `AND`, `OR`, and `XOR` are accepted as aliases for
310 the standard intrinsic functions `IAND`, `IOR`, and `IEOR`
312 * A digit count of d=0 is accepted in Ew.0, Dw.0, and Gw.0 output
313 editing if no nonzero scale factor (kP) is in effect.
314 * The name `IMAG` is accepted as an alias for the generic intrinsic
316 * The legacy extension intrinsic functions `IZEXT` and `JZEXT`
317 are supported; `ZEXT` has different behavior with various older
318 compilers, so it is not supported.
319 * f18 doesn't impose a limit on the number of continuation lines
320 allowed for a single statement.
321 * When a type-bound procedure declaration statement has neither interface
322 nor attributes, the "::" before the bindings is optional, even
323 if a binding has renaming with "=> proc".
324 The colons are not necessary for an unambiguous parse, C768
326 * A type-bound procedure binding can be passed as an actual
327 argument corresponding to a dummy procedure and can be used as
328 the target of a procedure pointer assignment statement.
329 * An explicit `INTERFACE` can declare the interface of a
330 procedure pointer even if it is not a dummy argument.
331 * A `NOPASS` type-bound procedure binding is required by C1529
332 to apply only to a scalar data-ref, but most compilers don't
333 enforce it and the constraint is not necessary for a correct
335 * A label may follow a semicolon in fixed form source.
336 * A logical dummy argument to a `BIND(C)` procedure, or a logical
337 component to a `BIND(C)` derived type does not have to have
338 `KIND=C_BOOL` since it can be converted to/from `_Bool` without
340 * The character length of the `SOURCE=` or `MOLD=` in `ALLOCATE`
341 may be distinct from the constant character length, if any,
342 of an allocated object.
343 * When a name is brought into a scope by multiple ways,
344 such as USE-association as well as an `IMPORT` from its host,
345 it's an error only if the resolution is ambiguous.
346 * An entity may appear in a `DATA` statement before its explicit
347 type declaration under `IMPLICIT NONE(TYPE)`.
348 * `INCLUDE` lines can start in any column, can be preceded in
349 fixed form source by a '0' in column 6, can contain spaces
350 between the letters of the word INCLUDE, and can have a
351 numeric character literal kind prefix on the file name.
352 * Intrinsic procedures SIND, COSD, TAND and ATAND. Constant folding
353 is currently not supported for these procedures but this is planned.
354 * When a pair of quotation marks in a character literal are split
355 by a line continuation in free form, the second quotation mark
356 may appear at the beginning of the continuation line without an
357 ampersand, althought one is required by the standard.
358 * Unrestricted `INTRINSIC` functions are accepted for use in
359 `PROCEDURE` statements in generic interfaces, as in some other
361 * A `NULL()` pointer is treated as an unallocated allocatable
362 when associated with an `INTENT(IN)` allocatable dummy argument.
363 * `READ(..., SIZE=n)` is accepted with `NML=` and `FMT=*` with
364 a portability warning.
365 The Fortran standard doesn't allow `SIZE=` with formatted input
366 modes that might require look-ahead, perhaps to ease implementations.
367 * When a file included via an `INCLUDE` line or `#include` directive
368 has a continuation marker at the end of its last line in free form,
369 Fortran line continuation works.
370 * A `NAMELIST` input group may omit its trailing `/` character if
371 it is followed by another `NAMELIST` input group.
372 * A `NAMELIST` input group may begin with either `&` or `$`.
373 * A comma in a fixed-width numeric input field terminates the
374 field rather than signaling an invalid character error.
375 * Arguments to the intrinsic functions `MAX` and `MIN` are converted
376 when necessary to the type of the result.
377 An `OPTIONAL`, `POINTER`, or `ALLOCATABLE` argument after
378 the first two cannot be converted, as it may not be present.
379 * A derived type that meets (most of) the requirements of an interoperable
380 derived type can be used as such where an interoperable type is
381 required, with warnings, even if it lacks the BIND(C) attribute.
382 * A "mult-operand" in an expression can be preceded by a unary
384 * `BIND(C, NAME="...", CDEFINED)` signifies that the storage for an
385 interoperable variable will be allocated outside of Fortran,
386 probably by a C or C++ external definition.
387 * An automatic data object may be declared in the specification part
389 * A local data object may appear in a specification expression, even
390 when it is not a dummy argument or in COMMON, so long as it is
391 has the SAVE attribute and was initialized.
392 * `PRINT namelistname` is accepted and interpreted as
393 `WRITE(*,NML=namelistname)`, a near-universal extension.
395 ### Extensions supported when enabled by options
397 * C-style backslash escape sequences in quoted CHARACTER literals
398 (but not Hollerith) [-fbackslash], including Unicode escapes
400 * Logical abbreviations `.T.`, `.F.`, `.N.`, `.A.`, `.O.`, and `.X.`
401 [-flogical-abbreviations]
402 * `.XOR.` as a synonym for `.NEQV.` [-fxor-operator]
403 * The default `INTEGER` type is required by the standard to occupy
404 the same amount of storage as the default `REAL` type. Default
405 `REAL` is of course 32-bit IEEE-754 floating-point today. This legacy
406 rule imposes an artificially small constraint in some cases
407 where Fortran mandates that something have the default `INTEGER`
408 type: specifically, the results of references to the intrinsic functions
409 `SIZE`, `STORAGE_SIZE`,`LBOUND`, `UBOUND`, `SHAPE`, and the location reductions
410 `FINDLOC`, `MAXLOC`, and `MINLOC` in the absence of an explicit
411 `KIND=` actual argument. We return `INTEGER(KIND=8)` by default in
412 these cases when the `-flarge-sizes` option is enabled.
413 `SIZEOF` and `C_SIZEOF` always return `INTEGER(KIND=8)`.
414 * Treat each specification-part like is has `IMPLICIT NONE`
415 [-fimplicit-none-type-always]
416 * Ignore occurrences of `IMPLICIT NONE` and `IMPLICIT NONE(TYPE)`
417 [-fimplicit-none-type-never]
418 * Old-style `PARAMETER pi=3.14` statement without parentheses
419 [-falternative-parameter-statement]
421 ### Extensions and legacy features deliberately not supported
423 * `.LG.` as synonym for `.NE.`
425 * Allocatable `COMMON`
426 * Expressions in formats
427 * `ACCEPT` as synonym for `READ *`
428 * `TYPE` as synonym for `PRINT`
429 * `ARRAY` as synonym for `DIMENSION`
430 * `VIRTUAL` as synonym for `DIMENSION`
431 * `ENCODE` and `DECODE` as synonyms for internal I/O
432 * `IMPLICIT AUTOMATIC`, `IMPLICIT STATIC`
433 * Default exponent of zero, e.g. `3.14159E`
434 * Characters in defined operators that are neither letters nor digits
435 * `B` suffix on unquoted octal constants
436 * `Z` prefix on unquoted hexadecimal constants (dangerous)
437 * `T` and `F` as abbreviations for `.TRUE.` and `.FALSE.` in DATA (PGI/XLF)
438 * Use of host FORMAT labels in internal subprograms (PGI-only feature)
439 * ALLOCATE(TYPE(derived)::...) as variant of correct ALLOCATE(derived::...) (PGI only)
440 * Defining an explicit interface for a subprogram within itself (PGI only)
441 * USE association of a procedure interface within that same procedure's definition
442 * NULL() as a structure constructor expression for an ALLOCATABLE component (PGI).
443 * Conversion of LOGICAL to INTEGER in expressions.
444 * Use of INTEGER data with the intrinsic logical operators `.NOT.`, `.AND.`, `.OR.`,
446 * IF (integer expression) THEN ... END IF (PGI/Intel)
447 * Comparison of LOGICAL with ==/.EQ. rather than .EQV. (also .NEQV.) (PGI/Intel)
448 * Procedure pointers in COMMON blocks (PGI/Intel)
449 * Underindexing multi-dimensional arrays (e.g., A(1) rather than A(1,1)) (PGI only)
450 * Legacy PGI `NCHARACTER` type and `NC` Kanji character literals
451 * Using non-integer expressions for array bounds (e.g., REAL A(3.14159)) (PGI/Intel)
452 * Mixing INTEGER types as operands to bit intrinsics (e.g., IAND); only two
453 compilers support it, and they disagree on sign extension.
454 * Module & program names that conflict with an object inside the unit (PGI only).
455 * When the same name is brought into scope via USE association from
456 multiple modules, the name must refer to a generic interface; PGI
457 allows a name to be a procedure from one module and a generic interface
459 * Type parameter declarations must come first in a derived type definition;
460 some compilers allow them to follow `PRIVATE`, or be intermixed with the
461 component declarations.
462 * Wrong argument types in calls to specific intrinsics that have different names than the
463 related generics. Some accepted exceptions are listed above in the allowed extensions.
464 PGI, Intel, and XLF support this in ways that are not numerically equivalent.
465 PGI converts the arguments while Intel and XLF replace the specific by the related generic.
466 * VMS listing control directives (`%LIST`, `%NOLIST`, `%EJECT`)
467 * Continuation lines on `INCLUDE` lines
468 * `NULL()` actual argument corresponding to an `ALLOCATABLE` dummy data object
469 * User (non-intrinsic) `ELEMENTAL` procedures may not be passed as actual
470 arguments, in accordance with the standard; some Fortran compilers
472 * Constraint C1406, which prohibits the same module name from being used
473 in a scope for both an intrinsic and a non-intrinsic module, is implemented
474 as a portability warning only, not a hard error.
475 * IBM @PROCESS directive is accepted but ignored.
477 ## Preprocessing behavior
479 * The preprocessor is always run, whatever the filename extension may be.
480 * We respect Fortran comments in macro actual arguments (like GNU, Intel, NAG;
481 unlike PGI and XLF) on the principle that macro calls should be treated
482 like function references. Fortran's line continuation methods also work.
484 ## Standard features not silently accepted
486 * Fortran explicitly ignores type declaration statements when they
487 attempt to type the name of a generic intrinsic function (8.2 p3).
488 One can declare `CHARACTER::COS` and still get a real result
489 from `COS(3.14159)`, for example. f18 will complain when a
490 generic intrinsic function's inferred result type does not
491 match an explicit declaration. This message is a warning.
493 ## Standard features that might as well not be
495 * f18 supports designators with constant expressions, properly
496 constrained, as initial data targets for data pointers in
497 initializers of variable and component declarations and in
498 `DATA` statements; e.g., `REAL, POINTER :: P => T(1:10:2)`.
499 This Fortran 2008 feature might as well be viewed like an
500 extension; no other compiler that we've tested can handle
502 * According to 11.1.3.3p1, if a selector of an `ASSOCIATE` or
503 related construct is defined by a variable, it has the `TARGET`
504 attribute if the variable was a `POINTER` or `TARGET`.
505 We read this to include the case of the variable being a
506 pointer-valued function reference.
507 No other Fortran compiler seems to handle this correctly for
508 `ASSOCIATE`, though NAG gets it right for `SELECT TYPE`.
509 * The standard doesn't explicitly require that a named constant that
510 appears as part of a complex-literal-constant be a scalar, but
511 most compilers emit an error when an array appears.
512 f18 supports them with a portability warning.
513 * f18 does not enforce a blanket prohibition against generic
514 interfaces containing a mixture of functions and subroutines.
515 We allow both to appear, unlike several other Fortran compilers.
516 This is especially desirable when two generics of the same
517 name are combined due to USE association and the mixture may
519 * Since Fortran 90, `INCLUDE` lines have been allowed to have
520 a numeric kind parameter prefix on the file name. No other
521 Fortran compiler supports them that I can find.
522 * A `SEQUENCE` derived type is required (F'2023 C745) to have
523 at least one component. No compiler enforces this constraint;
524 this compiler emits a warning.
525 * Many compilers disallow a `VALUE` assumed-length character dummy
526 argument, which has been standard since F'2008.
527 We accept this usage with an optional portability warning.
528 * The `ASYNCHRONOUS` attribute can be implied by usage in data
529 transfer I/O statements. Only one other compiler supports this
530 correctly. This compiler does, apart from objects in asynchronous
531 NAMELIST I/O, for which an actual asynchronous runtime implementation
534 ## Behavior in cases where the standard is ambiguous or indefinite
536 * When an inner procedure of a subprogram uses the value or an attribute
537 of an undeclared name in a specification expression and that name does
538 not appear in the host, it is not clear in the standard whether that
539 name is an implicitly typed local variable of the inner procedure or a
540 host association with an implicitly typed local variable of the host.
546 ! Although "m" never appears in the specification or executable
547 ! parts of this subroutine, both of its contained subroutines
548 ! might be accessing it via host association.
549 integer, intent(in out) :: j
554 integer(kind(m)), intent(in) :: n
558 integer(kind(m)), intent(out) :: n
569 print *, k, " should be 3"
574 Other Fortran compilers disagree in their interpretations of this example;
575 some seem to treat the references to `m` as if they were host associations
576 to an implicitly typed variable (and print `3`), while others seem to
577 treat them as references to implicitly typed local variables, and
578 load uninitialized values.
580 In f18, we chose to emit an error message for this case since the standard
581 is unclear, the usage is not portable, and the issue can be easily resolved
582 by adding a declaration.
584 * In subclause 7.5.6.2 of Fortran 2018 the standard defines a partial ordering
585 of the final subroutine calls for finalizable objects, their non-parent
586 components, and then their parent components.
587 (The object is finalized, then the non-parent components of each element,
588 and then the parent component.)
589 Some have argued that the standard permits an implementation
590 to finalize the parent component before finalizing an allocatable component in
591 the context of deallocation, and the next revision of the language may codify
593 In the interest of avoiding needless confusion, this compiler implements what
594 we believe to be the least surprising order of finalization.
595 Specifically: all non-parent components are finalized before
596 the parent, allocatable or not;
597 all finalization takes place before any deallocation;
598 and no object or subobject will be finalized more than once.
600 * When `RECL=` is set via the `OPEN` statement for a sequential formatted input
601 file, it functions as an effective maximum record length.
602 Longer records, if any, will appear as if they had been truncated to
603 the value of `RECL=`.
604 (Other compilers ignore `RECL=`, signal an error, or apply effective truncation
605 to some forms of input in this situation.)
606 For sequential formatted output, RECL= serves as a limit on record lengths
607 that raises an error when it is exceeded.
609 * When a `DATA` statement in a `BLOCK` construct could be construed as
610 either initializing a host-associated object or declaring a new local
611 initialized object, f18 interprets the standard's classification of
612 a `DATA` statement as being a "declaration" rather than a "specification"
613 construct, and notes that the `BLOCK` construct is defined as localizing
614 names that have specifications in the `BLOCK` construct.
615 So this example will elicit an error about multiple initialization:
625 Other Fortran compilers disagree with each other in their interpretations
627 The precedent among the most commonly used compilers
628 agrees with f18's interpretation: a `DATA` statement without any other
629 specification of the name refers to the host-associated object.
631 * Many Fortran compilers allow a non-generic procedure to be `USE`-associated
632 into a scope that also contains a generic interface of the same name
633 but does not have the `USE`-associated non-generic procedure as a
639 integer, intent(in) :: n
646 module procedure noargs
654 This case elicits a warning from f18, as it should not be treated
655 any differently than the same case with the non-generic procedure of
656 the same name being defined in the same scope rather than being
657 `USE`-associated into it, which is explicitly non-conforming in the
658 standard and not allowed by most other compilers.
659 If the `USE`-associated entity of the same name is not a procedure,
660 most compilers disallow it as well.
662 * Fortran 2018 19.3.4p1: "A component name has the scope of its derived-type
663 definition. Outside the type definition, it may also appear ..." which
664 seems to imply that within its derived-type definition, a component
665 name is in its scope, and at least shadows any entity of the same name
666 in the enclosing scope and might be read, thanks to the "also", to mean
667 that a "bare" reference to the name could be used in a specification inquiry.
668 However, most other compilers do not allow a component to shadow exterior
669 symbols, much less appear in specification inquiries, and there are
670 application codes that expect exterior symbols whose names match
671 components to be visible in a derived-type definition's default initialization
672 expressions, and so f18 follows that precedent.
674 * 19.3.1p1 "Within its scope, a local identifier of an entity of class (1)
675 or class (4) shall not be the same as a global identifier used in that scope..."
676 is read so as to allow the name of a module, submodule, main program,
677 or `BLOCK DATA` subprogram to also be the name of an local entity in its
678 scope, with a portability warning, since that global name is not actually
679 capable of being "used" in its scope.
681 * In the definition of the `ASSOCIATED` intrinsic function (16.9.16), its optional
682 second argument `TARGET=` is required to be "allowable as the data-target or
683 proc-target in a pointer assignment statement (10.2.2) in which POINTER is
684 data-pointer-object or proc-pointer-object." Some Fortran compilers
685 interpret this to require that the first argument (`POINTER=`) be a valid
686 left-hand side for a pointer assignment statement -- in particular, it
687 cannot be `NULL()`, but also it is required to be modifiable.
688 As there is no good reason to disallow (say) an `INTENT(IN)` pointer here,
689 or even `NULL()` as a well-defined case that is always `.FALSE.`,
690 this compiler doesn't require the `POINTER=` argument to be a valid
691 left-hand side for a pointer assignment statement, and we emit a
692 portability warning when it is not.
694 * F18 allows a `USE` statement to reference a module that is defined later
695 in the same compilation unit, so long as mutual dependencies do not form
697 This feature forestalls any risk of such a `USE` statement reading an
698 obsolete module file from a previous compilation and then overwriting
701 * F18 allows `OPTIONAL` dummy arguments to interoperable procedures
702 unless they are `VALUE` (C865).
704 * F18 processes the `NAMELIST` group declarations in a scope after it
705 has resolved all of the names in that scope. This means that names
706 that appear before their local declarations do not resolve to host
707 associated objects and do not elicit errors about improper redeclarations
708 of implicitly typed entities.
710 * Standard Fortran allows forward references to derived types, which
711 can lead to ambiguity when combined with host association.
712 Some Fortran compilers resolve the type name to the host type,
713 others to the forward-referenced local type; this compiler diagnoses
717 type ambiguous; integer n; end type
720 type(ambiguous), pointer :: ptr
721 type ambiguous; real a; end type
726 * When an intrinsic procedure appears in the specification part of a module
727 only in function references, but not an explicit `INTRINSIC` statement,
728 its name is not brought into other scopes by a `USE` statement.
730 * The subclause on rounding in formatted I/O (13.7.2.3.8 in F'2023)
731 only discusses rounding for decimal-to/from-binary conversions,
732 omitting any mention of rounding for hexadecimal conversions.
733 As other compilers do apply rounding, so does this one.
735 * For real `MAXVAL`, `MINVAL`, `MAXLOC`, and `MINLOC`, NaN values are
736 essentially ignored unless there are some unmasked array entries and
737 *all* of them are NaNs.
739 * When `INDEX` is used as an unrestricted specific intrinsic function
740 in the context of an actual procedure, as the explicit interface in
741 a `PROCEDURE` declaration statement, or as the target of a procedure
742 pointer assignment, its interface has exactly two dummy arguments
743 (`STRING=` and `SUBSTRING=`), and includes neither `BACK=` nor
745 This is how `INDEX` as an unrestricted specific intrinsic function was
746 documented in FORTRAN '77 and Fortran '90; later revisions of the
747 standard deleted the argument information from the section on
748 unrestricted specific intrinsic functions.
749 At least one other compiler (XLF) seems to expect that the interface for
750 `INDEX` include an optional `BACK=` argument, but it doesn't actually
753 * Allocatable components of array and structure constructors are deallocated
754 after use without calling final subroutines.
755 The standard does not specify when and how deallocation of array and structure
756 constructors allocatable components should happen. All compilers free the
757 memory after use, but the behavior when the allocatable component is a derived
758 type with finalization differ, especially when dealing with nested array and
759 structure constructors expressions. Some compilers call final routine for the
760 allocatable components of each constructor sub-expressions, some call it only
761 for the allocatable component of the top level constructor, and some only
762 deallocate the memory. Deallocating only the memory offers the most
763 flexibility when lowering such expressions, and it is not clear finalization
764 is desirable in such context (Fortran interop 1.6.2 in F2018 standards require
765 array and structure constructors not to be finalized, so it also makes sense
766 not to finalize their allocatable components when releasing their storage).
768 * F'2023 19.4 paragraph 5: "If integer-type-spec appears in data-implied-do or
769 ac-implied-do-control it has the specified type and type parameters; otherwise
770 it has the type and type parameters that it would have if it were the name of
771 a variable in the innermost executable construct or scoping unit that includes
772 the DATA statement or array constructor, and this type shall be integer type."
773 Reading "would have if it were" as being the subjunctive, this would mean that
774 an untyped implied DO index variable should be implicitly typed according to
775 the rules active in the enclosing scope. But all other Fortran compilers interpret
776 the "would have if it were" as meaning "has if it is" -- i.e., if the name
777 is visible in the enclosing scope, the type of that name is used as the
778 type of the implied DO index. So this is an error, not a simple application
779 of the default implicit typing rule:
782 print *, [(j,j=1,10)]
785 * The Fortran standard doesn't mention integer overflow explicitly. In many cases,
786 however, integer overflow makes programs non-conforming.
787 F18 follows other widely-used Fortran compilers. Specifically, f18 assumes
788 integer overflow never occurs in address calculations and increment of
789 do-variable unless the option `-fwrapv` is enabled.
791 ## De Facto Standard Features
793 * `EXTENDS_TYPE_OF()` returns `.TRUE.` if both of its arguments have the
794 same type, a case that is technically implementation-defined.
796 * `ENCODING=` is not in the list of changeable modes on an I/O unit,
797 but every Fortran compiler allows the encoding to be changed on an
800 * A `NAMELIST` input item that references a scalar element of a vector
801 or contiguous array can be used as the initial element of a storage
802 sequence. For example, "&GRP A(1)=1. 2. 3./" is treated as if had been
803 "&GRP A(1:)=1. 2. 3./".