Skip to content

Commit 8167052

Browse files
committed
[flang][driver] Add -fdebug-dump-all
The new option will run the semantic checks and then dump the parse tree and all the symbols. This is equivalent to running the driver twice, once with `-fdebug-dump-parse-tree` and then with the `-fdebug-dump-symbols` action flag. Currently we wouldn't be able to achieve the same by simply running: ``` flang-new -fc1 -fdebug-dump-parse-tree -fdebug-dump-symbols <input-file> ``` That's because the new driver will only run one frontend action per invocation (both of the flags used here are action flags). Diverging from this design would lead to costly compromises and it's best avoided. We may want to consider re-designing our debugging actions (and action options) in the future so that there's more code re-use. For now, I'm focusing on making sure that we support all the major cases requested by our users. Differential Revision: https://reviews.llvm.org/D104305
1 parent 0b3fa79 commit 8167052

File tree

8 files changed

+69
-0
lines changed

8 files changed

+69
-0
lines changed

clang/include/clang/Driver/Options.td

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -4504,6 +4504,8 @@ def fdebug_dump_parse_tree_no_sema : Flag<["-"], "fdebug-dump-parse-tree-no-sema
45044504
HelpText<"Dump the parse tree (skips the semantic checks)">,
45054505
DocBrief<[{Run the Parser and then output the parse tree. Semantic
45064506
checks are disabled.}]>;
4507+
def fdebug_dump_all : Flag<["-"], "fdebug-dump-all">, Group<Action_Group>,
4508+
HelpText<"Dump symbols and the parse tree after the semantic checks">;
45074509
def fdebug_dump_provenance : Flag<["-"], "fdebug-dump-provenance">, Group<Action_Group>,
45084510
HelpText<"Dump provenance">;
45094511
def fdebug_dump_parsing_log : Flag<["-"], "fdebug-dump-parsing-log">, Group<Action_Group>,

flang/include/flang/Frontend/FrontendActions.h

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -112,6 +112,10 @@ class DebugDumpParseTreeAction : public PrescanAndSemaAction {
112112
void ExecuteAction() override;
113113
};
114114

115+
class DebugDumpAllAction : public PrescanAndSemaAction {
116+
void ExecuteAction() override;
117+
};
118+
115119
class DebugPreFIRTreeAction : public PrescanAndSemaAction {
116120
void ExecuteAction() override;
117121
};

flang/include/flang/Frontend/FrontendOptions.h

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -51,6 +51,9 @@ enum ActionKind {
5151
/// Parse, run semantics and then output the parse tree
5252
DebugDumpParseTree,
5353

54+
/// Parse, run semantics and then output the parse tree and symbols
55+
DebugDumpAll,
56+
5457
/// Parse and then output the parse tree, skip the semantic checks
5558
DebugDumpParseTreeNoSema,
5659

flang/lib/Frontend/CompilerInvocation.cpp

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -141,6 +141,9 @@ static bool ParseFrontendArgs(FrontendOptions &opts, llvm::opt::ArgList &args,
141141
case clang::driver::options::OPT_fdebug_dump_parse_tree:
142142
opts.programAction_ = DebugDumpParseTree;
143143
break;
144+
case clang::driver::options::OPT_fdebug_dump_all:
145+
opts.programAction_ = DebugDumpAll;
146+
break;
144147
case clang::driver::options::OPT_fdebug_dump_parse_tree_no_sema:
145148
opts.programAction_ = DebugDumpParseTreeNoSema;
146149
break;

flang/lib/Frontend/FrontendActions.cpp

Lines changed: 36 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -305,6 +305,42 @@ void DebugDumpSymbolsAction::ExecuteAction() {
305305
semantics.DumpSymbols(llvm::outs());
306306
}
307307

308+
void DebugDumpAllAction::ExecuteAction() {
309+
CompilerInstance &ci = this->instance();
310+
311+
// Dump parse tree
312+
auto &parseTree{instance().parsing().parseTree()};
313+
Fortran::parser::AnalyzedObjectsAsFortran asFortran =
314+
Fortran::frontend::getBasicAsFortran();
315+
llvm::outs() << "========================";
316+
llvm::outs() << " Flang: parse tree dump ";
317+
llvm::outs() << "========================\n";
318+
Fortran::parser::DumpTree(llvm::outs(), parseTree, &asFortran);
319+
320+
auto &semantics = this->semantics();
321+
auto tables{Fortran::semantics::BuildRuntimeDerivedTypeTables(
322+
instance().invocation().semanticsContext())};
323+
// The runtime derived type information table builder may find and report
324+
// semantic errors. So it is important that we report them _after_
325+
// BuildRuntimeDerivedTypeTables is run.
326+
reportFatalSemanticErrors(
327+
semantics, this->instance().diagnostics(), GetCurrentFileOrBufferName());
328+
329+
if (!tables.schemata) {
330+
unsigned DiagID =
331+
ci.diagnostics().getCustomDiagID(clang::DiagnosticsEngine::Error,
332+
"could not find module file for __fortran_type_info");
333+
ci.diagnostics().Report(DiagID);
334+
llvm::errs() << "\n";
335+
}
336+
337+
// Dump symbols
338+
llvm::outs() << "=====================";
339+
llvm::outs() << " Flang: symbols dump ";
340+
llvm::outs() << "=====================\n";
341+
semantics.DumpSymbols(llvm::outs());
342+
}
343+
308344
void DebugDumpParseTreeNoSemaAction::ExecuteAction() {
309345
auto &parseTree{instance().parsing().parseTree()};
310346
Fortran::parser::AnalyzedObjectsAsFortran asFortran =

flang/lib/FrontendTool/ExecuteCompilerInvocation.cpp

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -55,6 +55,9 @@ static std::unique_ptr<FrontendAction> CreateFrontendBaseAction(
5555
case DebugDumpParseTreeNoSema:
5656
return std::make_unique<DebugDumpParseTreeNoSemaAction>();
5757
break;
58+
case DebugDumpAll:
59+
return std::make_unique<DebugDumpAllAction>();
60+
break;
5861
case DebugDumpProvenance:
5962
return std::make_unique<DebugDumpProvenanceAction>();
6063
break;

flang/test/Driver/driver-help.f90

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -69,6 +69,7 @@
6969
! HELP-FC1-NEXT: -falternative-parameter-statement
7070
! HELP-FC1-NEXT: Enable the old style PARAMETER statement
7171
! HELP-FC1-NEXT: -fbackslash Specify that backslash in string introduces an escape character
72+
! HELP-FC1-NEXT: -fdebug-dump-all Dump symbols and the parse tree after the semantic checks
7273
! HELP-FC1-NEXT: -fdebug-dump-parse-tree-no-sema
7374
! HELP-FC1-NEXT: Dump the parse tree (skips the semantic checks)
7475
! HELP-FC1-NEXT: -fdebug-dump-parse-tree Dump the parse tree

flang/test/Driver/dump-all.f90

Lines changed: 17 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,17 @@
1+
!----------
2+
! RUN lines
3+
!----------
4+
! RUN: %flang_fc1 -fdebug-dump-all %s 2>&1 | FileCheck %s
5+
6+
!----------------
7+
! EXPECTED OUTPUT
8+
!----------------
9+
! CHECK: Flang: parse tree dump
10+
! CHECK: Flang: symbols dump
11+
12+
!-------
13+
! INPUT
14+
!-------
15+
parameter(i=1)
16+
integer :: j
17+
end program

0 commit comments

Comments
 (0)