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/Optimizer/Builder/Character.h"
26 #include "flang/Optimizer/Builder/FIRBuilder.h"
27 #include "flang/Optimizer/Builder/Runtime/Derived.h"
28 #include "flang/Optimizer/Builder/Todo.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       !Fortran::semantics::IsProcedurePointer(ultimate))
126     mlir::emitError(loc, "processing 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 
382   if (Fortran::semantics::IsProcedurePointer(sym))
383     TODO(loc, "procedure pointer globals");
384 
385   // If this is an array, check to see if we can use a dense attribute
386   // with a tensor mlir type.  This optimization currently only supports
387   // rank-1 Fortran arrays of integer, real, or logical. The tensor
388   // type does not support nested structures which are needed for
389   // complex numbers.
390   // To get multidimensional arrays to work, we will have to use column major
391   // array ordering with the tensor type (so it matches column major ordering
392   // with the Fortran fir.array).  By default, tensor types assume row major
393   // ordering. How to create this tensor type is to be determined.
394   if (symTy.isa<fir::SequenceType>() && sym.Rank() == 1 &&
395       !Fortran::semantics::IsAllocatableOrPointer(sym)) {
396     mlir::Type eleTy = symTy.cast<fir::SequenceType>().getEleTy();
397     if (eleTy.isa<mlir::IntegerType, mlir::FloatType, fir::LogicalType>()) {
398       const auto *details =
399           sym.detailsIf<Fortran::semantics::ObjectEntityDetails>();
400       if (details->init()) {
401         global = Fortran::lower::createDenseGlobal(
402             loc, symTy, globalName, linkage, isConst, details->init().value(),
403             converter);
404         if (global) {
405           global.setVisibility(mlir::SymbolTable::Visibility::Public);
406           return global;
407         }
408       }
409     }
410   }
411   if (!global)
412     global = builder.createGlobal(loc, symTy, globalName, linkage,
413                                   mlir::Attribute{}, isConst);
414   if (Fortran::semantics::IsAllocatableOrPointer(sym)) {
415     const auto *details =
416         sym.detailsIf<Fortran::semantics::ObjectEntityDetails>();
417     if (details && details->init()) {
418       auto expr = *details->init();
419       createGlobalInitialization(builder, global, [&](fir::FirOpBuilder &b) {
420         mlir::Value box =
421             Fortran::lower::genInitialDataTarget(converter, loc, symTy, expr);
422         b.create<fir::HasValueOp>(loc, box);
423       });
424     } else {
425       // Create unallocated/disassociated descriptor if no explicit init
426       createGlobalInitialization(builder, global, [&](fir::FirOpBuilder &b) {
427         mlir::Value box =
428             fir::factory::createUnallocatedBox(b, loc, symTy, llvm::None);
429         b.create<fir::HasValueOp>(loc, box);
430       });
431     }
432 
433   } else if (const auto *details =
434                  sym.detailsIf<Fortran::semantics::ObjectEntityDetails>()) {
435     if (details->init()) {
436       createGlobalInitialization(
437           builder, global, [&](fir::FirOpBuilder &builder) {
438             Fortran::lower::StatementContext stmtCtx(
439                 /*cleanupProhibited=*/true);
440             fir::ExtendedValue initVal = genInitializerExprValue(
441                 converter, loc, details->init().value(), stmtCtx);
442             mlir::Value castTo =
443                 builder.createConvert(loc, symTy, fir::getBase(initVal));
444             builder.create<fir::HasValueOp>(loc, castTo);
445           });
446     } else if (hasDefaultInitialization(sym)) {
447       createGlobalInitialization(
448           builder, global, [&](fir::FirOpBuilder &builder) {
449             Fortran::lower::StatementContext stmtCtx(
450                 /*cleanupProhibited=*/true);
451             mlir::Value initVal =
452                 genDefaultInitializerValue(converter, loc, sym, symTy, stmtCtx);
453             mlir::Value castTo = builder.createConvert(loc, symTy, initVal);
454             builder.create<fir::HasValueOp>(loc, castTo);
455           });
456     }
457   } else if (sym.has<Fortran::semantics::CommonBlockDetails>()) {
458     mlir::emitError(loc, "COMMON symbol processed elsewhere");
459   } else {
460     TODO(loc, "global"); // Procedure pointer or something else
461   }
462   // Creates undefined initializer for globals without initializers
463   if (!globalIsInitialized(global)) {
464     // TODO: Is it really required to add the undef init if the Public
465     // visibility is set ? We need to make sure the global is not optimized out
466     // by LLVM if unused in the current compilation unit, but at least for
467     // BIND(C) variables, an initial value may be given in another compilation
468     // unit (on the C side), and setting an undef init here creates linkage
469     // conflicts.
470     if (sym.attrs().test(Fortran::semantics::Attr::BIND_C))
471       TODO(loc, "BIND(C) module variable linkage");
472     createGlobalInitialization(
473         builder, global, [&](fir::FirOpBuilder &builder) {
474           builder.create<fir::HasValueOp>(
475               loc, builder.create<fir::UndefOp>(loc, symTy));
476         });
477   }
478   // Set public visibility to prevent global definition to be optimized out
479   // even if they have no initializer and are unused in this compilation unit.
480   global.setVisibility(mlir::SymbolTable::Visibility::Public);
481   return global;
482 }
483 
484 /// Return linkage attribute for \p var.
485 static mlir::StringAttr
486 getLinkageAttribute(fir::FirOpBuilder &builder,
487                     const Fortran::lower::pft::Variable &var) {
488   // Runtime type info for a same derived type is identical in each compilation
489   // unit. It desired to avoid having to link against module that only define a
490   // type. Therefore the runtime type info is generated everywhere it is needed
491   // with `linkonce_odr` LLVM linkage.
492   if (var.hasSymbol() && isRuntimeTypeInfoData(var.getSymbol()))
493     return builder.createLinkOnceODRLinkage();
494   if (var.isModuleVariable())
495     return {}; // external linkage
496   // Otherwise, the variable is owned by a procedure and must not be visible in
497   // other compilation units.
498   return builder.createInternalLinkage();
499 }
500 
501 /// Instantiate a global variable. If it hasn't already been processed, add
502 /// the global to the ModuleOp as a new uniqued symbol and initialize it with
503 /// the correct value. It will be referenced on demand using `fir.addr_of`.
504 static void instantiateGlobal(Fortran::lower::AbstractConverter &converter,
505                               const Fortran::lower::pft::Variable &var,
506                               Fortran::lower::SymMap &symMap) {
507   const Fortran::semantics::Symbol &sym = var.getSymbol();
508   assert(!var.isAlias() && "must be handled in instantiateAlias");
509   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
510   std::string globalName = Fortran::lower::mangle::mangleName(sym);
511   mlir::Location loc = converter.genLocation(sym.name());
512   fir::GlobalOp global = builder.getNamedGlobal(globalName);
513   mlir::StringAttr linkage = getLinkageAttribute(builder, var);
514   if (var.isModuleVariable()) {
515     // A module global was or will be defined when lowering the module. Emit
516     // only a declaration if the global does not exist at that point.
517     global = declareGlobal(converter, var, globalName, linkage);
518   } else {
519     global = defineGlobal(converter, var, globalName, linkage);
520   }
521   auto addrOf = builder.create<fir::AddrOfOp>(loc, global.resultType(),
522                                               global.getSymbol());
523   Fortran::lower::StatementContext stmtCtx;
524   mapSymbolAttributes(converter, var, symMap, stmtCtx, addrOf);
525 }
526 
527 //===----------------------------------------------------------------===//
528 // Local variables instantiation (not for alias)
529 //===----------------------------------------------------------------===//
530 
531 /// Create a stack slot for a local variable. Precondition: the insertion
532 /// point of the builder must be in the entry block, which is currently being
533 /// constructed.
534 static mlir::Value createNewLocal(Fortran::lower::AbstractConverter &converter,
535                                   mlir::Location loc,
536                                   const Fortran::lower::pft::Variable &var,
537                                   mlir::Value preAlloc,
538                                   llvm::ArrayRef<mlir::Value> shape = {},
539                                   llvm::ArrayRef<mlir::Value> lenParams = {}) {
540   if (preAlloc)
541     return preAlloc;
542   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
543   std::string nm = Fortran::lower::mangle::mangleName(var.getSymbol());
544   mlir::Type ty = converter.genType(var);
545   const Fortran::semantics::Symbol &ultimateSymbol =
546       var.getSymbol().GetUltimate();
547   llvm::StringRef symNm = toStringRef(ultimateSymbol.name());
548   bool isTarg = var.isTarget();
549   // Let the builder do all the heavy lifting.
550   return builder.allocateLocal(loc, ty, nm, symNm, shape, lenParams, isTarg);
551 }
552 
553 /// Must \p var be default initialized at runtime when entering its scope.
554 static bool
555 mustBeDefaultInitializedAtRuntime(const Fortran::lower::pft::Variable &var) {
556   if (!var.hasSymbol())
557     return false;
558   const Fortran::semantics::Symbol &sym = var.getSymbol();
559   if (var.isGlobal())
560     // Global variables are statically initialized.
561     return false;
562   if (Fortran::semantics::IsDummy(sym) && !Fortran::semantics::IsIntentOut(sym))
563     return false;
564   // Local variables (including function results), and intent(out) dummies must
565   // be default initialized at runtime if their type has default initialization.
566   return hasDefaultInitialization(sym);
567 }
568 
569 /// Call default initialization runtime routine to initialize \p var.
570 static void
571 defaultInitializeAtRuntime(Fortran::lower::AbstractConverter &converter,
572                            const Fortran::lower::pft::Variable &var,
573                            Fortran::lower::SymMap &symMap) {
574   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
575   mlir::Location loc = converter.getCurrentLocation();
576   const Fortran::semantics::Symbol &sym = var.getSymbol();
577   fir::ExtendedValue exv = symMap.lookupSymbol(sym).toExtendedValue();
578   if (Fortran::semantics::IsOptional(sym)) {
579     // 15.5.2.12 point 3, absent optional dummies are not initialized.
580     // Creating descriptor/passing null descriptor to the runtime would
581     // create runtime crashes.
582     auto isPresent = builder.create<fir::IsPresentOp>(loc, builder.getI1Type(),
583                                                       fir::getBase(exv));
584     builder.genIfThen(loc, isPresent)
585         .genThen([&]() {
586           auto box = builder.createBox(loc, exv);
587           fir::runtime::genDerivedTypeInitialize(builder, loc, box);
588         })
589         .end();
590   } else {
591     mlir::Value box = builder.createBox(loc, exv);
592     fir::runtime::genDerivedTypeInitialize(builder, loc, box);
593   }
594 }
595 
596 /// Instantiate a local variable. Precondition: Each variable will be visited
597 /// such that if its properties depend on other variables, the variables upon
598 /// which its properties depend will already have been visited.
599 static void instantiateLocal(Fortran::lower::AbstractConverter &converter,
600                              const Fortran::lower::pft::Variable &var,
601                              Fortran::lower::SymMap &symMap) {
602   assert(!var.isAlias());
603   Fortran::lower::StatementContext stmtCtx;
604   mapSymbolAttributes(converter, var, symMap, stmtCtx);
605   if (mustBeDefaultInitializedAtRuntime(var))
606     defaultInitializeAtRuntime(converter, var, symMap);
607 }
608 
609 //===----------------------------------------------------------------===//
610 // Aliased (EQUIVALENCE) variables instantiation
611 //===----------------------------------------------------------------===//
612 
613 /// Insert \p aggregateStore instance into an AggregateStoreMap.
614 static void insertAggregateStore(Fortran::lower::AggregateStoreMap &storeMap,
615                                  const Fortran::lower::pft::Variable &var,
616                                  mlir::Value aggregateStore) {
617   std::size_t off = var.getAggregateStore().getOffset();
618   Fortran::lower::AggregateStoreKey key = {var.getOwningScope(), off};
619   storeMap[key] = aggregateStore;
620 }
621 
622 /// Retrieve the aggregate store instance of \p alias from an
623 /// AggregateStoreMap.
624 static mlir::Value
625 getAggregateStore(Fortran::lower::AggregateStoreMap &storeMap,
626                   const Fortran::lower::pft::Variable &alias) {
627   Fortran::lower::AggregateStoreKey key = {alias.getOwningScope(),
628                                            alias.getAlias()};
629   auto iter = storeMap.find(key);
630   assert(iter != storeMap.end());
631   return iter->second;
632 }
633 
634 /// Build the name for the storage of a global equivalence.
635 static std::string mangleGlobalAggregateStore(
636     const Fortran::lower::pft::Variable::AggregateStore &st) {
637   return Fortran::lower::mangle::mangleName(st.getNamingSymbol());
638 }
639 
640 /// Build the type for the storage of an equivalence.
641 static mlir::Type
642 getAggregateType(Fortran::lower::AbstractConverter &converter,
643                  const Fortran::lower::pft::Variable::AggregateStore &st) {
644   if (const Fortran::semantics::Symbol *initSym = st.getInitialValueSymbol())
645     return converter.genType(*initSym);
646   mlir::IntegerType byteTy = converter.getFirOpBuilder().getIntegerType(8);
647   return fir::SequenceType::get(std::get<1>(st.interval), byteTy);
648 }
649 
650 /// Define a GlobalOp for the storage of a global equivalence described
651 /// by \p aggregate. The global is named \p aggName and is created with
652 /// the provided \p linkage.
653 /// If any of the equivalence members are initialized, an initializer is
654 /// created for the equivalence.
655 /// This is to be used when lowering the scope that owns the equivalence
656 /// (as opposed to simply using it through host or use association).
657 /// This is not to be used for equivalence of common block members (they
658 /// already have the common block GlobalOp for them, see defineCommonBlock).
659 static fir::GlobalOp defineGlobalAggregateStore(
660     Fortran::lower::AbstractConverter &converter,
661     const Fortran::lower::pft::Variable::AggregateStore &aggregate,
662     llvm::StringRef aggName, mlir::StringAttr linkage) {
663   assert(aggregate.isGlobal() && "not a global interval");
664   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
665   fir::GlobalOp global = builder.getNamedGlobal(aggName);
666   if (global && globalIsInitialized(global))
667     return global;
668   mlir::Location loc = converter.getCurrentLocation();
669   mlir::Type aggTy = getAggregateType(converter, aggregate);
670   if (!global)
671     global = builder.createGlobal(loc, aggTy, aggName, linkage);
672 
673   if (const Fortran::semantics::Symbol *initSym =
674           aggregate.getInitialValueSymbol())
675     if (const auto *objectDetails =
676             initSym->detailsIf<Fortran::semantics::ObjectEntityDetails>())
677       if (objectDetails->init()) {
678         createGlobalInitialization(
679             builder, global, [&](fir::FirOpBuilder &builder) {
680               Fortran::lower::StatementContext stmtCtx;
681               mlir::Value initVal = fir::getBase(genInitializerExprValue(
682                   converter, loc, objectDetails->init().value(), stmtCtx));
683               builder.create<fir::HasValueOp>(loc, initVal);
684             });
685         return global;
686       }
687   // Equivalence has no Fortran initial value. Create an undefined FIR initial
688   // value to ensure this is consider an object definition in the IR regardless
689   // of the linkage.
690   createGlobalInitialization(builder, global, [&](fir::FirOpBuilder &builder) {
691     Fortran::lower::StatementContext stmtCtx;
692     mlir::Value initVal = builder.create<fir::UndefOp>(loc, aggTy);
693     builder.create<fir::HasValueOp>(loc, initVal);
694   });
695   return global;
696 }
697 
698 /// Declare a GlobalOp for the storage of a global equivalence described
699 /// by \p aggregate. The global is named \p aggName and is created with
700 /// the provided \p linkage.
701 /// No initializer is built for the created GlobalOp.
702 /// This is to be used when lowering the scope that uses members of an
703 /// equivalence it through host or use association.
704 /// This is not to be used for equivalence of common block members (they
705 /// already have the common block GlobalOp for them, see defineCommonBlock).
706 static fir::GlobalOp declareGlobalAggregateStore(
707     Fortran::lower::AbstractConverter &converter, mlir::Location loc,
708     const Fortran::lower::pft::Variable::AggregateStore &aggregate,
709     llvm::StringRef aggName, mlir::StringAttr linkage) {
710   assert(aggregate.isGlobal() && "not a global interval");
711   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
712   if (fir::GlobalOp global = builder.getNamedGlobal(aggName))
713     return global;
714   mlir::Type aggTy = getAggregateType(converter, aggregate);
715   return builder.createGlobal(loc, aggTy, aggName, linkage);
716 }
717 
718 /// This is an aggregate store for a set of EQUIVALENCED variables. Create the
719 /// storage on the stack or global memory and add it to the map.
720 static void
721 instantiateAggregateStore(Fortran::lower::AbstractConverter &converter,
722                           const Fortran::lower::pft::Variable &var,
723                           Fortran::lower::AggregateStoreMap &storeMap) {
724   assert(var.isAggregateStore() && "not an interval");
725   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
726   mlir::IntegerType i8Ty = builder.getIntegerType(8);
727   mlir::Location loc = converter.getCurrentLocation();
728   std::string aggName = mangleGlobalAggregateStore(var.getAggregateStore());
729   if (var.isGlobal()) {
730     fir::GlobalOp global;
731     auto &aggregate = var.getAggregateStore();
732     mlir::StringAttr linkage = getLinkageAttribute(builder, var);
733     if (var.isModuleVariable()) {
734       // A module global was or will be defined when lowering the module. Emit
735       // only a declaration if the global does not exist at that point.
736       global = declareGlobalAggregateStore(converter, loc, aggregate, aggName,
737                                            linkage);
738     } else {
739       global =
740           defineGlobalAggregateStore(converter, aggregate, aggName, linkage);
741     }
742     auto addr = builder.create<fir::AddrOfOp>(loc, global.resultType(),
743                                               global.getSymbol());
744     auto size = std::get<1>(var.getInterval());
745     fir::SequenceType::Shape shape(1, size);
746     auto seqTy = fir::SequenceType::get(shape, i8Ty);
747     mlir::Type refTy = builder.getRefType(seqTy);
748     mlir::Value aggregateStore = builder.createConvert(loc, refTy, addr);
749     insertAggregateStore(storeMap, var, aggregateStore);
750     return;
751   }
752   // This is a local aggregate, allocate an anonymous block of memory.
753   auto size = std::get<1>(var.getInterval());
754   fir::SequenceType::Shape shape(1, size);
755   auto seqTy = fir::SequenceType::get(shape, i8Ty);
756   mlir::Value local =
757       builder.allocateLocal(loc, seqTy, aggName, "", llvm::None, llvm::None,
758                             /*target=*/false);
759   insertAggregateStore(storeMap, var, local);
760 }
761 
762 /// Cast an alias address (variable part of an equivalence) to fir.ptr so that
763 /// the optimizer is conservative and avoids doing copy elision in assignment
764 /// involving equivalenced variables.
765 /// TODO: Represent the equivalence aliasing constraint in another way to avoid
766 /// pessimizing array assignments involving equivalenced variables.
767 static mlir::Value castAliasToPointer(fir::FirOpBuilder &builder,
768                                       mlir::Location loc, mlir::Type aliasType,
769                                       mlir::Value aliasAddr) {
770   return builder.createConvert(loc, fir::PointerType::get(aliasType),
771                                aliasAddr);
772 }
773 
774 /// Instantiate a member of an equivalence. Compute its address in its
775 /// aggregate storage and lower its attributes.
776 static void instantiateAlias(Fortran::lower::AbstractConverter &converter,
777                              const Fortran::lower::pft::Variable &var,
778                              Fortran::lower::SymMap &symMap,
779                              Fortran::lower::AggregateStoreMap &storeMap) {
780   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
781   assert(var.isAlias());
782   const Fortran::semantics::Symbol &sym = var.getSymbol();
783   const mlir::Location loc = converter.genLocation(sym.name());
784   mlir::IndexType idxTy = builder.getIndexType();
785   std::size_t aliasOffset = var.getAlias();
786   mlir::Value store = getAggregateStore(storeMap, var);
787   mlir::IntegerType i8Ty = builder.getIntegerType(8);
788   mlir::Type i8Ptr = builder.getRefType(i8Ty);
789   mlir::Value offset = builder.createIntegerConstant(
790       loc, idxTy, sym.GetUltimate().offset() - aliasOffset);
791   auto ptr = builder.create<fir::CoordinateOp>(loc, i8Ptr, store,
792                                                mlir::ValueRange{offset});
793   mlir::Value preAlloc =
794       castAliasToPointer(builder, loc, converter.genType(sym), ptr);
795   Fortran::lower::StatementContext stmtCtx;
796   mapSymbolAttributes(converter, var, symMap, stmtCtx, preAlloc);
797   // Default initialization is possible for equivalence members: see
798   // F2018 19.5.3.4. Note that if several equivalenced entities have
799   // default initialization, they must have the same type, and the standard
800   // allows the storage to be default initialized several times (this has
801   // no consequences other than wasting some execution time). For now,
802   // do not try optimizing this to single default initializations of
803   // the equivalenced storages. Keep lowering simple.
804   if (mustBeDefaultInitializedAtRuntime(var))
805     defaultInitializeAtRuntime(converter, var, symMap);
806 }
807 
808 //===--------------------------------------------------------------===//
809 // COMMON blocks instantiation
810 //===--------------------------------------------------------------===//
811 
812 /// Does any member of the common block has an initializer ?
813 static bool
814 commonBlockHasInit(const Fortran::semantics::MutableSymbolVector &cmnBlkMems) {
815   for (const Fortran::semantics::MutableSymbolRef &mem : cmnBlkMems) {
816     if (const auto *memDet =
817             mem->detailsIf<Fortran::semantics::ObjectEntityDetails>())
818       if (memDet->init())
819         return true;
820   }
821   return false;
822 }
823 
824 /// Build a tuple type for a common block based on the common block
825 /// members and the common block size.
826 /// This type is only needed to build common block initializers where
827 /// the initial value is the collection of the member initial values.
828 static mlir::TupleType getTypeOfCommonWithInit(
829     Fortran::lower::AbstractConverter &converter,
830     const Fortran::semantics::MutableSymbolVector &cmnBlkMems,
831     std::size_t commonSize) {
832   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
833   llvm::SmallVector<mlir::Type> members;
834   std::size_t counter = 0;
835   for (const Fortran::semantics::MutableSymbolRef &mem : cmnBlkMems) {
836     if (const auto *memDet =
837             mem->detailsIf<Fortran::semantics::ObjectEntityDetails>()) {
838       if (mem->offset() > counter) {
839         fir::SequenceType::Shape len = {
840             static_cast<fir::SequenceType::Extent>(mem->offset() - counter)};
841         mlir::IntegerType byteTy = builder.getIntegerType(8);
842         auto memTy = fir::SequenceType::get(len, byteTy);
843         members.push_back(memTy);
844         counter = mem->offset();
845       }
846       if (memDet->init()) {
847         mlir::Type memTy = converter.genType(*mem);
848         members.push_back(memTy);
849         counter = mem->offset() + mem->size();
850       }
851     }
852   }
853   if (counter < commonSize) {
854     fir::SequenceType::Shape len = {
855         static_cast<fir::SequenceType::Extent>(commonSize - counter)};
856     mlir::IntegerType byteTy = builder.getIntegerType(8);
857     auto memTy = fir::SequenceType::get(len, byteTy);
858     members.push_back(memTy);
859   }
860   return mlir::TupleType::get(builder.getContext(), members);
861 }
862 
863 /// Common block members may have aliases. They are not in the common block
864 /// member list from the symbol. We need to know about these aliases if they
865 /// have initializer to generate the common initializer.
866 /// This function takes care of adding aliases with initializer to the member
867 /// list.
868 static Fortran::semantics::MutableSymbolVector
869 getCommonMembersWithInitAliases(const Fortran::semantics::Symbol &common) {
870   const auto &commonDetails =
871       common.get<Fortran::semantics::CommonBlockDetails>();
872   auto members = commonDetails.objects();
873 
874   // The number and size of equivalence and common is expected to be small, so
875   // no effort is given to optimize this loop of complexity equivalenced
876   // common members * common members
877   for (const Fortran::semantics::EquivalenceSet &set :
878        common.owner().equivalenceSets())
879     for (const Fortran::semantics::EquivalenceObject &obj : set) {
880       if (!obj.symbol.test(Fortran::semantics::Symbol::Flag::CompilerCreated)) {
881         if (const auto &details =
882                 obj.symbol
883                     .detailsIf<Fortran::semantics::ObjectEntityDetails>()) {
884           const Fortran::semantics::Symbol *com =
885               FindCommonBlockContaining(obj.symbol);
886           if (!details->init() || com != &common)
887             continue;
888           // This is an alias with an init that belongs to the list
889           if (std::find(members.begin(), members.end(), obj.symbol) ==
890               members.end())
891             members.emplace_back(obj.symbol);
892         }
893       }
894     }
895   return members;
896 }
897 
898 /// Return the fir::GlobalOp that was created of COMMON block \p common.
899 /// It is an error if the fir::GlobalOp was not created before this is
900 /// called (it cannot be created on the flight because it is not known here
901 /// what mlir type the GlobalOp should have to satisfy all the
902 /// appearances in the program).
903 static fir::GlobalOp
904 getCommonBlockGlobal(Fortran::lower::AbstractConverter &converter,
905                      const Fortran::semantics::Symbol &common) {
906   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
907   std::string commonName = Fortran::lower::mangle::mangleName(common);
908   fir::GlobalOp global = builder.getNamedGlobal(commonName);
909   // Common blocks are lowered before any subprograms to deal with common
910   // whose size may not be the same in every subprograms.
911   if (!global)
912     fir::emitFatalError(converter.genLocation(common.name()),
913                         "COMMON block was not lowered before its usage");
914   return global;
915 }
916 
917 /// Create the fir::GlobalOp for COMMON block \p common. If \p common has an
918 /// initial value, it is not created yet. Instead, the common block list
919 /// members is returned to later create the initial value in
920 /// finalizeCommonBlockDefinition.
921 static std::optional<std::tuple<
922     fir::GlobalOp, Fortran::semantics::MutableSymbolVector, mlir::Location>>
923 declareCommonBlock(Fortran::lower::AbstractConverter &converter,
924                    const Fortran::semantics::Symbol &common,
925                    std::size_t commonSize) {
926   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
927   std::string commonName = Fortran::lower::mangle::mangleName(common);
928   fir::GlobalOp global = builder.getNamedGlobal(commonName);
929   if (global)
930     return std::nullopt;
931   Fortran::semantics::MutableSymbolVector cmnBlkMems =
932       getCommonMembersWithInitAliases(common);
933   mlir::Location loc = converter.genLocation(common.name());
934   mlir::StringAttr linkage = builder.createCommonLinkage();
935   if (!commonBlockHasInit(cmnBlkMems)) {
936     // A COMMON block sans initializers is initialized to zero.
937     // mlir::Vector types must have a strictly positive size, so at least
938     // temporarily, force a zero size COMMON block to have one byte.
939     const auto sz =
940         static_cast<fir::SequenceType::Extent>(commonSize > 0 ? commonSize : 1);
941     fir::SequenceType::Shape shape = {sz};
942     mlir::IntegerType i8Ty = builder.getIntegerType(8);
943     auto commonTy = fir::SequenceType::get(shape, i8Ty);
944     auto vecTy = mlir::VectorType::get(sz, i8Ty);
945     mlir::Attribute zero = builder.getIntegerAttr(i8Ty, 0);
946     auto init = mlir::DenseElementsAttr::get(vecTy, llvm::makeArrayRef(zero));
947     builder.createGlobal(loc, commonTy, commonName, linkage, init);
948     // No need to add any initial value later.
949     return std::nullopt;
950   }
951   // COMMON block with initializer (note that initialized blank common are
952   // accepted as an extension by semantics). Sort members by offset before
953   // generating the type and initializer.
954   std::sort(cmnBlkMems.begin(), cmnBlkMems.end(),
955             [](auto &s1, auto &s2) { return s1->offset() < s2->offset(); });
956   mlir::TupleType commonTy =
957       getTypeOfCommonWithInit(converter, cmnBlkMems, commonSize);
958   // Create the global object, the initial value will be added later.
959   global = builder.createGlobal(loc, commonTy, commonName);
960   return std::make_tuple(global, std::move(cmnBlkMems), loc);
961 }
962 
963 /// Add initial value to a COMMON block fir::GlobalOp \p global given the list
964 /// \p cmnBlkMems of the common block member symbols that contains symbols with
965 /// an initial value.
966 static void finalizeCommonBlockDefinition(
967     mlir::Location loc, Fortran::lower::AbstractConverter &converter,
968     fir::GlobalOp global,
969     const Fortran::semantics::MutableSymbolVector &cmnBlkMems) {
970   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
971   mlir::TupleType commonTy = global.getType().cast<mlir::TupleType>();
972   auto initFunc = [&](fir::FirOpBuilder &builder) {
973     mlir::IndexType idxTy = builder.getIndexType();
974     mlir::Value cb = builder.create<fir::UndefOp>(loc, commonTy);
975     unsigned tupIdx = 0;
976     std::size_t offset = 0;
977     LLVM_DEBUG(llvm::dbgs() << "block {\n");
978     for (const Fortran::semantics::MutableSymbolRef &mem : cmnBlkMems) {
979       if (const auto *memDet =
980               mem->detailsIf<Fortran::semantics::ObjectEntityDetails>()) {
981         if (mem->offset() > offset) {
982           ++tupIdx;
983           offset = mem->offset();
984         }
985         if (memDet->init()) {
986           LLVM_DEBUG(llvm::dbgs()
987                      << "offset: " << mem->offset() << " is " << *mem << '\n');
988           Fortran::lower::StatementContext stmtCtx;
989           auto initExpr = memDet->init().value();
990           fir::ExtendedValue initVal =
991               Fortran::semantics::IsPointer(*mem)
992                   ? Fortran::lower::genInitialDataTarget(
993                         converter, loc, converter.genType(*mem), initExpr)
994                   : genInitializerExprValue(converter, loc, initExpr, stmtCtx);
995           mlir::IntegerAttr offVal = builder.getIntegerAttr(idxTy, tupIdx);
996           mlir::Value castVal = builder.createConvert(
997               loc, commonTy.getType(tupIdx), fir::getBase(initVal));
998           cb = builder.create<fir::InsertValueOp>(loc, commonTy, cb, castVal,
999                                                   builder.getArrayAttr(offVal));
1000           ++tupIdx;
1001           offset = mem->offset() + mem->size();
1002         }
1003       }
1004     }
1005     LLVM_DEBUG(llvm::dbgs() << "}\n");
1006     builder.create<fir::HasValueOp>(loc, cb);
1007   };
1008   createGlobalInitialization(builder, global, initFunc);
1009 }
1010 
1011 void Fortran::lower::defineCommonBlocks(
1012     Fortran::lower::AbstractConverter &converter,
1013     const Fortran::semantics::CommonBlockList &commonBlocks) {
1014   // Common blocks may depend on another common block address (if they contain
1015   // pointers with initial targets). To cover this case, create all common block
1016   // fir::Global before creating the initial values (if any).
1017   std::vector<std::tuple<fir::GlobalOp, Fortran::semantics::MutableSymbolVector,
1018                          mlir::Location>>
1019       delayedInitializations;
1020   for (const auto &[common, size] : commonBlocks)
1021     if (auto delayedInit = declareCommonBlock(converter, common, size))
1022       delayedInitializations.emplace_back(std::move(*delayedInit));
1023   for (auto &[global, cmnBlkMems, loc] : delayedInitializations)
1024     finalizeCommonBlockDefinition(loc, converter, global, cmnBlkMems);
1025 }
1026 
1027 /// The COMMON block is a global structure. `var` will be at some offset
1028 /// within the COMMON block. Adds the address of `var` (COMMON + offset) to
1029 /// the symbol map.
1030 static void instantiateCommon(Fortran::lower::AbstractConverter &converter,
1031                               const Fortran::semantics::Symbol &common,
1032                               const Fortran::lower::pft::Variable &var,
1033                               Fortran::lower::SymMap &symMap) {
1034   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
1035   const Fortran::semantics::Symbol &varSym = var.getSymbol();
1036   mlir::Location loc = converter.genLocation(varSym.name());
1037 
1038   mlir::Value commonAddr;
1039   if (Fortran::lower::SymbolBox symBox = symMap.lookupSymbol(common))
1040     commonAddr = symBox.getAddr();
1041   if (!commonAddr) {
1042     // introduce a local AddrOf and add it to the map
1043     fir::GlobalOp global = getCommonBlockGlobal(converter, common);
1044     commonAddr = builder.create<fir::AddrOfOp>(loc, global.resultType(),
1045                                                global.getSymbol());
1046 
1047     symMap.addSymbol(common, commonAddr);
1048   }
1049   std::size_t byteOffset = varSym.GetUltimate().offset();
1050   mlir::IntegerType i8Ty = builder.getIntegerType(8);
1051   mlir::Type i8Ptr = builder.getRefType(i8Ty);
1052   mlir::Type seqTy = builder.getRefType(builder.getVarLenSeqTy(i8Ty));
1053   mlir::Value base = builder.createConvert(loc, seqTy, commonAddr);
1054   mlir::Value offs =
1055       builder.createIntegerConstant(loc, builder.getIndexType(), byteOffset);
1056   auto varAddr = builder.create<fir::CoordinateOp>(loc, i8Ptr, base,
1057                                                    mlir::ValueRange{offs});
1058   mlir::Type symType = converter.genType(var.getSymbol());
1059   mlir::Value local;
1060   if (Fortran::semantics::FindEquivalenceSet(var.getSymbol()) != nullptr)
1061     local = castAliasToPointer(builder, loc, symType, varAddr);
1062   else
1063     local = builder.createConvert(loc, builder.getRefType(symType), varAddr);
1064   Fortran::lower::StatementContext stmtCtx;
1065   mapSymbolAttributes(converter, var, symMap, stmtCtx, local);
1066 }
1067 
1068 //===--------------------------------------------------------------===//
1069 // Lower Variables specification expressions and attributes
1070 //===--------------------------------------------------------------===//
1071 
1072 /// Helper to decide if a dummy argument must be tracked in an BoxValue.
1073 static bool lowerToBoxValue(const Fortran::semantics::Symbol &sym,
1074                             mlir::Value dummyArg) {
1075   // Only dummy arguments coming as fir.box can be tracked in an BoxValue.
1076   if (!dummyArg || !dummyArg.getType().isa<fir::BoxType>())
1077     return false;
1078   // Non contiguous arrays must be tracked in an BoxValue.
1079   if (sym.Rank() > 0 && !sym.attrs().test(Fortran::semantics::Attr::CONTIGUOUS))
1080     return true;
1081   // Assumed rank and optional fir.box cannot yet be read while lowering the
1082   // specifications.
1083   if (Fortran::evaluate::IsAssumedRank(sym) ||
1084       Fortran::semantics::IsOptional(sym))
1085     return true;
1086   // Polymorphic entity should be tracked through a fir.box that has the
1087   // dynamic type info.
1088   if (const Fortran::semantics::DeclTypeSpec *type = sym.GetType())
1089     if (type->IsPolymorphic())
1090       return true;
1091   return false;
1092 }
1093 
1094 /// Compute extent from lower and upper bound.
1095 static mlir::Value computeExtent(fir::FirOpBuilder &builder, mlir::Location loc,
1096                                  mlir::Value lb, mlir::Value ub) {
1097   mlir::IndexType idxTy = builder.getIndexType();
1098   // Let the folder deal with the common `ub - <const> + 1` case.
1099   auto diff = builder.create<mlir::arith::SubIOp>(loc, idxTy, ub, lb);
1100   mlir::Value one = builder.createIntegerConstant(loc, idxTy, 1);
1101   auto rawExtent = builder.create<mlir::arith::AddIOp>(loc, idxTy, diff, one);
1102   return fir::factory::genMaxWithZero(builder, loc, rawExtent);
1103 }
1104 
1105 /// Lower explicit lower bounds into \p result. Does nothing if this is not an
1106 /// array, or if the lower bounds are deferred, or all implicit or one.
1107 static void lowerExplicitLowerBounds(
1108     Fortran::lower::AbstractConverter &converter, mlir::Location loc,
1109     const Fortran::lower::BoxAnalyzer &box,
1110     llvm::SmallVectorImpl<mlir::Value> &result, Fortran::lower::SymMap &symMap,
1111     Fortran::lower::StatementContext &stmtCtx) {
1112   if (!box.isArray() || box.lboundIsAllOnes())
1113     return;
1114   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
1115   mlir::IndexType idxTy = builder.getIndexType();
1116   if (box.isStaticArray()) {
1117     for (int64_t lb : box.staticLBound())
1118       result.emplace_back(builder.createIntegerConstant(loc, idxTy, lb));
1119     return;
1120   }
1121   for (const Fortran::semantics::ShapeSpec *spec : box.dynamicBound()) {
1122     if (auto low = spec->lbound().GetExplicit()) {
1123       auto expr = Fortran::lower::SomeExpr{*low};
1124       mlir::Value lb = builder.createConvert(
1125           loc, idxTy, genScalarValue(converter, loc, expr, symMap, stmtCtx));
1126       result.emplace_back(lb);
1127     }
1128   }
1129   assert(result.empty() || result.size() == box.dynamicBound().size());
1130 }
1131 
1132 /// Lower explicit extents into \p result if this is an explicit-shape or
1133 /// assumed-size array. Does nothing if this is not an explicit-shape or
1134 /// assumed-size array.
1135 static void
1136 lowerExplicitExtents(Fortran::lower::AbstractConverter &converter,
1137                      mlir::Location loc, const Fortran::lower::BoxAnalyzer &box,
1138                      llvm::SmallVectorImpl<mlir::Value> &lowerBounds,
1139                      llvm::SmallVectorImpl<mlir::Value> &result,
1140                      Fortran::lower::SymMap &symMap,
1141                      Fortran::lower::StatementContext &stmtCtx) {
1142   if (!box.isArray())
1143     return;
1144   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
1145   mlir::IndexType idxTy = builder.getIndexType();
1146   if (box.isStaticArray()) {
1147     for (int64_t extent : box.staticShape())
1148       result.emplace_back(builder.createIntegerConstant(loc, idxTy, extent));
1149     return;
1150   }
1151   for (const auto &spec : llvm::enumerate(box.dynamicBound())) {
1152     if (auto up = spec.value()->ubound().GetExplicit()) {
1153       auto expr = Fortran::lower::SomeExpr{*up};
1154       mlir::Value ub = builder.createConvert(
1155           loc, idxTy, genScalarValue(converter, loc, expr, symMap, stmtCtx));
1156       if (lowerBounds.empty())
1157         result.emplace_back(fir::factory::genMaxWithZero(builder, loc, ub));
1158       else
1159         result.emplace_back(
1160             computeExtent(builder, loc, lowerBounds[spec.index()], ub));
1161     } else if (spec.value()->ubound().isStar()) {
1162       // Assumed extent is undefined. Must be provided by user's code.
1163       result.emplace_back(builder.create<fir::UndefOp>(loc, idxTy));
1164     }
1165   }
1166   assert(result.empty() || result.size() == box.dynamicBound().size());
1167 }
1168 
1169 /// Lower explicit character length if any. Return empty mlir::Value if no
1170 /// explicit length.
1171 static mlir::Value
1172 lowerExplicitCharLen(Fortran::lower::AbstractConverter &converter,
1173                      mlir::Location loc, const Fortran::lower::BoxAnalyzer &box,
1174                      Fortran::lower::SymMap &symMap,
1175                      Fortran::lower::StatementContext &stmtCtx) {
1176   if (!box.isChar())
1177     return mlir::Value{};
1178   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
1179   mlir::Type lenTy = builder.getCharacterLengthType();
1180   if (llvm::Optional<int64_t> len = box.getCharLenConst())
1181     return builder.createIntegerConstant(loc, lenTy, *len);
1182   if (llvm::Optional<Fortran::lower::SomeExpr> lenExpr = box.getCharLenExpr())
1183     // If the length expression is negative, the length is zero. See F2018
1184     // 7.4.4.2 point 5.
1185     return fir::factory::genMaxWithZero(
1186         builder, loc,
1187         genScalarValue(converter, loc, *lenExpr, symMap, stmtCtx));
1188   return mlir::Value{};
1189 }
1190 
1191 /// Treat negative values as undefined. Assumed size arrays will return -1 from
1192 /// the front end for example. Using negative values can produce hard to find
1193 /// bugs much further along in the compilation.
1194 static mlir::Value genExtentValue(fir::FirOpBuilder &builder,
1195                                   mlir::Location loc, mlir::Type idxTy,
1196                                   long frontEndExtent) {
1197   if (frontEndExtent >= 0)
1198     return builder.createIntegerConstant(loc, idxTy, frontEndExtent);
1199   return builder.create<fir::UndefOp>(loc, idxTy);
1200 }
1201 
1202 /// If a symbol is an array, it may have been declared with unknown extent
1203 /// parameters (e.g., `*`), but if it has an initial value then the actual size
1204 /// may be available from the initial array value's type.
1205 inline static llvm::SmallVector<std::int64_t>
1206 recoverShapeVector(llvm::ArrayRef<std::int64_t> shapeVec, mlir::Value initVal) {
1207   llvm::SmallVector<std::int64_t> result;
1208   if (initVal) {
1209     if (auto seqTy = fir::unwrapUntilSeqType(initVal.getType())) {
1210       for (auto [fst, snd] : llvm::zip(shapeVec, seqTy.getShape()))
1211         result.push_back(fst == fir::SequenceType::getUnknownExtent() ? snd
1212                                                                       : fst);
1213       return result;
1214     }
1215   }
1216   result.assign(shapeVec.begin(), shapeVec.end());
1217   return result;
1218 }
1219 
1220 /// Lower specification expressions and attributes of variable \p var and
1221 /// add it to the symbol map.  For a global or an alias, the address must be
1222 /// pre-computed and provided in \p preAlloc.  A dummy argument for the current
1223 /// entry point has already been mapped to an mlir block argument in
1224 /// mapDummiesAndResults.  Its mapping may be updated here.
1225 void Fortran::lower::mapSymbolAttributes(
1226     AbstractConverter &converter, const Fortran::lower::pft::Variable &var,
1227     Fortran::lower::SymMap &symMap, Fortran::lower::StatementContext &stmtCtx,
1228     mlir::Value preAlloc) {
1229   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
1230   const Fortran::semantics::Symbol &sym = var.getSymbol();
1231   const mlir::Location loc = converter.genLocation(sym.name());
1232   mlir::IndexType idxTy = builder.getIndexType();
1233   const bool isDeclaredDummy = Fortran::semantics::IsDummy(sym);
1234   // An active dummy from the current entry point.
1235   const bool isDummy = isDeclaredDummy && symMap.lookupSymbol(sym).getAddr();
1236   // An unused dummy from another entry point.
1237   const bool isUnusedEntryDummy = isDeclaredDummy && !isDummy;
1238   const bool isResult = Fortran::semantics::IsFunctionResult(sym);
1239   const bool replace = isDummy || isResult;
1240   fir::factory::CharacterExprHelper charHelp{builder, loc};
1241 
1242   if (Fortran::semantics::IsProcedure(sym)) {
1243     if (isUnusedEntryDummy) {
1244       // Additional discussion below.
1245       mlir::Type dummyProcType =
1246           Fortran::lower::getDummyProcedureType(sym, converter);
1247       mlir::Value undefOp = builder.create<fir::UndefOp>(loc, dummyProcType);
1248       symMap.addSymbol(sym, undefOp);
1249     }
1250     if (Fortran::semantics::IsPointer(sym))
1251       TODO(loc, "procedure pointers");
1252     return;
1253   }
1254 
1255   Fortran::lower::BoxAnalyzer ba;
1256   ba.analyze(sym);
1257 
1258   // First deal with pointers and allocatables, because their handling here
1259   // is the same regardless of their rank.
1260   if (Fortran::semantics::IsAllocatableOrPointer(sym)) {
1261     // Get address of fir.box describing the entity.
1262     // global
1263     mlir::Value boxAlloc = preAlloc;
1264     // dummy or passed result
1265     if (!boxAlloc)
1266       if (Fortran::lower::SymbolBox symbox = symMap.lookupSymbol(sym))
1267         boxAlloc = symbox.getAddr();
1268     // local
1269     if (!boxAlloc)
1270       boxAlloc = createNewLocal(converter, loc, var, preAlloc);
1271     // Lower non deferred parameters.
1272     llvm::SmallVector<mlir::Value> nonDeferredLenParams;
1273     if (ba.isChar()) {
1274       if (mlir::Value len =
1275               lowerExplicitCharLen(converter, loc, ba, symMap, stmtCtx))
1276         nonDeferredLenParams.push_back(len);
1277       else if (Fortran::semantics::IsAssumedLengthCharacter(sym))
1278         TODO(loc, "assumed length character allocatable");
1279     } else if (const Fortran::semantics::DeclTypeSpec *declTy = sym.GetType()) {
1280       if (const Fortran::semantics::DerivedTypeSpec *derived =
1281               declTy->AsDerived())
1282         if (Fortran::semantics::CountLenParameters(*derived) != 0)
1283           TODO(loc,
1284                "derived type allocatable or pointer with length parameters");
1285     }
1286     fir::MutableBoxValue box = Fortran::lower::createMutableBox(
1287         converter, loc, var, boxAlloc, nonDeferredLenParams);
1288     symMap.addAllocatableOrPointer(var.getSymbol(), box, replace);
1289     return;
1290   }
1291 
1292   if (isDummy) {
1293     mlir::Value dummyArg = symMap.lookupSymbol(sym).getAddr();
1294     if (lowerToBoxValue(sym, dummyArg)) {
1295       llvm::SmallVector<mlir::Value> lbounds;
1296       llvm::SmallVector<mlir::Value> explicitExtents;
1297       llvm::SmallVector<mlir::Value> explicitParams;
1298       // Lower lower bounds, explicit type parameters and explicit
1299       // extents if any.
1300       if (ba.isChar())
1301         if (mlir::Value len =
1302                 lowerExplicitCharLen(converter, loc, ba, symMap, stmtCtx))
1303           explicitParams.push_back(len);
1304       // TODO: derived type length parameters.
1305       lowerExplicitLowerBounds(converter, loc, ba, lbounds, symMap, stmtCtx);
1306       lowerExplicitExtents(converter, loc, ba, lbounds, explicitExtents, symMap,
1307                            stmtCtx);
1308       symMap.addBoxSymbol(sym, dummyArg, lbounds, explicitParams,
1309                           explicitExtents, replace);
1310       return;
1311     }
1312   }
1313 
1314   // A dummy from another entry point that is not declared in the current
1315   // entry point requires a skeleton definition.  Most such "unused" dummies
1316   // will not survive into final generated code, but some will.  It is illegal
1317   // to reference one at run time if it does.  Such a dummy is mapped to a
1318   // value in one of three ways:
1319   //
1320   //  - Generate a fir::UndefOp value.  This is lightweight, easy to clean up,
1321   //    and often valid, but it may fail for a dummy with dynamic bounds,
1322   //    or a dummy used to define another dummy.  Information to distinguish
1323   //    valid cases is not generally available here, with the exception of
1324   //    dummy procedures.  See the first function exit above.
1325   //
1326   //  - Allocate an uninitialized stack slot.  This is an intermediate-weight
1327   //    solution that is harder to clean up.  It is often valid, but may fail
1328   //    for an object with dynamic bounds.  This option is "automatically"
1329   //    used by default for cases that do not use one of the other options.
1330   //
1331   //  - Allocate a heap box/descriptor, initialized to zero.  This always
1332   //    works, but is more heavyweight and harder to clean up.  It is used
1333   //    for dynamic objects via calls to genUnusedEntryPointBox.
1334 
1335   auto genUnusedEntryPointBox = [&]() {
1336     if (isUnusedEntryDummy) {
1337       assert(!Fortran::semantics::IsAllocatableOrPointer(sym) &&
1338              "handled above");
1339       // The box is read right away because lowering code does not expect
1340       // a non pointer/allocatable symbol to be mapped to a MutableBox.
1341       symMap.addSymbol(sym, fir::factory::genMutableBoxRead(
1342                                 builder, loc,
1343                                 fir::factory::createTempMutableBox(
1344                                     builder, loc, converter.genType(var))));
1345       return true;
1346     }
1347     return false;
1348   };
1349 
1350   // Helper to generate scalars for the symbol properties.
1351   auto genValue = [&](const Fortran::lower::SomeExpr &expr) {
1352     return genScalarValue(converter, loc, expr, symMap, stmtCtx);
1353   };
1354 
1355   // For symbols reaching this point, all properties are constant and can be
1356   // read/computed already into ssa values.
1357 
1358   // The origin must be \vec{1}.
1359   auto populateShape = [&](auto &shapes, const auto &bounds, mlir::Value box) {
1360     for (auto iter : llvm::enumerate(bounds)) {
1361       auto *spec = iter.value();
1362       assert(spec->lbound().GetExplicit() &&
1363              "lbound must be explicit with constant value 1");
1364       if (auto high = spec->ubound().GetExplicit()) {
1365         Fortran::lower::SomeExpr highEx{*high};
1366         mlir::Value ub = genValue(highEx);
1367         ub = builder.createConvert(loc, idxTy, ub);
1368         shapes.emplace_back(fir::factory::genMaxWithZero(builder, loc, ub));
1369       } else if (spec->ubound().isColon()) {
1370         assert(box && "assumed bounds require a descriptor");
1371         mlir::Value dim =
1372             builder.createIntegerConstant(loc, idxTy, iter.index());
1373         auto dimInfo =
1374             builder.create<fir::BoxDimsOp>(loc, idxTy, idxTy, idxTy, box, dim);
1375         shapes.emplace_back(dimInfo.getResult(1));
1376       } else if (spec->ubound().isStar()) {
1377         shapes.emplace_back(builder.create<fir::UndefOp>(loc, idxTy));
1378       } else {
1379         llvm::report_fatal_error("unknown bound category");
1380       }
1381     }
1382   };
1383 
1384   // The origin is not \vec{1}.
1385   auto populateLBoundsExtents = [&](auto &lbounds, auto &extents,
1386                                     const auto &bounds, mlir::Value box) {
1387     for (auto iter : llvm::enumerate(bounds)) {
1388       auto *spec = iter.value();
1389       fir::BoxDimsOp dimInfo;
1390       mlir::Value ub, lb;
1391       if (spec->lbound().isColon() || spec->ubound().isColon()) {
1392         // This is an assumed shape because allocatables and pointers extents
1393         // are not constant in the scope and are not read here.
1394         assert(box && "deferred bounds require a descriptor");
1395         mlir::Value dim =
1396             builder.createIntegerConstant(loc, idxTy, iter.index());
1397         dimInfo =
1398             builder.create<fir::BoxDimsOp>(loc, idxTy, idxTy, idxTy, box, dim);
1399         extents.emplace_back(dimInfo.getResult(1));
1400         if (auto low = spec->lbound().GetExplicit()) {
1401           auto expr = Fortran::lower::SomeExpr{*low};
1402           mlir::Value lb = builder.createConvert(loc, idxTy, genValue(expr));
1403           lbounds.emplace_back(lb);
1404         } else {
1405           // Implicit lower bound is 1 (Fortran 2018 section 8.5.8.3 point 3.)
1406           lbounds.emplace_back(builder.createIntegerConstant(loc, idxTy, 1));
1407         }
1408       } else {
1409         if (auto low = spec->lbound().GetExplicit()) {
1410           auto expr = Fortran::lower::SomeExpr{*low};
1411           lb = builder.createConvert(loc, idxTy, genValue(expr));
1412         } else {
1413           TODO(loc, "support for assumed rank entities");
1414         }
1415         lbounds.emplace_back(lb);
1416 
1417         if (auto high = spec->ubound().GetExplicit()) {
1418           auto expr = Fortran::lower::SomeExpr{*high};
1419           ub = builder.createConvert(loc, idxTy, genValue(expr));
1420           extents.emplace_back(computeExtent(builder, loc, lb, ub));
1421         } else {
1422           // An assumed size array. The extent is not computed.
1423           assert(spec->ubound().isStar() && "expected assumed size");
1424           extents.emplace_back(builder.create<fir::UndefOp>(loc, idxTy));
1425         }
1426       }
1427     }
1428   };
1429 
1430   // Lower length expression for non deferred and non dummy assumed length
1431   // characters.
1432   auto genExplicitCharLen =
1433       [&](llvm::Optional<Fortran::lower::SomeExpr> charLen) -> mlir::Value {
1434     if (!charLen)
1435       fir::emitFatalError(loc, "expected explicit character length");
1436     mlir::Value rawLen = genValue(*charLen);
1437     // If the length expression is negative, the length is zero. See
1438     // F2018 7.4.4.2 point 5.
1439     return fir::factory::genMaxWithZero(builder, loc, rawLen);
1440   };
1441 
1442   ba.match(
1443       //===--------------------------------------------------------------===//
1444       // Trivial case.
1445       //===--------------------------------------------------------------===//
1446       [&](const Fortran::lower::details::ScalarSym &) {
1447         if (isDummy) {
1448           // This is an argument.
1449           if (!symMap.lookupSymbol(sym))
1450             mlir::emitError(loc, "symbol \"")
1451                 << toStringRef(sym.name()) << "\" must already be in map";
1452           return;
1453         } else if (isResult) {
1454           // Some Fortran results may be passed by argument (e.g. derived
1455           // types)
1456           if (symMap.lookupSymbol(sym))
1457             return;
1458         }
1459         // Otherwise, it's a local variable or function result.
1460         mlir::Value local = createNewLocal(converter, loc, var, preAlloc);
1461         symMap.addSymbol(sym, local);
1462       },
1463 
1464       //===--------------------------------------------------------------===//
1465       // The non-trivial cases are when we have an argument or local that has
1466       // a repetition value. Arguments might be passed as simple pointers and
1467       // need to be cast to a multi-dimensional array with constant bounds
1468       // (possibly with a missing column), bounds computed in the callee
1469       // (here), or with bounds from the caller (boxed somewhere else). Locals
1470       // have the same properties except they are never boxed arguments from
1471       // the caller and never having a missing column size.
1472       //===--------------------------------------------------------------===//
1473 
1474       [&](const Fortran::lower::details::ScalarStaticChar &x) {
1475         // type is a CHARACTER, determine the LEN value
1476         auto charLen = x.charLen();
1477         if (replace) {
1478           Fortran::lower::SymbolBox symBox = symMap.lookupSymbol(sym);
1479           std::pair<mlir::Value, mlir::Value> unboxchar =
1480               charHelp.createUnboxChar(symBox.getAddr());
1481           mlir::Value boxAddr = unboxchar.first;
1482           // Set/override LEN with a constant
1483           mlir::Value len = builder.createIntegerConstant(loc, idxTy, charLen);
1484           symMap.addCharSymbol(sym, boxAddr, len, true);
1485           return;
1486         }
1487         mlir::Value len = builder.createIntegerConstant(loc, idxTy, charLen);
1488         if (preAlloc) {
1489           symMap.addCharSymbol(sym, preAlloc, len);
1490           return;
1491         }
1492         mlir::Value local = createNewLocal(converter, loc, var, preAlloc);
1493         symMap.addCharSymbol(sym, local, len);
1494       },
1495 
1496       //===--------------------------------------------------------------===//
1497 
1498       [&](const Fortran::lower::details::ScalarDynamicChar &x) {
1499         if (genUnusedEntryPointBox())
1500           return;
1501         // type is a CHARACTER, determine the LEN value
1502         auto charLen = x.charLen();
1503         if (replace) {
1504           Fortran::lower::SymbolBox symBox = symMap.lookupSymbol(sym);
1505           mlir::Value boxAddr = symBox.getAddr();
1506           mlir::Value len;
1507           mlir::Type addrTy = boxAddr.getType();
1508           if (addrTy.isa<fir::BoxCharType>() || addrTy.isa<fir::BoxType>())
1509             std::tie(boxAddr, len) = charHelp.createUnboxChar(symBox.getAddr());
1510           // Override LEN with an expression
1511           if (charLen)
1512             len = genExplicitCharLen(charLen);
1513           symMap.addCharSymbol(sym, boxAddr, len, true);
1514           return;
1515         }
1516         // local CHARACTER variable
1517         mlir::Value len = genExplicitCharLen(charLen);
1518         if (preAlloc) {
1519           symMap.addCharSymbol(sym, preAlloc, len);
1520           return;
1521         }
1522         llvm::SmallVector<mlir::Value> lengths = {len};
1523         mlir::Value local =
1524             createNewLocal(converter, loc, var, preAlloc, llvm::None, lengths);
1525         symMap.addCharSymbol(sym, local, len);
1526       },
1527 
1528       //===--------------------------------------------------------------===//
1529 
1530       [&](const Fortran::lower::details::StaticArray &x) {
1531         // object shape is constant, not a character
1532         mlir::Type castTy = builder.getRefType(converter.genType(var));
1533         mlir::Value addr = symMap.lookupSymbol(sym).getAddr();
1534         if (addr)
1535           addr = builder.createConvert(loc, castTy, addr);
1536         if (x.lboundAllOnes()) {
1537           // if lower bounds are all ones, build simple shaped object
1538           llvm::SmallVector<mlir::Value> shape;
1539           for (int64_t i : recoverShapeVector(x.shapes, preAlloc))
1540             shape.push_back(genExtentValue(builder, loc, idxTy, i));
1541           mlir::Value local =
1542               isDummy ? addr : createNewLocal(converter, loc, var, preAlloc);
1543           symMap.addSymbolWithShape(sym, local, shape, isDummy);
1544           return;
1545         }
1546         // If object is an array process the lower bound and extent values by
1547         // constructing constants and populating the lbounds and extents.
1548         llvm::SmallVector<mlir::Value> extents;
1549         llvm::SmallVector<mlir::Value> lbounds;
1550         for (auto [fst, snd] :
1551              llvm::zip(x.lbounds, recoverShapeVector(x.shapes, preAlloc))) {
1552           lbounds.emplace_back(builder.createIntegerConstant(loc, idxTy, fst));
1553           extents.emplace_back(genExtentValue(builder, loc, idxTy, snd));
1554         }
1555         mlir::Value local =
1556             isDummy ? addr
1557                     : createNewLocal(converter, loc, var, preAlloc, extents);
1558         // Must be a dummy argument, have an explicit shape, or be a PARAMETER.
1559         assert(isDummy || Fortran::lower::isExplicitShape(sym) ||
1560                Fortran::semantics::IsNamedConstant(sym));
1561         symMap.addSymbolWithBounds(sym, local, extents, lbounds, isDummy);
1562       },
1563 
1564       //===--------------------------------------------------------------===//
1565 
1566       [&](const Fortran::lower::details::DynamicArray &x) {
1567         if (genUnusedEntryPointBox())
1568           return;
1569         // cast to the known constant parts from the declaration
1570         mlir::Type varType = converter.genType(var);
1571         mlir::Value addr = symMap.lookupSymbol(sym).getAddr();
1572         mlir::Value argBox;
1573         mlir::Type castTy = builder.getRefType(varType);
1574         if (addr) {
1575           if (auto boxTy = addr.getType().dyn_cast<fir::BoxType>()) {
1576             argBox = addr;
1577             mlir::Type refTy = builder.getRefType(boxTy.getEleTy());
1578             addr = builder.create<fir::BoxAddrOp>(loc, refTy, argBox);
1579           }
1580           addr = builder.createConvert(loc, castTy, addr);
1581         }
1582         if (x.lboundAllOnes()) {
1583           // if lower bounds are all ones, build simple shaped object
1584           llvm::SmallVector<mlir::Value> shapes;
1585           populateShape(shapes, x.bounds, argBox);
1586           if (isDummy) {
1587             symMap.addSymbolWithShape(sym, addr, shapes, true);
1588             return;
1589           }
1590           // local array with computed bounds
1591           assert(Fortran::lower::isExplicitShape(sym) ||
1592                  Fortran::semantics::IsAllocatableOrPointer(sym));
1593           mlir::Value local =
1594               createNewLocal(converter, loc, var, preAlloc, shapes);
1595           symMap.addSymbolWithShape(sym, local, shapes);
1596           return;
1597         }
1598         // if object is an array process the lower bound and extent values
1599         llvm::SmallVector<mlir::Value> extents;
1600         llvm::SmallVector<mlir::Value> lbounds;
1601         populateLBoundsExtents(lbounds, extents, x.bounds, argBox);
1602         if (isDummy) {
1603           symMap.addSymbolWithBounds(sym, addr, extents, lbounds, true);
1604           return;
1605         }
1606         // local array with computed bounds
1607         assert(Fortran::lower::isExplicitShape(sym));
1608         mlir::Value local =
1609             createNewLocal(converter, loc, var, preAlloc, extents);
1610         symMap.addSymbolWithBounds(sym, local, extents, lbounds);
1611       },
1612 
1613       //===--------------------------------------------------------------===//
1614 
1615       [&](const Fortran::lower::details::StaticArrayStaticChar &x) {
1616         // if element type is a CHARACTER, determine the LEN value
1617         auto charLen = x.charLen();
1618         mlir::Value addr;
1619         mlir::Value len;
1620         if (isDummy) {
1621           Fortran::lower::SymbolBox symBox = symMap.lookupSymbol(sym);
1622           std::pair<mlir::Value, mlir::Value> unboxchar =
1623               charHelp.createUnboxChar(symBox.getAddr());
1624           addr = unboxchar.first;
1625           // Set/override LEN with a constant
1626           len = builder.createIntegerConstant(loc, idxTy, charLen);
1627         } else {
1628           // local CHARACTER variable
1629           len = builder.createIntegerConstant(loc, idxTy, charLen);
1630         }
1631 
1632         // object shape is constant
1633         mlir::Type castTy = builder.getRefType(converter.genType(var));
1634         if (addr)
1635           addr = builder.createConvert(loc, castTy, addr);
1636 
1637         if (x.lboundAllOnes()) {
1638           // if lower bounds are all ones, build simple shaped object
1639           llvm::SmallVector<mlir::Value> shape;
1640           for (int64_t i : recoverShapeVector(x.shapes, preAlloc))
1641             shape.push_back(genExtentValue(builder, loc, idxTy, i));
1642           mlir::Value local =
1643               isDummy ? addr : createNewLocal(converter, loc, var, preAlloc);
1644           symMap.addCharSymbolWithShape(sym, local, len, shape, isDummy);
1645           return;
1646         }
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         // construct constants and populate `bounds`
1652         for (auto [fst, snd] :
1653              llvm::zip(x.lbounds, recoverShapeVector(x.shapes, preAlloc))) {
1654           lbounds.emplace_back(builder.createIntegerConstant(loc, idxTy, fst));
1655           extents.emplace_back(genExtentValue(builder, loc, idxTy, snd));
1656         }
1657 
1658         if (isDummy) {
1659           symMap.addCharSymbolWithBounds(sym, addr, len, extents, lbounds,
1660                                          true);
1661           return;
1662         }
1663         // local CHARACTER array with computed bounds
1664         assert(Fortran::lower::isExplicitShape(sym));
1665         mlir::Value local =
1666             createNewLocal(converter, loc, var, preAlloc, extents);
1667         symMap.addCharSymbolWithBounds(sym, local, len, extents, lbounds);
1668       },
1669 
1670       //===--------------------------------------------------------------===//
1671 
1672       [&](const Fortran::lower::details::StaticArrayDynamicChar &x) {
1673         if (genUnusedEntryPointBox())
1674           return;
1675         mlir::Value addr;
1676         mlir::Value len;
1677         [[maybe_unused]] bool mustBeDummy = false;
1678         auto charLen = x.charLen();
1679         // if element type is a CHARACTER, determine the LEN value
1680         if (isDummy) {
1681           Fortran::lower::SymbolBox symBox = symMap.lookupSymbol(sym);
1682           std::pair<mlir::Value, mlir::Value> unboxchar =
1683               charHelp.createUnboxChar(symBox.getAddr());
1684           addr = unboxchar.first;
1685           if (charLen) {
1686             // Set/override LEN with an expression
1687             len = genExplicitCharLen(charLen);
1688           } else {
1689             // LEN is from the boxchar
1690             len = unboxchar.second;
1691             mustBeDummy = true;
1692           }
1693         } else {
1694           // local CHARACTER variable
1695           len = genExplicitCharLen(charLen);
1696         }
1697         llvm::SmallVector<mlir::Value> lengths = {len};
1698 
1699         // cast to the known constant parts from the declaration
1700         mlir::Type castTy = builder.getRefType(converter.genType(var));
1701         if (addr)
1702           addr = builder.createConvert(loc, castTy, addr);
1703 
1704         if (x.lboundAllOnes()) {
1705           // if lower bounds are all ones, build simple shaped object
1706           llvm::SmallVector<mlir::Value> shape;
1707           for (int64_t i : recoverShapeVector(x.shapes, preAlloc))
1708             shape.push_back(genExtentValue(builder, loc, idxTy, i));
1709           if (isDummy) {
1710             symMap.addCharSymbolWithShape(sym, addr, len, shape, true);
1711             return;
1712           }
1713           // local CHARACTER array with constant size
1714           mlir::Value local = createNewLocal(converter, loc, var, preAlloc,
1715                                              llvm::None, lengths);
1716           symMap.addCharSymbolWithShape(sym, local, len, shape);
1717           return;
1718         }
1719 
1720         // if object is an array process the lower bound and extent values
1721         llvm::SmallVector<mlir::Value> extents;
1722         llvm::SmallVector<mlir::Value> lbounds;
1723 
1724         // construct constants and populate `bounds`
1725         for (auto [fst, snd] :
1726              llvm::zip(x.lbounds, recoverShapeVector(x.shapes, preAlloc))) {
1727           lbounds.emplace_back(builder.createIntegerConstant(loc, idxTy, fst));
1728           extents.emplace_back(genExtentValue(builder, loc, idxTy, snd));
1729         }
1730         if (isDummy) {
1731           symMap.addCharSymbolWithBounds(sym, addr, len, extents, lbounds,
1732                                          true);
1733           return;
1734         }
1735         // local CHARACTER array with computed bounds
1736         assert((!mustBeDummy) && (Fortran::lower::isExplicitShape(sym)));
1737         mlir::Value local =
1738             createNewLocal(converter, loc, var, preAlloc, llvm::None, lengths);
1739         symMap.addCharSymbolWithBounds(sym, local, len, extents, lbounds);
1740       },
1741 
1742       //===--------------------------------------------------------------===//
1743 
1744       [&](const Fortran::lower::details::DynamicArrayStaticChar &x) {
1745         if (genUnusedEntryPointBox())
1746           return;
1747         mlir::Value addr;
1748         mlir::Value len;
1749         mlir::Value argBox;
1750         auto charLen = x.charLen();
1751         // if element type is a CHARACTER, determine the LEN value
1752         if (isDummy) {
1753           mlir::Value actualArg = symMap.lookupSymbol(sym).getAddr();
1754           if (auto boxTy = actualArg.getType().dyn_cast<fir::BoxType>()) {
1755             argBox = actualArg;
1756             mlir::Type refTy = builder.getRefType(boxTy.getEleTy());
1757             addr = builder.create<fir::BoxAddrOp>(loc, refTy, argBox);
1758           } else {
1759             addr = charHelp.createUnboxChar(actualArg).first;
1760           }
1761           // Set/override LEN with a constant
1762           len = builder.createIntegerConstant(loc, idxTy, charLen);
1763         } else {
1764           // local CHARACTER variable
1765           len = builder.createIntegerConstant(loc, idxTy, charLen);
1766         }
1767 
1768         // cast to the known constant parts from the declaration
1769         mlir::Type castTy = builder.getRefType(converter.genType(var));
1770         if (addr)
1771           addr = builder.createConvert(loc, castTy, addr);
1772         if (x.lboundAllOnes()) {
1773           // if lower bounds are all ones, build simple shaped object
1774           llvm::SmallVector<mlir::Value> shape;
1775           populateShape(shape, x.bounds, argBox);
1776           if (isDummy) {
1777             symMap.addCharSymbolWithShape(sym, addr, len, shape, true);
1778             return;
1779           }
1780           // local CHARACTER array
1781           mlir::Value local =
1782               createNewLocal(converter, loc, var, preAlloc, shape);
1783           symMap.addCharSymbolWithShape(sym, local, len, shape);
1784           return;
1785         }
1786         // if object is an array process the lower bound and extent values
1787         llvm::SmallVector<mlir::Value> extents;
1788         llvm::SmallVector<mlir::Value> lbounds;
1789         populateLBoundsExtents(lbounds, extents, x.bounds, argBox);
1790         if (isDummy) {
1791           symMap.addCharSymbolWithBounds(sym, addr, len, extents, lbounds,
1792                                          true);
1793           return;
1794         }
1795         // local CHARACTER array with computed bounds
1796         assert(Fortran::lower::isExplicitShape(sym));
1797         mlir::Value local =
1798             createNewLocal(converter, loc, var, preAlloc, extents);
1799         symMap.addCharSymbolWithBounds(sym, local, len, extents, lbounds);
1800       },
1801 
1802       //===--------------------------------------------------------------===//
1803 
1804       [&](const Fortran::lower::details::DynamicArrayDynamicChar &x) {
1805         if (genUnusedEntryPointBox())
1806           return;
1807         mlir::Value addr;
1808         mlir::Value len;
1809         mlir::Value argBox;
1810         auto charLen = x.charLen();
1811         // if element type is a CHARACTER, determine the LEN value
1812         if (isDummy) {
1813           mlir::Value actualArg = symMap.lookupSymbol(sym).getAddr();
1814           if (auto boxTy = actualArg.getType().dyn_cast<fir::BoxType>()) {
1815             argBox = actualArg;
1816             mlir::Type refTy = builder.getRefType(boxTy.getEleTy());
1817             addr = builder.create<fir::BoxAddrOp>(loc, refTy, argBox);
1818             if (charLen)
1819               // Set/override LEN with an expression.
1820               len = genExplicitCharLen(charLen);
1821             else
1822               // Get the length from the actual arguments.
1823               len = charHelp.readLengthFromBox(argBox);
1824           } else {
1825             std::pair<mlir::Value, mlir::Value> unboxchar =
1826                 charHelp.createUnboxChar(actualArg);
1827             addr = unboxchar.first;
1828             if (charLen) {
1829               // Set/override LEN with an expression
1830               len = genExplicitCharLen(charLen);
1831             } else {
1832               // Get the length from the actual arguments.
1833               len = unboxchar.second;
1834             }
1835           }
1836         } else {
1837           // local CHARACTER variable
1838           len = genExplicitCharLen(charLen);
1839         }
1840         llvm::SmallVector<mlir::Value> lengths = {len};
1841 
1842         // cast to the known constant parts from the declaration
1843         mlir::Type castTy = builder.getRefType(converter.genType(var));
1844         if (addr)
1845           addr = builder.createConvert(loc, castTy, addr);
1846         if (x.lboundAllOnes()) {
1847           // if lower bounds are all ones, build simple shaped object
1848           llvm::SmallVector<mlir::Value> shape;
1849           populateShape(shape, x.bounds, argBox);
1850           if (isDummy) {
1851             symMap.addCharSymbolWithShape(sym, addr, len, shape, true);
1852             return;
1853           }
1854           // local CHARACTER array
1855           mlir::Value local =
1856               createNewLocal(converter, loc, var, preAlloc, shape, lengths);
1857           symMap.addCharSymbolWithShape(sym, local, len, shape);
1858           return;
1859         }
1860         // Process the lower bound and extent values.
1861         llvm::SmallVector<mlir::Value> extents;
1862         llvm::SmallVector<mlir::Value> lbounds;
1863         populateLBoundsExtents(lbounds, extents, x.bounds, argBox);
1864         if (isDummy) {
1865           symMap.addCharSymbolWithBounds(sym, addr, len, extents, lbounds,
1866                                          true);
1867           return;
1868         }
1869         // local CHARACTER array with computed bounds
1870         assert(Fortran::lower::isExplicitShape(sym));
1871         mlir::Value local =
1872             createNewLocal(converter, loc, var, preAlloc, extents, lengths);
1873         symMap.addCharSymbolWithBounds(sym, local, len, extents, lbounds);
1874       },
1875 
1876       //===--------------------------------------------------------------===//
1877 
1878       [&](const Fortran::lower::BoxAnalyzer::None &) {
1879         mlir::emitError(loc, "symbol analysis failed on ")
1880             << toStringRef(sym.name());
1881       });
1882 }
1883 
1884 void Fortran::lower::defineModuleVariable(
1885     AbstractConverter &converter, const Fortran::lower::pft::Variable &var) {
1886   // Use empty linkage for module variables, which makes them available
1887   // for use in another unit.
1888   mlir::StringAttr linkage =
1889       getLinkageAttribute(converter.getFirOpBuilder(), var);
1890   if (!var.isGlobal())
1891     fir::emitFatalError(converter.getCurrentLocation(),
1892                         "attempting to lower module variable as local");
1893   // Define aggregate storages for equivalenced objects.
1894   if (var.isAggregateStore()) {
1895     const Fortran::lower::pft::Variable::AggregateStore &aggregate =
1896         var.getAggregateStore();
1897     std::string aggName = mangleGlobalAggregateStore(aggregate);
1898     defineGlobalAggregateStore(converter, aggregate, aggName, linkage);
1899     return;
1900   }
1901   const Fortran::semantics::Symbol &sym = var.getSymbol();
1902   if (const Fortran::semantics::Symbol *common =
1903           Fortran::semantics::FindCommonBlockContaining(var.getSymbol())) {
1904     // Nothing to do, common block are generated before everything. Ensure
1905     // this was done by calling getCommonBlockGlobal.
1906     getCommonBlockGlobal(converter, *common);
1907   } else if (var.isAlias()) {
1908     // Do nothing. Mapping will be done on user side.
1909   } else {
1910     std::string globalName = Fortran::lower::mangle::mangleName(sym);
1911     defineGlobal(converter, var, globalName, linkage);
1912   }
1913 }
1914 
1915 void Fortran::lower::instantiateVariable(AbstractConverter &converter,
1916                                          const pft::Variable &var,
1917                                          Fortran::lower::SymMap &symMap,
1918                                          AggregateStoreMap &storeMap) {
1919   if (var.isAggregateStore()) {
1920     instantiateAggregateStore(converter, var, storeMap);
1921   } else if (const Fortran::semantics::Symbol *common =
1922                  Fortran::semantics::FindCommonBlockContaining(
1923                      var.getSymbol().GetUltimate())) {
1924     instantiateCommon(converter, *common, var, symMap);
1925   } else if (var.isAlias()) {
1926     instantiateAlias(converter, var, symMap, storeMap);
1927   } else if (var.isGlobal()) {
1928     instantiateGlobal(converter, var, symMap);
1929   } else {
1930     instantiateLocal(converter, var, symMap);
1931   }
1932 }
1933 
1934 void Fortran::lower::mapCallInterfaceSymbols(
1935     AbstractConverter &converter, const Fortran::lower::CallerInterface &caller,
1936     SymMap &symMap) {
1937   Fortran::lower::AggregateStoreMap storeMap;
1938   const Fortran::semantics::Symbol &result = caller.getResultSymbol();
1939   for (Fortran::lower::pft::Variable var :
1940        Fortran::lower::pft::buildFuncResultDependencyList(result)) {
1941     if (var.isAggregateStore()) {
1942       instantiateVariable(converter, var, symMap, storeMap);
1943     } else {
1944       const Fortran::semantics::Symbol &sym = var.getSymbol();
1945       const auto *hostDetails =
1946           sym.detailsIf<Fortran::semantics::HostAssocDetails>();
1947       if (hostDetails && !var.isModuleVariable()) {
1948         // The callee is an internal procedure `A` whose result properties
1949         // depend on host variables. The caller may be the host, or another
1950         // internal procedure `B` contained in the same host.  In the first
1951         // case, the host symbol is obviously mapped, in the second case, it
1952         // must also be mapped because
1953         // HostAssociations::internalProcedureBindings that was called when
1954         // lowering `B` will have mapped all host symbols of captured variables
1955         // to the tuple argument containing the composite of all host associated
1956         // variables, whether or not the host symbol is actually referred to in
1957         // `B`. Hence it is possible to simply lookup the variable associated to
1958         // the host symbol without having to go back to the tuple argument.
1959         Fortran::lower::SymbolBox hostValue =
1960             symMap.lookupSymbol(hostDetails->symbol());
1961         assert(hostValue && "callee host symbol must be mapped on caller side");
1962         symMap.addSymbol(sym, hostValue.toExtendedValue());
1963         // The SymbolBox associated to the host symbols is complete, skip
1964         // instantiateVariable that would try to allocate a new storage.
1965         continue;
1966       }
1967       if (Fortran::semantics::IsDummy(sym) && sym.owner() == result.owner()) {
1968         // Get the argument for the dummy argument symbols of the current call.
1969         symMap.addSymbol(sym, caller.getArgumentValue(sym));
1970         // All the properties of the dummy variable may not come from the actual
1971         // argument, let instantiateVariable handle this.
1972       }
1973       // If this is neither a host associated or dummy symbol, it must be a
1974       // module or common block variable to satisfy specification expression
1975       // requirements in 10.1.11, instantiateVariable will get its address and
1976       // properties.
1977       instantiateVariable(converter, var, symMap, storeMap);
1978     }
1979   }
1980 }
1981 
1982 void Fortran::lower::createRuntimeTypeInfoGlobal(
1983     Fortran::lower::AbstractConverter &converter, mlir::Location loc,
1984     const Fortran::semantics::Symbol &typeInfoSym) {
1985   fir::FirOpBuilder &builder = converter.getFirOpBuilder();
1986   std::string globalName = Fortran::lower::mangle::mangleName(typeInfoSym);
1987   auto var = Fortran::lower::pft::Variable(typeInfoSym, /*global=*/true);
1988   mlir::StringAttr linkage = getLinkageAttribute(builder, var);
1989   defineGlobal(converter, var, globalName, linkage);
1990 }
1991