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