1 //===-- ConvertVariable.cpp -- bridge to lower to MLIR --------------------===//
2 //
3 // Part of the LLVM Project, under the Apache License v2.0 with LLVM Exceptions.
4 // See https://llvm.org/LICENSE.txt for license information.
5 // SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception
6 //
7 //===----------------------------------------------------------------------===//
8 //
9 // Coding style: https://mlir.llvm.org/getting_started/DeveloperGuide/
10 //
11 //===----------------------------------------------------------------------===//
12 
13 #include "flang/Lower/ConvertVariable.h"
14 #include "flang/Lower/AbstractConverter.h"
15 #include "flang/Lower/Allocatable.h"
16 #include "flang/Lower/BoxAnalyzer.h"
17 #include "flang/Lower/CallInterface.h"
18 #include "flang/Lower/ConvertExpr.h"
19 #include "flang/Lower/IntrinsicCall.h"
20 #include "flang/Lower/Mangler.h"
21 #include "flang/Lower/PFTBuilder.h"
22 #include "flang/Lower/StatementContext.h"
23 #include "flang/Lower/Support/Utils.h"
24 #include "flang/Lower/SymbolMap.h"
25 #include "flang/Lower/Todo.h"
26 #include "flang/Optimizer/Builder/Character.h"
27 #include "flang/Optimizer/Builder/FIRBuilder.h"
28 #include "flang/Optimizer/Builder/Runtime/Derived.h"
29 #include "flang/Optimizer/Dialect/FIRAttr.h"
30 #include "flang/Optimizer/Dialect/FIRDialect.h"
31 #include "flang/Optimizer/Dialect/FIROps.h"
32 #include "flang/Optimizer/Support/FIRContext.h"
33 #include "flang/Optimizer/Support/FatalError.h"
34 #include "flang/Semantics/runtime-type-info.h"
35 #include "flang/Semantics/tools.h"
36 #include "llvm/Support/Debug.h"
37 
38 #define DEBUG_TYPE "flang-lower-variable"
39 
40 /// Helper to lower a scalar expression using a specific symbol mapping.
41 static mlir::Value genScalarValue(Fortran::lower::AbstractConverter &converter,
42                                   mlir::Location loc,
43                                   const Fortran::lower::SomeExpr &expr,
44                                   Fortran::lower::SymMap &symMap,
45                                   Fortran::lower::StatementContext &context) {
46   // This does not use the AbstractConverter member function to override the
47   // symbol mapping to be used expression lowering.
48   return fir::getBase(Fortran::lower::createSomeExtendedExpression(
49       loc, converter, expr, symMap, context));
50 }
51 
52 /// Does this variable have a default initialization?
53 static bool hasDefaultInitialization(const Fortran::semantics::Symbol &sym) {
54   if (sym.has<Fortran::semantics::ObjectEntityDetails>() && sym.size())
55     if (!Fortran::semantics::IsAllocatableOrPointer(sym))
56       if (const Fortran::semantics::DeclTypeSpec *declTypeSpec = sym.GetType())
57         if (const Fortran::semantics::DerivedTypeSpec *derivedTypeSpec =
58                 declTypeSpec->AsDerived())
59           return derivedTypeSpec->HasDefaultInitialization();
60   return false;
61 }
62 
63 //===----------------------------------------------------------------===//
64 // Global variables instantiation (not for alias and common)
65 //===----------------------------------------------------------------===//
66 
67 /// Helper to generate expression value inside global initializer.
68 static fir::ExtendedValue
69 genInitializerExprValue(Fortran::lower::AbstractConverter &converter,
70                         mlir::Location loc,
71                         const Fortran::lower::SomeExpr &expr,
72                         Fortran::lower::StatementContext &stmtCtx) {
73   // Data initializer are constant value and should not depend on other symbols
74   // given the front-end fold parameter references. In any case, the "current"
75   // map of the converter should not be used since it holds mapping to
76   // mlir::Value from another mlir region. If these value are used by accident
77   // in the initializer, this will lead to segfaults in mlir code.
78   Fortran::lower::SymMap emptyMap;
79   return Fortran::lower::createSomeInitializerExpression(loc, converter, expr,
80                                                          emptyMap, stmtCtx);
81 }
82 
83 /// Can this symbol constant be placed in read-only memory?
84 static bool isConstant(const Fortran::semantics::Symbol &sym) {
85   return sym.attrs().test(Fortran::semantics::Attr::PARAMETER) ||
86          sym.test(Fortran::semantics::Symbol::Flag::ReadOnly);
87 }
88 
89 /// Is this a compiler generated symbol to describe derived types ?
90 static bool isRuntimeTypeInfoData(const Fortran::semantics::Symbol &sym) {
91   // So far, use flags to detect if this symbol were generated during
92   // semantics::BuildRuntimeDerivedTypeTables(). Scope cannot be used since the
93   // symbols are injected in the user scopes defining the described derived
94   // types. A robustness improvement for this test could be to get hands on the
95   // semantics::RuntimeDerivedTypeTables and to check if the symbol names
96   // belongs to this structure.
97   return sym.test(Fortran::semantics::Symbol::Flag::CompilerCreated) &&
98          sym.test(Fortran::semantics::Symbol::Flag::ReadOnly);
99 }
100 
101 static fir::GlobalOp defineGlobal(Fortran::lower::AbstractConverter &converter,
102                                   const Fortran::lower::pft::Variable &var,
103                                   llvm::StringRef globalName,
104                                   mlir::StringAttr linkage);
105 
106 /// Create the global op declaration without any initializer
107 static fir::GlobalOp declareGlobal(Fortran::lower::AbstractConverter &converter,
108                                    const Fortran::lower::pft::Variable &var,
109                                    llvm::StringRef globalName,
110                                    mlir::StringAttr linkage) {
111   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
112   if (fir::GlobalOp global = builder.getNamedGlobal(globalName))
113     return global;
114   // Always define linkonce data since it may be optimized out from the module
115   // that actually owns the variable if it does not refers to it.
116   if (linkage == builder.createLinkOnceODRLinkage() ||
117       linkage == builder.createLinkOnceLinkage())
118     return defineGlobal(converter, var, globalName, linkage);
119   const Fortran::semantics::Symbol &sym = var.getSymbol();
120   mlir::Location loc = converter.genLocation(sym.name());
121   // Resolve potential host and module association before checking that this
122   // symbol is an object of a function pointer.
123   const Fortran::semantics::Symbol &ultimate = sym.GetUltimate();
124   if (!ultimate.has<Fortran::semantics::ObjectEntityDetails>() &&
125       !ultimate.has<Fortran::semantics::ProcEntityDetails>())
126     mlir::emitError(loc, "lowering global declaration: symbol '")
127         << toStringRef(sym.name()) << "' has unexpected details\n";
128   return builder.createGlobal(loc, converter.genType(var), globalName, linkage,
129                               mlir::Attribute{}, isConstant(ultimate));
130 }
131 
132 /// Temporary helper to catch todos in initial data target lowering.
133 static bool
134 hasDerivedTypeWithLengthParameters(const Fortran::semantics::Symbol &sym) {
135   if (const Fortran::semantics::DeclTypeSpec *declTy = sym.GetType())
136     if (const Fortran::semantics::DerivedTypeSpec *derived =
137             declTy->AsDerived())
138       return Fortran::semantics::CountLenParameters(*derived) > 0;
139   return false;
140 }
141 
142 static mlir::Type unwrapElementType(mlir::Type type) {
143   if (mlir::Type ty = fir::dyn_cast_ptrOrBoxEleTy(type))
144     type = ty;
145   if (auto seqType = type.dyn_cast<fir::SequenceType>())
146     type = seqType.getEleTy();
147   return type;
148 }
149 
150 fir::ExtendedValue Fortran::lower::genExtAddrInInitializer(
151     Fortran::lower::AbstractConverter &converter, mlir::Location loc,
152     const Fortran::lower::SomeExpr &addr) {
153   Fortran::lower::SymMap globalOpSymMap;
154   Fortran::lower::AggregateStoreMap storeMap;
155   Fortran::lower::StatementContext stmtCtx;
156   if (const Fortran::semantics::Symbol *sym =
157           Fortran::evaluate::GetFirstSymbol(addr)) {
158     // Length parameters processing will need care in global initializer
159     // context.
160     if (hasDerivedTypeWithLengthParameters(*sym))
161       TODO(loc, "initial-data-target with derived type length parameters");
162 
163     auto var = Fortran::lower::pft::Variable(*sym, /*global=*/true);
164     Fortran::lower::instantiateVariable(converter, var, globalOpSymMap,
165                                         storeMap);
166   }
167   return Fortran::lower::createInitializerAddress(loc, converter, addr,
168                                                   globalOpSymMap, stmtCtx);
169 }
170 
171 /// create initial-data-target fir.box in a global initializer region.
172 mlir::Value Fortran::lower::genInitialDataTarget(
173     Fortran::lower::AbstractConverter &converter, mlir::Location loc,
174     mlir::Type boxType, const Fortran::lower::SomeExpr &initialTarget) {
175   Fortran::lower::SymMap globalOpSymMap;
176   Fortran::lower::AggregateStoreMap storeMap;
177   Fortran::lower::StatementContext stmtCtx;
178   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
179   if (Fortran::evaluate::UnwrapExpr<Fortran::evaluate::NullPointer>(
180           initialTarget))
181     return fir::factory::createUnallocatedBox(builder, loc, boxType,
182                                               /*nonDeferredParams=*/llvm::None);
183   // Pointer initial data target, and NULL(mold).
184   if (const Fortran::semantics::Symbol *sym =
185           Fortran::evaluate::GetFirstSymbol(initialTarget)) {
186     // Length parameters processing will need care in global initializer
187     // context.
188     if (hasDerivedTypeWithLengthParameters(*sym))
189       TODO(loc, "initial-data-target with derived type length parameters");
190 
191     auto var = Fortran::lower::pft::Variable(*sym, /*global=*/true);
192     Fortran::lower::instantiateVariable(converter, var, globalOpSymMap,
193                                         storeMap);
194   }
195   mlir::Value box;
196   if (initialTarget.Rank() > 0) {
197     box = fir::getBase(Fortran::lower::createSomeArrayBox(
198         converter, initialTarget, globalOpSymMap, stmtCtx));
199   } else {
200     fir::ExtendedValue addr = Fortran::lower::createInitializerAddress(
201         loc, converter, initialTarget, globalOpSymMap, stmtCtx);
202     box = builder.createBox(loc, addr);
203   }
204   // box is a fir.box<T>, not a fir.box<fir.ptr<T>> as it should to be used
205   // for pointers. A fir.convert should not be used here, because it would
206   // not actually set the pointer attribute in the descriptor.
207   // In a normal context, fir.rebox would be used to set the pointer attribute
208   // while copying the projection from another fir.box. But fir.rebox cannot be
209   // used in initializer because its current codegen expects that the input
210   // fir.box is in memory, which is not the case in initializers.
211   // So, just replace the fir.embox that created addr with one with
212   // fir.box<fir.ptr<T>> result type.
213   // Note that the descriptor cannot have been created with fir.rebox because
214   // the initial-data-target cannot be a fir.box itself (it cannot be
215   // assumed-shape, deferred-shape, or polymorphic as per C765). However the
216   // case where the initial data target is a derived type with length parameters
217   // will most likely be a bit trickier, hence the TODO above.
218 
219   mlir::Operation *op = box.getDefiningOp();
220   if (!op || !mlir::isa<fir::EmboxOp>(*op))
221     fir::emitFatalError(
222         loc, "fir.box must be created with embox in global initializers");
223   mlir::Type targetEleTy = unwrapElementType(box.getType());
224   if (!fir::isa_char(targetEleTy))
225     return builder.create<fir::EmboxOp>(loc, boxType, op->getOperands(),
226                                         op->getAttrs());
227 
228   // Handle the character case length particularities: embox takes a length
229   // value argument when the result type has unknown length, but not when the
230   // result type has constant length. The type of the initial target must be
231   // constant length, but the one of the pointer may not be. In this case, a
232   // length operand must be added.
233   auto targetLen = targetEleTy.cast<fir::CharacterType>().getLen();
234   auto ptrLen = unwrapElementType(boxType).cast<fir::CharacterType>().getLen();
235   if (ptrLen == targetLen)
236     // Nothing to do
237     return builder.create<fir::EmboxOp>(loc, boxType, op->getOperands(),
238                                         op->getAttrs());
239   auto embox = mlir::cast<fir::EmboxOp>(*op);
240   auto ptrType = boxType.cast<fir::BoxType>().getEleTy();
241   mlir::Value memref = builder.createConvert(loc, ptrType, embox.getMemref());
242   if (targetLen == fir::CharacterType::unknownLen())
243     // Drop the length argument.
244     return builder.create<fir::EmboxOp>(loc, boxType, memref, embox.getShape(),
245                                         embox.getSlice());
246   // targetLen is constant and ptrLen is unknown. Add a length argument.
247   mlir::Value targetLenValue =
248       builder.createIntegerConstant(loc, builder.getIndexType(), targetLen);
249   return builder.create<fir::EmboxOp>(loc, boxType, memref, embox.getShape(),
250                                       embox.getSlice(),
251                                       mlir::ValueRange{targetLenValue});
252 }
253 
254 static mlir::Value genDefaultInitializerValue(
255     Fortran::lower::AbstractConverter &converter, mlir::Location loc,
256     const Fortran::semantics::Symbol &sym, mlir::Type symTy,
257     Fortran::lower::StatementContext &stmtCtx) {
258   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
259   mlir::Type scalarType = symTy;
260   fir::SequenceType sequenceType;
261   if (auto ty = symTy.dyn_cast<fir::SequenceType>()) {
262     sequenceType = ty;
263     scalarType = ty.getEleTy();
264   }
265   // Build a scalar default value of the symbol type, looping through the
266   // components to build each component initial value.
267   auto recTy = scalarType.cast<fir::RecordType>();
268   auto fieldTy = fir::FieldType::get(scalarType.getContext());
269   mlir::Value initialValue = builder.create<fir::UndefOp>(loc, scalarType);
270   const Fortran::semantics::DeclTypeSpec *declTy = sym.GetType();
271   assert(declTy && "var with default initialization must have a type");
272   Fortran::semantics::OrderedComponentIterator components(
273       declTy->derivedTypeSpec());
274   for (const auto &component : components) {
275     // Skip parent components, the sub-components of parent types are part of
276     // components and will be looped through right after.
277     if (component.test(Fortran::semantics::Symbol::Flag::ParentComp))
278       continue;
279     mlir::Value componentValue;
280     llvm::StringRef name = toStringRef(component.name());
281     mlir::Type componentTy = recTy.getType(name);
282     assert(componentTy && "component not found in type");
283     if (const auto *object{
284             component.detailsIf<Fortran::semantics::ObjectEntityDetails>()}) {
285       if (const auto &init = object->init()) {
286         // Component has explicit initialization.
287         if (Fortran::semantics::IsPointer(component))
288           // Initial data target.
289           componentValue =
290               genInitialDataTarget(converter, loc, componentTy, *init);
291         else
292           // Initial value.
293           componentValue = fir::getBase(
294               genInitializerExprValue(converter, loc, *init, stmtCtx));
295       } else if (Fortran::semantics::IsAllocatableOrPointer(component)) {
296         // Pointer or allocatable without initialization.
297         // Create deallocated/disassociated value.
298         // From a standard point of view, pointer without initialization do not
299         // need to be disassociated, but for sanity and simplicity, do it in
300         // global constructor since this has no runtime cost.
301         componentValue = fir::factory::createUnallocatedBox(
302             builder, loc, componentTy, llvm::None);
303       } else if (hasDefaultInitialization(component)) {
304         // Component type has default initialization.
305         componentValue = genDefaultInitializerValue(converter, loc, component,
306                                                     componentTy, stmtCtx);
307       } else {
308         // Component has no initial value.
309         componentValue = builder.create<fir::UndefOp>(loc, componentTy);
310       }
311     } else if (const auto *proc{
312                    component
313                        .detailsIf<Fortran::semantics::ProcEntityDetails>()}) {
314       if (proc->init().has_value())
315         TODO(loc, "procedure pointer component default initialization");
316       else
317         componentValue = builder.create<fir::UndefOp>(loc, componentTy);
318     }
319     assert(componentValue && "must have been computed");
320     componentValue = builder.createConvert(loc, componentTy, componentValue);
321     // FIXME: type parameters must come from the derived-type-spec
322     auto field = builder.create<fir::FieldIndexOp>(
323         loc, fieldTy, name, scalarType,
324         /*typeParams=*/mlir::ValueRange{} /*TODO*/);
325     initialValue = builder.create<fir::InsertValueOp>(
326         loc, recTy, initialValue, componentValue,
327         builder.getArrayAttr(field.getAttributes()));
328   }
329 
330   if (sequenceType) {
331     // For arrays, duplicate the scalar value to all elements with an
332     // fir.insert_range covering the whole array.
333     auto arrayInitialValue = builder.create<fir::UndefOp>(loc, sequenceType);
334     llvm::SmallVector<int64_t> rangeBounds;
335     for (int64_t extent : sequenceType.getShape()) {
336       if (extent == fir::SequenceType::getUnknownExtent())
337         TODO(loc,
338              "default initial value of array component with length parameters");
339       rangeBounds.push_back(0);
340       rangeBounds.push_back(extent - 1);
341     }
342     return builder.create<fir::InsertOnRangeOp>(
343         loc, sequenceType, arrayInitialValue, initialValue,
344         builder.getIndexVectorAttr(rangeBounds));
345   }
346   return initialValue;
347 }
348 
349 /// Does this global already have an initializer ?
350 static bool globalIsInitialized(fir::GlobalOp global) {
351   return !global.getRegion().empty() || global.getInitVal();
352 }
353 
354 /// Call \p genInit to generate code inside \p global initializer region.
355 static void
356 createGlobalInitialization(fir::FirOpBuilder &builder, fir::GlobalOp global,
357                            std::function<void(fir::FirOpBuilder &)> genInit) {
358   mlir::Region &region = global.getRegion();
359   region.push_back(new mlir::Block);
360   mlir::Block &block = region.back();
361   auto insertPt = builder.saveInsertionPoint();
362   builder.setInsertionPointToStart(&block);
363   genInit(builder);
364   builder.restoreInsertionPoint(insertPt);
365 }
366 
367 /// Create the global op and its init if it has one
368 static fir::GlobalOp defineGlobal(Fortran::lower::AbstractConverter &converter,
369                                   const Fortran::lower::pft::Variable &var,
370                                   llvm::StringRef globalName,
371                                   mlir::StringAttr linkage) {
372   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
373   const Fortran::semantics::Symbol &sym = var.getSymbol();
374   mlir::Location loc = converter.genLocation(sym.name());
375   bool isConst = isConstant(sym);
376   fir::GlobalOp global = builder.getNamedGlobal(globalName);
377   mlir::Type symTy = converter.genType(var);
378 
379   if (global && globalIsInitialized(global))
380     return global;
381   // If this is an array, check to see if we can use a dense attribute
382   // with a tensor mlir type.  This optimization currently only supports
383   // rank-1 Fortran arrays of integer, real, or logical. The tensor
384   // type does not support nested structures which are needed for
385   // complex numbers.
386   // To get multidimensional arrays to work, we will have to use column major
387   // array ordering with the tensor type (so it matches column major ordering
388   // with the Fortran fir.array).  By default, tensor types assume row major
389   // ordering. How to create this tensor type is to be determined.
390   if (symTy.isa<fir::SequenceType>() && sym.Rank() == 1 &&
391       !Fortran::semantics::IsAllocatableOrPointer(sym)) {
392     mlir::Type eleTy = symTy.cast<fir::SequenceType>().getEleTy();
393     if (eleTy.isa<mlir::IntegerType, mlir::FloatType, fir::LogicalType>()) {
394       const auto *details =
395           sym.detailsIf<Fortran::semantics::ObjectEntityDetails>();
396       if (details->init()) {
397         global = Fortran::lower::createDenseGlobal(
398             loc, symTy, globalName, linkage, isConst, details->init().value(),
399             converter);
400         if (global) {
401           global.setVisibility(mlir::SymbolTable::Visibility::Public);
402           return global;
403         }
404       }
405     }
406   }
407   if (!global)
408     global = builder.createGlobal(loc, symTy, globalName, linkage,
409                                   mlir::Attribute{}, isConst);
410   if (Fortran::semantics::IsAllocatableOrPointer(sym)) {
411     const auto *details =
412         sym.detailsIf<Fortran::semantics::ObjectEntityDetails>();
413     if (details && details->init()) {
414       auto expr = *details->init();
415       createGlobalInitialization(builder, global, [&](fir::FirOpBuilder &b) {
416         mlir::Value box =
417             Fortran::lower::genInitialDataTarget(converter, loc, symTy, expr);
418         b.create<fir::HasValueOp>(loc, box);
419       });
420     } else {
421       // Create unallocated/disassociated descriptor if no explicit init
422       createGlobalInitialization(builder, global, [&](fir::FirOpBuilder &b) {
423         mlir::Value box =
424             fir::factory::createUnallocatedBox(b, loc, symTy, llvm::None);
425         b.create<fir::HasValueOp>(loc, box);
426       });
427     }
428 
429   } else if (const auto *details =
430                  sym.detailsIf<Fortran::semantics::ObjectEntityDetails>()) {
431     if (details->init()) {
432       createGlobalInitialization(
433           builder, global, [&](fir::FirOpBuilder &builder) {
434             Fortran::lower::StatementContext stmtCtx(
435                 /*cleanupProhibited=*/true);
436             fir::ExtendedValue initVal = genInitializerExprValue(
437                 converter, loc, details->init().value(), stmtCtx);
438             mlir::Value castTo =
439                 builder.createConvert(loc, symTy, fir::getBase(initVal));
440             builder.create<fir::HasValueOp>(loc, castTo);
441           });
442     } else if (hasDefaultInitialization(sym)) {
443       createGlobalInitialization(
444           builder, global, [&](fir::FirOpBuilder &builder) {
445             Fortran::lower::StatementContext stmtCtx(
446                 /*cleanupProhibited=*/true);
447             mlir::Value initVal =
448                 genDefaultInitializerValue(converter, loc, sym, symTy, stmtCtx);
449             mlir::Value castTo = builder.createConvert(loc, symTy, initVal);
450             builder.create<fir::HasValueOp>(loc, castTo);
451           });
452     }
453   } else if (sym.has<Fortran::semantics::CommonBlockDetails>()) {
454     mlir::emitError(loc, "COMMON symbol processed elsewhere");
455   } else {
456     TODO(loc, "global"); // Procedure pointer or something else
457   }
458   // Creates undefined initializer for globals without initializers
459   if (!globalIsInitialized(global))
460     createGlobalInitialization(
461         builder, global, [&](fir::FirOpBuilder &builder) {
462           builder.create<fir::HasValueOp>(
463               loc, builder.create<fir::UndefOp>(loc, symTy));
464         });
465   // Set public visibility to prevent global definition to be optimized out
466   // even if they have no initializer and are unused in this compilation unit.
467   global.setVisibility(mlir::SymbolTable::Visibility::Public);
468   return global;
469 }
470 
471 /// Return linkage attribute for \p var.
472 static mlir::StringAttr
473 getLinkageAttribute(fir::FirOpBuilder &builder,
474                     const Fortran::lower::pft::Variable &var) {
475   // Runtime type info for a same derived type is identical in each compilation
476   // unit. It desired to avoid having to link against module that only define a
477   // type. Therefore the runtime type info is generated everywhere it is needed
478   // with `linkonce_odr` LLVM linkage.
479   if (var.hasSymbol() && isRuntimeTypeInfoData(var.getSymbol()))
480     return builder.createLinkOnceODRLinkage();
481   if (var.isModuleVariable())
482     return {}; // external linkage
483   // Otherwise, the variable is owned by a procedure and must not be visible in
484   // other compilation units.
485   return builder.createInternalLinkage();
486 }
487 
488 /// Instantiate a global variable. If it hasn't already been processed, add
489 /// the global to the ModuleOp as a new uniqued symbol and initialize it with
490 /// the correct value. It will be referenced on demand using `fir.addr_of`.
491 static void instantiateGlobal(Fortran::lower::AbstractConverter &converter,
492                               const Fortran::lower::pft::Variable &var,
493                               Fortran::lower::SymMap &symMap) {
494   const Fortran::semantics::Symbol &sym = var.getSymbol();
495   assert(!var.isAlias() && "must be handled in instantiateAlias");
496   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
497   std::string globalName = Fortran::lower::mangle::mangleName(sym);
498   mlir::Location loc = converter.genLocation(sym.name());
499   fir::GlobalOp global = builder.getNamedGlobal(globalName);
500   mlir::StringAttr linkage = getLinkageAttribute(builder, var);
501   if (var.isModuleVariable()) {
502     // A module global was or will be defined when lowering the module. Emit
503     // only a declaration if the global does not exist at that point.
504     global = declareGlobal(converter, var, globalName, linkage);
505   } else {
506     global = defineGlobal(converter, var, globalName, linkage);
507   }
508   auto addrOf = builder.create<fir::AddrOfOp>(loc, global.resultType(),
509                                               global.getSymbol());
510   Fortran::lower::StatementContext stmtCtx;
511   mapSymbolAttributes(converter, var, symMap, stmtCtx, addrOf);
512 }
513 
514 //===----------------------------------------------------------------===//
515 // Local variables instantiation (not for alias)
516 //===----------------------------------------------------------------===//
517 
518 /// Create a stack slot for a local variable. Precondition: the insertion
519 /// point of the builder must be in the entry block, which is currently being
520 /// constructed.
521 static mlir::Value createNewLocal(Fortran::lower::AbstractConverter &converter,
522                                   mlir::Location loc,
523                                   const Fortran::lower::pft::Variable &var,
524                                   mlir::Value preAlloc,
525                                   llvm::ArrayRef<mlir::Value> shape = {},
526                                   llvm::ArrayRef<mlir::Value> lenParams = {}) {
527   if (preAlloc)
528     return preAlloc;
529   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
530   std::string nm = Fortran::lower::mangle::mangleName(var.getSymbol());
531   mlir::Type ty = converter.genType(var);
532   const Fortran::semantics::Symbol &ultimateSymbol =
533       var.getSymbol().GetUltimate();
534   llvm::StringRef symNm = toStringRef(ultimateSymbol.name());
535   bool isTarg = var.isTarget();
536   // Let the builder do all the heavy lifting.
537   return builder.allocateLocal(loc, ty, nm, symNm, shape, lenParams, isTarg);
538 }
539 
540 /// Must \p var be default initialized at runtime when entering its scope.
541 static bool
542 mustBeDefaultInitializedAtRuntime(const Fortran::lower::pft::Variable &var) {
543   if (!var.hasSymbol())
544     return false;
545   const Fortran::semantics::Symbol &sym = var.getSymbol();
546   if (var.isGlobal())
547     // Global variables are statically initialized.
548     return false;
549   if (Fortran::semantics::IsDummy(sym) && !Fortran::semantics::IsIntentOut(sym))
550     return false;
551   // Local variables (including function results), and intent(out) dummies must
552   // be default initialized at runtime if their type has default initialization.
553   return hasDefaultInitialization(sym);
554 }
555 
556 /// Call default initialization runtime routine to initialize \p var.
557 static void
558 defaultInitializeAtRuntime(Fortran::lower::AbstractConverter &converter,
559                            const Fortran::lower::pft::Variable &var,
560                            Fortran::lower::SymMap &symMap) {
561   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
562   mlir::Location loc = converter.getCurrentLocation();
563   const Fortran::semantics::Symbol &sym = var.getSymbol();
564   fir::ExtendedValue exv = symMap.lookupSymbol(sym).toExtendedValue();
565   if (Fortran::semantics::IsOptional(sym)) {
566     // 15.5.2.12 point 3, absent optional dummies are not initialized.
567     // Creating descriptor/passing null descriptor to the runtime would
568     // create runtime crashes.
569     auto isPresent = builder.create<fir::IsPresentOp>(loc, builder.getI1Type(),
570                                                       fir::getBase(exv));
571     builder.genIfThen(loc, isPresent)
572         .genThen([&]() {
573           auto box = builder.createBox(loc, exv);
574           fir::runtime::genDerivedTypeInitialize(builder, loc, box);
575         })
576         .end();
577   } else {
578     mlir::Value box = builder.createBox(loc, exv);
579     fir::runtime::genDerivedTypeInitialize(builder, loc, box);
580   }
581 }
582 
583 /// Instantiate a local variable. Precondition: Each variable will be visited
584 /// such that if its properties depend on other variables, the variables upon
585 /// which its properties depend will already have been visited.
586 static void instantiateLocal(Fortran::lower::AbstractConverter &converter,
587                              const Fortran::lower::pft::Variable &var,
588                              Fortran::lower::SymMap &symMap) {
589   assert(!var.isAlias());
590   Fortran::lower::StatementContext stmtCtx;
591   mapSymbolAttributes(converter, var, symMap, stmtCtx);
592   if (mustBeDefaultInitializedAtRuntime(var))
593     defaultInitializeAtRuntime(converter, var, symMap);
594 }
595 
596 //===----------------------------------------------------------------===//
597 // Aliased (EQUIVALENCE) variables instantiation
598 //===----------------------------------------------------------------===//
599 
600 /// Insert \p aggregateStore instance into an AggregateStoreMap.
601 static void insertAggregateStore(Fortran::lower::AggregateStoreMap &storeMap,
602                                  const Fortran::lower::pft::Variable &var,
603                                  mlir::Value aggregateStore) {
604   std::size_t off = var.getAggregateStore().getOffset();
605   Fortran::lower::AggregateStoreKey key = {var.getOwningScope(), off};
606   storeMap[key] = aggregateStore;
607 }
608 
609 /// Retrieve the aggregate store instance of \p alias from an
610 /// AggregateStoreMap.
611 static mlir::Value
612 getAggregateStore(Fortran::lower::AggregateStoreMap &storeMap,
613                   const Fortran::lower::pft::Variable &alias) {
614   Fortran::lower::AggregateStoreKey key = {alias.getOwningScope(),
615                                            alias.getAlias()};
616   auto iter = storeMap.find(key);
617   assert(iter != storeMap.end());
618   return iter->second;
619 }
620 
621 /// Build the name for the storage of a global equivalence.
622 static std::string mangleGlobalAggregateStore(
623     const Fortran::lower::pft::Variable::AggregateStore &st) {
624   return Fortran::lower::mangle::mangleName(st.getNamingSymbol());
625 }
626 
627 /// Build the type for the storage of an equivalence.
628 static mlir::Type
629 getAggregateType(Fortran::lower::AbstractConverter &converter,
630                  const Fortran::lower::pft::Variable::AggregateStore &st) {
631   if (const Fortran::semantics::Symbol *initSym = st.getInitialValueSymbol())
632     return converter.genType(*initSym);
633   mlir::IntegerType byteTy = converter.getFirOpBuilder().getIntegerType(8);
634   return fir::SequenceType::get(std::get<1>(st.interval), byteTy);
635 }
636 
637 /// Define a GlobalOp for the storage of a global equivalence described
638 /// by \p aggregate. The global is named \p aggName and is created with
639 /// the provided \p linkage.
640 /// If any of the equivalence members are initialized, an initializer is
641 /// created for the equivalence.
642 /// This is to be used when lowering the scope that owns the equivalence
643 /// (as opposed to simply using it through host or use association).
644 /// This is not to be used for equivalence of common block members (they
645 /// already have the common block GlobalOp for them, see defineCommonBlock).
646 static fir::GlobalOp defineGlobalAggregateStore(
647     Fortran::lower::AbstractConverter &converter,
648     const Fortran::lower::pft::Variable::AggregateStore &aggregate,
649     llvm::StringRef aggName, mlir::StringAttr linkage) {
650   assert(aggregate.isGlobal() && "not a global interval");
651   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
652   fir::GlobalOp global = builder.getNamedGlobal(aggName);
653   if (global && globalIsInitialized(global))
654     return global;
655   mlir::Location loc = converter.getCurrentLocation();
656   mlir::Type aggTy = getAggregateType(converter, aggregate);
657   if (!global)
658     global = builder.createGlobal(loc, aggTy, aggName, linkage);
659 
660   if (const Fortran::semantics::Symbol *initSym =
661           aggregate.getInitialValueSymbol())
662     if (const auto *objectDetails =
663             initSym->detailsIf<Fortran::semantics::ObjectEntityDetails>())
664       if (objectDetails->init()) {
665         createGlobalInitialization(
666             builder, global, [&](fir::FirOpBuilder &builder) {
667               Fortran::lower::StatementContext stmtCtx;
668               mlir::Value initVal = fir::getBase(genInitializerExprValue(
669                   converter, loc, objectDetails->init().value(), stmtCtx));
670               builder.create<fir::HasValueOp>(loc, initVal);
671             });
672         return global;
673       }
674   // Equivalence has no Fortran initial value. Create an undefined FIR initial
675   // value to ensure this is consider an object definition in the IR regardless
676   // of the linkage.
677   createGlobalInitialization(builder, global, [&](fir::FirOpBuilder &builder) {
678     Fortran::lower::StatementContext stmtCtx;
679     mlir::Value initVal = builder.create<fir::UndefOp>(loc, aggTy);
680     builder.create<fir::HasValueOp>(loc, initVal);
681   });
682   return global;
683 }
684 
685 /// Declare a GlobalOp for the storage of a global equivalence described
686 /// by \p aggregate. The global is named \p aggName and is created with
687 /// the provided \p linkage.
688 /// No initializer is built for the created GlobalOp.
689 /// This is to be used when lowering the scope that uses members of an
690 /// equivalence it through host or use association.
691 /// This is not to be used for equivalence of common block members (they
692 /// already have the common block GlobalOp for them, see defineCommonBlock).
693 static fir::GlobalOp declareGlobalAggregateStore(
694     Fortran::lower::AbstractConverter &converter, mlir::Location loc,
695     const Fortran::lower::pft::Variable::AggregateStore &aggregate,
696     llvm::StringRef aggName, mlir::StringAttr linkage) {
697   assert(aggregate.isGlobal() && "not a global interval");
698   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
699   if (fir::GlobalOp global = builder.getNamedGlobal(aggName))
700     return global;
701   mlir::Type aggTy = getAggregateType(converter, aggregate);
702   return builder.createGlobal(loc, aggTy, aggName, linkage);
703 }
704 
705 /// This is an aggregate store for a set of EQUIVALENCED variables. Create the
706 /// storage on the stack or global memory and add it to the map.
707 static void
708 instantiateAggregateStore(Fortran::lower::AbstractConverter &converter,
709                           const Fortran::lower::pft::Variable &var,
710                           Fortran::lower::AggregateStoreMap &storeMap) {
711   assert(var.isAggregateStore() && "not an interval");
712   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
713   mlir::IntegerType i8Ty = builder.getIntegerType(8);
714   mlir::Location loc = converter.getCurrentLocation();
715   std::string aggName = mangleGlobalAggregateStore(var.getAggregateStore());
716   if (var.isGlobal()) {
717     fir::GlobalOp global;
718     auto &aggregate = var.getAggregateStore();
719     mlir::StringAttr linkage = getLinkageAttribute(builder, var);
720     if (var.isModuleVariable()) {
721       // A module global was or will be defined when lowering the module. Emit
722       // only a declaration if the global does not exist at that point.
723       global = declareGlobalAggregateStore(converter, loc, aggregate, aggName,
724                                            linkage);
725     } else {
726       global =
727           defineGlobalAggregateStore(converter, aggregate, aggName, linkage);
728     }
729     auto addr = builder.create<fir::AddrOfOp>(loc, global.resultType(),
730                                               global.getSymbol());
731     auto size = std::get<1>(var.getInterval());
732     fir::SequenceType::Shape shape(1, size);
733     auto seqTy = fir::SequenceType::get(shape, i8Ty);
734     mlir::Type refTy = builder.getRefType(seqTy);
735     mlir::Value aggregateStore = builder.createConvert(loc, refTy, addr);
736     insertAggregateStore(storeMap, var, aggregateStore);
737     return;
738   }
739   // This is a local aggregate, allocate an anonymous block of memory.
740   auto size = std::get<1>(var.getInterval());
741   fir::SequenceType::Shape shape(1, size);
742   auto seqTy = fir::SequenceType::get(shape, i8Ty);
743   mlir::Value local =
744       builder.allocateLocal(loc, seqTy, aggName, "", llvm::None, llvm::None,
745                             /*target=*/false);
746   insertAggregateStore(storeMap, var, local);
747 }
748 
749 /// Cast an alias address (variable part of an equivalence) to fir.ptr so that
750 /// the optimizer is conservative and avoids doing copy elision in assignment
751 /// involving equivalenced variables.
752 /// TODO: Represent the equivalence aliasing constraint in another way to avoid
753 /// pessimizing array assignments involving equivalenced variables.
754 static mlir::Value castAliasToPointer(fir::FirOpBuilder &builder,
755                                       mlir::Location loc, mlir::Type aliasType,
756                                       mlir::Value aliasAddr) {
757   return builder.createConvert(loc, fir::PointerType::get(aliasType),
758                                aliasAddr);
759 }
760 
761 /// Instantiate a member of an equivalence. Compute its address in its
762 /// aggregate storage and lower its attributes.
763 static void instantiateAlias(Fortran::lower::AbstractConverter &converter,
764                              const Fortran::lower::pft::Variable &var,
765                              Fortran::lower::SymMap &symMap,
766                              Fortran::lower::AggregateStoreMap &storeMap) {
767   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
768   assert(var.isAlias());
769   const Fortran::semantics::Symbol &sym = var.getSymbol();
770   const mlir::Location loc = converter.genLocation(sym.name());
771   mlir::IndexType idxTy = builder.getIndexType();
772   std::size_t aliasOffset = var.getAlias();
773   mlir::Value store = getAggregateStore(storeMap, var);
774   mlir::IntegerType i8Ty = builder.getIntegerType(8);
775   mlir::Type i8Ptr = builder.getRefType(i8Ty);
776   mlir::Value offset = builder.createIntegerConstant(
777       loc, idxTy, sym.GetUltimate().offset() - aliasOffset);
778   auto ptr = builder.create<fir::CoordinateOp>(loc, i8Ptr, store,
779                                                mlir::ValueRange{offset});
780   mlir::Value preAlloc =
781       castAliasToPointer(builder, loc, converter.genType(sym), ptr);
782   Fortran::lower::StatementContext stmtCtx;
783   mapSymbolAttributes(converter, var, symMap, stmtCtx, preAlloc);
784   // Default initialization is possible for equivalence members: see
785   // F2018 19.5.3.4. Note that if several equivalenced entities have
786   // default initialization, they must have the same type, and the standard
787   // allows the storage to be default initialized several times (this has
788   // no consequences other than wasting some execution time). For now,
789   // do not try optimizing this to single default initializations of
790   // the equivalenced storages. Keep lowering simple.
791   if (mustBeDefaultInitializedAtRuntime(var))
792     defaultInitializeAtRuntime(converter, var, symMap);
793 }
794 
795 //===--------------------------------------------------------------===//
796 // COMMON blocks instantiation
797 //===--------------------------------------------------------------===//
798 
799 /// Does any member of the common block has an initializer ?
800 static bool
801 commonBlockHasInit(const Fortran::semantics::MutableSymbolVector &cmnBlkMems) {
802   for (const Fortran::semantics::MutableSymbolRef &mem : cmnBlkMems) {
803     if (const auto *memDet =
804             mem->detailsIf<Fortran::semantics::ObjectEntityDetails>())
805       if (memDet->init())
806         return true;
807   }
808   return false;
809 }
810 
811 /// Build a tuple type for a common block based on the common block
812 /// members and the common block size.
813 /// This type is only needed to build common block initializers where
814 /// the initial value is the collection of the member initial values.
815 static mlir::TupleType getTypeOfCommonWithInit(
816     Fortran::lower::AbstractConverter &converter,
817     const Fortran::semantics::MutableSymbolVector &cmnBlkMems,
818     std::size_t commonSize) {
819   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
820   llvm::SmallVector<mlir::Type> members;
821   std::size_t counter = 0;
822   for (const Fortran::semantics::MutableSymbolRef &mem : cmnBlkMems) {
823     if (const auto *memDet =
824             mem->detailsIf<Fortran::semantics::ObjectEntityDetails>()) {
825       if (mem->offset() > counter) {
826         fir::SequenceType::Shape len = {
827             static_cast<fir::SequenceType::Extent>(mem->offset() - counter)};
828         mlir::IntegerType byteTy = builder.getIntegerType(8);
829         auto memTy = fir::SequenceType::get(len, byteTy);
830         members.push_back(memTy);
831         counter = mem->offset();
832       }
833       if (memDet->init()) {
834         mlir::Type memTy = converter.genType(*mem);
835         members.push_back(memTy);
836         counter = mem->offset() + mem->size();
837       }
838     }
839   }
840   if (counter < commonSize) {
841     fir::SequenceType::Shape len = {
842         static_cast<fir::SequenceType::Extent>(commonSize - counter)};
843     mlir::IntegerType byteTy = builder.getIntegerType(8);
844     auto memTy = fir::SequenceType::get(len, byteTy);
845     members.push_back(memTy);
846   }
847   return mlir::TupleType::get(builder.getContext(), members);
848 }
849 
850 /// Common block members may have aliases. They are not in the common block
851 /// member list from the symbol. We need to know about these aliases if they
852 /// have initializer to generate the common initializer.
853 /// This function takes care of adding aliases with initializer to the member
854 /// list.
855 static Fortran::semantics::MutableSymbolVector
856 getCommonMembersWithInitAliases(const Fortran::semantics::Symbol &common) {
857   const auto &commonDetails =
858       common.get<Fortran::semantics::CommonBlockDetails>();
859   auto members = commonDetails.objects();
860 
861   // The number and size of equivalence and common is expected to be small, so
862   // no effort is given to optimize this loop of complexity equivalenced
863   // common members * common members
864   for (const Fortran::semantics::EquivalenceSet &set :
865        common.owner().equivalenceSets())
866     for (const Fortran::semantics::EquivalenceObject &obj : set) {
867       if (!obj.symbol.test(Fortran::semantics::Symbol::Flag::CompilerCreated)) {
868         if (const auto &details =
869                 obj.symbol
870                     .detailsIf<Fortran::semantics::ObjectEntityDetails>()) {
871           const Fortran::semantics::Symbol *com =
872               FindCommonBlockContaining(obj.symbol);
873           if (!details->init() || com != &common)
874             continue;
875           // This is an alias with an init that belongs to the list
876           if (std::find(members.begin(), members.end(), obj.symbol) ==
877               members.end())
878             members.emplace_back(obj.symbol);
879         }
880       }
881     }
882   return members;
883 }
884 
885 /// Define a global for a common block if it does not already exist in the
886 /// mlir module.
887 /// There is no "declare" version since there is not a
888 /// scope that owns common blocks more that the others. All scopes using
889 /// a common block attempts to define it with common linkage.
890 static fir::GlobalOp
891 defineCommonBlock(Fortran::lower::AbstractConverter &converter,
892                   const Fortran::semantics::Symbol &common) {
893   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
894   std::string commonName = Fortran::lower::mangle::mangleName(common);
895   fir::GlobalOp global = builder.getNamedGlobal(commonName);
896   if (global)
897     return global;
898   Fortran::semantics::MutableSymbolVector cmnBlkMems =
899       getCommonMembersWithInitAliases(common);
900   mlir::Location loc = converter.genLocation(common.name());
901   mlir::IndexType idxTy = builder.getIndexType();
902   mlir::StringAttr linkage = builder.createCommonLinkage();
903   if (!common.name().size() || !commonBlockHasInit(cmnBlkMems)) {
904     // A blank (anonymous) COMMON block must always be initialized to zero.
905     // A named COMMON block sans initializers is also initialized to zero.
906     // mlir::Vector types must have a strictly positive size, so at least
907     // temporarily, force a zero size COMMON block to have one byte.
908     const auto sz = static_cast<fir::SequenceType::Extent>(
909         common.size() > 0 ? common.size() : 1);
910     fir::SequenceType::Shape shape = {sz};
911     mlir::IntegerType i8Ty = builder.getIntegerType(8);
912     auto commonTy = fir::SequenceType::get(shape, i8Ty);
913     auto vecTy = mlir::VectorType::get(sz, i8Ty);
914     mlir::Attribute zero = builder.getIntegerAttr(i8Ty, 0);
915     auto init = mlir::DenseElementsAttr::get(vecTy, llvm::makeArrayRef(zero));
916     return builder.createGlobal(loc, commonTy, commonName, linkage, init);
917   }
918 
919   // Named common with initializer, sort members by offset before generating
920   // the type and initializer.
921   std::sort(cmnBlkMems.begin(), cmnBlkMems.end(),
922             [](auto &s1, auto &s2) { return s1->offset() < s2->offset(); });
923   mlir::TupleType commonTy =
924       getTypeOfCommonWithInit(converter, cmnBlkMems, common.size());
925   auto initFunc = [&](fir::FirOpBuilder &builder) {
926     mlir::Value cb = builder.create<fir::UndefOp>(loc, commonTy);
927     unsigned tupIdx = 0;
928     std::size_t offset = 0;
929     LLVM_DEBUG(llvm::dbgs() << "block {\n");
930     for (const Fortran::semantics::MutableSymbolRef &mem : cmnBlkMems) {
931       if (const auto *memDet =
932               mem->detailsIf<Fortran::semantics::ObjectEntityDetails>()) {
933         if (mem->offset() > offset) {
934           ++tupIdx;
935           offset = mem->offset();
936         }
937         if (memDet->init()) {
938           LLVM_DEBUG(llvm::dbgs()
939                      << "offset: " << mem->offset() << " is " << *mem << '\n');
940           Fortran::lower::StatementContext stmtCtx;
941           auto initExpr = memDet->init().value();
942           fir::ExtendedValue initVal =
943               Fortran::semantics::IsPointer(*mem)
944                   ? Fortran::lower::genInitialDataTarget(
945                         converter, loc, converter.genType(*mem), initExpr)
946                   : genInitializerExprValue(converter, loc, initExpr, stmtCtx);
947           mlir::IntegerAttr offVal = builder.getIntegerAttr(idxTy, tupIdx);
948           mlir::Value castVal = builder.createConvert(
949               loc, commonTy.getType(tupIdx), fir::getBase(initVal));
950           cb = builder.create<fir::InsertValueOp>(loc, commonTy, cb, castVal,
951                                                   builder.getArrayAttr(offVal));
952           ++tupIdx;
953           offset = mem->offset() + mem->size();
954         }
955       }
956     }
957     LLVM_DEBUG(llvm::dbgs() << "}\n");
958     builder.create<fir::HasValueOp>(loc, cb);
959   };
960   // create the global object
961   return builder.createGlobal(loc, commonTy, commonName,
962                               /*isConstant=*/false, initFunc);
963 }
964 /// The COMMON block is a global structure. `var` will be at some offset
965 /// within the COMMON block. Adds the address of `var` (COMMON + offset) to
966 /// the symbol map.
967 static void instantiateCommon(Fortran::lower::AbstractConverter &converter,
968                               const Fortran::semantics::Symbol &common,
969                               const Fortran::lower::pft::Variable &var,
970                               Fortran::lower::SymMap &symMap) {
971   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
972   const Fortran::semantics::Symbol &varSym = var.getSymbol();
973   mlir::Location loc = converter.genLocation(varSym.name());
974 
975   mlir::Value commonAddr;
976   if (Fortran::lower::SymbolBox symBox = symMap.lookupSymbol(common))
977     commonAddr = symBox.getAddr();
978   if (!commonAddr) {
979     // introduce a local AddrOf and add it to the map
980     fir::GlobalOp global = defineCommonBlock(converter, common);
981     commonAddr = builder.create<fir::AddrOfOp>(loc, global.resultType(),
982                                                global.getSymbol());
983 
984     symMap.addSymbol(common, commonAddr);
985   }
986   std::size_t byteOffset = varSym.GetUltimate().offset();
987   mlir::IntegerType i8Ty = builder.getIntegerType(8);
988   mlir::Type i8Ptr = builder.getRefType(i8Ty);
989   mlir::Type seqTy = builder.getRefType(builder.getVarLenSeqTy(i8Ty));
990   mlir::Value base = builder.createConvert(loc, seqTy, commonAddr);
991   mlir::Value offs =
992       builder.createIntegerConstant(loc, builder.getIndexType(), byteOffset);
993   auto varAddr = builder.create<fir::CoordinateOp>(loc, i8Ptr, base,
994                                                    mlir::ValueRange{offs});
995   mlir::Type symType = converter.genType(var.getSymbol());
996   mlir::Value local;
997   if (Fortran::semantics::FindEquivalenceSet(var.getSymbol()) != nullptr)
998     local = castAliasToPointer(builder, loc, symType, varAddr);
999   else
1000     local = builder.createConvert(loc, builder.getRefType(symType), varAddr);
1001   Fortran::lower::StatementContext stmtCtx;
1002   mapSymbolAttributes(converter, var, symMap, stmtCtx, local);
1003 }
1004 
1005 //===--------------------------------------------------------------===//
1006 // Lower Variables specification expressions and attributes
1007 //===--------------------------------------------------------------===//
1008 
1009 /// Helper to decide if a dummy argument must be tracked in an BoxValue.
1010 static bool lowerToBoxValue(const Fortran::semantics::Symbol &sym,
1011                             mlir::Value dummyArg) {
1012   // Only dummy arguments coming as fir.box can be tracked in an BoxValue.
1013   if (!dummyArg || !dummyArg.getType().isa<fir::BoxType>())
1014     return false;
1015   // Non contiguous arrays must be tracked in an BoxValue.
1016   if (sym.Rank() > 0 && !sym.attrs().test(Fortran::semantics::Attr::CONTIGUOUS))
1017     return true;
1018   // Assumed rank and optional fir.box cannot yet be read while lowering the
1019   // specifications.
1020   if (Fortran::evaluate::IsAssumedRank(sym) ||
1021       Fortran::semantics::IsOptional(sym))
1022     return true;
1023   // Polymorphic entity should be tracked through a fir.box that has the
1024   // dynamic type info.
1025   if (const Fortran::semantics::DeclTypeSpec *type = sym.GetType())
1026     if (type->IsPolymorphic())
1027       return true;
1028   return false;
1029 }
1030 
1031 /// Compute extent from lower and upper bound.
1032 static mlir::Value computeExtent(fir::FirOpBuilder &builder, mlir::Location loc,
1033                                  mlir::Value lb, mlir::Value ub) {
1034   mlir::IndexType idxTy = builder.getIndexType();
1035   // Let the folder deal with the common `ub - <const> + 1` case.
1036   auto diff = builder.create<mlir::arith::SubIOp>(loc, idxTy, ub, lb);
1037   mlir::Value one = builder.createIntegerConstant(loc, idxTy, 1);
1038   auto rawExtent = builder.create<mlir::arith::AddIOp>(loc, idxTy, diff, one);
1039   return Fortran::lower::genMaxWithZero(builder, loc, rawExtent);
1040 }
1041 
1042 /// Lower explicit lower bounds into \p result. Does nothing if this is not an
1043 /// array, or if the lower bounds are deferred, or all implicit or one.
1044 static void lowerExplicitLowerBounds(
1045     Fortran::lower::AbstractConverter &converter, mlir::Location loc,
1046     const Fortran::lower::BoxAnalyzer &box,
1047     llvm::SmallVectorImpl<mlir::Value> &result, Fortran::lower::SymMap &symMap,
1048     Fortran::lower::StatementContext &stmtCtx) {
1049   if (!box.isArray() || box.lboundIsAllOnes())
1050     return;
1051   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
1052   mlir::IndexType idxTy = builder.getIndexType();
1053   if (box.isStaticArray()) {
1054     for (int64_t lb : box.staticLBound())
1055       result.emplace_back(builder.createIntegerConstant(loc, idxTy, lb));
1056     return;
1057   }
1058   for (const Fortran::semantics::ShapeSpec *spec : box.dynamicBound()) {
1059     if (auto low = spec->lbound().GetExplicit()) {
1060       auto expr = Fortran::lower::SomeExpr{*low};
1061       mlir::Value lb = builder.createConvert(
1062           loc, idxTy, genScalarValue(converter, loc, expr, symMap, stmtCtx));
1063       result.emplace_back(lb);
1064     }
1065   }
1066   assert(result.empty() || result.size() == box.dynamicBound().size());
1067 }
1068 
1069 /// Lower explicit extents into \p result if this is an explicit-shape or
1070 /// assumed-size array. Does nothing if this is not an explicit-shape or
1071 /// assumed-size array.
1072 static void
1073 lowerExplicitExtents(Fortran::lower::AbstractConverter &converter,
1074                      mlir::Location loc, const Fortran::lower::BoxAnalyzer &box,
1075                      llvm::SmallVectorImpl<mlir::Value> &lowerBounds,
1076                      llvm::SmallVectorImpl<mlir::Value> &result,
1077                      Fortran::lower::SymMap &symMap,
1078                      Fortran::lower::StatementContext &stmtCtx) {
1079   if (!box.isArray())
1080     return;
1081   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
1082   mlir::IndexType idxTy = builder.getIndexType();
1083   if (box.isStaticArray()) {
1084     for (int64_t extent : box.staticShape())
1085       result.emplace_back(builder.createIntegerConstant(loc, idxTy, extent));
1086     return;
1087   }
1088   for (const auto &spec : llvm::enumerate(box.dynamicBound())) {
1089     if (auto up = spec.value()->ubound().GetExplicit()) {
1090       auto expr = Fortran::lower::SomeExpr{*up};
1091       mlir::Value ub = builder.createConvert(
1092           loc, idxTy, genScalarValue(converter, loc, expr, symMap, stmtCtx));
1093       if (lowerBounds.empty())
1094         result.emplace_back(Fortran::lower::genMaxWithZero(builder, loc, ub));
1095       else
1096         result.emplace_back(
1097             computeExtent(builder, loc, lowerBounds[spec.index()], ub));
1098     } else if (spec.value()->ubound().isStar()) {
1099       // Assumed extent is undefined. Must be provided by user's code.
1100       result.emplace_back(builder.create<fir::UndefOp>(loc, idxTy));
1101     }
1102   }
1103   assert(result.empty() || result.size() == box.dynamicBound().size());
1104 }
1105 
1106 /// Lower explicit character length if any. Return empty mlir::Value if no
1107 /// explicit length.
1108 static mlir::Value
1109 lowerExplicitCharLen(Fortran::lower::AbstractConverter &converter,
1110                      mlir::Location loc, const Fortran::lower::BoxAnalyzer &box,
1111                      Fortran::lower::SymMap &symMap,
1112                      Fortran::lower::StatementContext &stmtCtx) {
1113   if (!box.isChar())
1114     return mlir::Value{};
1115   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
1116   mlir::Type lenTy = builder.getCharacterLengthType();
1117   if (llvm::Optional<int64_t> len = box.getCharLenConst())
1118     return builder.createIntegerConstant(loc, lenTy, *len);
1119   if (llvm::Optional<Fortran::lower::SomeExpr> lenExpr = box.getCharLenExpr())
1120     // If the length expression is negative, the length is zero. See F2018
1121     // 7.4.4.2 point 5.
1122     return Fortran::lower::genMaxWithZero(
1123         builder, loc,
1124         genScalarValue(converter, loc, *lenExpr, symMap, stmtCtx));
1125   return mlir::Value{};
1126 }
1127 
1128 /// Treat negative values as undefined. Assumed size arrays will return -1 from
1129 /// the front end for example. Using negative values can produce hard to find
1130 /// bugs much further along in the compilation.
1131 static mlir::Value genExtentValue(fir::FirOpBuilder &builder,
1132                                   mlir::Location loc, mlir::Type idxTy,
1133                                   long frontEndExtent) {
1134   if (frontEndExtent >= 0)
1135     return builder.createIntegerConstant(loc, idxTy, frontEndExtent);
1136   return builder.create<fir::UndefOp>(loc, idxTy);
1137 }
1138 
1139 /// Lower specification expressions and attributes of variable \p var and
1140 /// add it to the symbol map.
1141 /// For global and aliases, the address must be pre-computed and provided
1142 /// in \p preAlloc.
1143 /// Dummy arguments must have already been mapped to mlir block arguments
1144 /// their mapping may be updated here.
1145 void Fortran::lower::mapSymbolAttributes(
1146     AbstractConverter &converter, const Fortran::lower::pft::Variable &var,
1147     Fortran::lower::SymMap &symMap, Fortran::lower::StatementContext &stmtCtx,
1148     mlir::Value preAlloc) {
1149   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
1150   const Fortran::semantics::Symbol &sym = var.getSymbol();
1151   const mlir::Location loc = converter.genLocation(sym.name());
1152   mlir::IndexType idxTy = builder.getIndexType();
1153   const bool isDummy = Fortran::semantics::IsDummy(sym);
1154   const bool isResult = Fortran::semantics::IsFunctionResult(sym);
1155   const bool replace = isDummy || isResult;
1156   fir::factory::CharacterExprHelper charHelp{builder, loc};
1157   Fortran::lower::BoxAnalyzer ba;
1158   ba.analyze(sym);
1159 
1160   // First deal with pointers an allocatables, because their handling here
1161   // is the same regardless of their rank.
1162   if (Fortran::semantics::IsAllocatableOrPointer(sym)) {
1163     // Get address of fir.box describing the entity.
1164     // global
1165     mlir::Value boxAlloc = preAlloc;
1166     // dummy or passed result
1167     if (!boxAlloc)
1168       if (Fortran::lower::SymbolBox symbox = symMap.lookupSymbol(sym))
1169         boxAlloc = symbox.getAddr();
1170     // local
1171     if (!boxAlloc)
1172       boxAlloc = createNewLocal(converter, loc, var, preAlloc);
1173     // Lower non deferred parameters.
1174     llvm::SmallVector<mlir::Value> nonDeferredLenParams;
1175     if (ba.isChar()) {
1176       if (mlir::Value len =
1177               lowerExplicitCharLen(converter, loc, ba, symMap, stmtCtx))
1178         nonDeferredLenParams.push_back(len);
1179       else if (Fortran::semantics::IsAssumedLengthCharacter(sym))
1180         TODO(loc, "assumed length character allocatable");
1181     } else if (const Fortran::semantics::DeclTypeSpec *declTy = sym.GetType()) {
1182       if (const Fortran::semantics::DerivedTypeSpec *derived =
1183               declTy->AsDerived())
1184         if (Fortran::semantics::CountLenParameters(*derived) != 0)
1185           TODO(loc,
1186                "derived type allocatable or pointer with length parameters");
1187     }
1188     fir::MutableBoxValue box = Fortran::lower::createMutableBox(
1189         converter, loc, var, boxAlloc, nonDeferredLenParams);
1190     symMap.addAllocatableOrPointer(var.getSymbol(), box, replace);
1191     return;
1192   }
1193 
1194   if (isDummy) {
1195     mlir::Value dummyArg = symMap.lookupSymbol(sym).getAddr();
1196     if (lowerToBoxValue(sym, dummyArg)) {
1197       llvm::SmallVector<mlir::Value> lbounds;
1198       llvm::SmallVector<mlir::Value> explicitExtents;
1199       llvm::SmallVector<mlir::Value> explicitParams;
1200       // Lower lower bounds, explicit type parameters and explicit
1201       // extents if any.
1202       if (ba.isChar())
1203         if (mlir::Value len =
1204                 lowerExplicitCharLen(converter, loc, ba, symMap, stmtCtx))
1205           explicitParams.push_back(len);
1206       // TODO: derived type length parameters.
1207       lowerExplicitLowerBounds(converter, loc, ba, lbounds, symMap, stmtCtx);
1208       lowerExplicitExtents(converter, loc, ba, lbounds, explicitExtents, symMap,
1209                            stmtCtx);
1210       symMap.addBoxSymbol(sym, dummyArg, lbounds, explicitParams,
1211                           explicitExtents, replace);
1212       return;
1213     }
1214   }
1215 
1216   // Helper to generate scalars for the symbol properties.
1217   auto genValue = [&](const Fortran::lower::SomeExpr &expr) {
1218     return genScalarValue(converter, loc, expr, symMap, stmtCtx);
1219   };
1220 
1221   // For symbols reaching this point, all properties are constant and can be
1222   // read/computed already into ssa values.
1223 
1224   // The origin must be \vec{1}.
1225   auto populateShape = [&](auto &shapes, const auto &bounds, mlir::Value box) {
1226     for (auto iter : llvm::enumerate(bounds)) {
1227       auto *spec = iter.value();
1228       assert(spec->lbound().GetExplicit() &&
1229              "lbound must be explicit with constant value 1");
1230       if (auto high = spec->ubound().GetExplicit()) {
1231         Fortran::lower::SomeExpr highEx{*high};
1232         mlir::Value ub = genValue(highEx);
1233         ub = builder.createConvert(loc, idxTy, ub);
1234         shapes.emplace_back(genMaxWithZero(builder, loc, ub));
1235       } else if (spec->ubound().isColon()) {
1236         assert(box && "assumed bounds require a descriptor");
1237         mlir::Value dim =
1238             builder.createIntegerConstant(loc, idxTy, iter.index());
1239         auto dimInfo =
1240             builder.create<fir::BoxDimsOp>(loc, idxTy, idxTy, idxTy, box, dim);
1241         shapes.emplace_back(dimInfo.getResult(1));
1242       } else if (spec->ubound().isStar()) {
1243         shapes.emplace_back(builder.create<fir::UndefOp>(loc, idxTy));
1244       } else {
1245         llvm::report_fatal_error("unknown bound category");
1246       }
1247     }
1248   };
1249 
1250   // The origin is not \vec{1}.
1251   auto populateLBoundsExtents = [&](auto &lbounds, auto &extents,
1252                                     const auto &bounds, mlir::Value box) {
1253     for (auto iter : llvm::enumerate(bounds)) {
1254       auto *spec = iter.value();
1255       fir::BoxDimsOp dimInfo;
1256       mlir::Value ub, lb;
1257       if (spec->lbound().isColon() || spec->ubound().isColon()) {
1258         // This is an assumed shape because allocatables and pointers extents
1259         // are not constant in the scope and are not read here.
1260         assert(box && "deferred bounds require a descriptor");
1261         mlir::Value dim =
1262             builder.createIntegerConstant(loc, idxTy, iter.index());
1263         dimInfo =
1264             builder.create<fir::BoxDimsOp>(loc, idxTy, idxTy, idxTy, box, dim);
1265         extents.emplace_back(dimInfo.getResult(1));
1266         if (auto low = spec->lbound().GetExplicit()) {
1267           auto expr = Fortran::lower::SomeExpr{*low};
1268           mlir::Value lb = builder.createConvert(loc, idxTy, genValue(expr));
1269           lbounds.emplace_back(lb);
1270         } else {
1271           // Implicit lower bound is 1 (Fortran 2018 section 8.5.8.3 point 3.)
1272           lbounds.emplace_back(builder.createIntegerConstant(loc, idxTy, 1));
1273         }
1274       } else {
1275         if (auto low = spec->lbound().GetExplicit()) {
1276           auto expr = Fortran::lower::SomeExpr{*low};
1277           lb = builder.createConvert(loc, idxTy, genValue(expr));
1278         } else {
1279           TODO(loc, "assumed rank lowering");
1280         }
1281         lbounds.emplace_back(lb);
1282 
1283         if (auto high = spec->ubound().GetExplicit()) {
1284           auto expr = Fortran::lower::SomeExpr{*high};
1285           ub = builder.createConvert(loc, idxTy, genValue(expr));
1286           extents.emplace_back(computeExtent(builder, loc, lb, ub));
1287         } else {
1288           // An assumed size array. The extent is not computed.
1289           assert(spec->ubound().isStar() && "expected assumed size");
1290           extents.emplace_back(builder.create<fir::UndefOp>(loc, idxTy));
1291         }
1292       }
1293     }
1294   };
1295 
1296   // Lower length expression for non deferred and non dummy assumed length
1297   // characters.
1298   auto genExplicitCharLen =
1299       [&](llvm::Optional<Fortran::lower::SomeExpr> charLen) -> mlir::Value {
1300     if (!charLen)
1301       fir::emitFatalError(loc, "expected explicit character length");
1302     mlir::Value rawLen = genValue(*charLen);
1303     // If the length expression is negative, the length is zero. See
1304     // F2018 7.4.4.2 point 5.
1305     return genMaxWithZero(builder, loc, rawLen);
1306   };
1307 
1308   ba.match(
1309       //===--------------------------------------------------------------===//
1310       // Trivial case.
1311       //===--------------------------------------------------------------===//
1312       [&](const Fortran::lower::details::ScalarSym &) {
1313         if (isDummy) {
1314           // This is an argument.
1315           if (!symMap.lookupSymbol(sym))
1316             mlir::emitError(loc, "symbol \"")
1317                 << toStringRef(sym.name()) << "\" must already be in map";
1318           return;
1319         } else if (isResult) {
1320           // Some Fortran results may be passed by argument (e.g. derived
1321           // types)
1322           if (symMap.lookupSymbol(sym))
1323             return;
1324         }
1325         // Otherwise, it's a local variable or function result.
1326         mlir::Value local = createNewLocal(converter, loc, var, preAlloc);
1327         symMap.addSymbol(sym, local);
1328       },
1329 
1330       //===--------------------------------------------------------------===//
1331       // The non-trivial cases are when we have an argument or local that has
1332       // a repetition value. Arguments might be passed as simple pointers and
1333       // need to be cast to a multi-dimensional array with constant bounds
1334       // (possibly with a missing column), bounds computed in the callee
1335       // (here), or with bounds from the caller (boxed somewhere else). Locals
1336       // have the same properties except they are never boxed arguments from
1337       // the caller and never having a missing column size.
1338       //===--------------------------------------------------------------===//
1339 
1340       [&](const Fortran::lower::details::ScalarStaticChar &x) {
1341         // type is a CHARACTER, determine the LEN value
1342         auto charLen = x.charLen();
1343         if (replace) {
1344           Fortran::lower::SymbolBox symBox = symMap.lookupSymbol(sym);
1345           std::pair<mlir::Value, mlir::Value> unboxchar =
1346               charHelp.createUnboxChar(symBox.getAddr());
1347           mlir::Value boxAddr = unboxchar.first;
1348           // Set/override LEN with a constant
1349           mlir::Value len = builder.createIntegerConstant(loc, idxTy, charLen);
1350           symMap.addCharSymbol(sym, boxAddr, len, true);
1351           return;
1352         }
1353         mlir::Value len = builder.createIntegerConstant(loc, idxTy, charLen);
1354         if (preAlloc) {
1355           symMap.addCharSymbol(sym, preAlloc, len);
1356           return;
1357         }
1358         mlir::Value local = createNewLocal(converter, loc, var, preAlloc);
1359         symMap.addCharSymbol(sym, local, len);
1360       },
1361 
1362       //===--------------------------------------------------------------===//
1363 
1364       [&](const Fortran::lower::details::ScalarDynamicChar &x) {
1365         // type is a CHARACTER, determine the LEN value
1366         auto charLen = x.charLen();
1367         if (replace) {
1368           Fortran::lower::SymbolBox symBox = symMap.lookupSymbol(sym);
1369           mlir::Value boxAddr = symBox.getAddr();
1370           mlir::Value len;
1371           mlir::Type addrTy = boxAddr.getType();
1372           if (addrTy.isa<fir::BoxCharType>() || addrTy.isa<fir::BoxType>()) {
1373             std::tie(boxAddr, len) = charHelp.createUnboxChar(symBox.getAddr());
1374           } else {
1375             // dummy from an other entry case: we cannot get a dynamic length
1376             // for it, it's illegal for the user program to use it. However,
1377             // since we are lowering all function unit statements regardless
1378             // of whether the execution will reach them or not, we need to
1379             // fill a value for the length here.
1380             len = builder.createIntegerConstant(
1381                 loc, builder.getCharacterLengthType(), 1);
1382           }
1383           // Override LEN with an expression
1384           if (charLen)
1385             len = genExplicitCharLen(charLen);
1386           symMap.addCharSymbol(sym, boxAddr, len, true);
1387           return;
1388         }
1389         // local CHARACTER variable
1390         mlir::Value len = genExplicitCharLen(charLen);
1391         if (preAlloc) {
1392           symMap.addCharSymbol(sym, preAlloc, len);
1393           return;
1394         }
1395         llvm::SmallVector<mlir::Value> lengths = {len};
1396         mlir::Value local =
1397             createNewLocal(converter, loc, var, preAlloc, llvm::None, lengths);
1398         symMap.addCharSymbol(sym, local, len);
1399       },
1400 
1401       //===--------------------------------------------------------------===//
1402 
1403       [&](const Fortran::lower::details::StaticArray &x) {
1404         // object shape is constant, not a character
1405         mlir::Type castTy = builder.getRefType(converter.genType(var));
1406         mlir::Value addr = symMap.lookupSymbol(sym).getAddr();
1407         if (addr)
1408           addr = builder.createConvert(loc, castTy, addr);
1409         if (x.lboundAllOnes()) {
1410           // if lower bounds are all ones, build simple shaped object
1411           llvm::SmallVector<mlir::Value> shape;
1412           for (int64_t i : x.shapes)
1413             shape.push_back(genExtentValue(builder, loc, idxTy, i));
1414           mlir::Value local =
1415               isDummy ? addr : createNewLocal(converter, loc, var, preAlloc);
1416           symMap.addSymbolWithShape(sym, local, shape, isDummy);
1417           return;
1418         }
1419         // If object is an array process the lower bound and extent values by
1420         // constructing constants and populating the lbounds and extents.
1421         llvm::SmallVector<mlir::Value> extents;
1422         llvm::SmallVector<mlir::Value> lbounds;
1423         for (auto [fst, snd] : llvm::zip(x.lbounds, x.shapes)) {
1424           lbounds.emplace_back(builder.createIntegerConstant(loc, idxTy, fst));
1425           extents.emplace_back(genExtentValue(builder, loc, idxTy, snd));
1426         }
1427         mlir::Value local =
1428             isDummy ? addr
1429                     : createNewLocal(converter, loc, var, preAlloc, extents);
1430         assert(isDummy || Fortran::lower::isExplicitShape(sym));
1431         symMap.addSymbolWithBounds(sym, local, extents, lbounds, isDummy);
1432       },
1433 
1434       //===--------------------------------------------------------------===//
1435 
1436       [&](const Fortran::lower::details::DynamicArray &x) {
1437         // cast to the known constant parts from the declaration
1438         mlir::Type varType = converter.genType(var);
1439         mlir::Value addr = symMap.lookupSymbol(sym).getAddr();
1440         mlir::Value argBox;
1441         mlir::Type castTy = builder.getRefType(varType);
1442         if (addr) {
1443           if (auto boxTy = addr.getType().dyn_cast<fir::BoxType>()) {
1444             argBox = addr;
1445             mlir::Type refTy = builder.getRefType(boxTy.getEleTy());
1446             addr = builder.create<fir::BoxAddrOp>(loc, refTy, argBox);
1447           }
1448           addr = builder.createConvert(loc, castTy, addr);
1449         }
1450         if (x.lboundAllOnes()) {
1451           // if lower bounds are all ones, build simple shaped object
1452           llvm::SmallVector<mlir::Value> shapes;
1453           populateShape(shapes, x.bounds, argBox);
1454           if (isDummy) {
1455             symMap.addSymbolWithShape(sym, addr, shapes, true);
1456             return;
1457           }
1458           // local array with computed bounds
1459           assert(Fortran::lower::isExplicitShape(sym) ||
1460                  Fortran::semantics::IsAllocatableOrPointer(sym));
1461           mlir::Value local =
1462               createNewLocal(converter, loc, var, preAlloc, shapes);
1463           symMap.addSymbolWithShape(sym, local, shapes);
1464           return;
1465         }
1466         // if object is an array process the lower bound and extent values
1467         llvm::SmallVector<mlir::Value> extents;
1468         llvm::SmallVector<mlir::Value> lbounds;
1469         populateLBoundsExtents(lbounds, extents, x.bounds, argBox);
1470         if (isDummy) {
1471           symMap.addSymbolWithBounds(sym, addr, extents, lbounds, true);
1472           return;
1473         }
1474         // local array with computed bounds
1475         assert(Fortran::lower::isExplicitShape(sym));
1476         mlir::Value local =
1477             createNewLocal(converter, loc, var, preAlloc, extents);
1478         symMap.addSymbolWithBounds(sym, local, extents, lbounds);
1479       },
1480 
1481       //===--------------------------------------------------------------===//
1482 
1483       [&](const Fortran::lower::details::StaticArrayStaticChar &x) {
1484         // if element type is a CHARACTER, determine the LEN value
1485         auto charLen = x.charLen();
1486         mlir::Value addr;
1487         mlir::Value len;
1488         if (isDummy) {
1489           Fortran::lower::SymbolBox symBox = symMap.lookupSymbol(sym);
1490           std::pair<mlir::Value, mlir::Value> unboxchar =
1491               charHelp.createUnboxChar(symBox.getAddr());
1492           addr = unboxchar.first;
1493           // Set/override LEN with a constant
1494           len = builder.createIntegerConstant(loc, idxTy, charLen);
1495         } else {
1496           // local CHARACTER variable
1497           len = builder.createIntegerConstant(loc, idxTy, charLen);
1498         }
1499 
1500         // object shape is constant
1501         mlir::Type castTy = builder.getRefType(converter.genType(var));
1502         if (addr)
1503           addr = builder.createConvert(loc, castTy, addr);
1504 
1505         if (x.lboundAllOnes()) {
1506           // if lower bounds are all ones, build simple shaped object
1507           llvm::SmallVector<mlir::Value> shape;
1508           for (int64_t i : x.shapes)
1509             shape.push_back(genExtentValue(builder, loc, idxTy, i));
1510           mlir::Value local =
1511               isDummy ? addr : createNewLocal(converter, loc, var, preAlloc);
1512           symMap.addCharSymbolWithShape(sym, local, len, shape, isDummy);
1513           return;
1514         }
1515 
1516         // if object is an array process the lower bound and extent values
1517         llvm::SmallVector<mlir::Value> extents;
1518         llvm::SmallVector<mlir::Value> lbounds;
1519         // construct constants and populate `bounds`
1520         for (auto [fst, snd] : llvm::zip(x.lbounds, x.shapes)) {
1521           lbounds.emplace_back(builder.createIntegerConstant(loc, idxTy, fst));
1522           extents.emplace_back(genExtentValue(builder, loc, idxTy, snd));
1523         }
1524 
1525         if (isDummy) {
1526           symMap.addCharSymbolWithBounds(sym, addr, len, extents, lbounds,
1527                                          true);
1528           return;
1529         }
1530         // local CHARACTER array with computed bounds
1531         assert(Fortran::lower::isExplicitShape(sym));
1532         mlir::Value local =
1533             createNewLocal(converter, loc, var, preAlloc, extents);
1534         symMap.addCharSymbolWithBounds(sym, local, len, extents, lbounds);
1535       },
1536 
1537       //===--------------------------------------------------------------===//
1538 
1539       [&](const Fortran::lower::details::StaticArrayDynamicChar &x) {
1540         mlir::Value addr;
1541         mlir::Value len;
1542         [[maybe_unused]] bool mustBeDummy = false;
1543         auto charLen = x.charLen();
1544         // if element type is a CHARACTER, determine the LEN value
1545         if (isDummy) {
1546           Fortran::lower::SymbolBox symBox = symMap.lookupSymbol(sym);
1547           std::pair<mlir::Value, mlir::Value> unboxchar =
1548               charHelp.createUnboxChar(symBox.getAddr());
1549           addr = unboxchar.first;
1550           if (charLen) {
1551             // Set/override LEN with an expression
1552             len = genExplicitCharLen(charLen);
1553           } else {
1554             // LEN is from the boxchar
1555             len = unboxchar.second;
1556             mustBeDummy = true;
1557           }
1558         } else {
1559           // local CHARACTER variable
1560           len = genExplicitCharLen(charLen);
1561         }
1562         llvm::SmallVector<mlir::Value> lengths = {len};
1563 
1564         // cast to the known constant parts from the declaration
1565         mlir::Type castTy = builder.getRefType(converter.genType(var));
1566         if (addr)
1567           addr = builder.createConvert(loc, castTy, addr);
1568 
1569         if (x.lboundAllOnes()) {
1570           // if lower bounds are all ones, build simple shaped object
1571           llvm::SmallVector<mlir::Value> shape;
1572           for (int64_t i : x.shapes)
1573             shape.push_back(genExtentValue(builder, loc, idxTy, i));
1574           if (isDummy) {
1575             symMap.addCharSymbolWithShape(sym, addr, len, shape, true);
1576             return;
1577           }
1578           // local CHARACTER array with constant size
1579           mlir::Value local = createNewLocal(converter, loc, var, preAlloc,
1580                                              llvm::None, lengths);
1581           symMap.addCharSymbolWithShape(sym, local, len, shape);
1582           return;
1583         }
1584 
1585         // if object is an array process the lower bound and extent values
1586         llvm::SmallVector<mlir::Value> extents;
1587         llvm::SmallVector<mlir::Value> lbounds;
1588 
1589         // construct constants and populate `bounds`
1590         for (auto [fst, snd] : llvm::zip(x.lbounds, x.shapes)) {
1591           lbounds.emplace_back(builder.createIntegerConstant(loc, idxTy, fst));
1592           extents.emplace_back(genExtentValue(builder, loc, idxTy, snd));
1593         }
1594         if (isDummy) {
1595           symMap.addCharSymbolWithBounds(sym, addr, len, extents, lbounds,
1596                                          true);
1597           return;
1598         }
1599         // local CHARACTER array with computed bounds
1600         assert((!mustBeDummy) && (Fortran::lower::isExplicitShape(sym)));
1601         mlir::Value local =
1602             createNewLocal(converter, loc, var, preAlloc, llvm::None, lengths);
1603         symMap.addCharSymbolWithBounds(sym, local, len, extents, lbounds);
1604       },
1605 
1606       //===--------------------------------------------------------------===//
1607 
1608       [&](const Fortran::lower::details::DynamicArrayStaticChar &x) {
1609         mlir::Value addr;
1610         mlir::Value len;
1611         mlir::Value argBox;
1612         auto charLen = x.charLen();
1613         // if element type is a CHARACTER, determine the LEN value
1614         if (isDummy) {
1615           mlir::Value actualArg = symMap.lookupSymbol(sym).getAddr();
1616           if (auto boxTy = actualArg.getType().dyn_cast<fir::BoxType>()) {
1617             argBox = actualArg;
1618             mlir::Type refTy = builder.getRefType(boxTy.getEleTy());
1619             addr = builder.create<fir::BoxAddrOp>(loc, refTy, argBox);
1620           } else {
1621             addr = charHelp.createUnboxChar(actualArg).first;
1622           }
1623           // Set/override LEN with a constant
1624           len = builder.createIntegerConstant(loc, idxTy, charLen);
1625         } else {
1626           // local CHARACTER variable
1627           len = builder.createIntegerConstant(loc, idxTy, charLen);
1628         }
1629 
1630         // cast to the known constant parts from the declaration
1631         mlir::Type castTy = builder.getRefType(converter.genType(var));
1632         if (addr)
1633           addr = builder.createConvert(loc, castTy, addr);
1634         if (x.lboundAllOnes()) {
1635           // if lower bounds are all ones, build simple shaped object
1636           llvm::SmallVector<mlir::Value> shape;
1637           populateShape(shape, x.bounds, argBox);
1638           if (isDummy) {
1639             symMap.addCharSymbolWithShape(sym, addr, len, shape, true);
1640             return;
1641           }
1642           // local CHARACTER array
1643           mlir::Value local =
1644               createNewLocal(converter, loc, var, preAlloc, shape);
1645           symMap.addCharSymbolWithShape(sym, local, len, shape);
1646           return;
1647         }
1648         // if object is an array process the lower bound and extent values
1649         llvm::SmallVector<mlir::Value> extents;
1650         llvm::SmallVector<mlir::Value> lbounds;
1651         populateLBoundsExtents(lbounds, extents, x.bounds, argBox);
1652         if (isDummy) {
1653           symMap.addCharSymbolWithBounds(sym, addr, len, extents, lbounds,
1654                                          true);
1655           return;
1656         }
1657         // local CHARACTER array with computed bounds
1658         assert(Fortran::lower::isExplicitShape(sym));
1659         mlir::Value local =
1660             createNewLocal(converter, loc, var, preAlloc, extents);
1661         symMap.addCharSymbolWithBounds(sym, local, len, extents, lbounds);
1662       },
1663 
1664       //===--------------------------------------------------------------===//
1665 
1666       [&](const Fortran::lower::details::DynamicArrayDynamicChar &x) {
1667         mlir::Value addr;
1668         mlir::Value len;
1669         mlir::Value argBox;
1670         auto charLen = x.charLen();
1671         // if element type is a CHARACTER, determine the LEN value
1672         if (isDummy) {
1673           mlir::Value actualArg = symMap.lookupSymbol(sym).getAddr();
1674           if (auto boxTy = actualArg.getType().dyn_cast<fir::BoxType>()) {
1675             argBox = actualArg;
1676             mlir::Type refTy = builder.getRefType(boxTy.getEleTy());
1677             addr = builder.create<fir::BoxAddrOp>(loc, refTy, argBox);
1678             if (charLen)
1679               // Set/override LEN with an expression.
1680               len = genExplicitCharLen(charLen);
1681             else
1682               // Get the length from the actual arguments.
1683               len = charHelp.readLengthFromBox(argBox);
1684           } else {
1685             std::pair<mlir::Value, mlir::Value> unboxchar =
1686                 charHelp.createUnboxChar(actualArg);
1687             addr = unboxchar.first;
1688             if (charLen) {
1689               // Set/override LEN with an expression
1690               len = genExplicitCharLen(charLen);
1691             } else {
1692               // Get the length from the actual arguments.
1693               len = unboxchar.second;
1694             }
1695           }
1696         } else {
1697           // local CHARACTER variable
1698           len = genExplicitCharLen(charLen);
1699         }
1700         llvm::SmallVector<mlir::Value> lengths = {len};
1701 
1702         // cast to the known constant parts from the declaration
1703         mlir::Type castTy = builder.getRefType(converter.genType(var));
1704         if (addr)
1705           addr = builder.createConvert(loc, castTy, addr);
1706         if (x.lboundAllOnes()) {
1707           // if lower bounds are all ones, build simple shaped object
1708           llvm::SmallVector<mlir::Value> shape;
1709           populateShape(shape, x.bounds, argBox);
1710           if (isDummy) {
1711             symMap.addCharSymbolWithShape(sym, addr, len, shape, true);
1712             return;
1713           }
1714           // local CHARACTER array
1715           mlir::Value local =
1716               createNewLocal(converter, loc, var, preAlloc, shape, lengths);
1717           symMap.addCharSymbolWithShape(sym, local, len, shape);
1718           return;
1719         }
1720         // Process the lower bound and extent values.
1721         llvm::SmallVector<mlir::Value> extents;
1722         llvm::SmallVector<mlir::Value> lbounds;
1723         populateLBoundsExtents(lbounds, extents, x.bounds, argBox);
1724         if (isDummy) {
1725           symMap.addCharSymbolWithBounds(sym, addr, len, extents, lbounds,
1726                                          true);
1727           return;
1728         }
1729         // local CHARACTER array with computed bounds
1730         assert(Fortran::lower::isExplicitShape(sym));
1731         mlir::Value local =
1732             createNewLocal(converter, loc, var, preAlloc, extents, lengths);
1733         symMap.addCharSymbolWithBounds(sym, local, len, extents, lbounds);
1734       },
1735 
1736       //===--------------------------------------------------------------===//
1737 
1738       [&](const Fortran::lower::BoxAnalyzer::None &) {
1739         mlir::emitError(loc, "symbol analysis failed on ")
1740             << toStringRef(sym.name());
1741       });
1742 }
1743 
1744 void Fortran::lower::defineModuleVariable(
1745     AbstractConverter &converter, const Fortran::lower::pft::Variable &var) {
1746   // Use empty linkage for module variables, which makes them available
1747   // for use in another unit.
1748   mlir::StringAttr linkage =
1749       getLinkageAttribute(converter.getFirOpBuilder(), var);
1750   if (!var.isGlobal())
1751     fir::emitFatalError(converter.getCurrentLocation(),
1752                         "attempting to lower module variable as local");
1753   // Define aggregate storages for equivalenced objects.
1754   if (var.isAggregateStore()) {
1755     const Fortran::lower::pft::Variable::AggregateStore &aggregate =
1756         var.getAggregateStore();
1757     std::string aggName = mangleGlobalAggregateStore(aggregate);
1758     defineGlobalAggregateStore(converter, aggregate, aggName, linkage);
1759     return;
1760   }
1761   const Fortran::semantics::Symbol &sym = var.getSymbol();
1762   if (const Fortran::semantics::Symbol *common =
1763           Fortran::semantics::FindCommonBlockContaining(var.getSymbol())) {
1764     // Define common block containing the variable.
1765     defineCommonBlock(converter, *common);
1766   } else if (var.isAlias()) {
1767     // Do nothing. Mapping will be done on user side.
1768   } else {
1769     std::string globalName = Fortran::lower::mangle::mangleName(sym);
1770     defineGlobal(converter, var, globalName, linkage);
1771   }
1772 }
1773 
1774 void Fortran::lower::instantiateVariable(AbstractConverter &converter,
1775                                          const pft::Variable &var,
1776                                          Fortran::lower::SymMap &symMap,
1777                                          AggregateStoreMap &storeMap) {
1778   if (var.isAggregateStore()) {
1779     instantiateAggregateStore(converter, var, storeMap);
1780   } else if (const Fortran::semantics::Symbol *common =
1781                  Fortran::semantics::FindCommonBlockContaining(
1782                      var.getSymbol().GetUltimate())) {
1783     instantiateCommon(converter, *common, var, symMap);
1784   } else if (var.isAlias()) {
1785     instantiateAlias(converter, var, symMap, storeMap);
1786   } else if (var.isGlobal()) {
1787     instantiateGlobal(converter, var, symMap);
1788   } else {
1789     instantiateLocal(converter, var, symMap);
1790   }
1791 }
1792 
1793 void Fortran::lower::mapCallInterfaceSymbols(
1794     AbstractConverter &converter, const Fortran::lower::CallerInterface &caller,
1795     SymMap &symMap) {
1796   Fortran::lower::AggregateStoreMap storeMap;
1797   const Fortran::semantics::Symbol &result = caller.getResultSymbol();
1798   for (Fortran::lower::pft::Variable var :
1799        Fortran::lower::pft::buildFuncResultDependencyList(result)) {
1800     if (var.isAggregateStore()) {
1801       instantiateVariable(converter, var, symMap, storeMap);
1802     } else {
1803       const Fortran::semantics::Symbol &sym = var.getSymbol();
1804       const auto *hostDetails =
1805           sym.detailsIf<Fortran::semantics::HostAssocDetails>();
1806       if (hostDetails && !var.isModuleVariable()) {
1807         // The callee is an internal procedure `A` whose result properties
1808         // depend on host variables. The caller may be the host, or another
1809         // internal procedure `B` contained in the same host.  In the first
1810         // case, the host symbol is obviously mapped, in the second case, it
1811         // must also be mapped because
1812         // HostAssociations::internalProcedureBindings that was called when
1813         // lowering `B` will have mapped all host symbols of captured variables
1814         // to the tuple argument containing the composite of all host associated
1815         // variables, whether or not the host symbol is actually referred to in
1816         // `B`. Hence it is possible to simply lookup the variable associated to
1817         // the host symbol without having to go back to the tuple argument.
1818         Fortran::lower::SymbolBox hostValue =
1819             symMap.lookupSymbol(hostDetails->symbol());
1820         assert(hostValue && "callee host symbol must be mapped on caller side");
1821         symMap.addSymbol(sym, hostValue.toExtendedValue());
1822         // The SymbolBox associated to the host symbols is complete, skip
1823         // instantiateVariable that would try to allocate a new storage.
1824         continue;
1825       }
1826       if (Fortran::semantics::IsDummy(sym) && sym.owner() == result.owner()) {
1827         // Get the argument for the dummy argument symbols of the current call.
1828         symMap.addSymbol(sym, caller.getArgumentValue(sym));
1829         // All the properties of the dummy variable may not come from the actual
1830         // argument, let instantiateVariable handle this.
1831       }
1832       // If this is neither a host associated or dummy symbol, it must be a
1833       // module or common block variable to satisfy specification expression
1834       // requirements in 10.1.11, instantiateVariable will get its address and
1835       // properties.
1836       instantiateVariable(converter, var, symMap, storeMap);
1837     }
1838   }
1839 }
1840 
1841 void Fortran::lower::createRuntimeTypeInfoGlobal(
1842     Fortran::lower::AbstractConverter &converter, mlir::Location loc,
1843     const Fortran::semantics::Symbol &typeInfoSym) {
1844   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
1845   std::string globalName = Fortran::lower::mangle::mangleName(typeInfoSym);
1846   auto var = Fortran::lower::pft::Variable(typeInfoSym, /*global=*/true);
1847   mlir::StringAttr linkage = getLinkageAttribute(builder, var);
1848   defineGlobal(converter, var, globalName, linkage);
1849 }
1850