Commit Graph

348 Commits

Author SHA1 Message Date
Peter Klausler
e1ad2735c3 [flang] Clean up ISO_FORTRAN_ENV, fix NUMERIC_STORAGE_SIZE (#87566)
Address TODOs in the intrinsic module ISO_FORTRAN_ENV, and extend the
implementation of NUMERIC_STORAGE_SIZE so that the calculation of its
value is deferred until it is needed so that the effects of
-fdefault-integer-8 or -fdefault-real-8 are reflected. Emit a warning
when NUMERIC_STORAGE_SIZE is used from the module file and the default
integer and real sizes do not match.

Fixes https://github.com/llvm/llvm-project/issues/87476.
2024-04-08 11:57:01 -07:00
Peter Klausler
aace1e1719 [flang] Improve error message with declaration (#87294)
When a program attempts to use a non-object entity as the base of a
component reference or type parameter inquiry, the message is somewhat
uninformative and the position of the entity's declaration will not
reflect any updates made to the symbol during name resolution.

Includes some NFC C++17 style clean-up on some code noticed while
debugging (missing mandatory braces).
2024-04-08 11:55:03 -07:00
Peter Klausler
af61d08280 [flang] Handle forward reference to shadowing derived type from IMPLICIT (#87280)
A derived type name in an IMPLICIT statement might be a host association
or it might be a forward reference to a local derived type, which may be
shadowing a host-associated name. Add a scan over the specification part
in search of derived type definitions to determine the right
interpretation.

Fixes https://github.com/llvm/llvm-project/issues/87215.
2024-04-08 11:54:37 -07:00
Peter Klausler
92ecc22b8d [flang] Fix crash in semantics on bad program (#87199)
Don't accept a putative statement function definition for a symbol that
is a subprogram but can't possibly be a statement function.

Fixes https://github.com/llvm/llvm-project/issues/86936.
2024-04-08 11:53:49 -07:00
Peter Klausler
8f01ecaeb8 [flang] Special-case handling of INTRINSIC in type-decl-stmt (#86518)
Fortran allows the INTRINSIC attribute to be specified with a distinct
attribute statement, and also as part of the attribute list of a
type-declaration-stmt. This is an odd case (especially as the declared
type is mandated to be ignored if it doesn't match the type of the
intrinsic function) that can lead to odd error messages and crashes,
since the rest of name resolution expects that intrinsics with explicit
declarations will have been declared with INTRINSIC attribute
statements. Resolve by handling an "inline" INTRINSIC attribute as a
special case while processing a type-declaration-stmt, so that

  real, intrinsic :: acos, asin, atan

is processed exactly as if it had been

  intrinsic acos, asin, atan; real acos, asin, atan

Fixes https://github.com/llvm/llvm-project/issues/86382.
2024-03-26 09:50:37 -07:00
Peter Klausler
f50f0caf87 [flang] Fix crash in name resolution (#85835)
ConvertToObjectEntity() returns true for use- and host-associated object
symbols, too. Ensure in this case that the symbol really is a
non-associated object.

Fixes https://github.com/llvm/llvm-project/issues/85776.
2024-03-26 08:59:22 -07:00
harishch4
a7eaae4ec6 [Flang] Fix to the module procedure interface block ignoring implicit… (#85735)
… of host scoping unit.

Fix as proposed by @thtsikas [here
](11d07d9ef6 (commitcomment-139798026)).
2024-03-19 22:46:57 +05:30
Peter Klausler
702a86a8f1 [flang] Correct accessibility of name that is both generic and derive… (#85098)
…d type

When the same name is used for a derived type and generic interface in a
module, and no explicit PUBLIC or PRIVATE statement appears for the name
but the derived type definition does have an explicit accessibility,
that accessibility must also apply to the generic interface.
2024-03-13 15:13:56 -07:00
Peter Klausler
83ca78deb9 [flang] Emit "raw" name for procedure interface in module file (#83915)
Save both the raw procedure interface symbol as well as the result of
passing it through GetUltimate() and BypassGeneric() in symbol table
entries with ProcEntityDetails. The raw symbol of the interface needs to
be the one used for emitting procedure symbols to module files.

Fixes https://github.com/llvm/llvm-project/issues/83836.
2024-03-05 12:00:46 -08:00
Peter Klausler
13cd0a905b [flang] Skim usage before marking unknown module externals as subrout… (#83897)
…ines

Name resolution needs to delay its default determination of module
external procedures as subroutines until after it has skimmed the
execution parts of module procedures.

Fixes https://github.com/llvm/llvm-project/issues/83622.
2024-03-05 11:41:12 -08:00
Peter Klausler
e09e9567fc [flang] Downgrade error to warning (#83032)
It's probably a bad idea to have a Cray pointer whose type is a derived
type that is not a sequence type, but the feature is a nonstandard
extension in the first place. Downgrade the message to a warning.

Fixes https://github.com/llvm/llvm-project/issues/82210.
2024-03-01 16:54:35 -08:00
Peter Klausler
2445a96ff2 [flang] Enforce F'2023 C1520 correctly (#82842)
When a procedure declaration statement has a binding label, it must
declare no more than one procedure.

Fixes https://github.com/llvm/llvm-project/issues/82528.
2024-03-01 16:49:43 -08:00
Peter Klausler
f4215f7140 [flang] Fix handling of shadowed procedure name used as interface (#82837)
Use BypassGeneric() to process the name of an interface in a procedure
declaration statement, so that if it's the name of a generic with a
homonymous specific procedure, that's what defines the interface.

Fixes https://github.com/llvm/llvm-project/issues/82267.
2024-03-01 16:42:00 -08:00
Peter Klausler
8bcb1ceded [flang] Allow PROCEDURE() with explicit type elsewhere (#82835)
Fortran allows a procedure declaration statement with no interface or
type, with an explicit type declaration statement elsewhere being used
to define a function's result.

Fixes https://github.com/llvm/llvm-project/issues/82006.
2024-03-01 16:31:13 -08:00
Peter Klausler
189d89a92c [flang] Ensure names resolve in DATA statement objects (#82825)
When DATA statement objects have derived types obtained by implicit
typing rules, their types aren't known until specification part
processing is complete. In the case of a derived type, any component
name in a designator may still be in need of name resolution. Take care
of it in the deferred check visitor that runs at the end of name
resolution in each specification and execution part.

Fixes https://github.com/llvm/llvm-project/issues/82069.
2024-03-01 16:19:01 -08:00
Peter Klausler
1c530b3d9f [flang] Whether a procedure's interface is explicit or not is not a d… (#82796)
…istinguishing characteristic

We note whether a procedure's interface is explicit or implicit as an
attribute of its characteristics, so that other semantics can be checked
appropriately, but this internal attribute should not be used as a
distinguishing characteristic in itself.

Fixes https://github.com/llvm/llvm-project/issues/81876.
2024-03-01 15:56:40 -08:00
Peter Klausler
a56ef9f9ce [flang] Catch attempt to type a subroutine (#82704)
The presence of a type in the prefix of a SUBROUTINE statement should
elicit an error message, not a crash.

Fixes https://github.com/llvm/llvm-project/issues/80530.
2024-03-01 15:23:24 -08:00
Peter Klausler
8f80d466d5 [flang] Fix crash in statement function semantics (bug #80532) (#82702)
When statement function expressions are analyzed, ensure that the
semantics context has a valid location set, otherwise a type spec (like
"integer::") can lead to a crash.

Fixes https://github.com/llvm/llvm-project/issues/80532.
2024-03-01 15:10:47 -08:00
Peter Klausler
8f141490b9 [flang] Fix separate MODULE PROCEDURE when binding label exists (#82686)
When a separate module procedure is defined with a MODULE PROCEDURE and
its corresponding interface has a binding label, the compiler was
emitting an error about mismatching binding labels because the binding
label wasn't being copied into the subprogram's definition.
2024-03-01 14:57:28 -08:00
Peter Klausler
f31ac3cb1f [flang] Handle implied ASYNCHRONOUS attribute (#82638)
The standard states that data objects involved in an asynchronous data
transfer statement gain the ASYNCHRONOUS attribute implicitly in the
surrounding subprogram or BLOCK scope. This attribute affects the checks
in call semantics, as an ASYNCHRONOUS actual object associated with an
ASYNCHRONOUS dummy argument must not require data copies in or out.

(Most compilers don't implement implied ASYNCHRONOUS attributes
correctly; XLF gets these right, and GNU is close.)
2024-03-01 14:43:31 -08:00
Peter Klausler
f7a15e0021 [flang] Use module file hashes for more checking and disambiguation (#80354)
f18's module files are Fortran with a leading header comment containing
the module file format version and a hash of the following contents.
This hash is currently used only to protect module files against
corruption and truncation.

Extend the use of these hashes to catch or avoid some error cases. When
one module file depends upon another, note its hash in additional module
file header comments. This allows the compiler to detect when the module
dependency is on a module file that has been updated. Further, it allows
the compiler to find the right module file dependency when the same
module file name appears in multiple directories on the module search
path.

The order in which module files are written, when multiple modules
appear in a source file, is such that every dependency is written before
the module(s) that depend upon it, so that their hashes are known.

A warning is emitted when a module file is not the first hit on the
module file search path.

Further work is needed to add a compiler option that emits (larger)
stand-alone module files that incorporate copies of their dependencies
rather than relying on search paths. This will be desirable for
application libraries that want to ship only "top-level" module files
without needing to include their dependencies.

Another future work item would be to admit multiple modules in the same
compilation with the same name if they have distinct hashes.
2024-03-01 13:58:36 -08:00
Peter Klausler
31ab2c4f61 [flang] Ensure USE-associated objects can be in NAMELIST (#82846)
The name resolution for NAMELIST objects didn't allow for symbols that
are not ObjectEntityDetails symbols.

Fixes https://github.com/llvm/llvm-project/issues/82574.
2024-02-23 21:15:32 -06:00
Pete Steinfeld
cc02e50e77 Revert "[Flang] Update the fix of PR 80738 to cover generic interface… (#81321)
… inside modules (#81087)"

This reverts commit 0802596df3.

See comments in PR #81087 for a test case that shows why I'm reverting.
2024-02-09 18:04:53 -08:00
Daniel Chen
0802596df3 [Flang] Update the fix of PR 80738 to cover generic interface inside modules (#81087)
The following test cases crashes. The problem is that the fix for PR
https://github.com/llvm/llvm-project/pull/80738 is not quite complete.
It should `GetUltimate()` of the `interface_` before check if it is
generic.


```
  MODULE M

    CONTAINS

    FUNCTION Int(Arg)
    INTEGER :: Int, Arg
      Int = Arg
    END FUNCTION

    FUNCTION Int8(Arg)
    INTEGER(8) :: Int8, Arg
      Int8 = 8_8
    END FUNCTION

  END MODULE

  MODULE M1
  USE M

    INTERFACE Int8
      MODULE PROCEDURE  Int
      MODULE PROCEDURE  Int8
    END INTERFACE

  END MODULE

  PROGRAM PtrAssignGen
  USE M
  USE M1
  IMPLICIT NONE

  INTERFACE Int
    MODULE PROCEDURE  Int
    MODULE PROCEDURE  Int8
  END INTERFACE

  PROCEDURE(Int8),   POINTER :: PtrInt8

  PtrInt8 => Int8
  IF ( PtrInt8(100_8) .NE. 8_8 ) ERROR STOP 12

  END
  ```
2024-02-08 10:38:50 -05:00
Daniel Chen
7e4ac8541d [Flang] Use specific symbol rather than generic symbol as procInterface to declare procedure pointer. (#80738)
Flang crashes when lowering the type of `p1` with the following code.
The problem is when it sets up the `procInterface`, it uses the generic
symbol `int`, not the specific `int`. This PR is to correct that.

```
  INTERFACE Int
    integer FUNCTION Int(arg)
      integer :: arg
    END FUNCTION
  END INTERFACE

  integer :: res
  procedure(int), pointer :: p1
  p1 => int
  res = p1(4)
  end
  ```
2024-02-07 11:36:26 -05:00
Peter Klausler
c322e92841 [flang] Silence bogus USE statement error (#79896)
When there are multiple USE statement for a particular module using
renaming, it is necessary to collect a set of all of the original
renaming targets before processing any of USE statements that don't have
ONLY: clauses.

Currently, if there is a name in the module that can't be added to the
current scope -- due to a conflict with an internal or module
subprogram, or with a previously use-associated name -- the compiler
will emit a bogus error message even if that conflicting name appear on
a later USE statement of the same module as the target of a renaming.

The new regression test case added with this patch provides a motivating
example.
2024-01-29 14:51:47 -08:00
Peter Klausler
2b7a928dd9 [flang] Improve USE merging of homonymous types, interfaces, and proc… (#79364)
…edures

Fortran allows a generic interface to have the same name as a derived
type in the same scope. It also allows a generic interface to have the
same name as one of its specific procedures.

When two modules define the same name, possibly more than once each,
things get exciting. The standard is not clear, and other compilers do
variously different things. We are currently emitting some errors
prematurely for some usage in pfUnit due to how it combines two versions
of a package together via USE association.

This patch handles combinations of derived types and generic interfaces
and their specific procedures in a more principled way. Errors due to
ambiguity are deferred to actual usage of derived types and specific
procedures -- and when they're not used, the program is unambiguous and
no error issues.
2024-01-25 16:51:30 -08:00
Peter Klausler
5bd87e65d6 [flang] Silence spurious errors about SAVE (#78765)
When an attribute specification statement follows a declaration that
applies the SAVE attribute to a symbol, name resolution can produce a
spurious error message about redundant SAVEs.

Fixes llvm-test-suite/Fortran/gfortran/regression/proc_ptr_9.f90.
2024-01-25 15:33:26 -08:00
Peter Klausler
c66645da55 [flang] Catch more initialization errors (#77850)
[flang] Catch more initialization errors
    
    Diagnose some error cases related to initialization that are
slipping past semantic checking: don't allow multiple initializations
    of the same symbol, and don't allow an object that was initialized
    as a scalar to become an array afterward.
    
Fixes llvm-test-suite/Fortran/gfortran/regression/initialization_17.f90.
2024-01-15 13:02:04 -08:00
Peter Klausler
6e0a2031f0 [flang] Catch name resolution error due to global scoping (#77683)
In
    CALL FOO
    PRINT *, ABS(FOO)
we currently resolve the first FOO to a global external subprogram, but
then the second FOO is treated as an implicitly typed local variable.
This happens because the name FOO is not present in the local scope.

Fix by adding FOO to the local scope using a place-holding
HostAssocDetails symbol whose existence prevents the creation of another
FOO in the local scope. The symbol stored in the parser::Name parse tree
nodes or used in typed expressions will all continue to point to the
global external subprogram.

Resolves llvm-test-suite/Fortran/gfortran/regression/pr71859.f90.
2024-01-15 12:40:46 -08:00
Peter Klausler
90828d67ea [flang] Weird restrictions on index variables (#77019)
There are some very odd (even for Fortran) rules in F'2023 subclause
19.4 (paras 6 & 8) pertaining to the index variables of FORALL and DO
CONCURRENT constructs/statements, and they are not currently implemented
correctly.

Although these index variables are construct entities, they have
restrictions in the standard that would essentially allow them to also
be variables in their enclosing scopes. If their names are present in
the enclosing scope, and the construct does not have an explicit type
specification for its indices, then the names in the enclosing scope
must either be scalar variables or COMMON blocks, and their type must be
integer.

Reimplement these restrictions largely with portability warnings rather
than hard errors. Retain the semantic interpretation that the type of an
untyped index variable be taken from the type of a variable of the same
name in the enclosing scope, if it exists, although that bit of the
standard could be interpreted otherwise.

Fixes https://github.com/llvm/llvm-project/issues/76978.
2024-01-15 10:50:40 -08:00
Peter Klausler
b29d632eea [flang] Accept BIND(C) derived type for Cray pointees (#76538)
The compiler requires that a Cray pointee have a SEQUENCE type, but a
recent bug report points out that a BIND(C) type should also be
accepted.

Fixes https://github.com/llvm/llvm-project/issues/76529.
2024-01-02 09:04:26 -08:00
Peter Klausler
571ad7324f [flang] Defer processing of non-pointer variable initializers (#76475)
Initializers in entity-decls don't need to have their expressions
analyzed immediately in name resolution unless of course they are
defining the values of named constants. By deferring the expression
analysis, the compiler can better handle references to module and
internal procedures that might appear in structure constructors; at
present, these are typically rejected as being forward references (which
they can be) to subprogram names that can't yet be checked for
compatibility with the characteristics of the corresponding procedure
component.
2024-01-02 08:29:06 -08:00
Peter Klausler
5a402c5622 [flang] USE-associated explicit INTRINSIC names (#76199)
The compiler doesn't USE-associate names of intrinsic procedures from
modules (in the absence of ONLY:), so that the associating scope doesn't
get populated with names of intrinsics that were used only in
declarations (e.g., SELECTED_REAL_KIND). A recent bug report (below)
shows that we should modify that policy in the case of names that appear
in explicit INTRINSIC attribute statements. The behaviors of other
Fortran compilers are not consistent and the requirements of the
standard are not clear; this fix follows the precedent set by gfortran
and nvfortran.

Fixes https://github.com/llvm/llvm-project/issues/72084.
2023-12-26 16:03:03 -08:00
Peter Klausler
a4745ff99b [flang] Detect more misparsed statement functions (same name as funct… (#73852)
…ion result)

A function can't return a statement function, so an apparent attempt to
define a statement function with the same name as the function's result
must be a misparsed assignment statement.
2023-11-30 13:35:07 -08:00
Peter Klausler
fddadd2939 [flang] Address case of under-processed array symbol (#73169)
Array element references are frequently parsed as function references
due to the ambiguous syntax of Fortran, and the parse tree is repaired
by semantics once the relevant symbol table entries are in hand. This
patch fixes a case in which the correction takes a path that leaves the
type of a symbol undetermined, leading to later spurious errors in
expression analysis.

Fixes https://github.com/llvm/llvm-project/issues/68652.
2023-11-30 13:07:49 -08:00
Peter Klausler
89165e8b1d [flang][openacc] Disable CUDA argument checks in OpenACC regions (#72310)
Checks for CUDA Fortran data attribute compatibility don't need to be
applied in OpenACC regions.
2023-11-30 10:58:51 -08:00
Kiran Chandramohan
63a6e51f8a [Flang][OpenMP] Fix issue with empty critical or critical without surrounding context (#71944)
Add the sourcerange for critical directive.

Fixes #65571
2023-11-27 15:56:39 +00:00
Peter Klausler
c3148e9f69 [flang] Identify misparsed statement function in BLOCK in ASSOCIATE (#72148)
When a BLOCK construct is within an ASSOCIATE or related construct,
don't misinterpret an assignment to an array element of a construct
entity as being an impermissible definition of a local statement
function.
2023-11-13 16:37:18 -08:00
Peter Klausler
94d47e6325 [flang] Catch nasty order-of-declarations case (#71881)
It is possible to declare the rank of an object after that object has
been used in the same specification part in a specification function
reference whose result or generic resolution may well have depended on
the object being apparently a scalar.

Catch this case, and emit a warning -- not an error, yet, due to fear of
false positives.

See the new test for examples.
2023-11-13 16:24:43 -08:00
Peter Klausler
1c91d9bdea [flang] Ensure that portability warnings are conditional (#71857)
Before emitting a warning message, code should check that the usage in
question should be diagnosed by calling ShouldWarn(). A fair number of
sites in the code do not, and can emit portability warnings
unconditionally, which can confuse a user that hasn't asked for them
(-pedantic) and isn't terribly concerned about portability *to* other
compilers.

Add calls to ShouldWarn() or IsEnabled() around messages that need them,
and add -pedantic to tests that now require it to test their portability
messages, and add more expected message lines to those tests when
-pedantic causes other diagnostics to fire.
2023-11-13 16:13:50 -08:00
Peter Klausler
fa6b574215 [flang] Account for shadowed symbols when skimming executable part (#70246)
Name resolution takes a quick pass over the executable part of a
(sub)program in search of symbols that appear to be called as
procedures, so that those names don't get mistakenly converted into
objects when finishing up specification part processing. This pass
doesn't currently cope with symbol shadowing by nested declarations in
executable constructs. This patch ensures that nested declarations for
symbols that could be used in contexts that might have been parsed as
function references properly shadow symbols of the same name in outer
scopes.
2023-10-31 11:51:00 -07:00
Peter Klausler
f87af714a5 [flang] Silence a bogus warning (#69799)
A recent fix (https://github.com/llvm/llvm-project/pull/66232) to
interpret a hitherto unknown name whose first appearance is as the
target of a procedure pointer initializer as an external procedure has
led to some inapproprite warning messages if the name is later defined
as an external subroutine ("X was already declared as an external").

Ensure that the EXTERNAL attribute is correctly noted as being implicit,
and that it's okay that neither the Subroutine nor Function flag has yet
been set for the implicit external.
2023-10-31 11:15:03 -07:00
Valentin Clement (バレンタイン クレメン)
828674395b [flang][openacc] Allow acc routine at the top level (#69936)
Some compilers allow the `$acc routine(<name>)` to be placed at the
program unit level. To be compatible, this patch enables the use of acc
routine at this level. These acc routine directives must have a name.
2023-10-24 09:17:48 -07:00
Peter Klausler
39f4ec5854 [flang] Catch a dangerous ambiguity in standard Fortran (#67483)
Fortran allows forward references to type names, which can lead to
ambiguity when coupled with host association, as in:

  module m
    type ambiguous; integer n; end type
   contains
    subroutine s
      type(ambiguous), pointer :: variable
      type t
        type(ambiguous), pointer :: component
      end type
      type ambiguous; real x; end type
    end
  end

Some other compilers resolve to a host association, some resolve to a
forward reference. This compiler will now emit an error.
2023-10-16 15:40:13 -07:00
Peter Klausler
e200b0e4a7 [flang] Submodule names can clash only with submodule names (#67361)
Name resolution creates symbols for submodules in their parents' scopes.
This can lead to bogus errors about name clashes between submodule names
and other entities in the parents' scopes.

Create symbols for submodules but do not add them to a scope's
dictionary.
2023-10-16 14:15:40 -07:00
jeanPerier
d4fd0a792f [flang] Fix symbol on module subroutine name with same name as generic (#67678)
When a MODULE SUBROUTINE or MODULE FUNCTION is implemented in the same
scope as its interface and appears in a generic with the same name, the
parse::Name of the implementation was not correctly reset and remained
the SubprogramNameDetails symbol after semantics, causing a crash in
lowering that picks up the procedure symbols on the parser names.

Reset the parser::Name symbol before the new symbol is created.
2023-09-28 18:00:34 +02:00
jeanPerier
b797a6aede [flang] Lower special bind(c) cases without binding labels (#65758)
1. Deal with BIND(C,NAME="")

BIND(C,NAME="") is different from BIND(C). The latter implies that there
us a binding label which is the Fortran symbol name (no Fortran mangling
must be added like underscores). The former implies there is no binding
label (the name in the object file must be the same as if it there was
no BIND(C) attribute at all).

This is correctly implemented in the front-end, but lowering mistakenly
overrode this in the code dealing with the case where BIND(C) is
inherited from a procedure interface. Handling of  this last case is moved into name
resolution.

2. Deal with BIND(C) internal procedure

Also according to 18.10.2, BIND(C) does not give a p prevent name
resolution from adding a label to them, otherwise,
bindc_internal_proc.f90 was not going through semantics (bogus error
about conflicting global names). Nothing TODO in lowering other than
removing the TODO.
2023-09-26 09:29:37 +02:00
Slava Zakharin
e7b8e18fc3 [flang] Set SAVE attribute for EQUIVALENCEd symbols consistently. (#67078)
Example:
```
subroutine global_sub()
  integer, dimension(4) :: iarr4=(/1,2,3,4/)
  integer, dimension(4) :: jarr4
  equivalence(iarr4,jarr4)
  call sub1
  print *, iarr4
contains
  subroutine sub1
    iarr4=jarr4((/4:1:-1/))
  end subroutine sub1
end subroutine global_sub
```

`iarr4` and `jarr4` are equivalenced via a global aggregate storage,
but the references inside `sub1` are lowered differently.
`iarr4` is accessed via the global aggregate storage, while `jarr4`
is accessed via the argument tuple. This confuses the FIR alias
analysis,
that claims that a host associated entity cannot alias with a global
(if they have different source and do not have Target/Pointer
attributes deduced by the alias analysis).

I am not convinced that there is an issue in the alias analysis yet.
I think we'd better lower the accesses uniformly, i.e. if one variable
from an equivalence is lowered via the global aggregate storage, then
any other variable from this equivalence should be lowered the same way
(even if they are used via host association).

This patch makes sure that all symbols from an EQUIVALENCE get
and implicit SAVE attribute, if they do not have it already and
any symbol from the EQUIVALENCE is SAVEd (explicitly or implicitly).
This makes the further lowering consistent.
2023-09-25 09:35:14 -07:00
Roger Ferrer Ibanez
996c0fb3a2 [flang] Avoid cycles during instantiation of derived types
Derived-type-spec (such as `type(t)`) typically cause the instantiation
of a class which is also used to define the offsets of its data
components and the size of the class.

Fortran derived types are always "completely" defined (i.e., no
incomplete / opaque derived types exist on which we can build a pointer
to them like in C/C++) so they can have their offsets always computed.

However, we must be careful not to instantiate a derived type while it
is being defined. This can happen due to cycles introduced by forward
references, such as the one below.

```lang=fortran
  type t1
    type(t2), pointer :: b ! (A)
  end type t1

  type :: t2 ! (B)
    type(t1), pointer :: a ! (C)
  end type t2 ! (D)
```

At `(A)`, flang determines that this is a forward declaration so no
instantiation happens.

At `(B)`, flang determines `t2` is not a forward declaration anymore,
because we are defining it.

At `(C)`, flang chooses to instantiate `t1`. Instantiation of `t1` finds
the field `b` at `(A)`. Now `t2` is not a forward declaration anymore,
so it can be instantiated. But at this point the field `a` has not been
added to `t2`, so we compute the size of an empty class. Because this
computation is done just once, we end emitting a wrong derived type
descriptor with a `sizeinbytes` field set to 0.

Because these kind of cycles can only happen via forward referenced
derived types specifiers, the idea here is to avoid instantiating the
derived type being defined (i.e. `t2`) until `(D)`. Keeping the
attribute "is forward reference" set until `(D)` avoids that.

Fixes https://github.com/llvm/llvm-project/issues/64973

Differential Revision: https://reviews.llvm.org/D159117
2023-09-21 12:39:23 +00:00