File tree Expand file tree Collapse file tree 2 files changed +5
-4
lines changed Expand file tree Collapse file tree 2 files changed +5
-4
lines changed Original file line number Diff line number Diff line change @@ -228,6 +228,8 @@ struct TypeBuilder {
228228 // links, the fir type is built based on the ultimate symbol. This relies
229229 // on the fact volatile and asynchronous are not reflected in fir types.
230230 const Fortran::semantics::Symbol &ultimate = symbol.GetUltimate ();
231+ if (Fortran::semantics::IsProcedurePointer (ultimate))
232+ TODO (loc, " procedure pointers" );
231233 if (const Fortran::semantics::DeclTypeSpec *type = ultimate.GetType ()) {
232234 if (const Fortran::semantics::IntrinsicTypeSpec *tySpec =
233235 type->AsIntrinsic ()) {
Original file line number Diff line number Diff line change @@ -1405,7 +1405,7 @@ struct SymbolDependenceDepth {
14051405 LLVM_DEBUG (llvm::dbgs () << " analyze symbol: " << sym << ' \n ' );
14061406 if (!done.second )
14071407 return 0 ;
1408- if (semantics::IsProcedure (sym)) {
1408+ if (semantics::IsProcedure (sym) && ! semantics::IsProcedurePointer (sym) ) {
14091409 // TODO: add declaration?
14101410 return 0 ;
14111411 }
@@ -1426,15 +1426,14 @@ struct SymbolDependenceDepth {
14261426
14271427 // Symbol must be something lowering will have to allocate.
14281428 int depth = 0 ;
1429- const semantics::DeclTypeSpec *symTy = sym.GetType ();
1430- assert (symTy && " symbol must have a type" );
1431-
14321429 // Analyze symbols appearing in object entity specification expression. This
14331430 // ensures these symbols will be instantiated before the current one.
14341431 // This is not done for object entities that are host associated because
14351432 // they must be instantiated from the value of the host symbols (the
14361433 // specification expressions should not be re-evaluated).
14371434 if (const auto *details = sym.detailsIf <semantics::ObjectEntityDetails>()) {
1435+ const semantics::DeclTypeSpec *symTy = sym.GetType ();
1436+ assert (symTy && " symbol must have a type" );
14381437 // check CHARACTER's length
14391438 if (symTy->category () == semantics::DeclTypeSpec::Character)
14401439 if (auto e = symTy->characterTypeSpec ().length ().GetExplicit ())
You can’t perform that action at this time.
0 commit comments