@@ -138,10 +138,10 @@ struct TypeBuilder {
138
138
: converter{converter}, context{&converter.getMLIRContext ()} {}
139
139
140
140
mlir::Type genExprType (const Fortran::lower::SomeExpr &expr) {
141
- auto dynamicType = expr.GetType ();
141
+ std::optional<Fortran::evaluate::DynamicType> dynamicType = expr.GetType ();
142
142
if (!dynamicType)
143
143
return genTypelessExprType (expr);
144
- auto category = dynamicType->category ();
144
+ Fortran::common::TypeCategory category = dynamicType->category ();
145
145
146
146
mlir::Type baseType;
147
147
if (category == Fortran::common::TypeCategory::Derived) {
@@ -152,18 +152,18 @@ struct TypeBuilder {
152
152
translateLenParameters (params, category, expr);
153
153
baseType = genFIRType (context, category, dynamicType->kind (), params);
154
154
}
155
- auto shapeExpr =
155
+ std::optional<Fortran::evaluate::Shape> shapeExpr =
156
156
Fortran::evaluate::GetShape (converter.getFoldingContext (), expr);
157
157
fir::SequenceType::Shape shape;
158
158
if (shapeExpr) {
159
159
translateShape (shape, std::move (*shapeExpr));
160
160
} else {
161
161
// Shape static analysis cannot return something useful for the shape.
162
162
// Use unknown extents.
163
- auto rank = expr.Rank ();
163
+ int rank = expr.Rank ();
164
164
if (rank < 0 )
165
165
TODO (converter.genLocation (), " Assumed rank expression type lowering" );
166
- for (auto dim = 0 ; dim < rank; ++dim)
166
+ for (int dim = 0 ; dim < rank; ++dim)
167
167
shape.emplace_back (fir::SequenceType::getUnknownExtent ());
168
168
}
169
169
if (!shape.empty ())
@@ -173,9 +173,10 @@ struct TypeBuilder {
173
173
174
174
template <typename A>
175
175
void translateShape (A &shape, Fortran::evaluate::Shape &&shapeExpr) {
176
- for (auto extentExpr : shapeExpr) {
177
- auto extent = fir::SequenceType::getUnknownExtent ();
178
- if (auto constantExtent = toInt64 (std::move (extentExpr)))
176
+ for (Fortran::evaluate::MaybeExtentExpr extentExpr : shapeExpr) {
177
+ fir::SequenceType::Extent extent = fir::SequenceType::getUnknownExtent ();
178
+ if (std::optional<std::int64_t > constantExtent =
179
+ toInt64 (std::move (extentExpr)))
179
180
extent = *constantExtent;
180
181
shape.push_back (extent);
181
182
}
@@ -216,22 +217,24 @@ struct TypeBuilder {
216
217
217
218
mlir::Type genSymbolType (const Fortran::semantics::Symbol &symbol,
218
219
bool isAlloc = false , bool isPtr = false ) {
219
- auto loc = converter.genLocation (symbol.name ());
220
+ mlir::Location loc = converter.genLocation (symbol.name ());
220
221
mlir::Type ty;
221
222
// If the symbol is not the same as the ultimate one (i.e, it is host or use
222
223
// associated), all the symbol properties are the ones of the ultimate
223
224
// symbol but the volatile and asynchronous attributes that may differ. To
224
225
// avoid issues with helper functions that would not follow association
225
226
// links, the fir type is built based on the ultimate symbol. This relies
226
227
// on the fact volatile and asynchronous are not reflected in fir types.
227
- const auto &ultimate = symbol.GetUltimate ();
228
- if (auto *type{ultimate.GetType ()}) {
229
- if (auto *tySpec{type->AsIntrinsic ()}) {
228
+ const Fortran::semantics::Symbol &ultimate = symbol.GetUltimate ();
229
+ if (const Fortran::semantics::DeclTypeSpec * type = ultimate.GetType ()) {
230
+ if (const Fortran::semantics::IntrinsicTypeSpec *
231
+ tySpec = type->AsIntrinsic ()) {
230
232
int kind = toInt64 (Fortran::common::Clone (tySpec->kind ())).value ();
231
233
llvm::SmallVector<Fortran::lower::LenParameterTy> params;
232
234
translateLenParameters (params, tySpec->category (), ultimate);
233
235
ty = genFIRType (context, tySpec->category (), kind, params);
234
- } else if (auto *tySpec = type->AsDerived ()) {
236
+ } else if (const Fortran::semantics::DerivedTypeSpec *tySpec =
237
+ type->AsDerived ()) {
235
238
ty = genDerivedType (*tySpec);
236
239
} else {
237
240
fir::emitFatalError (loc, " symbol's type must have a type spec" );
@@ -269,7 +272,7 @@ struct TypeBuilder {
269
272
const Fortran::semantics::Symbol &component) {
270
273
if (const auto *objDetails =
271
274
component.detailsIf <Fortran::semantics::ObjectEntityDetails>())
272
- for (const auto &bounds : objDetails->shape ())
275
+ for (const Fortran::semantics::ShapeSpec &bounds : objDetails->shape ())
273
276
if (auto lb = bounds.lbound ().GetExplicit ())
274
277
if (auto constant = Fortran::evaluate::ToInt64 (*lb))
275
278
if (!constant || *constant != 1 )
@@ -280,8 +283,8 @@ struct TypeBuilder {
280
283
mlir::Type genDerivedType (const Fortran::semantics::DerivedTypeSpec &tySpec) {
281
284
std::vector<std::pair<std::string, mlir::Type>> ps;
282
285
std::vector<std::pair<std::string, mlir::Type>> cs;
283
- const auto &typeSymbol = tySpec.typeSymbol ();
284
- if (auto ty = getTypeIfDerivedAlreadyInConstruction (typeSymbol))
286
+ const Fortran::semantics::Symbol &typeSymbol = tySpec.typeSymbol ();
287
+ if (mlir::Type ty = getTypeIfDerivedAlreadyInConstruction (typeSymbol))
285
288
return ty;
286
289
auto rec = fir::RecordType::get (context,
287
290
Fortran::lower::mangle::mangleName (tySpec));
@@ -297,7 +300,7 @@ struct TypeBuilder {
297
300
if (componentHasNonDefaultLowerBounds (field))
298
301
TODO (converter.genLocation (field.name ()),
299
302
" lowering derived type components with non default lower bounds" );
300
- auto ty = genSymbolType (field);
303
+ mlir::Type ty = genSymbolType (field);
301
304
// Do not add the parent component (component of the parents are
302
305
// added and should be sufficient, the parent component would
303
306
// duplicate the fields).
@@ -353,7 +356,7 @@ struct TypeBuilder {
353
356
}
354
357
Fortran::lower::LenParameterTy
355
358
getCharacterLength (const Fortran::semantics::Symbol &symbol) {
356
- auto *type = symbol.GetType ();
359
+ const Fortran::semantics::DeclTypeSpec *type = symbol.GetType ();
357
360
if (!type ||
358
361
type->category () != Fortran::semantics::DeclTypeSpec::Character ||
359
362
!type->AsIntrinsic ())
0 commit comments