1<!--
2Copyright (c) 2019, NVIDIA CORPORATION.  All rights reserved.
3-->
4
5## Procedure reference implementation protocol
6
7Fortran function and subroutine references are complicated.
8This document attempts to collect the requirements imposed by the 2018
9standard (and legacy extensions) on programs and implementations, work
10through the implications of the various features, and propose both a
11runtime model and a compiler design.
12
13All section, requirement, and constraint numbers herein pertain to
14the Fortran 2018 standard.
15
16This note does not consider calls to intrinsic procedures, statement
17functions, or calls to internal runtime support library routines.
18
19## Quick review of terminology
20
21* A *dummy argument* is a function or subroutine parameter.
22  It is *associated* with an *effective argument* at each call
23  to the procedure.
24* The *shape* of an array is a vector containing its extent (size)
25  on each dimension; the *rank* of an array is the number of its
26  dimensions (i.e., the shape of its shape).
27  The absolute values of the lower and upper bounds of the dimensions
28  of an array are not part of its shape, just their difference (plus 1).
29* An *explicit-shape* array has all of its bounds specified; lower
30  bounds default to 1.  These can be passed by with a single address
31  and their contents are contiguous.
32* An *assumed-size* array is an explicit-shape array with `*` as its
33  final dimension, which is the most-significant one in Fortran
34  and whose value does not affect indexed address calculations.
35* A *deferred-shape* array (`DIMENSION::A(:)`) is a `POINTER` or `ALLOCATABLE`.
36  `POINTER` target data might not be contiguous.
37* An *assumed-shape* (not size!) array (`DIMENSION::A(:)`) is a dummy argument
38  that is neither `POINTER` nor `ALLOCATABLE`; its lower bounds can be set
39  by the procedure that receives them (defaulting to 1), and its
40  upper bounds are functions of the lower bounds and the extents of
41  dimensions in the *shape* of the effective argument.
42* An *assumed-length* `CHARACTER(*)` dummy argument
43  takes its length from the effective argument.
44* An *assumed-length* `CHARACTER(*)` *result* of an external function (C721)
45  has its length determined by its eventual declaration in a calling scope.
46* An *assumed-rank* `DIMENSION::A(..)` dummy argument array has an unknown
47  number of dimensions.
48* A *polymorphic* `CLASS(t)` dummy argument, `ALLOCATABLE`, or `POINTER`
49  has a specific derived type or some extension of that type.
50  An *unlimited polymorphic* `CLASS(*)` object can have any
51  intrinsic or derived type.
52* *Interoperable* `BIND(C)` procedures are written in C or callable from C.
53
54## Interfaces
55
56Referenced procedures may or may not have declared interfaces
57available to their call sites.
58
59Procedures with some post-Fortran '77 features *require* an
60explicit interface to be called (15.4.2.2) or even passed (4.3.4(5)):
61
62* use of argument keywords in a call
63* procedures that are `ELEMENTAL` or `BIND(C)`
64* procedures that are required to be `PURE` due to the context of the call
65  (specification expression, `DO CONCURRENT`, `FORALL`)
66* dummy arguments with these attributes: `ALLOCATABLE`, `POINTER`,
67  `VALUE`, `TARGET`, `OPTIONAL`, `ASYNCHRONOUS`, `VOLATILE`,
68  and, as a consequence of limitations on its use, `CONTIGUOUS`;
69  `INTENT()`, however, does *not* require an explicit interface
70* dummy arguments that are coarrays
71* dummy arguments that are assumed-shape or assumed-rank arrays
72* dummy arguments with parameterized derived types
73* dummy arguments that are polymorphic
74* function result that is an array
75* function result that is `ALLOCATABLE` or `POINTER`
76* `CHARACTER` function result whose length is neither constant
77  nor assumed
78* derived type function result with `LEN` type parameter value that is
79  not constant
80  (note that result derived type parameters cannot be assumed (C795))
81
82Module procedures, internal procedures, procedure pointers,
83type-bound procedures, and recursive references by a procedure to itself
84always have explicit interfaces.
85(Consequently, they cannot be assumed-length `CHARACTER(*)` functions;
86conveniently, assumed-length `CHARACTER(*)` functions are prohibited from
87recursion (15.6.2.1(3))).
88
89Other uses of procedures besides calls may also require explicit interfaces,
90such as procedure pointer assignment, type-bound procedure bindings, &c.
91
92Note that non-parameterized monomorphic derived type arguments do
93*not* by themselves require the use of an explicit interface.
94However, dummy arguments with any derived type parameters *do*
95require an explicit interface, even if they are all `KIND` type
96parameters.
97
9815.5.2.9(2) explicitly allows an assumed-length `CHARACTER(*)` function
99to be passed as an actual argument to an explicit-length dummy;
100this has implications for calls to character-valued dummy functions
101and function pointers.
102(In the scopes that reference `CHARACTER` functions, they must have
103visible definitions with explicit result lengths.)
104
105### Implicit interfaces
106
107In the absence of any characteristic or context that *requires* an
108explicit interface (see above), an external function or subroutine (R503)
109or `ENTRY` (R1541) can be called directly or indirectly via its implicit interface.
110Each of the arguments can be passed as a simple address, including
111dummy procedures.
112Procedures that *can* be called via an implicit interface can
113undergo more thorough checking
114by semantics when an explicit interface for them exists, but they must be
115compiled as if all calls to them were through the implicit interface.
116This note will mention special handling for procedures that are exposed
117to the possibility of being called with an implicit interface as *F77ish* procedures
118below; this is of course not standard terminology.
119
120Internal and module subprograms that are ever passed as arguments &/or
121assigned as targets of procedure pointers may be F77ish.
122
123Every F77ish procedure can and must be distiguished at compilation time.
124Such procedures should respect the external naming conventions (when external)
125and any legacy ABI used for Fortran '77 programs on the target architecture,
126so that portable libraries can be compiled
127and used by distinct implementations (and their versions)
128of Fortran.
129
130Note that F77ish functions still have known result types, possibly by means
131of implicit typing of their names.
132They can also be `CHARACTER(*)` assumed-length character functions.
133
134In other words: these F77sh procedures that do not require the use of an explicit
135interface and that can possibly be referenced, directly or indirectly,
136with implicit interfaces are limited to argument lists that comprise
137only the addresses of effective arguments and the length of a `CHARACTER` function result
138(when there is one), and they can return only scalar values with constant
139type parameter values.
140None of their arguments or results need be (or can be) implemented
141with descriptors,
142and any internal procedures passed to them as arguments must be
143simple addresses of non-internal subprograms or trampolines for
144internal procedures.
145
146Note that the `INTENT` attribute does not, by itself,
147require the use of explicit interface; neither does the use of a dummy
148procedure (implicit or explicit in their interfaces).
149So the analyis of calls to F77ish procedures must allow for the
150invisible use of `INTENT(OUT)`.
151
152## Protocol overview
153
154Here is a summary script of all of the actions that may need to be taken
155by the calling procedure and its referenced procedure to effect
156the call, entry, exit, and return steps of the procedure reference
157protocol.
158The order of these steps is not particularly strict, and we have
159some design alternatives that are explored further below.
160
161### Before the call:
162
1631. Compute &/or copy into temporary storage the values of
164   some effective argument expressions and designators (see below).
1651. Create and populate descriptors for arguments that use them
166   (see below).
1671. Possibly allocate function result storage,
168   when its size can be known by all callers; function results that are
169   neither `POINTER` nor `ALLOCATABLE` must have explicit shapes (C816).
1701. Create and populate a descriptor for the function result, if it
171   needs one (deferred-shape/-length `POINTER`, any `ALLOCATABLE`,
172   derived type with non-constant length parameters, &c.).
1731. Capture the values of host-escaping local objects in memory;
174   package them into single address (for calls to internal procedures &
175   for calls that pass internal procedures as arguments).
1761. Resolve the target procedure's polymorphic binding, if any.
1771. Marshal effective argument addresses (or values for `%VAL()` and some
178   discretionary `VALUE` arguments) into registers.
1791. Marshal `CHARACTER` argument lengths in additional value arguments for
180   `CHARACTER` effective arguments not passed via descriptors.
1811. Marshal an extra argument for the length of a `CHARACTER` function
182   result if the function is F77ish.
1831. Marshal an extra argument for the function result's descriptor,
184   if it needs one.
1851. Set the "host instance" (static link) register when calling an internal
186   procedure from its host or another internal procedure, a procedure pointer,
187   or dummy procedure (when it has a descriptor).
1881. Jump.
189
190### On entry:
1911. For subprograms with alternate `ENTRY` points: shuffle `ENTRY` dummy arguments
192   set a compiler-generated variable to identify the alternate entry point,
193   and jump to the common entry point for common processing and a `switch()`
194   to the statement after the `ENTRY`.
1951. Capture `CHARACTER` argument &/or assumed-length result length values.
1961. Complete `VALUE` copying if this step will not always be done
197   by the caller (as I think it should be).
1981. Finalize &/or re-initialize `INTENT(OUT)` non-pointer
199   effective arguments (see below).
2001. For interoperable procedures called from C: compact discontiguous
201   dummy argument values when necessary (`CONTIGUOUS` &/or
202   explicit-shape/assumed-size arrays of assumed-length `CHARACTER(*)`).
2031. Optionally compact assumed-shape arguments for contiguity on one
204   or more leading dimensions to improve SIMD vectorization, if not
205   `TARGET` and not already sufficiently contiguous.
206   (PGI does this in the caller, whether the callee needs it or not.)
2071. Complete allocation of function result storage, if that has
208   not been done by the caller.
2091. Initialize components of derived type local variables,
210   including the function result.
211
212Execute the callee, populating the function result or selecting
213the subroutine's alternate return.
214
215### On exit:
2161. Clean up local scope (finalization, deallocation)
2171. Deallocate `VALUE` argument temporaries.
218   (But don't finalize them; see 7.5.6.3(3)).
2191. Replace any assumed-shape argument data that were compacted on
220   entry for contiguity when the data were possibly
221   modified across the call (never when `INTENT(IN)` or `VALUE`).
2221. Identify alternate `RETURN` to caller.
2231. Marshal results.
2241. Jump
225
226### On return to the caller:
2271. Save the result registers, if any.
2281. Copy effective argument array designator data that was copied into
229   a temporary back into its original storage (see below).
2301. Complete deallocation of effective argument temporaries (not `VALUE`).
2311. Reload definable host-escaping local objects from memory, if they
232   were saved to memory by the host before the call.
2331. `GO TO` alternate return, if any.
2341. Use the function result in an expression.
2351. Eventually, finalize &/or deallocate the function result.
236
237(I've omitted some obvious steps, like preserving/restoring callee-saved
238registers on entry/exit, dealing with caller-saved registers before/after
239calls, and architecture-dependent ABI requirements.)
240
241## The messy details
242
243### Copying effective argument values into temporary storage
244
245There are several conditions that require the compiler to generate
246code that allocates and populates temporary storage for an actual
247argument.
248
249First, effective arguments that are expressions, not designators, obviously
250need to be computed and captured into memory in order to be passed
251by reference.
252This includes parenthesized designators like `(X)`, which are
253expressions in Fortran, as an important special case.
254(This case also technically includes unparenthesized constants,
255but those are better implemented by passing addresses in read-only
256memory.)
257The dummy argument cannot be known to have `INTENT(OUT)` or
258`INTENT(IN OUT)`.
259
260Small scalar or elemental `VALUE` arguments may be passed in registers,
261as should arguments wrapped in the legacy VMS `%VAL()` notation.
262Multiple elemental `VALUE` arguments might be packed into SIMD registers.
263
264Effective arguments that are designators, not expressions, must also
265be copied into temporaries in the following situations.
266
2671. Coindexed objects need to be copied into the local image.
268   This can get very involved if they contain `ALLOCATABLE`
269   components, which also need to be copied, along with their
270   `ALLOCATABLE` components, and may be best implemented with a runtime
271   library routine working off a description of the type.
2721. Effective arguments associated with dummies with the `VALUE`
273   attribute need to be copied; this can be done on either
274   side of the call, but there are optimization opportunities
275   available when the caller's side bears the responsibility.
2761. In non-elemental calls, the values of array sections with
277   vector-valued subscripts need to be gathered into temporaries.
278   These effective arguments are not definable, and they are not allowed to
279   be associated with non-`VALUE` dummy arguments with the attributes
280   `INTENT(OUT)`, `INTENT(IN OUT)`, `ASYNCHRONOUS`, or `VOLATILE`
281   (15.5.2.4(21)); `INTENT()` can't always be checked.
2821. Non-simply-contiguous (9.5.4) arrays being passed to non-`POINTER`
283   dummy arguments that must be contiguous (due to a `CONTIGUOUS`
284   attribute, or not being assumed-shape or assumed-rank; this
285   is always the case for F77ish procedures).
286   This should be a runtime decision, so that effective arguments
287   that turn out to be contiguous can be passed cheaply.
288   This rule does not apply to coarray dummies, whose effective arguments
289   are required to be simply contiguous when this rule would otherwise
290   force the use of a temporary (15.5.2.8); neither does it apply
291   to `ASYNCHRONOUS` and `VOLATILE` effective arguments, which are
292   disallowed when copies would be necessary (C1538 - C1540).
293   *Only temporaries created by this contiguity requirement are
294   candidates for being copied back to the original variable after
295   the call* (see below).
296
297Fortran requires (18.3.6(5)) that calls to interoperable procedures
298with dummy argument arrays with contiguity requirements
299handle the compaction of discontiguous data *in the Fortran callee*,
300at least when called from C.
301And discontiguous data must be compacted on the *caller's* side
302when passed from Fortran to C (18.3.6(6)).
303
304We could perform all argument compaction (discretionary or
305required) in the callee, but there are many cases where the
306compiler knows that the effective argument data are contiguous
307when compiling the caller (a temporary is needed for other reasons,
308or the effective argument is simply contiguous) and a run-time test for
309discontiguity in the callee can be avoided by using a caller-compaction
310convention when we have the freedom to choose.
311
312While we are unlikely to want to _needlessly_ use a temporary for
313an effective argument that does not require one for any of these
314reasons above, we are specifically disallowed from doing so
315by the standard in cases where pointers to the original target
316data are required to be valid across the call (15.5.2.4(9-10)).
317In particular, compaction of assumed-shape arrays for discretionary
318contiguity on the leading dimension to ease SIMD vectorization
319cannot be done safely for `TARGET` dummies without `VALUE`.
320
321Effective arguments associated with known `INTENT(OUT)` dummies that
322require allocation of a temporary -- and this can only be for reasons of
323contiguity -- don't have to populate it, but they do have to perform
324minimal initialization of any `ALLOCATABLE` components so that
325the runtime doesn't crash when the callee finalizes and deallocates
326them.
327`ALLOCATABLE` coarrays are prohibited from being affected by `INTENT(OUT)`
328(see C846).
329Note that calls to implicit interfaces must conservatively allow
330for the use of `INTENT(OUT)` by the callee.
331
332Except for `VALUE` and known `INTENT(IN)` dummy arguments, the original
333contents of local designators that have been compacted into temporaries
334could optionally have their `ALLOCATABLE` components invalidated
335across the call as an aid to debugging.
336
337Except for `VALUE` and known `INTENT(IN)` dummy arguments, the contents of
338the temporary storage will be copied back into the effective argument
339designator after control returns from the procedure, and it may be necessary
340to preserve addresses (or the values of subscripts and cosubscripts
341needed to recalculate them) of the effective argument designator, or its
342elements, in additional temporary storage if they can't be safely or
343quickly recomputed after the call.
344
345### `INTENT(OUT)` preparation
346
347Effective arguments that are associated with `INTENT(OUT)`
348dummy arguments are required to be definable.
349This cannot always be checked, as the use of `INTENT(OUT)`
350does not by itself mandate the use of an explicit interface.
351
352`INTENT(OUT)` arguments are finalized (as if) on entry to the called
353procedure.  In particular, in calls to elemental procedures,
354the elements of an array are finalized by a scalar or elemental
355`FINAL` procedure (7.5.6.3(7)).
356
357Derived type components that are `ALLOCATABLE` are finalized
358and deallocated; they are prohibited from being coarrays.
359Components with initializers are (re)initialized.
360
361The preparation of effective arguments for `INTENT(OUT)` could be
362done on either side of the call.  If the preparation is
363done by the caller, there is an optimization opportunity
364in situations where unmodified incoming `INTENT(OUT)` dummy
365arguments whose types lack `FINAL` procedures are being passed
366onward as outgoing `INTENT(OUT)` arguments.
367
368### Arguments and function results requiring descriptors
369
370Dummy arguments are represented with the addresses of new descriptors
371when they have any of the following characteristics:
372
3731. assumed-shape array (`DIMENSION::A(:)`)
3741. assumed-rank array (`DIMENSION::A(..)`)
3751. parameterized derived type with assumed `LEN` parameters
3761. polymorphic (`CLASS(T)`, `CLASS(*)`)
3771. assumed-type (`TYPE(*)`)
3781. coarray dummy argument
3791. `INTENT(IN) POINTER` argument (15.5.2.7, C.10.4)
380
381`ALLOCATABLE` and other `POINTER` arguments can be passed by simple
382address.
383
384Non-F77ish procedures use descriptors to represent two further
385kinds of dummy arguments:
386
3871. assumed-length `CHARACTER(*)`
3881. dummy procedures
389
390F77ish procedures use other means to convey character length and host instance
391links (respectively) for these arguments.
392
393Function results are described by the caller & callee in
394a caller-supplied descriptor when they have any of the following
395characteristics, some which necessitate an explicit interface:
396
3971. deferred-shape array (so `ALLOCATABLE` or `POINTER`)
3981. derived type with any non-constant `LEN` parameter
399   (C795 prohibit assumed lengths)
4001. procedure pointer result (when the interface must be explicit)
401
402Storage for a function call's result is allocated by the caller when
403possible: the result is neither `ALLOCATABLE` nor `POINTER`,
404the shape is scalar or explicit, and the type has `LEN` parameters
405that are constant expressions.
406In other words, the result doesn't require the use of a descriptor
407but can't be returned in registers.
408This allows a function result to be written directly into a local
409variable or temporary when it is safe to treat the variable as if
410it were an additional `INTENT(OUT)` argument.
411(Storage for `CHARACTER` results, assumed or explicit, is always
412allocated by the caller, and the length is always passed so that
413an assumed-length external function will work when eventually
414called from a scope that declares the length that it will use
415(15.5.2.9 (2)).)
416
417Note that the lower bounds of the dimensions of non-`POINTER`
418non-`ALLOCATABLE` dummy argument arrays are determined by the
419callee, not the caller.
420(A Fortran pitfall: declaring `A(0:9)`, passing it to a dummy
421array `D(:)`, and assuming that `LBOUND(D,1)` will be zero
422in the callee.)
423If the declaration of an assumed-shape dummy argument array
424contains an explicit lower bound expression (R819), its value
425needs to be computed by the callee;
426it may be captured and saved in the incoming descriptor
427as long as we assume that argument descriptors can be modified
428by callees.
429Callers should fill in all of the fields of outgoing
430non-`POINTER` non-`ALLOCATABLE` argument
431descriptors with the assumption that the callee will use 1 for
432lower bound values, and callees can rely on them being 1 if
433not modified.
434
435### Copying temporary storage back into argument designators
436
437Except for `VALUE` and known `INTENT(IN)` dummy arguments and array sections
438with vector-valued subscripts (15.5.2.4(21)), temporary storage into
439which effective argument data were compacted for contiguity before the call
440must be redistributed back to its original storage by the caller after
441the return.
442
443In conjunction with saved cosubscript values, a standard descriptor
444would suffice to represent a pointer to the original storage into which the
445temporary data should be redistributed;
446the descriptor need not be fully populated with type information.
447
448Note that coindexed objects with `ALLOCATABLE` ultimate components
449are required to be associated only with dummy arguments with the
450`VALUE` &/or `INTENT(IN)` attributes (15.6.2.4(6)), so there is no
451requirement that the local image somehow reallocate remote storage
452when copying the data back.
453
454### Polymorphic bindings
455
456Calls to the type-bound procedures of monomorphic types are
457resolved at compilation time, as are calls to `NON_OVERRIDABLE`
458type-bound procedures.
459The resolution of calls to overridable type-bound procedures of
460polymorphic types must be completed at execution (generic resolution
461of type-bound procedure bindings from effective argument types, kinds,
462and ranks is always a compilation-time task (15.5.6, C.10.6)).
463
464Each derived type that declares or inherits any overridable
465type-bound procedure bindings must correspond to a static constant
466table of code addresses (or, more likely, a static constant type
467description containing or pointing to such a table, along with
468information used by the runtime support library for initialization,
469copying, finalization, and I/O of type instances).  Each overridable
470type-bound procedure in the type corresponds to an index into this table.
471
472### Host instance linkage
473
474Calls to dummy procedures and procedure pointers that resolve to
475internal procedures need to pass an additional "host instance" argument that
476addresses a block of storage in the stack frame of the their
477host subprogram that was active at the time they were passed as an
478effective argument or associated with a procedure pointer.
479This is similar to a static link in implementations of programming
480languages with nested subprograms, although Fortran only allows
481one level of nesting.
482The 64-bit x86 and little-endian OpenPower ABIs reserve registers
483for this purpose (`%r10` & `R11`); 64-bit ARM has a reserved register
484that can be used (`x18`).
485
486The host subprogram objects that are visible to any of their internal
487subprograms need to be resident in memory across any calls to them
488(direct or not).  Any host subprogram object that might be defined
489during a call to an internal subprogram needs to be reloaded after
490a call or reside permanently in memory.
491A simple conservative analysis of the internal subprograms can
492identify all of these escaping objects and their definable subset.
493
494The address of the host subprogram storage used to hold the escaping
495objects needs to be saved alongside the code address(es) that
496represent a procedure pointer.
497It also needs to be conveyed alongside the text address for a
498dummy procedure.
499
500For F77ish procedures, we cannot use a "procedure pointer descriptor"
501to pass a procedure argument -- they expect to receive a single
502address argument.
503We will need to package the host instance link in a trampoline
504that loads its address into the designated register.
505
506GNU Fortran and Intel Fortran construct trampolines by writing
507a sequence of machine instructions to a block of storage in the
508host's stack frame, which requires the stack to be executable,
509which seems inadvisable for security reasons;
510XLF manages trampolines in its runtime support library, which adds some overhead
511to their construction and a reclamation obligation;
512NAG Fortran manages a static fixed-sized stack of trampolines
513per call site, imposing a hidden limit on recursion and foregoing
514reentrancy;
515PGI passes host instance links in descriptors in additional arguments
516that are not always successfully forwarded across implicit interfaces,
517sometimes leading to crashes when they turn out to be needed.
518
519F18 will manage a pool of trampolines in its runtime support library
520that can be used to pass internal procedures as effective arguments
521to F77ish procedures, so that
522a bare code address can serve to represent the effective argument.
523But targets that can only be called with an explicit interface
524have the option of using a "fat pointer" (or additional argument)
525to represent a dummy procedure closure so as
526to avoid the overhead of constructing and reclaiming a trampoline.
527Procedure descriptors can also support multiple code addresses.
528
529### Naming
530
531External subroutines and functions (R503) and `ENTRY` points (R1541)
532with `BIND(C)` (R808) have linker-visible names that are either explicitly
533specified in the program or determined by straightforward rules.
534The names of other F77ish external procedures should respect the conventions
535of the target architecture for legacy Fortran '77 programs; this is typically
536something like `foo_`.
537
538In other cases, however, we have fewer constraints on external naming,
539as well as some additional requirements and goals.
540
541Module procedures need to be distinguished by the name of their module
542and (when they have one) the submodule where their interface was
543defined.
544Note that submodule names are distinct in their modules, not hierarchical,
545so at most two levels of qualification are needed.
546
547Pure `ELEMENTAL` functions (15.8) must use distinct names for any alternate
548entry points used for packed SIMD arguments of various widths if we support
549calls to these functions in SIMD parallel contexts.
550There are already conventions for these names in `libpgmath`.
551
552The names of non-F77ish external procedures
553should be distinguished as such so that incorrect attempts to call or pass
554them with an implicit interface will fail to resolve at link time.
555Fortran 2018 explicitly enables us to do this with a correction to Fortran
5562003 in 4.3.4(5).
557
558Last, there must be reasonably permanent naming conventions used
559by the F18 runtime library for those unrestricted specific intrinsic
560functions (table 16.2 in 16.8) and extensions that can be passed as
561arguments.
562
563In these cases where external naming is at the discretion
564of the implementation, we should use names that are not in the C language
565user namespace, begin with something that identifies
566the current incompatible version of F18, the module, the submodule, and
567elemental SIMD width, and are followed by the external name.
568The parts of the external name can be separated by some character that
569is acceptable for use in LLVM IR and assembly language but not in user
570Fortran or C code, or by switching case
571(so long as there's a way to cope with extension names that don't begin
572with letters).
573
574In particular, the period (`.`) seems safe to use as a separator character,
575so a `Fa.` prefix can serve to isolate these discretionary names from
576other uses and to identify the earliest link-compatible version.
577For examples: `Fa.mod.foo`, `Fa.mod.submod.foo`, and (for an external
578subprogram that requires an explicit interface) `Fa.foo`.
579When the ABI changes in the future in an incompatible way, the
580initial prefix becomes `Fb.`, `Fc.`, &c.
581
582## Summary of checks to be enforced in semantics analysis
583
5848.5.10 `INTENT` attributes
585* (C846) An `INTENT(OUT)` argument shall not be associated with an
586  object that is or has an allocatable coarray.
587* (C847) An `INTENT(OUT)` argument shall not have `LOCK_TYPE` or `EVENT_TYPE`.
588
5898.5.18 `VALUE` attribute
590* (C863) The argument cannot be assumed-size, a coarray, or have a coarray
591  ultimate component.
592* (C864) The argument cannot be `ALLOCATABLE`, `POINTER`, `INTENT(OUT)`,
593  `INTENT(IN OUT)`, or `VOLATILE`.
594* (C865) If the procedure is `BIND(C)`, the argument cannot be `OPTIONAL`.
595
59615.5.1 procedure references:
597* (C1533) can't pass non-intrinsic `ELEMENTAL` as argument
598* (C1536) alternate return labels must be in the inclusive scope
599* (C1537) coindexed argument cannot have a `POINTER` ultimate component
600
60115.5.2.4 requirements for non-`POINTER` non-`ALLOCATABLE` dummies:
602* (2) dummy must be monomorphic for coindexed polymorphic actual
603* (2) dummy must be polymorphic for assumed-size polymorphic actual
604* (2) dummy cannot be `TYPE(*)` if effective is PDT or has TBPs or `FINAL`
605* (4) character length of effective cannot be less than dummy
606* (6) coindexed effective with `ALLOCATABLE` ultimate component requires
607      `INTENT(IN)` &/or `VALUE` dummy
608* (13) a coindexed scalar effective requires a scalar dummy
609* (14) a non-conindexed scalar effective usually requires a scalar dummy,
610  but there are some exceptions that allow elements of storage sequences
611  to be passed and treated like explicit-shape or assumed-size arrays
612  (see 15.5.2.11)
613* (16) array rank agreement
614* (20) `INTENT(OUT)` & `INTENT(IN OUT)` dummies require definable actuals
615* (21) array sections with vector subscripts can't be passed to definable dummies
616       (`INTENT(OUT)`, `INTENT(IN OUT)`, `ASYNCHRONOUS`, `VOLATILE`)
617* (22) `VOLATILE` attributes must match when dummy has a coarray ultimate component
618* (C1538 - C1540) checks for `ASYNCHRONOUS` and `VOLATILE`
619
62015.5.2.5 requirements for `ALLOCATABLE` & `POINTER` arguments when both
621the dummy and effective arguments have the same attributes:
622* (2) both or neither can be polymorphic
623* (2) both are unlimited polymorphic or both have the same declared type
624* (3) rank compatibility
625* (4) effective argument must have deferred the same type parameters as the dummy
626
62715.5.2.6 `ALLOCATABLE` dummy arguments:
628* (2) effective must be `ALLOCATABLE`
629* (3) corank must match
630* (4) coindexed effective requires `INTENT(IN)` dummy
631* (7) `INTENT(OUT)` & `INTENT(IN OUT)` dummies require definable actuals
632
63315.5.2.7 `POINTER` dummy arguments:
634* (C1541) `CONTIGUOUS` dummy requires simply contiguous actual
635* (C1542) effective argument cannot be coindexed unless procedure is intrinsic
636* (2) effective argument must be `POINTER` unless dummy is `INTENT(IN)` and
637  effective could be the right-hand side of a pointer assignment statement
638
63915.5.2.8 corray dummy arguments:
640* (1) effective argument must be coarray
641* (1) `VOLATILE` attributes must match
642* (2) explicitly or implicitly contiguous dummy array requires a simply contiguous actual
643
64415.5.2.9 dummy procedures:
645* (1) explicit dummy procedure interface must have same characteristics as actual
646* (5) dummy procedure `POINTER` requirements on effective arguments
647
64815.6.2.1 procedure definitions:
649* `NON_RECURSIVE` procedures cannot recurse.
650* Assumed-length `CHARACTER(*)` functions cannot be declared as `RECURSIVE`, array-valued,
651  `POINTER`, `ELEMENTAL`, or `PURE' (C723), and cannot be called recursively (15.6.2.1(3)).
652* (C823) A function result cannot be a coarray or contain a coarray ultimate component.
653
654`PURE` requirements (15.7): C1583 - C1599.
655These also apply to `ELEMENTAL` procedures that are not `IMPURE`.
656
657`ELEMENTAL` requirements (15.8.1): C15100-C15103,
658and C1533 (can't pass as effective argument unless intrinsic)
659
660For interoperable procedures and interfaces (18.3.6):
661* C1552 - C1559
662* function result is scalar and of interoperable type (C1553, 18.3.1-3)
663* `VALUE` arguments are scalar and of interoperable type
664* `POINTER` dummies cannot be `CONTIGUOUS` (18.3.6 paragraph 2(5))
665* assumed-type dummies cannot be `ALLOCATABLE`, `POINTER`, assumed-shape, or assumed-rank (18.3.6 paragraph 2 (5))
666* `CHARACTER` dummies that are `ALLOCATABLE` or `POINTER` must be deferred-length
667
668## Further topics to document
669
670* Alternate return specifiers
671* `%VAL()`, `%REF()`, and `%DESCR()` legacy VMS interoperability extensions
672* Unrestricted specific intrinsic functions as effective arguments
673* SIMD variants of `ELEMENTAL` procedures (& unrestricted specific intrinsics)
674* Elemental subroutine calls with array arguments
675