@@ -29,21 +29,21 @@ static void moduleNames(const Fortran::semantics::Scope &scope,
29
29
}
30
30
moduleNames (scope.parent (), result);
31
31
if (scope.kind () == Fortran::semantics::Scope::Kind::Module)
32
- if (auto *symbol = scope.symbol ())
32
+ if (const Fortran::semantics::Symbol *symbol = scope.symbol ())
33
33
result.emplace_back (toStringRef (symbol->name ()));
34
34
}
35
35
36
36
static llvm::SmallVector<llvm::StringRef>
37
37
moduleNames (const Fortran::semantics::Symbol &symbol) {
38
- const auto &scope = symbol.owner ();
38
+ const Fortran::semantics::Scope &scope = symbol.owner ();
39
39
llvm::SmallVector<llvm::StringRef> result;
40
40
moduleNames (scope, result);
41
41
return result;
42
42
}
43
43
44
44
static llvm::Optional<llvm::StringRef>
45
45
hostName (const Fortran::semantics::Symbol &symbol) {
46
- const auto &scope = symbol.owner ();
46
+ const Fortran::semantics::Scope &scope = symbol.owner ();
47
47
if (scope.kind () == Fortran::semantics::Scope::Kind::Subprogram) {
48
48
assert (scope.symbol () && " subprogram scope must have a symbol" );
49
49
return toStringRef (scope.symbol ()->name ());
@@ -59,12 +59,12 @@ hostName(const Fortran::semantics::Symbol &symbol) {
59
59
60
60
static const Fortran::semantics::Symbol *
61
61
findInterfaceIfSeperateMP (const Fortran::semantics::Symbol &symbol) {
62
- const auto &scope = symbol.owner ();
62
+ const Fortran::semantics::Scope &scope = symbol.owner ();
63
63
if (symbol.attrs ().test (Fortran::semantics::Attr::MODULE) &&
64
64
scope.IsSubmodule ()) {
65
65
// FIXME symbol from MpSubprogramStmt do not seem to have
66
66
// Attr::MODULE set.
67
- const auto *iface = scope.parent ().FindSymbol (symbol.name ());
67
+ const Fortran::semantics::Symbol *iface = scope.parent ().FindSymbol (symbol.name ());
68
68
assert (iface && " Separate module procedure must be declared" );
69
69
return iface;
70
70
}
@@ -77,8 +77,8 @@ std::string
77
77
Fortran::lower::mangle::mangleName (const Fortran::semantics::Symbol &symbol,
78
78
bool keepExternalInScope) {
79
79
// Resolve host and module association before mangling
80
- const auto &ultimateSymbol = symbol.GetUltimate ();
81
- auto symbolName = toStringRef (ultimateSymbol.name ());
80
+ const Fortran::semantics::Symbol &ultimateSymbol = symbol.GetUltimate ();
81
+ llvm::StringRef symbolName = toStringRef (ultimateSymbol.name ());
82
82
83
83
return std::visit (
84
84
Fortran::common::visitors{
@@ -94,10 +94,10 @@ Fortran::lower::mangle::mangleName(const Fortran::semantics::Symbol &symbol,
94
94
// Separate module subprograms must be mangled according to the
95
95
// scope where they were declared (the symbol we have is the
96
96
// definition).
97
- const auto *interface = &ultimateSymbol;
97
+ const Fortran::semantics::Symbol *interface = &ultimateSymbol;
98
98
if (const auto *mpIface = findInterfaceIfSeperateMP (ultimateSymbol))
99
99
interface = mpIface;
100
- auto modNames = moduleNames (*interface);
100
+ llvm::SmallVector<llvm::StringRef> modNames = moduleNames (*interface);
101
101
return fir::NameUniquer::doProcedure (modNames, hostName (*interface),
102
102
symbolName);
103
103
},
@@ -115,16 +115,16 @@ Fortran::lower::mangle::mangleName(const Fortran::semantics::Symbol &symbol,
115
115
symbolName);
116
116
},
117
117
[&](const Fortran::semantics::ObjectEntityDetails &) {
118
- auto modNames = moduleNames (ultimateSymbol);
119
- auto optHost = hostName (ultimateSymbol);
118
+ llvm::SmallVector<llvm::StringRef> modNames = moduleNames (ultimateSymbol);
119
+ llvm::Optional<llvm::StringRef> optHost = hostName (ultimateSymbol);
120
120
if (Fortran::semantics::IsNamedConstant (ultimateSymbol))
121
121
return fir::NameUniquer::doConstant (modNames, optHost,
122
122
symbolName);
123
123
return fir::NameUniquer::doVariable (modNames, optHost, symbolName);
124
124
},
125
125
[&](const Fortran::semantics::NamelistDetails &) {
126
- auto modNames = moduleNames (ultimateSymbol);
127
- auto optHost = hostName (ultimateSymbol);
126
+ llvm::SmallVector<llvm::StringRef> modNames = moduleNames (ultimateSymbol);
127
+ llvm::Optional<llvm::StringRef> optHost = hostName (ultimateSymbol);
128
128
return fir::NameUniquer::doNamelistGroup (modNames, optHost,
129
129
symbolName);
130
130
},
@@ -145,21 +145,21 @@ Fortran::lower::mangle::mangleName(const Fortran::semantics::Symbol &symbol,
145
145
std::string Fortran::lower::mangle::mangleName (
146
146
const Fortran::semantics::DerivedTypeSpec &derivedType) {
147
147
// Resolve host and module association before mangling
148
- const auto &ultimateSymbol = derivedType.typeSymbol ().GetUltimate ();
149
- auto symbolName = toStringRef (ultimateSymbol.name ());
150
- auto modNames = moduleNames (ultimateSymbol);
151
- auto optHost = hostName (ultimateSymbol);
148
+ const Fortran::semantics::Symbol &ultimateSymbol = derivedType.typeSymbol ().GetUltimate ();
149
+ llvm::StringRef symbolName = toStringRef (ultimateSymbol.name ());
150
+ llvm::SmallVector<llvm::StringRef> modNames = moduleNames (ultimateSymbol);
151
+ llvm::Optional<llvm::StringRef> optHost = hostName (ultimateSymbol);
152
152
llvm::SmallVector<std::int64_t > kinds;
153
153
for (const auto ¶m :
154
154
Fortran::semantics::OrderParameterDeclarations (ultimateSymbol)) {
155
155
const auto ¶mDetails =
156
156
param->get <Fortran::semantics::TypeParamDetails>();
157
157
if (paramDetails.attr () == Fortran::common::TypeParamAttr::Kind) {
158
- const auto *paramValue = derivedType.FindParameter (param->name ());
158
+ const Fortran::semantics::ParamValue *paramValue = derivedType.FindParameter (param->name ());
159
159
assert (paramValue && " derived type kind parameter value not found" );
160
- auto paramExpr = paramValue->GetExplicit ();
160
+ const Fortran::semantics::MaybeIntExpr paramExpr = paramValue->GetExplicit ();
161
161
assert (paramExpr && " derived type kind param not explicit" );
162
- auto init = Fortran::evaluate::ToInt64 (paramValue->GetExplicit ());
162
+ std::optional< int64_t > init = Fortran::evaluate::ToInt64 (paramValue->GetExplicit ());
163
163
assert (init && " derived type kind param is not constant" );
164
164
kinds.emplace_back (*init);
165
165
}
@@ -201,12 +201,12 @@ std::string Fortran::lower::mangle::mangleArrayLiteral(
201
201
Fortran::common::TypeCategory cat, int kind,
202
202
Fortran::common::ConstantSubscript charLen) {
203
203
std::string typeId = " " ;
204
- for (auto extent : shape)
204
+ for (Fortran::evaluate::ConstantSubscript extent : shape)
205
205
typeId.append (std::to_string (extent)).append (" x" );
206
206
if (charLen >= 0 )
207
207
typeId.append (std::to_string (charLen)).append (" x" );
208
208
typeId.append (typeToString (cat, kind));
209
- auto name = fir::NameUniquer::doGenerated (" ro." s.append (typeId).append (" ." ));
209
+ std::string name = fir::NameUniquer::doGenerated (" ro." s.append (typeId).append (" ." ));
210
210
if (!size)
211
211
return name += " null" ;
212
212
llvm::MD5 hashValue{};
@@ -258,7 +258,7 @@ std::string fir::mangleIntrinsicProcedure(llvm::StringRef intrinsic,
258
258
name.append (intrinsic.str ()).append (" ." );
259
259
assert (funTy.getNumResults () == 1 && " only function mangling supported" );
260
260
name.append (typeToString (funTy.getResult (0 )));
261
- auto e = funTy.getNumInputs ();
261
+ unsigned e = funTy.getNumInputs ();
262
262
for (decltype (e) i = 0 ; i < e; ++i)
263
263
name.append (" ." ).append (typeToString (funTy.getInput (i)));
264
264
return name;
0 commit comments