Skip to content

Commit 4d61bbc

Browse files
authored
Review usage of auto in Lower/ConvertType.cpp (#1311)
* Review usage of `auto` in Lower/ConvertType.cpp * Remov brace init
1 parent 57d7438 commit 4d61bbc

File tree

1 file changed

+21
-18
lines changed

1 file changed

+21
-18
lines changed

flang/lib/Lower/ConvertType.cpp

Lines changed: 21 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -138,10 +138,10 @@ struct TypeBuilder {
138138
: converter{converter}, context{&converter.getMLIRContext()} {}
139139

140140
mlir::Type genExprType(const Fortran::lower::SomeExpr &expr) {
141-
auto dynamicType = expr.GetType();
141+
std::optional<Fortran::evaluate::DynamicType> dynamicType = expr.GetType();
142142
if (!dynamicType)
143143
return genTypelessExprType(expr);
144-
auto category = dynamicType->category();
144+
Fortran::common::TypeCategory category = dynamicType->category();
145145

146146
mlir::Type baseType;
147147
if (category == Fortran::common::TypeCategory::Derived) {
@@ -152,18 +152,18 @@ struct TypeBuilder {
152152
translateLenParameters(params, category, expr);
153153
baseType = genFIRType(context, category, dynamicType->kind(), params);
154154
}
155-
auto shapeExpr =
155+
std::optional<Fortran::evaluate::Shape> shapeExpr =
156156
Fortran::evaluate::GetShape(converter.getFoldingContext(), expr);
157157
fir::SequenceType::Shape shape;
158158
if (shapeExpr) {
159159
translateShape(shape, std::move(*shapeExpr));
160160
} else {
161161
// Shape static analysis cannot return something useful for the shape.
162162
// Use unknown extents.
163-
auto rank = expr.Rank();
163+
int rank = expr.Rank();
164164
if (rank < 0)
165165
TODO(converter.genLocation(), "Assumed rank expression type lowering");
166-
for (auto dim = 0; dim < rank; ++dim)
166+
for (int dim = 0; dim < rank; ++dim)
167167
shape.emplace_back(fir::SequenceType::getUnknownExtent());
168168
}
169169
if (!shape.empty())
@@ -173,9 +173,10 @@ struct TypeBuilder {
173173

174174
template <typename A>
175175
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)))
179180
extent = *constantExtent;
180181
shape.push_back(extent);
181182
}
@@ -216,22 +217,24 @@ struct TypeBuilder {
216217

217218
mlir::Type genSymbolType(const Fortran::semantics::Symbol &symbol,
218219
bool isAlloc = false, bool isPtr = false) {
219-
auto loc = converter.genLocation(symbol.name());
220+
mlir::Location loc = converter.genLocation(symbol.name());
220221
mlir::Type ty;
221222
// If the symbol is not the same as the ultimate one (i.e, it is host or use
222223
// associated), all the symbol properties are the ones of the ultimate
223224
// symbol but the volatile and asynchronous attributes that may differ. To
224225
// avoid issues with helper functions that would not follow association
225226
// links, the fir type is built based on the ultimate symbol. This relies
226227
// 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()) {
230232
int kind = toInt64(Fortran::common::Clone(tySpec->kind())).value();
231233
llvm::SmallVector<Fortran::lower::LenParameterTy> params;
232234
translateLenParameters(params, tySpec->category(), ultimate);
233235
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()) {
235238
ty = genDerivedType(*tySpec);
236239
} else {
237240
fir::emitFatalError(loc, "symbol's type must have a type spec");
@@ -269,7 +272,7 @@ struct TypeBuilder {
269272
const Fortran::semantics::Symbol &component) {
270273
if (const auto *objDetails =
271274
component.detailsIf<Fortran::semantics::ObjectEntityDetails>())
272-
for (const auto &bounds : objDetails->shape())
275+
for (const Fortran::semantics::ShapeSpec &bounds : objDetails->shape())
273276
if (auto lb = bounds.lbound().GetExplicit())
274277
if (auto constant = Fortran::evaluate::ToInt64(*lb))
275278
if (!constant || *constant != 1)
@@ -280,8 +283,8 @@ struct TypeBuilder {
280283
mlir::Type genDerivedType(const Fortran::semantics::DerivedTypeSpec &tySpec) {
281284
std::vector<std::pair<std::string, mlir::Type>> ps;
282285
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))
285288
return ty;
286289
auto rec = fir::RecordType::get(context,
287290
Fortran::lower::mangle::mangleName(tySpec));
@@ -297,7 +300,7 @@ struct TypeBuilder {
297300
if (componentHasNonDefaultLowerBounds(field))
298301
TODO(converter.genLocation(field.name()),
299302
"lowering derived type components with non default lower bounds");
300-
auto ty = genSymbolType(field);
303+
mlir::Type ty = genSymbolType(field);
301304
// Do not add the parent component (component of the parents are
302305
// added and should be sufficient, the parent component would
303306
// duplicate the fields).
@@ -353,7 +356,7 @@ struct TypeBuilder {
353356
}
354357
Fortran::lower::LenParameterTy
355358
getCharacterLength(const Fortran::semantics::Symbol &symbol) {
356-
auto *type = symbol.GetType();
359+
const Fortran::semantics::DeclTypeSpec *type = symbol.GetType();
357360
if (!type ||
358361
type->category() != Fortran::semantics::DeclTypeSpec::Character ||
359362
!type->AsIntrinsic())

0 commit comments

Comments
 (0)