1 //===-- lib/Parser/Fortran-parsers.cpp ------------------------------------===//
2 //
3 // Part of the LLVM Project, under the Apache License v2.0 with LLVM Exceptions.
4 // See https://llvm.org/LICENSE.txt for license information.
5 // SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception
6 //
7 //===----------------------------------------------------------------------===//
8 
9 // Top-level grammar specification for Fortran.  These parsers drive
10 // the tokenization parsers in cooked-tokens.h to consume characters,
11 // recognize the productions of Fortran, and to construct a parse tree.
12 // See ParserCombinators.md for documentation on the parser combinator
13 // library used here to implement an LL recursive descent recognizer.
14 
15 // The productions that follow are derived from the draft Fortran 2018
16 // standard, with some necessary modifications to remove left recursion
17 // and some generalization in order to defer cases where parses depend
18 // on the definitions of symbols.  The "Rxxx" numbers that appear in
19 // comments refer to these numbered requirements in the Fortran standard.
20 
21 // The whole Fortran grammar originally constituted one header file,
22 // but that turned out to require more memory to compile with current
23 // C++ compilers than some people were willing to accept, so now the
24 // various per-type parsers are partitioned into several C++ source
25 // files.  This file contains parsers for constants, types, declarations,
26 // and misfits (mostly clauses 7, 8, & 9 of Fortran 2018).  The others:
27 //  executable-parsers.cpp  Executable statements
28 //  expr-parsers.cpp        Expressions
29 //  io-parsers.cpp          I/O statements and FORMAT
30 //  openmp-parsers.cpp      OpenMP directives
31 //  program-parsers.cpp     Program units
32 
33 #include "basic-parsers.h"
34 #include "expr-parsers.h"
35 #include "misc-parsers.h"
36 #include "stmt-parser.h"
37 #include "token-parsers.h"
38 #include "type-parser-implementation.h"
39 #include "flang/Parser/parse-tree.h"
40 #include "flang/Parser/user-state.h"
41 
42 namespace Fortran::parser {
43 
44 // R601 alphanumeric-character -> letter | digit | underscore
45 // R603 name -> letter [alphanumeric-character]...
46 constexpr auto nonDigitIdChar{letter || otherIdChar};
47 constexpr auto rawName{nonDigitIdChar >> many(nonDigitIdChar || digit)};
48 TYPE_PARSER(space >> sourced(rawName >> construct<Name>()))
49 
50 // R608 intrinsic-operator ->
51 //        power-op | mult-op | add-op | concat-op | rel-op |
52 //        not-op | and-op | or-op | equiv-op
53 // R610 extended-intrinsic-op -> intrinsic-operator
54 // These parsers must be ordered carefully to avoid misrecognition.
55 constexpr auto namedIntrinsicOperator{
56     ".LT." >> pure(DefinedOperator::IntrinsicOperator::LT) ||
57     ".LE." >> pure(DefinedOperator::IntrinsicOperator::LE) ||
58     ".EQ." >> pure(DefinedOperator::IntrinsicOperator::EQ) ||
59     ".NE." >> pure(DefinedOperator::IntrinsicOperator::NE) ||
60     ".GE." >> pure(DefinedOperator::IntrinsicOperator::GE) ||
61     ".GT." >> pure(DefinedOperator::IntrinsicOperator::GT) ||
62     ".NOT." >> pure(DefinedOperator::IntrinsicOperator::NOT) ||
63     ".AND." >> pure(DefinedOperator::IntrinsicOperator::AND) ||
64     ".OR." >> pure(DefinedOperator::IntrinsicOperator::OR) ||
65     ".EQV." >> pure(DefinedOperator::IntrinsicOperator::EQV) ||
66     ".NEQV." >> pure(DefinedOperator::IntrinsicOperator::NEQV) ||
67     extension<LanguageFeature::XOROperator>(
68         ".XOR." >> pure(DefinedOperator::IntrinsicOperator::NEQV)) ||
69     extension<LanguageFeature::LogicalAbbreviations>(
70         ".N." >> pure(DefinedOperator::IntrinsicOperator::NOT) ||
71         ".A." >> pure(DefinedOperator::IntrinsicOperator::AND) ||
72         ".O." >> pure(DefinedOperator::IntrinsicOperator::OR) ||
73         extension<LanguageFeature::XOROperator>(
74             ".X." >> pure(DefinedOperator::IntrinsicOperator::NEQV)))};
75 
76 constexpr auto intrinsicOperator{
77     "**" >> pure(DefinedOperator::IntrinsicOperator::Power) ||
78     "*" >> pure(DefinedOperator::IntrinsicOperator::Multiply) ||
79     "//" >> pure(DefinedOperator::IntrinsicOperator::Concat) ||
80     "/=" >> pure(DefinedOperator::IntrinsicOperator::NE) ||
81     "/" >> pure(DefinedOperator::IntrinsicOperator::Divide) ||
82     "+" >> pure(DefinedOperator::IntrinsicOperator::Add) ||
83     "-" >> pure(DefinedOperator::IntrinsicOperator::Subtract) ||
84     "<=" >> pure(DefinedOperator::IntrinsicOperator::LE) ||
85     extension<LanguageFeature::AlternativeNE>(
86         "<>" >> pure(DefinedOperator::IntrinsicOperator::NE)) ||
87     "<" >> pure(DefinedOperator::IntrinsicOperator::LT) ||
88     "==" >> pure(DefinedOperator::IntrinsicOperator::EQ) ||
89     ">=" >> pure(DefinedOperator::IntrinsicOperator::GE) ||
90     ">" >> pure(DefinedOperator::IntrinsicOperator::GT) ||
91     namedIntrinsicOperator};
92 
93 // R609 defined-operator ->
94 //        defined-unary-op | defined-binary-op | extended-intrinsic-op
95 TYPE_PARSER(construct<DefinedOperator>(intrinsicOperator) ||
96     construct<DefinedOperator>(definedOpName))
97 
98 // R505 implicit-part -> [implicit-part-stmt]... implicit-stmt
99 // N.B. PARAMETER, FORMAT, & ENTRY statements that appear before any
100 // other kind of declaration-construct will be parsed into the
101 // implicit-part.
102 TYPE_CONTEXT_PARSER("implicit part"_en_US,
103     construct<ImplicitPart>(many(Parser<ImplicitPartStmt>{})))
104 
105 // R506 implicit-part-stmt ->
106 //         implicit-stmt | parameter-stmt | format-stmt | entry-stmt
TYPE_PARSER(first (construct<ImplicitPartStmt> (statement (indirect (Parser<ImplicitStmt>{}))),construct<ImplicitPartStmt> (statement (indirect (parameterStmt))),construct<ImplicitPartStmt> (statement (indirect (oldParameterStmt))),construct<ImplicitPartStmt> (statement (indirect (formatStmt))),construct<ImplicitPartStmt> (statement (indirect (entryStmt))),construct<ImplicitPartStmt> (indirect (compilerDirective))))107 TYPE_PARSER(first(
108     construct<ImplicitPartStmt>(statement(indirect(Parser<ImplicitStmt>{}))),
109     construct<ImplicitPartStmt>(statement(indirect(parameterStmt))),
110     construct<ImplicitPartStmt>(statement(indirect(oldParameterStmt))),
111     construct<ImplicitPartStmt>(statement(indirect(formatStmt))),
112     construct<ImplicitPartStmt>(statement(indirect(entryStmt))),
113     construct<ImplicitPartStmt>(indirect(compilerDirective))))
114 
115 // R512 internal-subprogram -> function-subprogram | subroutine-subprogram
116 // Internal subprograms are not program units, so their END statements
117 // can be followed by ';' and another statement on the same line.
118 TYPE_CONTEXT_PARSER("internal subprogram"_en_US,
119     (construct<InternalSubprogram>(indirect(functionSubprogram)) ||
120         construct<InternalSubprogram>(indirect(subroutineSubprogram))) /
121         forceEndOfStmt)
122 
123 // R511 internal-subprogram-part -> contains-stmt [internal-subprogram]...
124 TYPE_CONTEXT_PARSER("internal subprogram part"_en_US,
125     construct<InternalSubprogramPart>(statement(containsStmt),
126         many(StartNewSubprogram{} >> Parser<InternalSubprogram>{})))
127 
128 // R605 literal-constant ->
129 //        int-literal-constant | real-literal-constant |
130 //        complex-literal-constant | logical-literal-constant |
131 //        char-literal-constant | boz-literal-constant
132 TYPE_PARSER(
133     first(construct<LiteralConstant>(Parser<HollerithLiteralConstant>{}),
134         construct<LiteralConstant>(realLiteralConstant),
135         construct<LiteralConstant>(intLiteralConstant),
136         construct<LiteralConstant>(Parser<ComplexLiteralConstant>{}),
137         construct<LiteralConstant>(Parser<BOZLiteralConstant>{}),
138         construct<LiteralConstant>(charLiteralConstant),
139         construct<LiteralConstant>(Parser<LogicalLiteralConstant>{})))
140 
141 // R606 named-constant -> name
142 TYPE_PARSER(construct<NamedConstant>(name))
143 
144 // R701 type-param-value -> scalar-int-expr | * | :
145 TYPE_PARSER(construct<TypeParamValue>(scalarIntExpr) ||
146     construct<TypeParamValue>(star) ||
147     construct<TypeParamValue>(construct<TypeParamValue::Deferred>(":"_tok)))
148 
149 // R702 type-spec -> intrinsic-type-spec | derived-type-spec
150 // N.B. This type-spec production is one of two instances in the Fortran
151 // grammar where intrinsic types and bare derived type names can clash;
152 // the other is below in R703 declaration-type-spec.  Look-ahead is required
153 // to disambiguate the cases where a derived type name begins with the name
154 // of an intrinsic type, e.g., REALITY.
155 TYPE_CONTEXT_PARSER("type spec"_en_US,
156     construct<TypeSpec>(intrinsicTypeSpec / lookAhead("::"_tok || ")"_tok)) ||
157         construct<TypeSpec>(derivedTypeSpec))
158 
159 // R703 declaration-type-spec ->
160 //        intrinsic-type-spec | TYPE ( intrinsic-type-spec ) |
161 //        TYPE ( derived-type-spec ) | CLASS ( derived-type-spec ) |
162 //        CLASS ( * ) | TYPE ( * )
163 // N.B. It is critical to distribute "parenthesized()" over the alternatives
164 // for TYPE (...), rather than putting the alternatives within it, which
165 // would fail on "TYPE(real_derived)" with a misrecognition of "real" as an
166 // intrinsic-type-spec.
167 TYPE_CONTEXT_PARSER("declaration type spec"_en_US,
168     construct<DeclarationTypeSpec>(intrinsicTypeSpec) ||
169         "TYPE" >>
170             (parenthesized(construct<DeclarationTypeSpec>(intrinsicTypeSpec)) ||
171                 parenthesized(construct<DeclarationTypeSpec>(
172                     construct<DeclarationTypeSpec::Type>(derivedTypeSpec))) ||
173                 construct<DeclarationTypeSpec>(
174                     "( * )" >> construct<DeclarationTypeSpec::TypeStar>())) ||
175         "CLASS" >> parenthesized(construct<DeclarationTypeSpec>(
176                                      construct<DeclarationTypeSpec::Class>(
177                                          derivedTypeSpec)) ||
178                        construct<DeclarationTypeSpec>("*" >>
179                            construct<DeclarationTypeSpec::ClassStar>())) ||
180         extension<LanguageFeature::DECStructures>(
181             construct<DeclarationTypeSpec>(
182                 construct<DeclarationTypeSpec::Record>(
183                     "RECORD /" >> name / "/"))))
184 
185 // R704 intrinsic-type-spec ->
186 //        integer-type-spec | REAL [kind-selector] | DOUBLE PRECISION |
187 //        COMPLEX [kind-selector] | CHARACTER [char-selector] |
188 //        LOGICAL [kind-selector]
189 // Extensions: DOUBLE COMPLEX, BYTE
190 TYPE_CONTEXT_PARSER("intrinsic type spec"_en_US,
191     first(construct<IntrinsicTypeSpec>(integerTypeSpec),
192         construct<IntrinsicTypeSpec>(
193             construct<IntrinsicTypeSpec::Real>("REAL" >> maybe(kindSelector))),
194         construct<IntrinsicTypeSpec>("DOUBLE PRECISION" >>
195             construct<IntrinsicTypeSpec::DoublePrecision>()),
196         construct<IntrinsicTypeSpec>(construct<IntrinsicTypeSpec::Complex>(
197             "COMPLEX" >> maybe(kindSelector))),
198         construct<IntrinsicTypeSpec>(construct<IntrinsicTypeSpec::Character>(
199             "CHARACTER" >> maybe(Parser<CharSelector>{}))),
200         construct<IntrinsicTypeSpec>(construct<IntrinsicTypeSpec::Logical>(
201             "LOGICAL" >> maybe(kindSelector))),
202         construct<IntrinsicTypeSpec>("DOUBLE COMPLEX" >>
203             extension<LanguageFeature::DoubleComplex>(
204                 construct<IntrinsicTypeSpec::DoubleComplex>())),
205         extension<LanguageFeature::Byte>(
206             construct<IntrinsicTypeSpec>(construct<IntegerTypeSpec>(
207                 "BYTE" >> construct<std::optional<KindSelector>>(pure(1)))))))
208 
209 // R705 integer-type-spec -> INTEGER [kind-selector]
210 TYPE_PARSER(construct<IntegerTypeSpec>("INTEGER" >> maybe(kindSelector)))
211 
212 // R706 kind-selector -> ( [KIND =] scalar-int-constant-expr )
213 // Legacy extension: kind-selector -> * digit-string
214 TYPE_PARSER(construct<KindSelector>(
215                 parenthesized(maybe("KIND ="_tok) >> scalarIntConstantExpr)) ||
216     extension<LanguageFeature::StarKind>(construct<KindSelector>(
217         construct<KindSelector::StarSize>("*" >> digitString64 / spaceCheck))))
218 
219 // R707 signed-int-literal-constant -> [sign] int-literal-constant
220 TYPE_PARSER(sourced(construct<SignedIntLiteralConstant>(
221     SignedIntLiteralConstantWithoutKind{}, maybe(underscore >> kindParam))))
222 
223 // R708 int-literal-constant -> digit-string [_ kind-param]
224 // The negated look-ahead for a trailing underscore prevents misrecognition
225 // when the digit string is a numeric kind parameter of a character literal.
226 TYPE_PARSER(construct<IntLiteralConstant>(
227     space >> digitString, maybe(underscore >> kindParam) / !underscore))
228 
229 // R709 kind-param -> digit-string | scalar-int-constant-name
230 TYPE_PARSER(construct<KindParam>(digitString64) ||
231     construct<KindParam>(scalar(integer(constant(name)))))
232 
233 // R712 sign -> + | -
234 // N.B. A sign constitutes a whole token, so a space is allowed in free form
235 // after the sign and before a real-literal-constant or
236 // complex-literal-constant.  A sign is not a unary operator in these contexts.
237 constexpr auto sign{
238     "+"_tok >> pure(Sign::Positive) || "-"_tok >> pure(Sign::Negative)};
239 
240 // R713 signed-real-literal-constant -> [sign] real-literal-constant
241 constexpr auto signedRealLiteralConstant{
242     construct<SignedRealLiteralConstant>(maybe(sign), realLiteralConstant)};
243 
244 // R714 real-literal-constant ->
245 //        significand [exponent-letter exponent] [_ kind-param] |
246 //        digit-string exponent-letter exponent [_ kind-param]
247 // R715 significand -> digit-string . [digit-string] | . digit-string
248 // R716 exponent-letter -> E | D
249 // Extension: Q
250 // R717 exponent -> signed-digit-string
251 constexpr auto exponentPart{
252     ("ed"_ch || extension<LanguageFeature::QuadPrecision>("q"_ch)) >>
253     SignedDigitString{}};
254 
255 TYPE_CONTEXT_PARSER("REAL literal constant"_en_US,
256     space >>
257         construct<RealLiteralConstant>(
258             sourced((digitString >> "."_ch >>
259                             !(some(letter) >>
260                                 "."_ch /* don't misinterpret 1.AND. */) >>
261                             maybe(digitString) >> maybe(exponentPart) >> ok ||
262                         "."_ch >> digitString >> maybe(exponentPart) >> ok ||
263                         digitString >> exponentPart >> ok) >>
264                 construct<RealLiteralConstant::Real>()),
265             maybe(underscore >> kindParam)))
266 
267 // R718 complex-literal-constant -> ( real-part , imag-part )
268 TYPE_CONTEXT_PARSER("COMPLEX literal constant"_en_US,
269     parenthesized(construct<ComplexLiteralConstant>(
270         Parser<ComplexPart>{} / ",", Parser<ComplexPart>{})))
271 
272 // PGI/Intel extension: signed complex literal constant
TYPE_PARSER(construct<SignedComplexLiteralConstant> (sign,Parser<ComplexLiteralConstant>{}))273 TYPE_PARSER(construct<SignedComplexLiteralConstant>(
274     sign, Parser<ComplexLiteralConstant>{}))
275 
276 // R719 real-part ->
277 //        signed-int-literal-constant | signed-real-literal-constant |
278 //        named-constant
279 // R720 imag-part ->
280 //        signed-int-literal-constant | signed-real-literal-constant |
281 //        named-constant
282 TYPE_PARSER(construct<ComplexPart>(signedRealLiteralConstant) ||
283     construct<ComplexPart>(signedIntLiteralConstant) ||
284     construct<ComplexPart>(namedConstant))
285 
286 // R721 char-selector ->
287 //        length-selector |
288 //        ( LEN = type-param-value , KIND = scalar-int-constant-expr ) |
289 //        ( type-param-value , [KIND =] scalar-int-constant-expr ) |
290 //        ( KIND = scalar-int-constant-expr [, LEN = type-param-value] )
291 TYPE_PARSER(construct<CharSelector>(Parser<LengthSelector>{}) ||
292     parenthesized(construct<CharSelector>(
293         "LEN =" >> typeParamValue, ", KIND =" >> scalarIntConstantExpr)) ||
294     parenthesized(construct<CharSelector>(
295         typeParamValue / ",", maybe("KIND ="_tok) >> scalarIntConstantExpr)) ||
296     parenthesized(construct<CharSelector>(
297         "KIND =" >> scalarIntConstantExpr, maybe(", LEN =" >> typeParamValue))))
298 
299 // R722 length-selector -> ( [LEN =] type-param-value ) | * char-length [,]
300 // N.B. The trailing [,] in the production is permitted by the Standard
301 // only in the context of a type-declaration-stmt, but even with that
302 // limitation, it would seem to be unnecessary and buggy to consume the comma
303 // here.
304 TYPE_PARSER(construct<LengthSelector>(
305                 parenthesized(maybe("LEN ="_tok) >> typeParamValue)) ||
306     construct<LengthSelector>("*" >> charLength /* / maybe(","_tok) */))
307 
308 // R723 char-length -> ( type-param-value ) | digit-string
309 TYPE_PARSER(construct<CharLength>(parenthesized(typeParamValue)) ||
310     construct<CharLength>(space >> digitString64 / spaceCheck))
311 
312 // R724 char-literal-constant ->
313 //        [kind-param _] ' [rep-char]... ' |
314 //        [kind-param _] " [rep-char]... "
315 // "rep-char" is any non-control character.  Doubled interior quotes are
316 // combined.  Backslash escapes can be enabled.
317 // N.B. the parsing of "kind-param" takes care to not consume the '_'.
318 TYPE_CONTEXT_PARSER("CHARACTER literal constant"_en_US,
319     construct<CharLiteralConstant>(
320         kindParam / underscore, charLiteralConstantWithoutKind) ||
321         construct<CharLiteralConstant>(construct<std::optional<KindParam>>(),
322             space >> charLiteralConstantWithoutKind))
323 
324 TYPE_CONTEXT_PARSER(
325     "Hollerith"_en_US, construct<HollerithLiteralConstant>(rawHollerithLiteral))
326 
327 // R725 logical-literal-constant ->
328 //        .TRUE. [_ kind-param] | .FALSE. [_ kind-param]
329 // Also accept .T. and .F. as extensions.
330 TYPE_PARSER(construct<LogicalLiteralConstant>(
331                 logicalTRUE, maybe(underscore >> kindParam)) ||
332     construct<LogicalLiteralConstant>(
333         logicalFALSE, maybe(underscore >> kindParam)))
334 
335 // R726 derived-type-def ->
336 //        derived-type-stmt [type-param-def-stmt]...
337 //        [private-or-sequence]... [component-part]
338 //        [type-bound-procedure-part] end-type-stmt
339 // R735 component-part -> [component-def-stmt]...
340 TYPE_CONTEXT_PARSER("derived type definition"_en_US,
341     construct<DerivedTypeDef>(statement(Parser<DerivedTypeStmt>{}),
342         many(unambiguousStatement(Parser<TypeParamDefStmt>{})),
343         many(statement(Parser<PrivateOrSequence>{})),
344         many(inContext("component"_en_US,
345             unambiguousStatement(Parser<ComponentDefStmt>{}))),
346         maybe(Parser<TypeBoundProcedurePart>{}),
347         statement(Parser<EndTypeStmt>{})))
348 
349 // R727 derived-type-stmt ->
350 //        TYPE [[, type-attr-spec-list] ::] type-name [(
351 //        type-param-name-list )]
352 TYPE_CONTEXT_PARSER("TYPE statement"_en_US,
353     construct<DerivedTypeStmt>(
354         "TYPE" >> optionalListBeforeColons(Parser<TypeAttrSpec>{}), name,
355         defaulted(parenthesized(nonemptyList(name)))))
356 
357 // R728 type-attr-spec ->
358 //        ABSTRACT | access-spec | BIND(C) | EXTENDS ( parent-type-name )
359 TYPE_PARSER(construct<TypeAttrSpec>(construct<Abstract>("ABSTRACT"_tok)) ||
360     construct<TypeAttrSpec>(construct<TypeAttrSpec::BindC>("BIND ( C )"_tok)) ||
361     construct<TypeAttrSpec>(
362         construct<TypeAttrSpec::Extends>("EXTENDS" >> parenthesized(name))) ||
363     construct<TypeAttrSpec>(accessSpec))
364 
365 // R729 private-or-sequence -> private-components-stmt | sequence-stmt
366 TYPE_PARSER(construct<PrivateOrSequence>(Parser<PrivateStmt>{}) ||
367     construct<PrivateOrSequence>(Parser<SequenceStmt>{}))
368 
369 // R730 end-type-stmt -> END TYPE [type-name]
370 TYPE_PARSER(construct<EndTypeStmt>(
371     recovery("END TYPE" >> maybe(name), endStmtErrorRecovery)))
372 
373 // R731 sequence-stmt -> SEQUENCE
374 TYPE_PARSER(construct<SequenceStmt>("SEQUENCE"_tok))
375 
376 // R732 type-param-def-stmt ->
377 //        integer-type-spec , type-param-attr-spec :: type-param-decl-list
378 // R734 type-param-attr-spec -> KIND | LEN
379 constexpr auto kindOrLen{"KIND" >> pure(common::TypeParamAttr::Kind) ||
380     "LEN" >> pure(common::TypeParamAttr::Len)};
381 TYPE_PARSER(construct<TypeParamDefStmt>(integerTypeSpec / ",", kindOrLen,
382     "::" >> nonemptyList("expected type parameter declarations"_err_en_US,
383                 Parser<TypeParamDecl>{})))
384 
385 // R733 type-param-decl -> type-param-name [= scalar-int-constant-expr]
386 TYPE_PARSER(construct<TypeParamDecl>(name, maybe("=" >> scalarIntConstantExpr)))
387 
388 // R736 component-def-stmt -> data-component-def-stmt |
389 //        proc-component-def-stmt
390 // Accidental extension not enabled here: PGI accepts type-param-def-stmt in
391 // component-part of derived-type-def.
392 TYPE_PARSER(recovery(
393     withMessage("expected component definition"_err_en_US,
394         first(construct<ComponentDefStmt>(Parser<DataComponentDefStmt>{}),
395             construct<ComponentDefStmt>(Parser<ProcComponentDefStmt>{}))),
396     construct<ComponentDefStmt>(inStmtErrorRecovery)))
397 
398 // R737 data-component-def-stmt ->
399 //        declaration-type-spec [[, component-attr-spec-list] ::]
400 //        component-decl-list
401 // N.B. The standard requires double colons if there's an initializer.
402 TYPE_PARSER(construct<DataComponentDefStmt>(declarationTypeSpec,
403     optionalListBeforeColons(Parser<ComponentAttrSpec>{}),
404     nonemptyList(
405         "expected component declarations"_err_en_US, Parser<ComponentDecl>{})))
406 
407 // R738 component-attr-spec ->
408 //        access-spec | ALLOCATABLE |
409 //        CODIMENSION lbracket coarray-spec rbracket |
410 //        CONTIGUOUS | DIMENSION ( component-array-spec ) | POINTER
411 TYPE_PARSER(construct<ComponentAttrSpec>(accessSpec) ||
412     construct<ComponentAttrSpec>(allocatable) ||
413     construct<ComponentAttrSpec>("CODIMENSION" >> coarraySpec) ||
414     construct<ComponentAttrSpec>(contiguous) ||
415     construct<ComponentAttrSpec>("DIMENSION" >> Parser<ComponentArraySpec>{}) ||
416     construct<ComponentAttrSpec>(pointer) ||
417     construct<ComponentAttrSpec>(recovery(
418         fail<ErrorRecovery>(
419             "type parameter definitions must appear before component declarations"_err_en_US),
420         kindOrLen >> construct<ErrorRecovery>())))
421 
422 // R739 component-decl ->
423 //        component-name [( component-array-spec )]
424 //        [lbracket coarray-spec rbracket] [* char-length]
425 //        [component-initialization]
426 TYPE_CONTEXT_PARSER("component declaration"_en_US,
427     construct<ComponentDecl>(name, maybe(Parser<ComponentArraySpec>{}),
428         maybe(coarraySpec), maybe("*" >> charLength), maybe(initialization)))
429 
430 // R740 component-array-spec ->
431 //        explicit-shape-spec-list | deferred-shape-spec-list
432 // N.B. Parenthesized here rather than around references to this production.
433 TYPE_PARSER(construct<ComponentArraySpec>(parenthesized(
434                 nonemptyList("expected explicit shape specifications"_err_en_US,
435                     explicitShapeSpec))) ||
436     construct<ComponentArraySpec>(parenthesized(deferredShapeSpecList)))
437 
438 // R741 proc-component-def-stmt ->
439 //        PROCEDURE ( [proc-interface] ) , proc-component-attr-spec-list
440 //          :: proc-decl-list
441 TYPE_CONTEXT_PARSER("PROCEDURE component definition statement"_en_US,
442     construct<ProcComponentDefStmt>(
443         "PROCEDURE" >> parenthesized(maybe(procInterface)),
444         localRecovery("expected PROCEDURE component attributes"_err_en_US,
445             "," >> nonemptyList(Parser<ProcComponentAttrSpec>{}), ok),
446         localRecovery("expected PROCEDURE declarations"_err_en_US,
447             "::" >> nonemptyList(procDecl), SkipTo<'\n'>{})))
448 
449 // R742 proc-component-attr-spec ->
450 //        access-spec | NOPASS | PASS [(arg-name)] | POINTER
451 constexpr auto noPass{construct<NoPass>("NOPASS"_tok)};
452 constexpr auto pass{construct<Pass>("PASS" >> maybe(parenthesized(name)))};
453 TYPE_PARSER(construct<ProcComponentAttrSpec>(accessSpec) ||
454     construct<ProcComponentAttrSpec>(noPass) ||
455     construct<ProcComponentAttrSpec>(pass) ||
456     construct<ProcComponentAttrSpec>(pointer))
457 
458 // R744 initial-data-target -> designator
459 constexpr auto initialDataTarget{indirect(designator)};
460 
461 // R743 component-initialization ->
462 //        = constant-expr | => null-init | => initial-data-target
463 // R805 initialization ->
464 //        = constant-expr | => null-init | => initial-data-target
465 // Universal extension: initialization -> / data-stmt-value-list /
466 TYPE_PARSER(construct<Initialization>("=>" >> nullInit) ||
467     construct<Initialization>("=>" >> initialDataTarget) ||
468     construct<Initialization>("=" >> constantExpr) ||
469     extension<LanguageFeature::SlashInitialization>(construct<Initialization>(
470         "/" >> nonemptyList("expected values"_err_en_US,
471                    indirect(Parser<DataStmtValue>{})) /
472             "/")))
473 
474 // R745 private-components-stmt -> PRIVATE
475 // R747 binding-private-stmt -> PRIVATE
476 TYPE_PARSER(construct<PrivateStmt>("PRIVATE"_tok))
477 
478 // R746 type-bound-procedure-part ->
479 //        contains-stmt [binding-private-stmt] [type-bound-proc-binding]...
480 TYPE_CONTEXT_PARSER("type bound procedure part"_en_US,
481     construct<TypeBoundProcedurePart>(statement(containsStmt),
482         maybe(statement(Parser<PrivateStmt>{})),
483         many(statement(Parser<TypeBoundProcBinding>{}))))
484 
485 // R748 type-bound-proc-binding ->
486 //        type-bound-procedure-stmt | type-bound-generic-stmt |
487 //        final-procedure-stmt
488 TYPE_CONTEXT_PARSER("type bound procedure binding"_en_US,
489     recovery(
490         first(construct<TypeBoundProcBinding>(Parser<TypeBoundProcedureStmt>{}),
491             construct<TypeBoundProcBinding>(Parser<TypeBoundGenericStmt>{}),
492             construct<TypeBoundProcBinding>(Parser<FinalProcedureStmt>{})),
493         construct<TypeBoundProcBinding>(
494             !"END"_tok >> SkipTo<'\n'>{} >> construct<ErrorRecovery>())))
495 
496 // R749 type-bound-procedure-stmt ->
497 //        PROCEDURE [[, bind-attr-list] ::] type-bound-proc-decl-list |
498 //        PROCEDURE ( interface-name ) , bind-attr-list :: binding-name-list
499 TYPE_CONTEXT_PARSER("type bound PROCEDURE statement"_en_US,
500     "PROCEDURE" >>
501         (construct<TypeBoundProcedureStmt>(
502              construct<TypeBoundProcedureStmt::WithInterface>(
503                  parenthesized(name),
504                  localRecovery("expected list of binding attributes"_err_en_US,
505                      "," >> nonemptyList(Parser<BindAttr>{}), ok),
506                  localRecovery("expected list of binding names"_err_en_US,
507                      "::" >> listOfNames, SkipTo<'\n'>{}))) ||
508             construct<TypeBoundProcedureStmt>(
509                 construct<TypeBoundProcedureStmt::WithoutInterface>(
510                     optionalListBeforeColons(Parser<BindAttr>{}),
511                     nonemptyList(
512                         "expected type bound procedure declarations"_err_en_US,
513                         Parser<TypeBoundProcDecl>{})))))
514 
515 // R750 type-bound-proc-decl -> binding-name [=> procedure-name]
516 TYPE_PARSER(construct<TypeBoundProcDecl>(name, maybe("=>" >> name)))
517 
518 // R751 type-bound-generic-stmt ->
519 //        GENERIC [, access-spec] :: generic-spec => binding-name-list
520 TYPE_CONTEXT_PARSER("type bound GENERIC statement"_en_US,
521     construct<TypeBoundGenericStmt>("GENERIC" >> maybe("," >> accessSpec),
522         "::" >> indirect(genericSpec), "=>" >> listOfNames))
523 
524 // R752 bind-attr ->
525 //        access-spec | DEFERRED | NON_OVERRIDABLE | NOPASS | PASS [(arg-name)]
526 TYPE_PARSER(construct<BindAttr>(accessSpec) ||
527     construct<BindAttr>(construct<BindAttr::Deferred>("DEFERRED"_tok)) ||
528     construct<BindAttr>(
529         construct<BindAttr::Non_Overridable>("NON_OVERRIDABLE"_tok)) ||
530     construct<BindAttr>(noPass) || construct<BindAttr>(pass))
531 
532 // R753 final-procedure-stmt -> FINAL [::] final-subroutine-name-list
533 TYPE_CONTEXT_PARSER("FINAL statement"_en_US,
534     construct<FinalProcedureStmt>("FINAL" >> maybe("::"_tok) >> listOfNames))
535 
536 // R754 derived-type-spec -> type-name [(type-param-spec-list)]
537 TYPE_PARSER(construct<DerivedTypeSpec>(name,
538     defaulted(parenthesized(nonemptyList(
539         "expected type parameters"_err_en_US, Parser<TypeParamSpec>{})))))
540 
541 // R755 type-param-spec -> [keyword =] type-param-value
542 TYPE_PARSER(construct<TypeParamSpec>(maybe(keyword / "="), typeParamValue))
543 
544 // R756 structure-constructor -> derived-type-spec ( [component-spec-list] )
545 TYPE_PARSER((construct<StructureConstructor>(derivedTypeSpec,
546                  parenthesized(optionalList(Parser<ComponentSpec>{}))) ||
547                 // This alternative corrects misrecognition of the
548                 // component-spec-list as the type-param-spec-list in
549                 // derived-type-spec.
550                 construct<StructureConstructor>(
551                     construct<DerivedTypeSpec>(
552                         name, construct<std::list<TypeParamSpec>>()),
553                     parenthesized(optionalList(Parser<ComponentSpec>{})))) /
554     !"("_tok)
555 
556 // R757 component-spec -> [keyword =] component-data-source
557 TYPE_PARSER(construct<ComponentSpec>(
558     maybe(keyword / "="), Parser<ComponentDataSource>{}))
559 
560 // R758 component-data-source -> expr | data-target | proc-target
TYPE_PARSER(construct<ComponentDataSource> (indirect (expr)))561 TYPE_PARSER(construct<ComponentDataSource>(indirect(expr)))
562 
563 // R759 enum-def ->
564 //        enum-def-stmt enumerator-def-stmt [enumerator-def-stmt]...
565 //        end-enum-stmt
566 TYPE_CONTEXT_PARSER("enum definition"_en_US,
567     construct<EnumDef>(statement(Parser<EnumDefStmt>{}),
568         some(unambiguousStatement(Parser<EnumeratorDefStmt>{})),
569         statement(Parser<EndEnumStmt>{})))
570 
571 // R760 enum-def-stmt -> ENUM, BIND(C)
572 TYPE_PARSER(construct<EnumDefStmt>("ENUM , BIND ( C )"_tok))
573 
574 // R761 enumerator-def-stmt -> ENUMERATOR [::] enumerator-list
575 TYPE_CONTEXT_PARSER("ENUMERATOR statement"_en_US,
576     construct<EnumeratorDefStmt>("ENUMERATOR" >> maybe("::"_tok) >>
577         nonemptyList("expected enumerators"_err_en_US, Parser<Enumerator>{})))
578 
579 // R762 enumerator -> named-constant [= scalar-int-constant-expr]
580 TYPE_PARSER(
581     construct<Enumerator>(namedConstant, maybe("=" >> scalarIntConstantExpr)))
582 
583 // R763 end-enum-stmt -> END ENUM
584 TYPE_PARSER(recovery("END ENUM"_tok, "END" >> SkipPast<'\n'>{}) >>
585     construct<EndEnumStmt>())
586 
587 // R801 type-declaration-stmt ->
588 //        declaration-type-spec [[, attr-spec]... ::] entity-decl-list
589 constexpr auto entityDeclWithoutEqInit{construct<EntityDecl>(name,
590     maybe(arraySpec), maybe(coarraySpec), maybe("*" >> charLength),
591     !"="_tok >> maybe(initialization))}; // old-style REAL A/0/ still works
592 TYPE_PARSER(
593     construct<TypeDeclarationStmt>(declarationTypeSpec,
594         defaulted("," >> nonemptyList(Parser<AttrSpec>{})) / "::",
595         nonemptyList("expected entity declarations"_err_en_US, entityDecl)) ||
596     // C806: no initializers allowed without colons ("REALA=1" is ambiguous)
597     construct<TypeDeclarationStmt>(declarationTypeSpec,
598         construct<std::list<AttrSpec>>(),
599         nonemptyList("expected entity declarations"_err_en_US,
600             entityDeclWithoutEqInit)) ||
601     // PGI-only extension: comma in place of doubled colons
602     extension<LanguageFeature::MissingColons>(construct<TypeDeclarationStmt>(
603         declarationTypeSpec, defaulted("," >> nonemptyList(Parser<AttrSpec>{})),
604         withMessage("expected entity declarations"_err_en_US,
605             "," >> nonemptyList(entityDecl)))))
606 
607 // R802 attr-spec ->
608 //        access-spec | ALLOCATABLE | ASYNCHRONOUS |
609 //        CODIMENSION lbracket coarray-spec rbracket | CONTIGUOUS |
610 //        DIMENSION ( array-spec ) | EXTERNAL | INTENT ( intent-spec ) |
611 //        INTRINSIC | language-binding-spec | OPTIONAL | PARAMETER | POINTER |
612 //        PROTECTED | SAVE | TARGET | VALUE | VOLATILE
613 TYPE_PARSER(construct<AttrSpec>(accessSpec) ||
614     construct<AttrSpec>(allocatable) ||
615     construct<AttrSpec>(construct<Asynchronous>("ASYNCHRONOUS"_tok)) ||
616     construct<AttrSpec>("CODIMENSION" >> coarraySpec) ||
617     construct<AttrSpec>(contiguous) ||
618     construct<AttrSpec>("DIMENSION" >> arraySpec) ||
619     construct<AttrSpec>(construct<External>("EXTERNAL"_tok)) ||
620     construct<AttrSpec>("INTENT" >> parenthesized(intentSpec)) ||
621     construct<AttrSpec>(construct<Intrinsic>("INTRINSIC"_tok)) ||
622     construct<AttrSpec>(languageBindingSpec) || construct<AttrSpec>(optional) ||
623     construct<AttrSpec>(construct<Parameter>("PARAMETER"_tok)) ||
624     construct<AttrSpec>(pointer) || construct<AttrSpec>(protectedAttr) ||
625     construct<AttrSpec>(save) ||
626     construct<AttrSpec>(construct<Target>("TARGET"_tok)) ||
627     construct<AttrSpec>(construct<Value>("VALUE"_tok)) ||
628     construct<AttrSpec>(construct<Volatile>("VOLATILE"_tok)))
629 
630 // R804 object-name -> name
631 constexpr auto objectName{name};
632 
633 // R803 entity-decl ->
634 //        object-name [( array-spec )] [lbracket coarray-spec rbracket]
635 //          [* char-length] [initialization] |
636 //        function-name [* char-length]
637 TYPE_PARSER(construct<EntityDecl>(objectName, maybe(arraySpec),
638     maybe(coarraySpec), maybe("*" >> charLength), maybe(initialization)))
639 
640 // R806 null-init -> function-reference   ... which must resolve to NULL()
641 TYPE_PARSER(lookAhead(name / "( )") >> construct<NullInit>(expr))
642 
643 // R807 access-spec -> PUBLIC | PRIVATE
644 TYPE_PARSER(construct<AccessSpec>("PUBLIC" >> pure(AccessSpec::Kind::Public)) ||
645     construct<AccessSpec>("PRIVATE" >> pure(AccessSpec::Kind::Private)))
646 
647 // R808 language-binding-spec ->
648 //        BIND ( C [, NAME = scalar-default-char-constant-expr] )
649 // R1528 proc-language-binding-spec -> language-binding-spec
650 TYPE_PARSER(construct<LanguageBindingSpec>(
651     "BIND ( C" >> maybe(", NAME =" >> scalarDefaultCharConstantExpr) / ")"))
652 
653 // R809 coarray-spec -> deferred-coshape-spec-list | explicit-coshape-spec
654 // N.B. Bracketed here rather than around references, for consistency with
655 // array-spec.
656 TYPE_PARSER(
657     construct<CoarraySpec>(bracketed(Parser<DeferredCoshapeSpecList>{})) ||
658     construct<CoarraySpec>(bracketed(Parser<ExplicitCoshapeSpec>{})))
659 
660 // R810 deferred-coshape-spec -> :
661 // deferred-coshape-spec-list - just a list of colons
listLength(std::list<Success> && xs)662 inline int listLength(std::list<Success> &&xs) { return xs.size(); }
663 
664 TYPE_PARSER(construct<DeferredCoshapeSpecList>(
665     applyFunction(listLength, nonemptyList(":"_tok))))
666 
667 // R811 explicit-coshape-spec ->
668 //        [[lower-cobound :] upper-cobound ,]... [lower-cobound :] *
669 // R812 lower-cobound -> specification-expr
670 // R813 upper-cobound -> specification-expr
671 TYPE_PARSER(construct<ExplicitCoshapeSpec>(
672     many(explicitShapeSpec / ","), maybe(specificationExpr / ":") / "*"))
673 
674 // R815 array-spec ->
675 //        explicit-shape-spec-list | assumed-shape-spec-list |
676 //        deferred-shape-spec-list | assumed-size-spec | implied-shape-spec |
677 //        implied-shape-or-assumed-size-spec | assumed-rank-spec
678 // N.B. Parenthesized here rather than around references to avoid
679 // a need for forced look-ahead.
680 // Shape specs that could be deferred-shape-spec or assumed-shape-spec
681 // (e.g. '(:,:)') are parsed as the former.
682 TYPE_PARSER(
683     construct<ArraySpec>(parenthesized(nonemptyList(explicitShapeSpec))) ||
684     construct<ArraySpec>(parenthesized(deferredShapeSpecList)) ||
685     construct<ArraySpec>(
686         parenthesized(nonemptyList(Parser<AssumedShapeSpec>{}))) ||
687     construct<ArraySpec>(parenthesized(Parser<AssumedSizeSpec>{})) ||
688     construct<ArraySpec>(parenthesized(Parser<ImpliedShapeSpec>{})) ||
689     construct<ArraySpec>(parenthesized(Parser<AssumedRankSpec>{})))
690 
691 // R816 explicit-shape-spec -> [lower-bound :] upper-bound
692 // R817 lower-bound -> specification-expr
693 // R818 upper-bound -> specification-expr
694 TYPE_PARSER(construct<ExplicitShapeSpec>(
695     maybe(specificationExpr / ":"), specificationExpr))
696 
697 // R819 assumed-shape-spec -> [lower-bound] :
698 TYPE_PARSER(construct<AssumedShapeSpec>(maybe(specificationExpr) / ":"))
699 
700 // R820 deferred-shape-spec -> :
701 // deferred-shape-spec-list - just a list of colons
702 TYPE_PARSER(construct<DeferredShapeSpecList>(
703     applyFunction(listLength, nonemptyList(":"_tok))))
704 
705 // R821 assumed-implied-spec -> [lower-bound :] *
706 TYPE_PARSER(construct<AssumedImpliedSpec>(maybe(specificationExpr / ":") / "*"))
707 
708 // R822 assumed-size-spec -> explicit-shape-spec-list , assumed-implied-spec
709 TYPE_PARSER(construct<AssumedSizeSpec>(
710     nonemptyList(explicitShapeSpec) / ",", assumedImpliedSpec))
711 
712 // R823 implied-shape-or-assumed-size-spec -> assumed-implied-spec
713 // R824 implied-shape-spec -> assumed-implied-spec , assumed-implied-spec-list
714 // I.e., when the assumed-implied-spec-list has a single item, it constitutes an
715 // implied-shape-or-assumed-size-spec; otherwise, an implied-shape-spec.
TYPE_PARSER(construct<ImpliedShapeSpec> (nonemptyList (assumedImpliedSpec)))716 TYPE_PARSER(construct<ImpliedShapeSpec>(nonemptyList(assumedImpliedSpec)))
717 
718 // R825 assumed-rank-spec -> ..
719 TYPE_PARSER(construct<AssumedRankSpec>(".."_tok))
720 
721 // R826 intent-spec -> IN | OUT | INOUT
722 TYPE_PARSER(construct<IntentSpec>("IN OUT" >> pure(IntentSpec::Intent::InOut) ||
723     "IN" >> pure(IntentSpec::Intent::In) ||
724     "OUT" >> pure(IntentSpec::Intent::Out)))
725 
726 // R827 access-stmt -> access-spec [[::] access-id-list]
727 TYPE_PARSER(construct<AccessStmt>(accessSpec,
728     defaulted(maybe("::"_tok) >>
729         nonemptyList("expected names and generic specifications"_err_en_US,
730             Parser<AccessId>{}))))
731 
732 // R828 access-id -> access-name | generic-spec
733 TYPE_PARSER(construct<AccessId>(indirect(genericSpec)) ||
734     construct<AccessId>(name)) // initially ambiguous with genericSpec
735 
736 // R829 allocatable-stmt -> ALLOCATABLE [::] allocatable-decl-list
737 TYPE_PARSER(construct<AllocatableStmt>("ALLOCATABLE" >> maybe("::"_tok) >>
738     nonemptyList(
739         "expected object declarations"_err_en_US, Parser<ObjectDecl>{})))
740 
741 // R830 allocatable-decl ->
742 //        object-name [( array-spec )] [lbracket coarray-spec rbracket]
743 // R860 target-decl ->
744 //        object-name [( array-spec )] [lbracket coarray-spec rbracket]
745 TYPE_PARSER(
746     construct<ObjectDecl>(objectName, maybe(arraySpec), maybe(coarraySpec)))
747 
748 // R831 asynchronous-stmt -> ASYNCHRONOUS [::] object-name-list
749 TYPE_PARSER(construct<AsynchronousStmt>("ASYNCHRONOUS" >> maybe("::"_tok) >>
750     nonemptyList("expected object names"_err_en_US, objectName)))
751 
752 // R832 bind-stmt -> language-binding-spec [::] bind-entity-list
753 TYPE_PARSER(construct<BindStmt>(languageBindingSpec / maybe("::"_tok),
754     nonemptyList("expected bind entities"_err_en_US, Parser<BindEntity>{})))
755 
756 // R833 bind-entity -> entity-name | / common-block-name /
757 TYPE_PARSER(construct<BindEntity>(pure(BindEntity::Kind::Object), name) ||
758     construct<BindEntity>("/" >> pure(BindEntity::Kind::Common), name / "/"))
759 
760 // R834 codimension-stmt -> CODIMENSION [::] codimension-decl-list
761 TYPE_PARSER(construct<CodimensionStmt>("CODIMENSION" >> maybe("::"_tok) >>
762     nonemptyList("expected codimension declarations"_err_en_US,
763         Parser<CodimensionDecl>{})))
764 
765 // R835 codimension-decl -> coarray-name lbracket coarray-spec rbracket
766 TYPE_PARSER(construct<CodimensionDecl>(name, coarraySpec))
767 
768 // R836 contiguous-stmt -> CONTIGUOUS [::] object-name-list
769 TYPE_PARSER(construct<ContiguousStmt>("CONTIGUOUS" >> maybe("::"_tok) >>
770     nonemptyList("expected object names"_err_en_US, objectName)))
771 
772 // R837 data-stmt -> DATA data-stmt-set [[,] data-stmt-set]...
773 TYPE_CONTEXT_PARSER("DATA statement"_en_US,
774     construct<DataStmt>(
775         "DATA" >> nonemptySeparated(Parser<DataStmtSet>{}, maybe(","_tok))))
776 
777 // R838 data-stmt-set -> data-stmt-object-list / data-stmt-value-list /
778 TYPE_PARSER(construct<DataStmtSet>(
779     nonemptyList(
780         "expected DATA statement objects"_err_en_US, Parser<DataStmtObject>{}),
781     withMessage("expected DATA statement value list"_err_en_US,
782         "/"_tok >> nonemptyList("expected DATA statement values"_err_en_US,
783                        Parser<DataStmtValue>{})) /
784         "/"))
785 
786 // R839 data-stmt-object -> variable | data-implied-do
787 TYPE_PARSER(construct<DataStmtObject>(indirect(variable)) ||
788     construct<DataStmtObject>(dataImpliedDo))
789 
790 // R840 data-implied-do ->
791 //        ( data-i-do-object-list , [integer-type-spec ::] data-i-do-variable
792 //        = scalar-int-constant-expr , scalar-int-constant-expr
793 //        [, scalar-int-constant-expr] )
794 // R842 data-i-do-variable -> do-variable
795 TYPE_PARSER(parenthesized(construct<DataImpliedDo>(
796     nonemptyList(Parser<DataIDoObject>{} / lookAhead(","_tok)) / ",",
797     maybe(integerTypeSpec / "::"), loopBounds(scalarIntConstantExpr))))
798 
799 // R841 data-i-do-object ->
800 //        array-element | scalar-structure-component | data-implied-do
801 TYPE_PARSER(construct<DataIDoObject>(scalar(indirect(designator))) ||
802     construct<DataIDoObject>(indirect(dataImpliedDo)))
803 
804 // R843 data-stmt-value -> [data-stmt-repeat *] data-stmt-constant
805 TYPE_PARSER(construct<DataStmtValue>(
806     maybe(Parser<DataStmtRepeat>{} / "*"), Parser<DataStmtConstant>{}))
807 
808 // R847 constant-subobject -> designator
809 // R846 int-constant-subobject -> constant-subobject
810 constexpr auto constantSubobject{constant(indirect(designator))};
811 
812 // R844 data-stmt-repeat -> scalar-int-constant | scalar-int-constant-subobject
813 // R607 int-constant -> constant
814 // Factored into: constant -> literal-constant -> int-literal-constant
815 // The named-constant alternative of constant is subsumed by constant-subobject
816 TYPE_PARSER(construct<DataStmtRepeat>(intLiteralConstant) ||
817     construct<DataStmtRepeat>(scalar(integer(constantSubobject))))
818 
819 // R845 data-stmt-constant ->
820 //        scalar-constant | scalar-constant-subobject |
821 //        signed-int-literal-constant | signed-real-literal-constant |
822 //        null-init | initial-data-target |
823 //        constant-structure-constructor
824 // N.B. scalar-constant and scalar-constant-subobject are ambiguous with
825 // initial-data-target; null-init and structure-constructor are ambiguous
826 // in the absence of parameters and components; structure-constructor with
827 // components can be ambiguous with a scalar-constant-subobject.
828 // So we parse literal constants, designator, null-init, and
829 // structure-constructor, so that semantics can figure things out later
830 // with the symbol table.
831 TYPE_PARSER(sourced(first(construct<DataStmtConstant>(literalConstant),
832     construct<DataStmtConstant>(signedRealLiteralConstant),
833     construct<DataStmtConstant>(signedIntLiteralConstant),
834     extension<LanguageFeature::SignedComplexLiteral>(
835         construct<DataStmtConstant>(Parser<SignedComplexLiteralConstant>{})),
836     construct<DataStmtConstant>(nullInit),
837     construct<DataStmtConstant>(indirect(designator) / !"("_tok),
838     construct<DataStmtConstant>(Parser<StructureConstructor>{}))))
839 
840 // R848 dimension-stmt ->
841 //        DIMENSION [::] array-name ( array-spec )
842 //        [, array-name ( array-spec )]...
843 TYPE_CONTEXT_PARSER("DIMENSION statement"_en_US,
844     construct<DimensionStmt>("DIMENSION" >> maybe("::"_tok) >>
845         nonemptyList("expected array specifications"_err_en_US,
846             construct<DimensionStmt::Declaration>(name, arraySpec))))
847 
848 // R849 intent-stmt -> INTENT ( intent-spec ) [::] dummy-arg-name-list
849 TYPE_CONTEXT_PARSER("INTENT statement"_en_US,
850     construct<IntentStmt>(
851         "INTENT" >> parenthesized(intentSpec) / maybe("::"_tok), listOfNames))
852 
853 // R850 optional-stmt -> OPTIONAL [::] dummy-arg-name-list
854 TYPE_PARSER(
855     construct<OptionalStmt>("OPTIONAL" >> maybe("::"_tok) >> listOfNames))
856 
857 // R851 parameter-stmt -> PARAMETER ( named-constant-def-list )
858 // Legacy extension: omitted parentheses, no implicit typing from names
859 TYPE_CONTEXT_PARSER("PARAMETER statement"_en_US,
860     construct<ParameterStmt>(
861         "PARAMETER" >> parenthesized(nonemptyList(Parser<NamedConstantDef>{}))))
862 TYPE_CONTEXT_PARSER("old style PARAMETER statement"_en_US,
863     extension<LanguageFeature::OldStyleParameter>(construct<OldParameterStmt>(
864         "PARAMETER" >> nonemptyList(Parser<NamedConstantDef>{}))))
865 
866 // R852 named-constant-def -> named-constant = constant-expr
867 TYPE_PARSER(construct<NamedConstantDef>(namedConstant, "=" >> constantExpr))
868 
869 // R853 pointer-stmt -> POINTER [::] pointer-decl-list
870 TYPE_PARSER(construct<PointerStmt>("POINTER" >> maybe("::"_tok) >>
871     nonemptyList(
872         "expected pointer declarations"_err_en_US, Parser<PointerDecl>{})))
873 
874 // R854 pointer-decl ->
875 //        object-name [( deferred-shape-spec-list )] | proc-entity-name
TYPE_PARSER(construct<PointerDecl> (name,maybe (parenthesized (deferredShapeSpecList))))876 TYPE_PARSER(
877     construct<PointerDecl>(name, maybe(parenthesized(deferredShapeSpecList))))
878 
879 // R855 protected-stmt -> PROTECTED [::] entity-name-list
880 TYPE_PARSER(
881     construct<ProtectedStmt>("PROTECTED" >> maybe("::"_tok) >> listOfNames))
882 
883 // R856 save-stmt -> SAVE [[::] saved-entity-list]
884 TYPE_PARSER(construct<SaveStmt>(
885     "SAVE" >> defaulted(maybe("::"_tok) >>
886                   nonemptyList("expected SAVE entities"_err_en_US,
887                       Parser<SavedEntity>{}))))
888 
889 // R857 saved-entity -> object-name | proc-pointer-name | / common-block-name /
890 // R858 proc-pointer-name -> name
891 TYPE_PARSER(construct<SavedEntity>(pure(SavedEntity::Kind::Entity), name) ||
892     construct<SavedEntity>("/" >> pure(SavedEntity::Kind::Common), name / "/"))
893 
894 // R859 target-stmt -> TARGET [::] target-decl-list
895 TYPE_PARSER(construct<TargetStmt>("TARGET" >> maybe("::"_tok) >>
896     nonemptyList("expected objects"_err_en_US, Parser<ObjectDecl>{})))
897 
898 // R861 value-stmt -> VALUE [::] dummy-arg-name-list
899 TYPE_PARSER(construct<ValueStmt>("VALUE" >> maybe("::"_tok) >> listOfNames))
900 
901 // R862 volatile-stmt -> VOLATILE [::] object-name-list
902 TYPE_PARSER(construct<VolatileStmt>("VOLATILE" >> maybe("::"_tok) >>
903     nonemptyList("expected object names"_err_en_US, objectName)))
904 
905 // R866 implicit-name-spec -> EXTERNAL | TYPE
906 constexpr auto implicitNameSpec{
907     "EXTERNAL" >> pure(ImplicitStmt::ImplicitNoneNameSpec::External) ||
908     "TYPE" >> pure(ImplicitStmt::ImplicitNoneNameSpec::Type)};
909 
910 // R863 implicit-stmt ->
911 //        IMPLICIT implicit-spec-list |
912 //        IMPLICIT NONE [( [implicit-name-spec-list] )]
913 TYPE_CONTEXT_PARSER("IMPLICIT statement"_en_US,
914     construct<ImplicitStmt>(
915         "IMPLICIT" >> nonemptyList("expected IMPLICIT specifications"_err_en_US,
916                           Parser<ImplicitSpec>{})) ||
917         construct<ImplicitStmt>("IMPLICIT NONE"_sptok >>
918             defaulted(parenthesized(optionalList(implicitNameSpec)))))
919 
920 // R864 implicit-spec -> declaration-type-spec ( letter-spec-list )
921 // The variant form of declarationTypeSpec is meant to avoid misrecognition
922 // of a letter-spec as a simple parenthesized expression for kind or character
923 // length, e.g., PARAMETER(I=5,N=1); IMPLICIT REAL(I-N)(O-Z) vs.
924 // IMPLICIT REAL(I-N).  The variant form needs to attempt to reparse only
925 // types with optional parenthesized kind/length expressions, so derived
926 // type specs, DOUBLE PRECISION, and DOUBLE COMPLEX need not be considered.
927 constexpr auto noKindSelector{construct<std::optional<KindSelector>>()};
928 constexpr auto implicitSpecDeclarationTypeSpecRetry{
929     construct<DeclarationTypeSpec>(first(
930         construct<IntrinsicTypeSpec>(
931             construct<IntegerTypeSpec>("INTEGER" >> noKindSelector)),
932         construct<IntrinsicTypeSpec>(
933             construct<IntrinsicTypeSpec::Real>("REAL" >> noKindSelector)),
934         construct<IntrinsicTypeSpec>(
935             construct<IntrinsicTypeSpec::Complex>("COMPLEX" >> noKindSelector)),
936         construct<IntrinsicTypeSpec>(construct<IntrinsicTypeSpec::Character>(
937             "CHARACTER" >> construct<std::optional<CharSelector>>())),
938         construct<IntrinsicTypeSpec>(construct<IntrinsicTypeSpec::Logical>(
939             "LOGICAL" >> noKindSelector))))};
940 
941 TYPE_PARSER(construct<ImplicitSpec>(declarationTypeSpec,
942                 parenthesized(nonemptyList(Parser<LetterSpec>{}))) ||
943     construct<ImplicitSpec>(implicitSpecDeclarationTypeSpecRetry,
944         parenthesized(nonemptyList(Parser<LetterSpec>{}))))
945 
946 // R865 letter-spec -> letter [- letter]
947 TYPE_PARSER(space >> (construct<LetterSpec>(letter, maybe("-" >> letter)) ||
948                          construct<LetterSpec>(otherIdChar,
949                              construct<std::optional<const char *>>())))
950 
951 // R867 import-stmt ->
952 //        IMPORT [[::] import-name-list] |
953 //        IMPORT , ONLY : import-name-list | IMPORT , NONE | IMPORT , ALL
954 TYPE_CONTEXT_PARSER("IMPORT statement"_en_US,
955     construct<ImportStmt>(
956         "IMPORT , ONLY :" >> pure(common::ImportKind::Only), listOfNames) ||
957         construct<ImportStmt>(
958             "IMPORT , NONE" >> pure(common::ImportKind::None)) ||
959         construct<ImportStmt>(
960             "IMPORT , ALL" >> pure(common::ImportKind::All)) ||
961         construct<ImportStmt>(
962             "IMPORT" >> maybe("::"_tok) >> optionalList(name)))
963 
964 // R868 namelist-stmt ->
965 //        NAMELIST / namelist-group-name / namelist-group-object-list
966 //        [[,] / namelist-group-name / namelist-group-object-list]...
967 // R869 namelist-group-object -> variable-name
968 TYPE_PARSER(construct<NamelistStmt>("NAMELIST" >>
969     nonemptySeparated(
970         construct<NamelistStmt::Group>("/" >> name / "/", listOfNames),
971         maybe(","_tok))))
972 
973 // R870 equivalence-stmt -> EQUIVALENCE equivalence-set-list
974 // R871 equivalence-set -> ( equivalence-object , equivalence-object-list )
975 TYPE_PARSER(construct<EquivalenceStmt>("EQUIVALENCE" >>
976     nonemptyList(
977         parenthesized(nonemptyList("expected EQUIVALENCE objects"_err_en_US,
978             Parser<EquivalenceObject>{})))))
979 
980 // R872 equivalence-object -> variable-name | array-element | substring
TYPE_PARSER(construct<EquivalenceObject> (indirect (designator)))981 TYPE_PARSER(construct<EquivalenceObject>(indirect(designator)))
982 
983 // R873 common-stmt ->
984 //        COMMON [/ [common-block-name] /] common-block-object-list
985 //        [[,] / [common-block-name] / common-block-object-list]...
986 TYPE_PARSER(
987     construct<CommonStmt>("COMMON" >> defaulted("/" >> maybe(name) / "/"),
988         nonemptyList("expected COMMON block objects"_err_en_US,
989             Parser<CommonBlockObject>{}),
990         many(maybe(","_tok) >>
991             construct<CommonStmt::Block>("/" >> maybe(name) / "/",
992                 nonemptyList("expected COMMON block objects"_err_en_US,
993                     Parser<CommonBlockObject>{})))))
994 
995 // R874 common-block-object -> variable-name [( array-spec )]
996 TYPE_PARSER(construct<CommonBlockObject>(name, maybe(arraySpec)))
997 
998 // R901 designator -> object-name | array-element | array-section |
999 //                    coindexed-named-object | complex-part-designator |
1000 //                    structure-component | substring
1001 // The Standard's productions for designator and its alternatives are
1002 // ambiguous without recourse to a symbol table.  Many of the alternatives
1003 // for designator (viz., array-element, coindexed-named-object,
1004 // and structure-component) are all syntactically just data-ref.
1005 // What designator boils down to is this:
1006 //  It starts with either a name or a character literal.
1007 //  If it starts with a character literal, it must be a substring.
1008 //  If it starts with a name, it's a sequence of %-separated parts;
1009 //  each part is a name, maybe a (section-subscript-list), and
1010 //  maybe an [image-selector].
1011 //  If it's a substring, it ends with (substring-range).
1012 TYPE_CONTEXT_PARSER("designator"_en_US,
1013     sourced(construct<Designator>(substring) || construct<Designator>(dataRef)))
1014 
1015 constexpr auto percentOrDot{"%"_tok ||
1016     // legacy VAX extension for RECORD field access
1017     extension<LanguageFeature::DECStructures>(
1018         "."_tok / lookAhead(OldStructureComponentName{}))};
1019 
1020 // R902 variable -> designator | function-reference
1021 // This production appears to be left-recursive in the grammar via
1022 //   function-reference ->  procedure-designator -> proc-component-ref ->
1023 //     scalar-variable
1024 // and would be so if we were to allow functions to be called via procedure
1025 // pointer components within derived type results of other function references
1026 // (a reasonable extension, esp. in the case of procedure pointer components
1027 // that are NOPASS).  However, Fortran constrains the use of a variable in a
1028 // proc-component-ref to be a data-ref without coindices (C1027).
1029 // Some array element references will be misrecognized as function references.
1030 constexpr auto noMoreAddressing{!"("_tok >> !"["_tok >> !percentOrDot};
1031 TYPE_CONTEXT_PARSER("variable"_en_US,
1032     construct<Variable>(indirect(functionReference / noMoreAddressing)) ||
1033         construct<Variable>(indirect(designator)))
1034 
1035 // R908 substring -> parent-string ( substring-range )
1036 // R909 parent-string ->
1037 //        scalar-variable-name | array-element | coindexed-named-object |
1038 //        scalar-structure-component | scalar-char-literal-constant |
1039 //        scalar-named-constant
TYPE_PARSER(construct<Substring> (dataRef,parenthesized (Parser<SubstringRange>{})))1040 TYPE_PARSER(
1041     construct<Substring>(dataRef, parenthesized(Parser<SubstringRange>{})))
1042 
1043 TYPE_PARSER(construct<CharLiteralConstantSubstring>(
1044     charLiteralConstant, parenthesized(Parser<SubstringRange>{})))
1045 
1046 // R910 substring-range -> [scalar-int-expr] : [scalar-int-expr]
1047 TYPE_PARSER(construct<SubstringRange>(
1048     maybe(scalarIntExpr), ":" >> maybe(scalarIntExpr)))
1049 
1050 // R911 data-ref -> part-ref [% part-ref]...
1051 // R914 coindexed-named-object -> data-ref
1052 // R917 array-element -> data-ref
1053 TYPE_PARSER(
1054     construct<DataRef>(nonemptySeparated(Parser<PartRef>{}, percentOrDot)))
1055 
1056 // R912 part-ref -> part-name [( section-subscript-list )] [image-selector]
1057 TYPE_PARSER(construct<PartRef>(name,
1058     defaulted(
1059         parenthesized(nonemptyList(Parser<SectionSubscript>{})) / !"=>"_tok),
1060     maybe(Parser<ImageSelector>{})))
1061 
1062 // R913 structure-component -> data-ref
1063 // The final part-ref in the data-ref is not allowed to have subscripts.
1064 TYPE_PARSER(construct<StructureComponent>(
1065     construct<DataRef>(some(Parser<PartRef>{} / percentOrDot)), name))
1066 
1067 // R919 subscript -> scalar-int-expr
1068 constexpr auto subscript{scalarIntExpr};
1069 
1070 // R920 section-subscript -> subscript | subscript-triplet | vector-subscript
1071 // R923 vector-subscript -> int-expr
1072 // N.B. The distinction that needs to be made between "subscript" and
1073 // "vector-subscript" is deferred to semantic analysis.
1074 TYPE_PARSER(construct<SectionSubscript>(Parser<SubscriptTriplet>{}) ||
1075     construct<SectionSubscript>(intExpr))
1076 
1077 // R921 subscript-triplet -> [subscript] : [subscript] [: stride]
1078 TYPE_PARSER(construct<SubscriptTriplet>(
1079     maybe(subscript), ":" >> maybe(subscript), maybe(":" >> subscript)))
1080 
1081 // R925 cosubscript -> scalar-int-expr
1082 constexpr auto cosubscript{scalarIntExpr};
1083 
1084 // R924 image-selector ->
1085 //        lbracket cosubscript-list [, image-selector-spec-list] rbracket
1086 TYPE_CONTEXT_PARSER("image selector"_en_US,
1087     construct<ImageSelector>("[" >> nonemptyList(cosubscript / !"="_tok),
1088         defaulted("," >> nonemptyList(Parser<ImageSelectorSpec>{})) / "]"))
1089 
1090 // R926 image-selector-spec ->
1091 //        STAT = stat-variable | TEAM = team-value |
1092 //        TEAM_NUMBER = scalar-int-expr
1093 TYPE_PARSER(construct<ImageSelectorSpec>(construct<ImageSelectorSpec::Stat>(
1094                 "STAT =" >> scalar(integer(indirect(variable))))) ||
1095     construct<ImageSelectorSpec>(construct<TeamValue>("TEAM =" >> teamValue)) ||
1096     construct<ImageSelectorSpec>(construct<ImageSelectorSpec::Team_Number>(
1097         "TEAM_NUMBER =" >> scalarIntExpr)))
1098 
1099 // R927 allocate-stmt ->
1100 //        ALLOCATE ( [type-spec ::] allocation-list [, alloc-opt-list] )
1101 TYPE_CONTEXT_PARSER("ALLOCATE statement"_en_US,
1102     construct<AllocateStmt>("ALLOCATE (" >> maybe(typeSpec / "::"),
1103         nonemptyList(Parser<Allocation>{}),
1104         defaulted("," >> nonemptyList(Parser<AllocOpt>{})) / ")"))
1105 
1106 // R928 alloc-opt ->
1107 //        ERRMSG = errmsg-variable | MOLD = source-expr |
1108 //        SOURCE = source-expr | STAT = stat-variable
1109 // R931 source-expr -> expr
1110 TYPE_PARSER(construct<AllocOpt>(
1111                 construct<AllocOpt::Mold>("MOLD =" >> indirect(expr))) ||
1112     construct<AllocOpt>(
1113         construct<AllocOpt::Source>("SOURCE =" >> indirect(expr))) ||
1114     construct<AllocOpt>(statOrErrmsg))
1115 
1116 // R929 stat-variable -> scalar-int-variable
TYPE_PARSER(construct<StatVariable> (scalar (integer (variable))))1117 TYPE_PARSER(construct<StatVariable>(scalar(integer(variable))))
1118 
1119 // R932 allocation ->
1120 //        allocate-object [( allocate-shape-spec-list )]
1121 //        [lbracket allocate-coarray-spec rbracket]
1122 TYPE_PARSER(construct<Allocation>(Parser<AllocateObject>{},
1123     defaulted(parenthesized(nonemptyList(Parser<AllocateShapeSpec>{}))),
1124     maybe(bracketed(Parser<AllocateCoarraySpec>{}))))
1125 
1126 // R933 allocate-object -> variable-name | structure-component
1127 TYPE_PARSER(construct<AllocateObject>(structureComponent) ||
1128     construct<AllocateObject>(name / !"="_tok))
1129 
1130 // R934 allocate-shape-spec -> [lower-bound-expr :] upper-bound-expr
1131 // R938 allocate-coshape-spec -> [lower-bound-expr :] upper-bound-expr
1132 TYPE_PARSER(construct<AllocateShapeSpec>(maybe(boundExpr / ":"), boundExpr))
1133 
1134 // R937 allocate-coarray-spec ->
1135 //      [allocate-coshape-spec-list ,] [lower-bound-expr :] *
1136 TYPE_PARSER(construct<AllocateCoarraySpec>(
1137     defaulted(nonemptyList(Parser<AllocateShapeSpec>{}) / ","),
1138     maybe(boundExpr / ":") / "*"))
1139 
1140 // R939 nullify-stmt -> NULLIFY ( pointer-object-list )
1141 TYPE_CONTEXT_PARSER("NULLIFY statement"_en_US,
1142     "NULLIFY" >> parenthesized(construct<NullifyStmt>(
1143                      nonemptyList(Parser<PointerObject>{}))))
1144 
1145 // R940 pointer-object ->
1146 //        variable-name | structure-component | proc-pointer-name
1147 TYPE_PARSER(construct<PointerObject>(structureComponent) ||
1148     construct<PointerObject>(name))
1149 
1150 // R941 deallocate-stmt ->
1151 //        DEALLOCATE ( allocate-object-list [, dealloc-opt-list] )
1152 TYPE_CONTEXT_PARSER("DEALLOCATE statement"_en_US,
1153     construct<DeallocateStmt>(
1154         "DEALLOCATE (" >> nonemptyList(Parser<AllocateObject>{}),
1155         defaulted("," >> nonemptyList(statOrErrmsg)) / ")"))
1156 
1157 // R942 dealloc-opt -> STAT = stat-variable | ERRMSG = errmsg-variable
1158 // R1165 sync-stat -> STAT = stat-variable | ERRMSG = errmsg-variable
1159 TYPE_PARSER(construct<StatOrErrmsg>("STAT =" >> statVariable) ||
1160     construct<StatOrErrmsg>("ERRMSG =" >> msgVariable))
1161 
1162 // Directives, extensions, and deprecated statements
1163 // !DIR$ IGNORE_TKR [ [(tkr...)] name ]...
1164 // !DIR$ name...
1165 constexpr auto beginDirective{skipStuffBeforeStatement >> "!"_ch};
1166 constexpr auto endDirective{space >> endOfLine};
1167 constexpr auto ignore_tkr{
1168     "DIR$ IGNORE_TKR" >> optionalList(construct<CompilerDirective::IgnoreTKR>(
1169                              defaulted(parenthesized(some("tkr"_ch))), name))};
1170 TYPE_PARSER(beginDirective >>
1171     sourced(construct<CompilerDirective>(ignore_tkr) ||
1172         construct<CompilerDirective>(
1173             "DIR$" >> many(construct<CompilerDirective::NameValue>(name,
1174                           maybe(("="_tok || ":"_tok) >> digitString64))))) /
1175         endDirective)
1176 
1177 TYPE_PARSER(extension<LanguageFeature::CrayPointer>(construct<BasedPointerStmt>(
1178     "POINTER" >> nonemptyList("expected POINTER associations"_err_en_US,
1179                      construct<BasedPointer>("(" >> objectName / ",",
1180                          objectName, maybe(Parser<ArraySpec>{}) / ")")))))
1181 
1182 TYPE_PARSER(construct<StructureStmt>("STRUCTURE /" >> name / "/", pure(true),
1183                 optionalList(entityDecl)) ||
1184     construct<StructureStmt>(
1185         "STRUCTURE" >> name, pure(false), pure<std::list<EntityDecl>>()))
1186 
1187 TYPE_PARSER(construct<StructureField>(statement(StructureComponents{})) ||
1188     construct<StructureField>(indirect(Parser<Union>{})) ||
1189     construct<StructureField>(indirect(Parser<StructureDef>{})))
1190 
1191 TYPE_CONTEXT_PARSER("STRUCTURE definition"_en_US,
1192     extension<LanguageFeature::DECStructures>(construct<StructureDef>(
1193         statement(Parser<StructureStmt>{}), many(Parser<StructureField>{}),
1194         statement(
1195             construct<StructureDef::EndStructureStmt>("END STRUCTURE"_tok)))))
1196 
1197 TYPE_CONTEXT_PARSER("UNION definition"_en_US,
1198     construct<Union>(statement(construct<Union::UnionStmt>("UNION"_tok)),
1199         many(Parser<Map>{}),
1200         statement(construct<Union::EndUnionStmt>("END UNION"_tok))))
1201 
1202 TYPE_CONTEXT_PARSER("MAP definition"_en_US,
1203     construct<Map>(statement(construct<Map::MapStmt>("MAP"_tok)),
1204         many(Parser<StructureField>{}),
1205         statement(construct<Map::EndMapStmt>("END MAP"_tok))))
1206 
1207 TYPE_CONTEXT_PARSER("arithmetic IF statement"_en_US,
1208     deprecated<LanguageFeature::ArithmeticIF>(construct<ArithmeticIfStmt>(
1209         "IF" >> parenthesized(expr), label / ",", label / ",", label)))
1210 
1211 TYPE_CONTEXT_PARSER("ASSIGN statement"_en_US,
1212     deprecated<LanguageFeature::Assign>(
1213         construct<AssignStmt>("ASSIGN" >> label, "TO" >> name)))
1214 
1215 TYPE_CONTEXT_PARSER("assigned GOTO statement"_en_US,
1216     deprecated<LanguageFeature::AssignedGOTO>(construct<AssignedGotoStmt>(
1217         "GO TO" >> name,
1218         defaulted(maybe(","_tok) >>
1219             parenthesized(nonemptyList("expected labels"_err_en_US, label))))))
1220 
1221 TYPE_CONTEXT_PARSER("PAUSE statement"_en_US,
1222     deprecated<LanguageFeature::Pause>(
1223         construct<PauseStmt>("PAUSE" >> maybe(Parser<StopCode>{}))))
1224 
1225 // These requirement productions are defined by the Fortran standard but never
1226 // used directly by the grammar:
1227 //   R620 delimiter -> ( | ) | / | [ | ] | (/ | /)
1228 //   R1027 numeric-expr -> expr
1229 //   R1031 int-constant-expr -> int-expr
1230 //   R1221 dtv-type-spec -> TYPE ( derived-type-spec ) |
1231 //           CLASS ( derived-type-spec )
1232 //
1233 // These requirement productions are defined and used, but need not be
1234 // defined independently here in this file:
1235 //   R771 lbracket -> [
1236 //   R772 rbracket -> ]
1237 //
1238 // Further note that:
1239 //   R607 int-constant -> constant
1240 //     is used only once via R844 scalar-int-constant
1241 //   R904 logical-variable -> variable
1242 //     is used only via scalar-logical-variable
1243 //   R906 default-char-variable -> variable
1244 //     is used only via scalar-default-char-variable
1245 //   R907 int-variable -> variable
1246 //     is used only via scalar-int-variable
1247 //   R915 complex-part-designator -> designator % RE | designator % IM
1248 //     %RE and %IM are initially recognized as structure components
1249 //   R916 type-param-inquiry -> designator % type-param-name
1250 //     is occulted by structure component designators
1251 //   R918 array-section ->
1252 //        data-ref [( substring-range )] | complex-part-designator
1253 //     is not used because parsing is not sensitive to rank
1254 //   R1030 default-char-constant-expr -> default-char-expr
1255 //     is only used via scalar-default-char-constant-expr
1256 } // namespace Fortran::parser
1257