Skip to content

Commit 1b142d9

Browse files
klauslerjeanPerier
authored andcommitted
[flang] Enforce fixed form rules about END continuation
From subclause 6.3.3.5: a program unit END statement cannot be continued in fixed form, and other statements cannot have initial lines that look like program unit END statements. I think this is to avoid violating assumptions that are important to legacy compilers' statement classification routines. Differential Revision: https://reviews.llvm.org/D109933
1 parent 75e5f22 commit 1b142d9

File tree

5 files changed

+101
-2
lines changed

5 files changed

+101
-2
lines changed

flang/lib/Parser/prescan.cpp

Lines changed: 64 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -217,6 +217,9 @@ void Prescanner::Statement() {
217217
if (line.kind == LineClassification::Kind::CompilerDirective) {
218218
SourceFormChange(tokens.ToString());
219219
}
220+
if (inFixedForm_ && line.kind == LineClassification::Kind::Source) {
221+
EnforceStupidEndStatementRules(tokens);
222+
}
220223
tokens.CheckBadFortranCharacters(messages_).Emit(cooked_);
221224
}
222225
if (omitNewline_) {
@@ -288,6 +291,67 @@ void Prescanner::LabelField(TokenSequence &token) {
288291
}
289292
}
290293

294+
// 6.3.3.5: A program unit END statement, or any other statement whose
295+
// initial line resembles an END statement, shall not be continued in
296+
// fixed form source.
297+
void Prescanner::EnforceStupidEndStatementRules(const TokenSequence &tokens) {
298+
CharBlock cBlock{tokens.ToCharBlock()};
299+
const char *str{cBlock.begin()};
300+
std::size_t n{cBlock.size()};
301+
if (n < 3) {
302+
return;
303+
}
304+
std::size_t j{0};
305+
for (; j < n && (str[j] == ' ' || (str[j] >= '0' && str[j] <= '9')); ++j) {
306+
}
307+
if (j + 3 > n || std::memcmp(str + j, "end", 3) != 0) {
308+
return;
309+
}
310+
// It starts with END, possibly after a label.
311+
auto start{allSources_.GetSourcePosition(tokens.GetCharProvenance(j))};
312+
auto end{allSources_.GetSourcePosition(tokens.GetCharProvenance(n - 1))};
313+
if (!start || !end) {
314+
return;
315+
}
316+
if (&start->file == &end->file && start->line == end->line) {
317+
return; // no continuation
318+
}
319+
j += 3;
320+
static const char *const prefixes[]{"program", "subroutine", "function",
321+
"blockdata", "module", "submodule", nullptr};
322+
CharBlock stmt{tokens.ToCharBlock()};
323+
bool isPrefix{j == n || !IsLegalInIdentifier(str[j])}; // prefix is END
324+
std::size_t endOfPrefix{j - 1};
325+
for (const char *const *p{prefixes}; *p; ++p) {
326+
std::size_t pLen{std::strlen(*p)};
327+
if (j + pLen <= n && std::memcmp(str + j, *p, pLen) == 0) {
328+
isPrefix = true; // END thing as prefix
329+
j += pLen;
330+
endOfPrefix = j - 1;
331+
for (; j < n && IsLegalInIdentifier(str[j]); ++j) {
332+
}
333+
break;
334+
}
335+
}
336+
if (isPrefix) {
337+
auto range{tokens.GetTokenProvenanceRange(1)};
338+
if (j == n) { // END or END thing [name]
339+
Say(range,
340+
"Program unit END statement may not be continued in fixed form source"_err_en_US);
341+
} else {
342+
auto endOfPrefixPos{
343+
allSources_.GetSourcePosition(tokens.GetCharProvenance(endOfPrefix))};
344+
auto next{allSources_.GetSourcePosition(tokens.GetCharProvenance(j))};
345+
if (endOfPrefixPos && next && &endOfPrefixPos->file == &start->file &&
346+
endOfPrefixPos->line == start->line &&
347+
(&next->file != &start->file || next->line != start->line)) {
348+
Say(range,
349+
"Initial line of continued statement must not appear to be a program unit END in fixed form source"_err_en_US);
350+
}
351+
}
352+
}
353+
}
354+
291355
void Prescanner::SkipToEndOfLine() {
292356
while (*at_ != '\n') {
293357
++at_, ++column_;

flang/lib/Parser/prescan.h

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -150,6 +150,7 @@ class Prescanner {
150150
}
151151

152152
void LabelField(TokenSequence &);
153+
void EnforceStupidEndStatementRules(const TokenSequence &);
153154
void SkipToEndOfLine();
154155
bool MustSkipToEndOfLine() const;
155156
void NextChar();

flang/lib/Parser/token-sequence.cpp

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -286,10 +286,14 @@ llvm::raw_ostream &TokenSequence::Dump(llvm::raw_ostream &o) const {
286286
return o;
287287
}
288288

289+
Provenance TokenSequence::GetCharProvenance(std::size_t offset) const {
290+
ProvenanceRange range{provenances_.Map(offset)};
291+
return range.start();
292+
}
293+
289294
Provenance TokenSequence::GetTokenProvenance(
290295
std::size_t token, std::size_t offset) const {
291-
ProvenanceRange range{provenances_.Map(start_[token] + offset)};
292-
return range.start();
296+
return GetCharProvenance(start_[token] + offset);
293297
}
294298

295299
ProvenanceRange TokenSequence::GetTokenProvenanceRange(

flang/lib/Parser/token-sequence.h

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -102,6 +102,7 @@ class TokenSequence {
102102
void Put(const std::string &, Provenance);
103103
void Put(llvm::raw_string_ostream &, Provenance);
104104

105+
Provenance GetCharProvenance(std::size_t) const;
105106
Provenance GetTokenProvenance(
106107
std::size_t token, std::size_t offset = 0) const;
107108
ProvenanceRange GetTokenProvenanceRange(

flang/test/Parser/end.f

Lines changed: 29 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,29 @@
1+
! RUN: not %flang_fc1 -fsyntax-only %s 2>&1 | FileCheck %s
2+
! CHECK: end.f:3:7: error: Program unit END statement may not be continued in fixed form source
3+
e
4+
+ nd
5+
! CHECK: end.f:6:7: error: Program unit END statement may not be continued in fixed form source
6+
end prog
7+
+ ram
8+
! CHECK: end.f:9:7: error: Program unit END statement may not be continued in fixed form source
9+
end
10+
+ program
11+
! CHECK: end.f:12:7: error: Program unit END statement may not be continued in fixed form source
12+
end
13+
+ program
14+
1 main
15+
! CHECK: end.f:16:7: error: Program unit END statement may not be continued in fixed form source
16+
end program
17+
1 main
18+
! CHECK: end.f:19:7: error: Initial line of continued statement must not appear to be a program unit END in fixed form source
19+
end
20+
+ = end + 1
21+
! CHECK: end.f:22:7: error: Initial line of continued statement must not appear to be a program unit END in fixed form source
22+
end module
23+
+ = end module + 1
24+
! CHECK-NOT: end.f:25:7: error: Initial line of continued statement must not appear to be a program unit END in fixed form source
25+
end =
26+
+ end + 1
27+
! CHECK-NOT: end.f:28:7: error: Initial line of continued statement must not appear to be a program unit END in fixed form source
28+
end block data (
29+
+ 1) = 666

0 commit comments

Comments
 (0)