Skip to content

Commit 5ae76be

Browse files
committed
[flang][driver] Add -fno-analyzed-objects-for-unparse
This patch adds a new option for the new Flang driver: `-fno-analyzed-objects-for-unparse`. The semantics are similar to `-funparse-typed-exprs-to-f18-fc` from `f18`. For consistency, the latter is replaced with `-fno-analyzed-objects-for-unparse`. The new option controls the behaviour of the unparser (i.e. the action corresponding to `-fdebug-unparse`). The default behaviour is to use the analyzed objects when unparsing. The new flag can be used to turn this off, so that the original parse-tree objects are used. The analyzed objects are generated during the semantic checks [1]. This patch also updates the semantics of `-fno-analyzed-objects-for-unparse`/`-funparse-typed-exprs-to-f18-fc` in `f18`, so that this flag is always taken into account when `Unparse` is used (this way the semantics in `f18` and `flang-new` are identical). The added test file is based on example from Peter Steinfeld. [1] https://github.com/llvm/llvm-project/blob/main/flang/docs/Semantics.md Differential Revision: https://reviews.llvm.org/D103612
1 parent b976b4a commit 5ae76be

File tree

9 files changed

+106
-50
lines changed

9 files changed

+106
-50
lines changed

clang/include/clang/Driver/Options.td

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -4521,6 +4521,11 @@ def fget_symbols_sources : Flag<["-"], "fget-symbols-sources">, Group<Action_Gro
45214521

45224522
def module_suffix : Separate<["-"], "module-suffix">, Group<f_Group>, MetaVarName<"<suffix>">,
45234523
HelpText<"Use <suffix> as the suffix for module files (the default value is `.mod`)">;
4524+
def fanalyzed_objects_for_unparse : Flag<["-"],
4525+
"fanalyzed-objects-for-unparse">, Group<f_Group>;
4526+
def fno_analyzed_objects_for_unparse : Flag<["-"],
4527+
"fno-analyzed-objects-for-unparse">, Group<f_Group>,
4528+
HelpText<"Do not use the analyzed objects when unparsing">;
45244529

45254530
}
45264531

flang/include/flang/Frontend/CompilerInvocation.h

