1baa12ddbSEric Schweitz //===-- ConvertType.cpp ---------------------------------------------------===//
2baa12ddbSEric Schweitz //
3baa12ddbSEric Schweitz // Part of the LLVM Project, under the Apache License v2.0 with LLVM Exceptions.
4baa12ddbSEric Schweitz // See https://llvm.org/LICENSE.txt for license information.
5baa12ddbSEric Schweitz // SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception
6baa12ddbSEric Schweitz //
7baa12ddbSEric Schweitz //===----------------------------------------------------------------------===//
8baa12ddbSEric Schweitz 
9baa12ddbSEric Schweitz #include "flang/Lower/ConvertType.h"
102c2e5a5dSValentin Clement #include "flang/Lower/AbstractConverter.h"
119aeb7f03SValentin Clement #include "flang/Lower/CallInterface.h"
129aeb7f03SValentin Clement #include "flang/Lower/ConvertVariable.h"
13589d51eaSValentin Clement #include "flang/Lower/Mangler.h"
14baa12ddbSEric Schweitz #include "flang/Lower/PFTBuilder.h"
15e641c29fSValentin Clement #include "flang/Lower/Support/Utils.h"
165b66cc10SValentin Clement #include "flang/Optimizer/Builder/Todo.h"
17baa12ddbSEric Schweitz #include "flang/Optimizer/Dialect/FIRType.h"
18baa12ddbSEric Schweitz #include "flang/Semantics/tools.h"
19baa12ddbSEric Schweitz #include "flang/Semantics/type.h"
20baa12ddbSEric Schweitz #include "mlir/IR/Builders.h"
2109f7a55fSRiver Riddle #include "mlir/IR/BuiltinTypes.h"
22589d51eaSValentin Clement #include "llvm/Support/Debug.h"
23baa12ddbSEric Schweitz 
24ad40cc14SValentin Clement #define DEBUG_TYPE "flang-lower-type"
25ad40cc14SValentin Clement 
26ad40cc14SValentin Clement //===--------------------------------------------------------------------===//
27ad40cc14SValentin Clement // Intrinsic type translation helpers
28ad40cc14SValentin Clement //===--------------------------------------------------------------------===//
29ad40cc14SValentin Clement 
genRealType(mlir::MLIRContext * context,int kind)300a0b3029SValentin Clement static mlir::Type genRealType(mlir::MLIRContext *context, int kind) {
310a0b3029SValentin Clement   if (Fortran::evaluate::IsValidKindOfIntrinsicType(
320a0b3029SValentin Clement           Fortran::common::TypeCategory::Real, kind)) {
330a0b3029SValentin Clement     switch (kind) {
340a0b3029SValentin Clement     case 2:
350a0b3029SValentin Clement       return mlir::FloatType::getF16(context);
360a0b3029SValentin Clement     case 3:
370a0b3029SValentin Clement       return mlir::FloatType::getBF16(context);
380a0b3029SValentin Clement     case 4:
390a0b3029SValentin Clement       return mlir::FloatType::getF32(context);
400a0b3029SValentin Clement     case 8:
410a0b3029SValentin Clement       return mlir::FloatType::getF64(context);
420a0b3029SValentin Clement     case 10:
430a0b3029SValentin Clement       return mlir::FloatType::getF80(context);
440a0b3029SValentin Clement     case 16:
450a0b3029SValentin Clement       return mlir::FloatType::getF128(context);
460a0b3029SValentin Clement     }
470a0b3029SValentin Clement   }
480a0b3029SValentin Clement   llvm_unreachable("REAL type translation not implemented");
490a0b3029SValentin Clement }
500a0b3029SValentin Clement 
51ad40cc14SValentin Clement template <int KIND>
getIntegerBits()52ad40cc14SValentin Clement int getIntegerBits() {
53ad40cc14SValentin Clement   return Fortran::evaluate::Type<Fortran::common::TypeCategory::Integer,
54ad40cc14SValentin Clement                                  KIND>::Scalar::bits;
55ad40cc14SValentin Clement }
genIntegerType(mlir::MLIRContext * context,int kind)56ad40cc14SValentin Clement static mlir::Type genIntegerType(mlir::MLIRContext *context, int kind) {
57ad40cc14SValentin Clement   if (Fortran::evaluate::IsValidKindOfIntrinsicType(
58ad40cc14SValentin Clement           Fortran::common::TypeCategory::Integer, kind)) {
59ad40cc14SValentin Clement     switch (kind) {
60ad40cc14SValentin Clement     case 1:
61ad40cc14SValentin Clement       return mlir::IntegerType::get(context, getIntegerBits<1>());
62ad40cc14SValentin Clement     case 2:
63ad40cc14SValentin Clement       return mlir::IntegerType::get(context, getIntegerBits<2>());
64ad40cc14SValentin Clement     case 4:
65ad40cc14SValentin Clement       return mlir::IntegerType::get(context, getIntegerBits<4>());
66ad40cc14SValentin Clement     case 8:
67ad40cc14SValentin Clement       return mlir::IntegerType::get(context, getIntegerBits<8>());
68ad40cc14SValentin Clement     case 16:
69ad40cc14SValentin Clement       return mlir::IntegerType::get(context, getIntegerBits<16>());
70ad40cc14SValentin Clement     }
71ad40cc14SValentin Clement   }
72ad40cc14SValentin Clement   llvm_unreachable("INTEGER kind not translated");
73ad40cc14SValentin Clement }
74ad40cc14SValentin Clement 
genLogicalType(mlir::MLIRContext * context,int KIND)75ad40cc14SValentin Clement static mlir::Type genLogicalType(mlir::MLIRContext *context, int KIND) {
76ad40cc14SValentin Clement   if (Fortran::evaluate::IsValidKindOfIntrinsicType(
77ad40cc14SValentin Clement           Fortran::common::TypeCategory::Logical, KIND))
78ad40cc14SValentin Clement     return fir::LogicalType::get(context, KIND);
79ad40cc14SValentin Clement   return {};
80ad40cc14SValentin Clement }
81ad40cc14SValentin Clement 
genCharacterType(mlir::MLIRContext * context,int KIND,Fortran::lower::LenParameterTy len=fir::CharacterType::unknownLen ())828c22cb84SValentin Clement static mlir::Type genCharacterType(
838c22cb84SValentin Clement     mlir::MLIRContext *context, int KIND,
848c22cb84SValentin Clement     Fortran::lower::LenParameterTy len = fir::CharacterType::unknownLen()) {
858c22cb84SValentin Clement   if (Fortran::evaluate::IsValidKindOfIntrinsicType(
868c22cb84SValentin Clement           Fortran::common::TypeCategory::Character, KIND))
878c22cb84SValentin Clement     return fir::CharacterType::get(context, KIND, len);
888c22cb84SValentin Clement   return {};
898c22cb84SValentin Clement }
908c22cb84SValentin Clement 
genComplexType(mlir::MLIRContext * context,int KIND)911ceb1d9bSValentin Clement static mlir::Type genComplexType(mlir::MLIRContext *context, int KIND) {
921ceb1d9bSValentin Clement   if (Fortran::evaluate::IsValidKindOfIntrinsicType(
931ceb1d9bSValentin Clement           Fortran::common::TypeCategory::Complex, KIND))
941ceb1d9bSValentin Clement     return fir::ComplexType::get(context, KIND);
951ceb1d9bSValentin Clement   return {};
961ceb1d9bSValentin Clement }
971ceb1d9bSValentin Clement 
988c22cb84SValentin Clement static mlir::Type
genFIRType(mlir::MLIRContext * context,Fortran::common::TypeCategory tc,int kind,llvm::ArrayRef<Fortran::lower::LenParameterTy> lenParameters)998c22cb84SValentin Clement genFIRType(mlir::MLIRContext *context, Fortran::common::TypeCategory tc,
1008c22cb84SValentin Clement            int kind,
1018c22cb84SValentin Clement            llvm::ArrayRef<Fortran::lower::LenParameterTy> lenParameters) {
102ad40cc14SValentin Clement   switch (tc) {
103ad40cc14SValentin Clement   case Fortran::common::TypeCategory::Real:
1040a0b3029SValentin Clement     return genRealType(context, kind);
105ad40cc14SValentin Clement   case Fortran::common::TypeCategory::Integer:
106ad40cc14SValentin Clement     return genIntegerType(context, kind);
107ad40cc14SValentin Clement   case Fortran::common::TypeCategory::Complex:
1081ceb1d9bSValentin Clement     return genComplexType(context, kind);
109ad40cc14SValentin Clement   case Fortran::common::TypeCategory::Logical:
110ad40cc14SValentin Clement     return genLogicalType(context, kind);
111ad40cc14SValentin Clement   case Fortran::common::TypeCategory::Character:
1128c22cb84SValentin Clement     if (!lenParameters.empty())
1138c22cb84SValentin Clement       return genCharacterType(context, kind, lenParameters[0]);
1148c22cb84SValentin Clement     return genCharacterType(context, kind);
115ad40cc14SValentin Clement   default:
116ad40cc14SValentin Clement     break;
117ad40cc14SValentin Clement   }
118ad40cc14SValentin Clement   llvm_unreachable("unhandled type category");
119baa12ddbSEric Schweitz }
120baa12ddbSEric Schweitz 
121307ccf4cSValentin Clement //===--------------------------------------------------------------------===//
122307ccf4cSValentin Clement // Symbol and expression type translation
123307ccf4cSValentin Clement //===--------------------------------------------------------------------===//
124baa12ddbSEric Schweitz 
125307ccf4cSValentin Clement /// TypeBuilder translates expression and symbol type taking into account
126307ccf4cSValentin Clement /// their shape and length parameters. For symbols, attributes such as
127307ccf4cSValentin Clement /// ALLOCATABLE or POINTER are reflected in the fir type.
128307ccf4cSValentin Clement /// It uses evaluate::DynamicType and evaluate::Shape when possible to
129307ccf4cSValentin Clement /// avoid re-implementing type/shape analysis here.
130307ccf4cSValentin Clement /// Do not use the FirOpBuilder from the AbstractConverter to get fir/mlir types
131307ccf4cSValentin Clement /// since it is not guaranteed to exist yet when we lower types.
132baa12ddbSEric Schweitz namespace {
1339aeb7f03SValentin Clement struct TypeBuilder {
1349aeb7f03SValentin Clement 
TypeBuilder__anon8bca3fa80111::TypeBuilder1352c2e5a5dSValentin Clement   TypeBuilder(Fortran::lower::AbstractConverter &converter)
136ad40cc14SValentin Clement       : converter{converter}, context{&converter.getMLIRContext()} {}
137ad40cc14SValentin Clement 
genExprType__anon8bca3fa80111::TypeBuilder138e641c29fSValentin Clement   mlir::Type genExprType(const Fortran::lower::SomeExpr &expr) {
139e641c29fSValentin Clement     std::optional<Fortran::evaluate::DynamicType> dynamicType = expr.GetType();
140e641c29fSValentin Clement     if (!dynamicType)
141e641c29fSValentin Clement       return genTypelessExprType(expr);
142e641c29fSValentin Clement     Fortran::common::TypeCategory category = dynamicType->category();
143e641c29fSValentin Clement 
144e641c29fSValentin Clement     mlir::Type baseType;
145e641c29fSValentin Clement     if (category == Fortran::common::TypeCategory::Derived) {
146589d51eaSValentin Clement       baseType = genDerivedType(dynamicType->GetDerivedTypeSpec());
147e641c29fSValentin Clement     } else {
148e641c29fSValentin Clement       // LOGICAL, INTEGER, REAL, COMPLEX, CHARACTER
1498c22cb84SValentin Clement       llvm::SmallVector<Fortran::lower::LenParameterTy> params;
1508c22cb84SValentin Clement       translateLenParameters(params, category, expr);
1518c22cb84SValentin Clement       baseType = genFIRType(context, category, dynamicType->kind(), params);
152e641c29fSValentin Clement     }
153e641c29fSValentin Clement     std::optional<Fortran::evaluate::Shape> shapeExpr =
154e641c29fSValentin Clement         Fortran::evaluate::GetShape(converter.getFoldingContext(), expr);
155e641c29fSValentin Clement     fir::SequenceType::Shape shape;
156e641c29fSValentin Clement     if (shapeExpr) {
157e641c29fSValentin Clement       translateShape(shape, std::move(*shapeExpr));
158e641c29fSValentin Clement     } else {
159e641c29fSValentin Clement       // Shape static analysis cannot return something useful for the shape.
160e641c29fSValentin Clement       // Use unknown extents.
161e641c29fSValentin Clement       int rank = expr.Rank();
162e641c29fSValentin Clement       if (rank < 0)
16339377d52SValentin Clement         TODO(converter.getCurrentLocation(), "assumed rank expression types");
164e641c29fSValentin Clement       for (int dim = 0; dim < rank; ++dim)
165e641c29fSValentin Clement         shape.emplace_back(fir::SequenceType::getUnknownExtent());
166e641c29fSValentin Clement     }
167e641c29fSValentin Clement     if (!shape.empty())
168e641c29fSValentin Clement       return fir::SequenceType::get(shape, baseType);
169e641c29fSValentin Clement     return baseType;
170e641c29fSValentin Clement   }
171e641c29fSValentin Clement 
172ad40cc14SValentin Clement   template <typename A>
translateShape__anon8bca3fa80111::TypeBuilder173c807aa53SValentin Clement   void translateShape(A &shape, Fortran::evaluate::Shape &&shapeExpr) {
174c807aa53SValentin Clement     for (Fortran::evaluate::MaybeExtentExpr extentExpr : shapeExpr) {
175c807aa53SValentin Clement       fir::SequenceType::Extent extent = fir::SequenceType::getUnknownExtent();
176c807aa53SValentin Clement       if (std::optional<std::int64_t> constantExtent =
177c807aa53SValentin Clement               toInt64(std::move(extentExpr)))
178c807aa53SValentin Clement         extent = *constantExtent;
179c807aa53SValentin Clement       shape.push_back(extent);
180c807aa53SValentin Clement     }
181c807aa53SValentin Clement   }
182c807aa53SValentin Clement 
183c807aa53SValentin Clement   template <typename A>
toInt64__anon8bca3fa80111::TypeBuilder184ad40cc14SValentin Clement   std::optional<std::int64_t> toInt64(A &&expr) {
185ad40cc14SValentin Clement     return Fortran::evaluate::ToInt64(Fortran::evaluate::Fold(
186ad40cc14SValentin Clement         converter.getFoldingContext(), std::move(expr)));
187ad40cc14SValentin Clement   }
188ad40cc14SValentin Clement 
genTypelessExprType__anon8bca3fa80111::TypeBuilder189e641c29fSValentin Clement   mlir::Type genTypelessExprType(const Fortran::lower::SomeExpr &expr) {
190e641c29fSValentin Clement     return std::visit(
191e641c29fSValentin Clement         Fortran::common::visitors{
192e641c29fSValentin Clement             [&](const Fortran::evaluate::BOZLiteralConstant &) -> mlir::Type {
193e641c29fSValentin Clement               return mlir::NoneType::get(context);
194e641c29fSValentin Clement             },
195e641c29fSValentin Clement             [&](const Fortran::evaluate::NullPointer &) -> mlir::Type {
196e641c29fSValentin Clement               return fir::ReferenceType::get(mlir::NoneType::get(context));
197e641c29fSValentin Clement             },
198e641c29fSValentin Clement             [&](const Fortran::evaluate::ProcedureDesignator &proc)
199e641c29fSValentin Clement                 -> mlir::Type {
2009aeb7f03SValentin Clement               return Fortran::lower::translateSignature(proc, converter);
201e641c29fSValentin Clement             },
202e641c29fSValentin Clement             [&](const Fortran::evaluate::ProcedureRef &) -> mlir::Type {
203e641c29fSValentin Clement               return mlir::NoneType::get(context);
204e641c29fSValentin Clement             },
205e641c29fSValentin Clement             [](const auto &x) -> mlir::Type {
206e641c29fSValentin Clement               using T = std::decay_t<decltype(x)>;
207e641c29fSValentin Clement               static_assert(!Fortran::common::HasMember<
208e641c29fSValentin Clement                                 T, Fortran::evaluate::TypelessExpression>,
20939377d52SValentin Clement                             "missing typeless expr handling");
210e641c29fSValentin Clement               llvm::report_fatal_error("not a typeless expression");
211e641c29fSValentin Clement             },
212e641c29fSValentin Clement         },
213e641c29fSValentin Clement         expr.u);
214e641c29fSValentin Clement   }
215e641c29fSValentin Clement 
genSymbolType__anon8bca3fa80111::TypeBuilder216ad40cc14SValentin Clement   mlir::Type genSymbolType(const Fortran::semantics::Symbol &symbol,
217ad40cc14SValentin Clement                            bool isAlloc = false, bool isPtr = false) {
218ad40cc14SValentin Clement     mlir::Location loc = converter.genLocation(symbol.name());
219ad40cc14SValentin Clement     mlir::Type ty;
220ad40cc14SValentin Clement     // If the symbol is not the same as the ultimate one (i.e, it is host or use
221ad40cc14SValentin Clement     // associated), all the symbol properties are the ones of the ultimate
222ad40cc14SValentin Clement     // symbol but the volatile and asynchronous attributes that may differ. To
223ad40cc14SValentin Clement     // avoid issues with helper functions that would not follow association
224ad40cc14SValentin Clement     // links, the fir type is built based on the ultimate symbol. This relies
225ad40cc14SValentin Clement     // on the fact volatile and asynchronous are not reflected in fir types.
226ad40cc14SValentin Clement     const Fortran::semantics::Symbol &ultimate = symbol.GetUltimate();
2271e1f60c6SV Donaldson     if (Fortran::semantics::IsProcedurePointer(ultimate))
2281e1f60c6SV Donaldson       TODO(loc, "procedure pointers");
229ad40cc14SValentin Clement     if (const Fortran::semantics::DeclTypeSpec *type = ultimate.GetType()) {
230ad40cc14SValentin Clement       if (const Fortran::semantics::IntrinsicTypeSpec *tySpec =
231ad40cc14SValentin Clement               type->AsIntrinsic()) {
232ad40cc14SValentin Clement         int kind = toInt64(Fortran::common::Clone(tySpec->kind())).value();
2338c22cb84SValentin Clement         llvm::SmallVector<Fortran::lower::LenParameterTy> params;
2348c22cb84SValentin Clement         translateLenParameters(params, tySpec->category(), ultimate);
2358c22cb84SValentin Clement         ty = genFIRType(context, tySpec->category(), kind, params);
236ad40cc14SValentin Clement       } else if (type->IsPolymorphic()) {
23739377d52SValentin Clement         TODO(loc, "support for polymorphic types");
238589d51eaSValentin Clement       } else if (const Fortran::semantics::DerivedTypeSpec *tySpec =
239589d51eaSValentin Clement                      type->AsDerived()) {
240589d51eaSValentin Clement         ty = genDerivedType(*tySpec);
241ad40cc14SValentin Clement       } else {
242ad40cc14SValentin Clement         fir::emitFatalError(loc, "symbol's type must have a type spec");
243ad40cc14SValentin Clement       }
244ad40cc14SValentin Clement     } else {
245ad40cc14SValentin Clement       fir::emitFatalError(loc, "symbol must have a type");
246ad40cc14SValentin Clement     }
247c807aa53SValentin Clement     if (ultimate.IsObjectArray()) {
248c807aa53SValentin Clement       auto shapeExpr = Fortran::evaluate::GetShapeHelper{
249c807aa53SValentin Clement           converter.getFoldingContext()}(ultimate);
250c807aa53SValentin Clement       if (!shapeExpr)
25139377d52SValentin Clement         TODO(loc, "assumed rank symbol type");
252c807aa53SValentin Clement       fir::SequenceType::Shape shape;
253c807aa53SValentin Clement       translateShape(shape, std::move(*shapeExpr));
254c807aa53SValentin Clement       ty = fir::SequenceType::get(shape, ty);
255c807aa53SValentin Clement     }
256ad40cc14SValentin Clement 
257ad40cc14SValentin Clement     if (Fortran::semantics::IsPointer(symbol))
258ad40cc14SValentin Clement       return fir::BoxType::get(fir::PointerType::get(ty));
259ad40cc14SValentin Clement     if (Fortran::semantics::IsAllocatable(symbol))
260ad40cc14SValentin Clement       return fir::BoxType::get(fir::HeapType::get(ty));
261ad40cc14SValentin Clement     // isPtr and isAlloc are variable that were promoted to be on the
262ad40cc14SValentin Clement     // heap or to be pointers, but they do not have Fortran allocatable
263ad40cc14SValentin Clement     // or pointer semantics, so do not use box for them.
264ad40cc14SValentin Clement     if (isPtr)
265ad40cc14SValentin Clement       return fir::PointerType::get(ty);
266ad40cc14SValentin Clement     if (isAlloc)
267ad40cc14SValentin Clement       return fir::HeapType::get(ty);
268ad40cc14SValentin Clement     return ty;
269ad40cc14SValentin Clement   }
270baa12ddbSEric Schweitz 
271589d51eaSValentin Clement   /// Does \p component has non deferred lower bounds that are not compile time
272589d51eaSValentin Clement   /// constant 1.
componentHasNonDefaultLowerBounds__anon8bca3fa80111::TypeBuilder273589d51eaSValentin Clement   static bool componentHasNonDefaultLowerBounds(
274589d51eaSValentin Clement       const Fortran::semantics::Symbol &component) {
275589d51eaSValentin Clement     if (const auto *objDetails =
276589d51eaSValentin Clement             component.detailsIf<Fortran::semantics::ObjectEntityDetails>())
277589d51eaSValentin Clement       for (const Fortran::semantics::ShapeSpec &bounds : objDetails->shape())
278589d51eaSValentin Clement         if (auto lb = bounds.lbound().GetExplicit())
279589d51eaSValentin Clement           if (auto constant = Fortran::evaluate::ToInt64(*lb))
280589d51eaSValentin Clement             if (!constant || *constant != 1)
281589d51eaSValentin Clement               return true;
282589d51eaSValentin Clement     return false;
283589d51eaSValentin Clement   }
284589d51eaSValentin Clement 
genDerivedType__anon8bca3fa80111::TypeBuilder285589d51eaSValentin Clement   mlir::Type genDerivedType(const Fortran::semantics::DerivedTypeSpec &tySpec) {
286589d51eaSValentin Clement     std::vector<std::pair<std::string, mlir::Type>> ps;
287589d51eaSValentin Clement     std::vector<std::pair<std::string, mlir::Type>> cs;
288589d51eaSValentin Clement     const Fortran::semantics::Symbol &typeSymbol = tySpec.typeSymbol();
289589d51eaSValentin Clement     if (mlir::Type ty = getTypeIfDerivedAlreadyInConstruction(typeSymbol))
290589d51eaSValentin Clement       return ty;
291*740633ffSValentin Clement 
292*740633ffSValentin Clement     if (Fortran::semantics::IsFinalizable(tySpec))
293*740633ffSValentin Clement       TODO(converter.genLocation(tySpec.name()), "derived type finalization");
294*740633ffSValentin Clement 
295589d51eaSValentin Clement     auto rec = fir::RecordType::get(context,
296589d51eaSValentin Clement                                     Fortran::lower::mangle::mangleName(tySpec));
297589d51eaSValentin Clement     // Maintain the stack of types for recursive references.
298589d51eaSValentin Clement     derivedTypeInConstruction.emplace_back(typeSymbol, rec);
299589d51eaSValentin Clement 
300589d51eaSValentin Clement     // Gather the record type fields.
301589d51eaSValentin Clement     // (1) The data components.
302589d51eaSValentin Clement     for (const auto &field :
303589d51eaSValentin Clement          Fortran::semantics::OrderedComponentIterator(tySpec)) {
304589d51eaSValentin Clement       // Lowering is assuming non deferred component lower bounds are always 1.
305589d51eaSValentin Clement       // Catch any situations where this is not true for now.
306589d51eaSValentin Clement       if (componentHasNonDefaultLowerBounds(field))
307589d51eaSValentin Clement         TODO(converter.genLocation(field.name()),
30839377d52SValentin Clement              "derived type components with non default lower bounds");
3098594b051SPeter Klausler       if (IsProcedure(field))
310589d51eaSValentin Clement         TODO(converter.genLocation(field.name()), "procedure components");
311589d51eaSValentin Clement       mlir::Type ty = genSymbolType(field);
312589d51eaSValentin Clement       // Do not add the parent component (component of the parents are
313589d51eaSValentin Clement       // added and should be sufficient, the parent component would
314589d51eaSValentin Clement       // duplicate the fields).
315589d51eaSValentin Clement       if (field.test(Fortran::semantics::Symbol::Flag::ParentComp))
316589d51eaSValentin Clement         continue;
317589d51eaSValentin Clement       cs.emplace_back(field.name().ToString(), ty);
318589d51eaSValentin Clement     }
319589d51eaSValentin Clement 
320589d51eaSValentin Clement     // (2) The LEN type parameters.
321589d51eaSValentin Clement     for (const auto &param :
322589d51eaSValentin Clement          Fortran::semantics::OrderParameterDeclarations(typeSymbol))
323589d51eaSValentin Clement       if (param->get<Fortran::semantics::TypeParamDetails>().attr() ==
324589d51eaSValentin Clement           Fortran::common::TypeParamAttr::Len)
325589d51eaSValentin Clement         ps.emplace_back(param->name().ToString(), genSymbolType(*param));
326589d51eaSValentin Clement 
327589d51eaSValentin Clement     rec.finalize(ps, cs);
328589d51eaSValentin Clement     popDerivedTypeInConstruction();
329589d51eaSValentin Clement 
3309aeb7f03SValentin Clement     mlir::Location loc = converter.genLocation(typeSymbol.name());
331589d51eaSValentin Clement     if (!ps.empty()) {
332589d51eaSValentin Clement       // This type is a PDT (parametric derived type). Create the functions to
333589d51eaSValentin Clement       // use for allocation, dereferencing, and address arithmetic here.
33439377d52SValentin Clement       TODO(loc, "parameterized derived types");
335589d51eaSValentin Clement     }
336589d51eaSValentin Clement     LLVM_DEBUG(llvm::dbgs() << "derived type: " << rec << '\n');
3379aeb7f03SValentin Clement 
3389aeb7f03SValentin Clement     // Generate the type descriptor object if any
3399aeb7f03SValentin Clement     if (const Fortran::semantics::Scope *derivedScope =
3409aeb7f03SValentin Clement             tySpec.scope() ? tySpec.scope() : tySpec.typeSymbol().scope())
3419aeb7f03SValentin Clement       if (const Fortran::semantics::Symbol *typeInfoSym =
3429aeb7f03SValentin Clement               derivedScope->runtimeDerivedTypeDescription())
3439aeb7f03SValentin Clement         converter.registerRuntimeTypeInfo(loc, *typeInfoSym);
344589d51eaSValentin Clement     return rec;
345589d51eaSValentin Clement   }
346589d51eaSValentin Clement 
3478c22cb84SValentin Clement   // To get the character length from a symbol, make an fold a designator for
3488c22cb84SValentin Clement   // the symbol to cover the case where the symbol is an assumed length named
3498c22cb84SValentin Clement   // constant and its length comes from its init expression length.
3508c22cb84SValentin Clement   template <int Kind>
3518c22cb84SValentin Clement   fir::SequenceType::Extent
getCharacterLengthHelper__anon8bca3fa80111::TypeBuilder3528c22cb84SValentin Clement   getCharacterLengthHelper(const Fortran::semantics::Symbol &symbol) {
3538c22cb84SValentin Clement     using TC =
3548c22cb84SValentin Clement         Fortran::evaluate::Type<Fortran::common::TypeCategory::Character, Kind>;
3558c22cb84SValentin Clement     auto designator = Fortran::evaluate::Fold(
3568c22cb84SValentin Clement         converter.getFoldingContext(),
3578c22cb84SValentin Clement         Fortran::evaluate::Expr<TC>{Fortran::evaluate::Designator<TC>{symbol}});
3588c22cb84SValentin Clement     if (auto len = toInt64(std::move(designator.LEN())))
3598c22cb84SValentin Clement       return *len;
3608c22cb84SValentin Clement     return fir::SequenceType::getUnknownExtent();
3618c22cb84SValentin Clement   }
3628c22cb84SValentin Clement 
3638c22cb84SValentin Clement   template <typename T>
translateLenParameters__anon8bca3fa80111::TypeBuilder3648c22cb84SValentin Clement   void translateLenParameters(
3658c22cb84SValentin Clement       llvm::SmallVectorImpl<Fortran::lower::LenParameterTy> &params,
3668c22cb84SValentin Clement       Fortran::common::TypeCategory category, const T &exprOrSym) {
3678c22cb84SValentin Clement     if (category == Fortran::common::TypeCategory::Character)
3688c22cb84SValentin Clement       params.push_back(getCharacterLength(exprOrSym));
3698c22cb84SValentin Clement     else if (category == Fortran::common::TypeCategory::Derived)
37039377d52SValentin Clement       TODO(converter.getCurrentLocation(), "derived type length parameters");
3718c22cb84SValentin Clement   }
3728c22cb84SValentin Clement   Fortran::lower::LenParameterTy
getCharacterLength__anon8bca3fa80111::TypeBuilder3738c22cb84SValentin Clement   getCharacterLength(const Fortran::semantics::Symbol &symbol) {
3748c22cb84SValentin Clement     const Fortran::semantics::DeclTypeSpec *type = symbol.GetType();
3758c22cb84SValentin Clement     if (!type ||
3768c22cb84SValentin Clement         type->category() != Fortran::semantics::DeclTypeSpec::Character ||
3778c22cb84SValentin Clement         !type->AsIntrinsic())
3788c22cb84SValentin Clement       llvm::report_fatal_error("not a character symbol");
3798c22cb84SValentin Clement     int kind =
3808c22cb84SValentin Clement         toInt64(Fortran::common::Clone(type->AsIntrinsic()->kind())).value();
3818c22cb84SValentin Clement     switch (kind) {
3828c22cb84SValentin Clement     case 1:
3838c22cb84SValentin Clement       return getCharacterLengthHelper<1>(symbol);
3848c22cb84SValentin Clement     case 2:
3858c22cb84SValentin Clement       return getCharacterLengthHelper<2>(symbol);
3868c22cb84SValentin Clement     case 4:
3878c22cb84SValentin Clement       return getCharacterLengthHelper<4>(symbol);
3888c22cb84SValentin Clement     }
3898c22cb84SValentin Clement     llvm_unreachable("unknown character kind");
3908c22cb84SValentin Clement   }
3918c22cb84SValentin Clement   Fortran::lower::LenParameterTy
getCharacterLength__anon8bca3fa80111::TypeBuilder3928c22cb84SValentin Clement   getCharacterLength(const Fortran::lower::SomeExpr &expr) {
3938c22cb84SValentin Clement     // Do not use dynamic type length here. We would miss constant
3948c22cb84SValentin Clement     // lengths opportunities because dynamic type only has the length
3958c22cb84SValentin Clement     // if it comes from a declaration.
3968c22cb84SValentin Clement     auto charExpr =
3978c22cb84SValentin Clement         std::get<Fortran::evaluate::Expr<Fortran::evaluate::SomeCharacter>>(
3988c22cb84SValentin Clement             expr.u);
3998c22cb84SValentin Clement     if (auto constantLen = toInt64(charExpr.LEN()))
4008c22cb84SValentin Clement       return *constantLen;
4018c22cb84SValentin Clement     return fir::SequenceType::getUnknownExtent();
4028c22cb84SValentin Clement   }
4038c22cb84SValentin Clement 
genVariableType__anon8bca3fa80111::TypeBuilder4042c2e5a5dSValentin Clement   mlir::Type genVariableType(const Fortran::lower::pft::Variable &var) {
405ad40cc14SValentin Clement     return genSymbolType(var.getSymbol(), var.isHeapAlloc(), var.isPointer());
406baa12ddbSEric Schweitz   }
407baa12ddbSEric Schweitz 
408589d51eaSValentin Clement   /// Derived type can be recursive. That is, pointer components of a derived
409589d51eaSValentin Clement   /// type `t` have type `t`. This helper returns `t` if it is already being
410589d51eaSValentin Clement   /// lowered to avoid infinite loops.
getTypeIfDerivedAlreadyInConstruction__anon8bca3fa80111::TypeBuilder411589d51eaSValentin Clement   mlir::Type getTypeIfDerivedAlreadyInConstruction(
412589d51eaSValentin Clement       const Fortran::lower::SymbolRef derivedSym) const {
413589d51eaSValentin Clement     for (const auto &[sym, type] : derivedTypeInConstruction)
414589d51eaSValentin Clement       if (sym == derivedSym)
415589d51eaSValentin Clement         return type;
416589d51eaSValentin Clement     return {};
417589d51eaSValentin Clement   }
418589d51eaSValentin Clement 
popDerivedTypeInConstruction__anon8bca3fa80111::TypeBuilder419589d51eaSValentin Clement   void popDerivedTypeInConstruction() {
420589d51eaSValentin Clement     assert(!derivedTypeInConstruction.empty());
421589d51eaSValentin Clement     derivedTypeInConstruction.pop_back();
422589d51eaSValentin Clement   }
423589d51eaSValentin Clement 
424589d51eaSValentin Clement   /// Stack derived type being processed to avoid infinite loops in case of
425589d51eaSValentin Clement   /// recursive derived types. The depth of derived types is expected to be
426589d51eaSValentin Clement   /// shallow (<10), so a SmallVector is sufficient.
427589d51eaSValentin Clement   llvm::SmallVector<std::pair<const Fortran::lower::SymbolRef, mlir::Type>>
428589d51eaSValentin Clement       derivedTypeInConstruction;
429ad40cc14SValentin Clement   Fortran::lower::AbstractConverter &converter;
430baa12ddbSEric Schweitz   mlir::MLIRContext *context;
431baa12ddbSEric Schweitz };
432baa12ddbSEric Schweitz } // namespace
433baa12ddbSEric Schweitz 
getFIRType(mlir::MLIRContext * context,Fortran::common::TypeCategory tc,int kind,llvm::ArrayRef<LenParameterTy> params)434dc6a3446SValentin Clement mlir::Type Fortran::lower::getFIRType(mlir::MLIRContext *context,
435dc6a3446SValentin Clement                                       Fortran::common::TypeCategory tc,
4368c22cb84SValentin Clement                                       int kind,
4378c22cb84SValentin Clement                                       llvm::ArrayRef<LenParameterTy> params) {
4388c22cb84SValentin Clement   return genFIRType(context, tc, kind, params);
439baa12ddbSEric Schweitz }
440baa12ddbSEric Schweitz 
translateDerivedTypeToFIRType(Fortran::lower::AbstractConverter & converter,const Fortran::semantics::DerivedTypeSpec & tySpec)441589d51eaSValentin Clement mlir::Type Fortran::lower::translateDerivedTypeToFIRType(
442589d51eaSValentin Clement     Fortran::lower::AbstractConverter &converter,
443589d51eaSValentin Clement     const Fortran::semantics::DerivedTypeSpec &tySpec) {
444589d51eaSValentin Clement   return TypeBuilder{converter}.genDerivedType(tySpec);
445589d51eaSValentin Clement }
446589d51eaSValentin Clement 
translateSomeExprToFIRType(Fortran::lower::AbstractConverter & converter,const SomeExpr & expr)447baa12ddbSEric Schweitz mlir::Type Fortran::lower::translateSomeExprToFIRType(
448e641c29fSValentin Clement     Fortran::lower::AbstractConverter &converter, const SomeExpr &expr) {
449e641c29fSValentin Clement   return TypeBuilder{converter}.genExprType(expr);
450baa12ddbSEric Schweitz }
451baa12ddbSEric Schweitz 
translateSymbolToFIRType(Fortran::lower::AbstractConverter & converter,const SymbolRef symbol)452baa12ddbSEric Schweitz mlir::Type Fortran::lower::translateSymbolToFIRType(
4532c2e5a5dSValentin Clement     Fortran::lower::AbstractConverter &converter, const SymbolRef symbol) {
454ad40cc14SValentin Clement   return TypeBuilder{converter}.genSymbolType(symbol);
455baa12ddbSEric Schweitz }
456baa12ddbSEric Schweitz 
translateVariableToFIRType(Fortran::lower::AbstractConverter & converter,const Fortran::lower::pft::Variable & var)457baa12ddbSEric Schweitz mlir::Type Fortran::lower::translateVariableToFIRType(
4582c2e5a5dSValentin Clement     Fortran::lower::AbstractConverter &converter,
459baa12ddbSEric Schweitz     const Fortran::lower::pft::Variable &var) {
4602c2e5a5dSValentin Clement   return TypeBuilder{converter}.genVariableType(var);
461baa12ddbSEric Schweitz }
462baa12ddbSEric Schweitz 
convertReal(mlir::MLIRContext * context,int kind)463baa12ddbSEric Schweitz mlir::Type Fortran::lower::convertReal(mlir::MLIRContext *context, int kind) {
464b3d1f073SValentin Clement   return genRealType(context, kind);
465baa12ddbSEric Schweitz }
466