Lines changed: 42 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -75,11 +75,39 @@ class CompilerInvocation : public CompilerInvocationBase {
7575

7676
bool warnAsErr_ = false;
7777

78+
/// This flag controls the unparsing and is used to decide whether to print out
79+
/// the semantically analyzed version of an object or expression or the plain
80+
/// version that does not include any information from semantic analysis.
81+
bool useAnalyzedObjectsForUnparse_ = true;
82+
7883
// Fortran Dialect options
7984
Fortran::common::IntrinsicTypeDefaultKinds defaultKinds_;
8085

8186
bool EnableConformanceChecks_ = false;
8287

88+
/// Used in e.g. unparsing to dump the analyzed rather than the original
89+
/// parse-tree objects.
90+
Fortran::parser::AnalyzedObjectsAsFortran AsFortran_{
91+
[](llvm::raw_ostream &o, const Fortran::evaluate::GenericExprWrapper &x) {
92+
if (x.v) {
93+
x.v->AsFortran(o);
94+
} else {
95+
o << "(bad expression)";
96+
}
97+
},
98+
[](llvm::raw_ostream &o,
99+
const Fortran::evaluate::GenericAssignmentWrapper &x) {
100+
if (x.v) {
101+
x.v->AsFortran(o);
102+
} else {
103+
o << "(bad assignment)";
104+
}
105+
},
106+
[](llvm::raw_ostream &o, const Fortran::evaluate::ProcedureRef &x) {
107+
x.AsFortran(o << "CALL ");
108+
},
109+
};
110+
83111
public:
84112
CompilerInvocation() = default;
85113

@@ -108,11 +136,21 @@ class CompilerInvocation : public CompilerInvocationBase {
108136
bool &warnAsErr() { return warnAsErr_; }
109137
const bool &warnAsErr() const { return warnAsErr_; }
110138

139+
bool &useAnalyzedObjectsForUnparse() { return useAnalyzedObjectsForUnparse_; }
140+
const bool &useAnalyzedObjectsForUnparse() const {
141+
return useAnalyzedObjectsForUnparse_;
142+
}
143+
111144
bool &enableConformanceChecks() { return EnableConformanceChecks_; }
112145
const bool &enableConformanceChecks() const {
113146
return EnableConformanceChecks_;
114147
}
115148

149+
Fortran::parser::AnalyzedObjectsAsFortran &asFortran() { return AsFortran_; }
150+
const Fortran::parser::AnalyzedObjectsAsFortran &asFortran() const {
151+
return AsFortran_;
152+
}
153+
116154
Fortran::common::IntrinsicTypeDefaultKinds &defaultKinds() {
117155
return defaultKinds_;
118156
}
@@ -142,6 +180,10 @@ class CompilerInvocation : public CompilerInvocationBase {
142180

143181
void SetWarnAsErr(bool flag) { warnAsErr_ = flag; }
144182

183+
void SetUseAnalyzedObjectsForUnparse(bool flag) {
184+
useAnalyzedObjectsForUnparse_ = flag;
185+
}
186+
145187
/// Set the Fortran options to predifined defaults. These defaults are
146188
/// consistend with f18/f18.cpp.
147189
// TODO: We should map frontendOpts_ to parserOpts_ instead. For that, we

flang/lib/Frontend/CompilerInvocation.cpp

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -401,6 +401,12 @@ static bool parseSemaArgs(CompilerInvocation &res, llvm::opt::ArgList &args,
401401
res.SetModuleFileSuffix(moduleSuffix->getValue());
402402
}
403403

404+
// -fno-analyzed-objects-for-unparse
405+
if (args.hasArg(
406+
clang::driver::options::OPT_fno_analyzed_objects_for_unparse)) {
407+
res.SetUseAnalyzedObjectsForUnparse(false);
408+
}
409+
404410
return diags.getNumErrors() == numErrorsBefore;
405411
}
406412

flang/lib/Frontend/FrontendActions.cpp

Lines changed: 13 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -242,28 +242,27 @@ void ParseSyntaxOnlyAction::ExecuteAction() {
242242
}
243243

244244
void DebugUnparseNoSemaAction::ExecuteAction() {
245+
auto &invoc = this->instance().invocation();
245246
auto &parseTree{instance().parsing().parseTree()};
246247

247-
Fortran::parser::AnalyzedObjectsAsFortran asFortran =
248-
Fortran::frontend::getBasicAsFortran();
249-
250248
// TODO: Options should come from CompilerInvocation
251249
Unparse(llvm::outs(), *parseTree,
252250
/*encoding=*/Fortran::parser::Encoding::UTF_8,
253251
/*capitalizeKeywords=*/true, /*backslashEscapes=*/false,
254-
/*preStatement=*/nullptr, &asFortran);
252+
/*preStatement=*/nullptr,
253+
invoc.useAnalyzedObjectsForUnparse() ? &invoc.asFortran() : nullptr);
255254
}
256255

257256
void DebugUnparseAction::ExecuteAction() {
257+
auto &invoc = this->instance().invocation();
258258
auto &parseTree{instance().parsing().parseTree()};
259-
Fortran::parser::AnalyzedObjectsAsFortran asFortran =
260-
Fortran::frontend::getBasicAsFortran();
261259

262260
// TODO: Options should come from CompilerInvocation
263261
Unparse(llvm::outs(), *parseTree,
264262
/*encoding=*/Fortran::parser::Encoding::UTF_8,
265263
/*capitalizeKeywords=*/true, /*backslashEscapes=*/false,
266-
/*preStatement=*/nullptr, &asFortran);
264+
/*preStatement=*/nullptr,
265+
invoc.useAnalyzedObjectsForUnparse() ? &invoc.asFortran() : nullptr);
267266

268267
// Report fatal semantic errors
269268
reportFatalSemanticErrors(semantics(), this->instance().diagnostics(),
@@ -310,12 +309,11 @@ void DebugDumpAllAction::ExecuteAction() {
310309

311310
// Dump parse tree
312311
auto &parseTree{instance().parsing().parseTree()};
313-
Fortran::parser::AnalyzedObjectsAsFortran asFortran =
314-
Fortran::frontend::getBasicAsFortran();
315312
llvm::outs() << "========================";
316313
llvm::outs() << " Flang: parse tree dump ";
317314
llvm::outs() << "========================\n";
318-
Fortran::parser::DumpTree(llvm::outs(), parseTree, &asFortran);
315+
Fortran::parser::DumpTree(
316+
llvm::outs(), parseTree, &ci.invocation().asFortran());
319317

320318
auto &semantics = this->semantics();
321319
auto tables{Fortran::semantics::BuildRuntimeDerivedTypeTables(
@@ -343,20 +341,19 @@ void DebugDumpAllAction::ExecuteAction() {
343341

344342
void DebugDumpParseTreeNoSemaAction::ExecuteAction() {
345343
auto &parseTree{instance().parsing().parseTree()};
346-
Fortran::parser::AnalyzedObjectsAsFortran asFortran =
347-
Fortran::frontend::getBasicAsFortran();
348344

349345
// Dump parse tree
350-
Fortran::parser::DumpTree(llvm::outs(), parseTree, &asFortran);
346+
Fortran::parser::DumpTree(
347+
llvm::outs(), parseTree, &this->instance().invocation().asFortran());
351348
}
352349

353350
void DebugDumpParseTreeAction::ExecuteAction() {
354351
auto &parseTree{instance().parsing().parseTree()};
355-
Fortran::parser::AnalyzedObjectsAsFortran asFortran =
356-
Fortran::frontend::getBasicAsFortran();
357352

358353
// Dump parse tree
359-
Fortran::parser::DumpTree(llvm::outs(), parseTree, &asFortran);
354+
Fortran::parser::DumpTree(
355+
llvm::outs(), parseTree, &this->instance().invocation().asFortran());
356+
360357
// Report fatal semantic errors
361358
reportFatalSemanticErrors(semantics(), this->instance().diagnostics(),
362359
GetCurrentFileOrBufferName());

flang/lib/Frontend/FrontendOptions.cpp

Lines changed: 0 additions & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -32,34 +32,6 @@ bool Fortran::frontend::mustBePreprocessed(llvm::StringRef suffix) {
3232
suffix == "F03" || suffix == "F08" || suffix == "F18";
3333
}
3434

35-
// TODO: This is a copy of `asFortran` from f18.cpp and is added here for
36-
// compatiblity. It doesn't really belong here, but I couldn't find a better
37-
// place. We should decide whether to add it to the Evaluate or Parse/Unparse
38-
// APIs or some dedicated utility library in the driver.
39-
Fortran::parser::AnalyzedObjectsAsFortran
40-
Fortran::frontend::getBasicAsFortran() {
41-
return Fortran::parser::AnalyzedObjectsAsFortran{
42-
[](llvm::raw_ostream &o, const Fortran::evaluate::GenericExprWrapper &x) {
43-
if (x.v) {
44-
x.v->AsFortran(o);
45-
} else {
46-
o << "(bad expression)";
47-
}
48-
},
49-
[](llvm::raw_ostream &o,
50-
const Fortran::evaluate::GenericAssignmentWrapper &x) {
51-
if (x.v) {
52-
x.v->AsFortran(o);
53-
} else {
54-
o << "(bad assignment)";
55-
}
56-
},
57-
[](llvm::raw_ostream &o, const Fortran::evaluate::ProcedureRef &x) {
58-
x.AsFortran(o << "CALL ");
59-
},
60-
};
61-
}
62-
6335
InputKind FrontendOptions::GetInputKindForExtension(llvm::StringRef extension) {
6436
if (isFixedFormSuffix(extension) || isFreeFormSuffix(extension)) {
6537
return Language::Fortran;

flang/test/Driver/driver-help.f90

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -101,6 +101,8 @@
101101
! HELP-FC1-NEXT: Specify where to find the compiled intrinsic modules
102102
! HELP-FC1-NEXT: -flarge-sizes Use INTEGER(KIND=8) for the result type in size-related intrinsics
103103
! HELP-FC1-NEXT: -flogical-abbreviations Enable logical abbreviations
104+
! HELP-FC1-NEXT: -fno-analyzed-objects-for-unparse
105+
! HELP-FC1-NEXT: Do not use the analyzed objects when unparsing
104106
! HELP-FC1-NEXT: -fopenacc Enable OpenACC
105107
! HELP-FC1-NEXT: -fopenmp Parse OpenMP pragmas and generate parallel code.
106108
! HELP-FC1-NEXT: -fxor-operator Enable .XOR. as a synonym of .NEQV.
Lines changed: 31 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,31 @@
1+
! Tests `-fno-analyzed-exprs-as-fortran` frontend option
2+
3+
!--------------------------
4+
! RUN lines
5+
!--------------------------
6+
! RUN: %flang_fc1 -fdebug-unparse %s | FileCheck %s --check-prefix=DEFAULT
7+
! RUN: %flang_fc1 -fdebug-unparse -fno-analyzed-objects-for-unparse %s | FileCheck %s --check-prefix=DISABLED
8+
9+
!------------------------------------------------
10+
! EXPECTED OUTPUT: default - use analyzed objects
11+
!------------------------------------------------
12+
! DEFAULT: PROGRAM test
13+
! DEFAULT-NEXT: REAL, PARAMETER :: val = 3.43e2_4
14+
! DEFAULT-NEXT: PRINT *, 3.47e2_4
15+
! DEFAULT-NEXT: END PROGRAM
16+
17+
!-----------------------------------------------------------
18+
! EXPECTED OUTPUT: disabled - don't use the analyzed objects
19+
!-----------------------------------------------------------
20+
! DISABLED: PROGRAM test
21+
! DISABLED-NEXT: REAL, PARAMETER :: val = 343.0
22+
! DISABLED-NEXT: PRINT *, val+4
23+
! DISABLED-NEXT: END PROGRAM
24+
25+
!--------------------------
26+
! INPUT
27+
!--------------------------
28+
program test
29+
real, parameter :: val = 343.0
30+
print *, val + 4
31+
end program

flang/tools/f18/f18.cpp

Lines changed: 6 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -104,7 +104,7 @@ struct DriverOptions {
104104
bool debugModuleWriter{false};
105105
bool defaultReal8{false};
106106
bool measureTree{false};
107-
bool unparseTypedExprsToF18_FC{false};
107+
bool useAnalyzedObjectsForUnparse{true};
108108
std::vector<std::string> F18_FCArgs;
109109
const char *prefix{nullptr};
110110
bool getDefinition{false};
@@ -321,7 +321,8 @@ std::string CompileFortran(std::string path, Fortran::parser::Options options,
321321
Unparse(llvm::outs(), parseTree, driver.encoding, true /*capitalize*/,
322322
options.features.IsEnabled(
323323
Fortran::common::LanguageFeature::BackslashEscapes),
324-
nullptr /* action before each statement */, &asFortran);
324+
nullptr /* action before each statement */,
325+
driver.useAnalyzedObjectsForUnparse ? &asFortran : nullptr);
325326
return {};
326327
}
327328
if (driver.syntaxOnly) {
@@ -344,7 +345,7 @@ std::string CompileFortran(std::string path, Fortran::parser::Options options,
344345
options.features.IsEnabled(
345346
Fortran::common::LanguageFeature::BackslashEscapes),
346347
nullptr /* action before each statement */,
347-
driver.unparseTypedExprsToF18_FC ? &asFortran : nullptr);
348+
driver.useAnalyzedObjectsForUnparse ? &asFortran : nullptr);
348349
}
349350

350351
RunOtherCompiler(driver, tmpSourcePath.data(), relo.data());
@@ -567,8 +568,8 @@ int main(int argc, char *const argv[]) {
567568
} else if (arg == "-funparse-with-symbols" ||
568569
arg == "-fdebug-unparse-with-symbols") {
569570
driver.dumpUnparseWithSymbols = true;
570-
} else if (arg == "-funparse-typed-exprs-to-f18-fc") {
571-
driver.unparseTypedExprsToF18_FC = true;
571+
} else if (arg == "-fno-analyzed-objects-for-unparse") {
572+
driver.useAnalyzedObjectsForUnparse = false;
572573
} else if (arg == "-fparse-only" || arg == "-fsyntax-only") {
573574
driver.syntaxOnly = true;
574575
} else if (arg == "-c") {

flang/tools/f18/flang

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,7 @@
88
#===------------------------------------------------------------------------===#
99

1010
wd=$(cd $(dirname "$0")/.. && pwd)
11-
opts="-module-suffix .f18.mod "
11+
opts="-fno-analyzed-objects-for-unparse -module-suffix .f18.mod "
1212
if ! $wd/bin/f18 $opts "$@"
1313
then status=$?
1414
echo flang: in $PWD, f18 failed with exit status $status: $wd/bin/f18 $opts "$@" >&2

0 commit comments

Comments
 (0)