1 module epgrammar;
2 
3 // Extended Pascal grammar.
4 // Comments refer to the section numbers in the standard:
5 // http://dx.doi.org/10.1109/IEEESTD.1990.101061
6 // http://pascal-central.com/docs/iso10206.pdf
7 //
8 // Uses extended PEG syntax:
9 // https://github.com/PhilippeSigaud/Pegged/wiki/Extended-PEG-Syntax
10 //
11 // Minor edits have been made, marked with BNV, with the following objectives:
12 // 1 - Retain layout and comments.
13 // 2 - Reorder choices from long to short in order to get the longest match.
14 // 3 - Identify certain identifiers in the translator.
15 //
16 // In addition, the following Prospero extensions have been added, marked with Prospero
17 // 1 - Type viewing (casting) with the '::' operator.
18 // 2 - Labels can be identifiers
19 
20 enum EPgrammar = `
21 EP:
22     BNVCompileUnit  <- Program eoi
23 
24 # 6.1.1
25     Digit           <- digit
26     Letter          <- [a-zA-Z]
27 
28 # 6.1.3
29     BNVAnyIdentifier    <~ Letter ( "_"? ( Letter / Digit ) )*
30     Identifier          <- BNVAnyIdentifier {failOnWordSymbol}
31 
32 # 6.1.4 (complete)
33     RemoteDirective <- "forward"i / "external"i
34 
35 # 6.1.5 (complete)
36     InterfaceDirective <- "interface"i / "external"i
37 
38 # 6.1.6 (complete)
39     ImplementationDirective <- "implementation"i
40 
41 # 6.1.7 (complete)
42     SignedNumber    <- SignedReal / SignedInteger       # BNV changed order: real match is always longer dan integer match.
43     SignedReal      <~ Sign? UnsignedReal
44     SignedInteger   <~ Sign? UnsignedInteger
45     UnsignedNumber  <- UnsignedReal / UnsignedInteger   # BNV changed order: real match is always longer dan integer match.
46     Sign            <- [-+]
47     UnsignedReal    <~ DigitSequence "." FractionalPart ( [eE] ScaleFactor )? | DigitSequence [eE] ScaleFactor
48     UnsignedInteger <- DigitSequence
49     FractionalPart  <- DigitSequence
50     ScaleFactor     <~ Sign? DigitSequence
51     DigitSequence   <~ digits
52     Number          <~ SignedNumber | Sign? ( DigitSequence "." / "." FractionalPart ) ( [eE] ScaleFactor )?
53     ExtendedDigit   <- Digit / Letter
54     ExtendedNumber  <- UnsignedInteger "#" ExtendedDigit+
55 
56 # 6.1.8 (complete)
57 #    Label   <- DigitSequence
58 # Prospero supports identifiers as labels:
59     Label   <- DigitSequence / Identifier
60 
61 # 6.1.9 (complete)
62     CharacterString <- "'" StringElement* "'"
63     StringElement   <- ApostropheImage / StringCharacter
64     ApostropheImage <- "''"
65     StringCharacter <- !"'" .
66 
67 # 6.1.10 Token separators
68     Spacing         <~ blank+   # BNV Do not discard spacing.
69     _               <- ( Spacing / TrailingComment / InlineComment )*
70     Comment         <- ( :Spacing / TrailingComment / InlineComment )+
71     CommentOpen     <-  "{" / "(*"
72     CommentClose    <-  "}" / "*)"
73     CommentContent  <~ ( !CommentClose . )*
74     InlineComment   <- CommentOpen CommentContent CommentClose !endOfLine
75     TrailingComment <- CommentOpen CommentContent CommentClose &endOfLine
76 
77 # 6.2.1 (complete)
78     Block                               <- ImportPart ( _ ( LabelDeclarationPart / ConstantDefinitionPart / TypeDefinitionPart / VariableDeclarationPart / ProcedureAndFunctionDeclarationPart ) )* _ StatementPart _
79     ImportPart                          <- (:IMPORT _ ( ImportSpecification _ :";" _ )+ )?
80     LabelDeclarationPart                <- :LABEL _ Label ( _ "," _ Label )* _ :";" _
81     ConstantDefinitionPart              <- :CONST _ ( ConstantDefinition _ :";" _ )+
82     TypeDefinitionPart                  <- :TYPE _ ( ( TypeDefinition / SchemaDefinition) _ :";" _ )+
83     VariableDeclarationPart             <- :VAR _ ( VariableDeclaration _ :";" _ )+
84     ProcedureAndFunctionDeclarationPart <- ( ( ProcedureDeclaration / FunctionDeclaration ) _ :";" _ )*
85     StatementPart                       <- CompoundStatement
86 
87 # 6.3.1 (complete)
88     ConstantDefinition  <- Identifier _ "=" _ ConstantExpression
89     ConstantIdentifier  <- Identifier
90     ConstantName        <- ( ImportedInterfaceIdentifier _ DOT _ )? ConstantIdentifier
91 
92 # 6.4.1 (complete)
93     TypeDefinition      <- BNVTypeDefName _ "=" _ TypeDenoter
94     TypeDenoter         <- :(BINDABLE _ )? ( TypeName | NewType | TypeInquiry | DiscriminatedSchema ) _ InitialStateSpecifier?
95     NewType             <- NewOrdinalType | NewStructuredType | NewPointerType | RestrictedType
96     #SimpleTypeName      <- TypeName    # BNV Semantic only
97     StructuredTypeName  <- ArrayTypeName / RecordTypeName / SetTypeName / FileTypeName
98     ArrayTypeName       <- TypeName
99     RecordTypeName      <- TypeName
100     SetTypeName         <- TypeName
101     FileTypeName        <- TypeName
102     #PointerTypeName     <- TypeName    # BNV Semantic only
103     TypeIdentifier      <- Identifier
104     TypeName            <- ( ImportedInterfaceIdentifier _ DOT _ )? TypeIdentifier
105 #BNV extensions
106     BNVTypeDefName      <- Identifier
107 
108 # 6.4.2.1 (complete)
109     #SimpleType          <- OrdinalType / RealTypeName / ComplexTypeName    # BNV Semantic only
110     OrdinalType         <- NewOrdinalType | OrdinalTypeName | TypeInquiry | DiscriminatedSchema
111     NewOrdinalType      <- EnumeratedType | SubrangeType
112     OrdinalTypeName     <- TypeName
113     #RealTypeName        <- TypeName    # BNV Semantic only
114     #ComplexTypeName     <- TypeName    # BNV Semantic only
115 
116 # 6.4.2.3 (complete)
117     EnumeratedType      <- "(" _ IdentifierList _ ")"
118     IdentifierList      <- Identifier ( _ COMMA _ Identifier )*
119 
120 # 6.4.2.4 (complete)
121     SubrangeType        <- SubrangeBound _ ".." _ SubrangeBound
122     SubrangeBound       <- Expression
123 
124 # 6.4.2.5 (complete)
125     RestrictedType      <- :RESTRICTED _ TypeName
126 
127 # 6.4.3.1 (complete)
128     #StructuredType          <- NewStructuredType / StructuredTypeName  # BNV Semantic only
129     NewStructuredType       <- :PACKED? _ UnpackedStructuredType
130     UnpackedStructuredType  <- ArrayType / RecordType / SetType / FileType
131 
132 # 6.4.3.2 (complete)
133     ArrayType           <- :ARRAY _ "[" _ IndexType ( _ COMMA _ IndexType )* _ "]" _ :OF _ ComponentType
134     IndexType           <- OrdinalType
135     ComponentType       <- TypeDenoter
136 
137 # 6.4.3.3 String types. TODO
138 
139 # 6.4.3.4 (complete)
140     RecordType          <- :RECORD _ FieldList _ :END
141     FieldList           <- ( ( FixedPart ( _ ";" _ VariantPart )? / VariantPart ) _ ";"? )?
142     FixedPart           <- RecordSection ( _ ";" _ RecordSection )*
143     RecordSection       <- IdentifierList _ ":" _ TypeDenoter
144     FieldIdentifier     <- Identifier
145     VariantPart         <- :CASE _ VariantSelector _ :OF _ ( VariantListElement ( _ ";" _ VariantListElement )* ( _ ":"? _ VariantPartCompleter )? | VariantPartCompleter )
146     VariantListElement  <- CaseConstantList _ ":" _ VariantDenoter
147     VariantPartCompleter    <- OTHERWISE _ VariantDenoter
148     VariantDenoter      <- "(" _ FieldList _ ")"
149     VariantSelector     <- ( TagField _ ":" _ )? TagType | DiscriminantIdentifier
150     TagField            <- Identifier
151     TagType             <- OrdinalTypeName
152     CaseConstantList    <- CaseRange ( _ "," _ CaseRange )*
153     CaseRange           <- CaseConstant ( _ ".." _ CaseConstant )?
154     CaseConstant        <- ConstantExpression
155 
156 # 6.4.3.5 (complete)
157     SetType             <- :SET _ :OF _ BaseType
158     BaseType            <- OrdinalType
159 
160 # 6.4.3.6 (complete)
161     FileType            <- :FILE _ ( "[" _ IndexType _ "]" _ )? :OF _ ComponentType
162 
163 # 6.4.4 (complete)
164     #PointerType         <- NewPointerType / PointerTypeName    # BNV Semantic only
165     NewPointerType      <- :"^" _ DomainType
166     DomainType          <- TypeName | SchemaName
167 
168 # 6.4.7 (complete)
169     SchemaDefinition            <- ( Identifier _ "=" _ SchemaName ) | ( Identifier _ FormalDiscriminantPart _ "=" _ TypeDenoter )
170     FormalDiscriminantPart      <- "(" _ DiscriminantSpecification ( _ ";" _ DiscriminantSpecification )* _ ")"
171     DiscriminantSpecification   <- IdentifierList _ ":" _ OrdinalTypeName
172     DiscriminantIdentifier      <- Identifier
173     SchemaIdentifier            <- Identifier
174     SchemaName                  <- ( ImportedInterfaceIdentifier _ "." _ )? SchemaIdentifier
175 
176 # 6.4.8 (complete)
177     DiscriminatedSchema     <- SchemaName _ ActualDiscriminantPart
178     ActualDiscriminantPart  <- "(" _ DiscriminantValue _ ( "," _ DiscriminantValue _ )* ")"
179     DiscriminantValue       <- Expression
180 
181 # 6.4.9 (complete)
182     TypeInquiry         <- :TYPE _ :OF _ TypeInquiryObject
183     TypeInquiryObject   <- VariableName / ParameterIdentifier
184 
185 # 6.5.1 (complete)
186     VariableDeclaration <- IdentifierList _ ":" _ TypeDenoter
187     VariableIdentifier  <- Identifier
188     VariableName        <- ( ImportedInterfaceIdentifier _ DOT _ )? VariableIdentifier
189 #    VariableAccess      <- EntireVariable | ComponentVariable | IdentifiedVariable | BufferVariable | SubstringVariable | FunctionIdentifiedVariable
190 # Prospero extension: type viewing.
191     VariableAccess      <- ( EntireVariable | ComponentVariable | IdentifiedVariable | BufferVariable | SubstringVariable | FunctionIdentifiedVariable ) ( _ "::" _ TypeName)?
192 
193 # 6.5.2 (complete)
194     EntireVariable      <- VariableName
195 
196 # 6.5.3.1 (complete)
197     ComponentVariable   <- IndexedVariable | FieldDesignator
198 
199 # 6.5.3.2 (complete)
200     IndexedVariable     <- (ArrayVariable _ "[" _ IndexExpression ( _ "," _ IndexExpression )* _ "]" ) | ( StringVariable _ "[" _ IndexExpression _ "]" )
201     ArrayVariable       <- VariableAccess
202     StringVariable      <- VariableAccess
203     IndexExpression     <- Expression
204 
205 # 6.5.3.3 (complete)
206     FieldDesignator     <- ( RecordVariable _ "." _ FieldSpecifier ) | FieldDesignatorIdentifier
207     RecordVariable      <- VariableAccess
208     FieldSpecifier      <- FieldIdentifier
209 
210 # 6.5.4 (complete)
211     IdentifiedVariable  <- PointerVariable _ :"^"
212     PointerVariable     <- VariableAccess
213 
214 # 6.5.5 (complete)
215     BufferVariable      <- FileVariable _ :"^"
216     FileVariable        <- VariableAccess
217 
218 # 6.5.6 (complete)
219     SubstringVariable   <- StringVariable _ "[" _ IndexExpression _ ".." _ IndexExpression _ "]"
220 
221 # 6.6 (complete)
222     InitialStateSpecifier   <- VALUE _ ComponentValue
223 
224 # 6.7.1 (complete)
225     ProcedureDeclaration    <- ProcedureHeading _ ";" _ RemoteDirective
226                              | ProcedureIdentification _ ";" _ ProcedureBlock
227                              | ProcedureHeading _ ";" _ ProcedureBlock
228     ProcedureHeading        <- PROCEDURE _ Identifier ( _ FormalParameterList )?
229     ProcedureIdentification <- PROCEDURE _ ProcedureIdentifier
230     ProcedureIdentifier     <- Identifier
231     ProcedureBlock          <- Block
232     ProcedureName           <- ( ImportedInterfaceIdentifier _ DOT _ )? ProcedureIdentifier
233 
234 # 6.7.2 (complete)
235     FunctionDeclaration         <- FunctionHeading _ ";" _ RemoteDirective
236                                  | FunctionIdentification _ ";" _ FunctionBlock
237                                  | FunctionHeading _ ";" _ FunctionBlock
238     FunctionHeading             <- :FUNCTION _ Identifier ( _ FormalParameterList )? ( _ ResultVariableSpecification )? _ ":" _ ResultType
239     ResultVariableSpecification <- "=" _ Identifier
240     FunctionIdentification      <- :FUNCTION _ FunctionIdentifier
241     FunctionIdentifier          <- Identifier
242     ResultType                  <- TypeName
243     FunctionBlock               <- Block
244     FunctionName                <- ( ImportedInterfaceIdentifier _ DOT _ )? FunctionIdentifier
245 
246 # 6.7.3.1 (complete)
247     FormalParameterList                 <- "(" _ FormalParameterSection ( _ ";" _ FormalParameterSection )* _ ")"
248     FormalParameterSection              <- ValueParameterSpecification
249                                          | VariableParameterSpecification
250                                          | ProceduralParameterSpecification
251                                          | FunctionalParameterSpecification
252                                          | ConformantArrayParameterSpecification    # BNV moved from section 6.7.3.7.1
253     ValueParameterSpecification         <- (PROTECTED _ )? IdentifierList _ ":" _ ParameterForm
254     VariableParameterSpecification      <- (PROTECTED _ )? VAR _ IdentifierList _ ":" _ ParameterForm
255     ParameterForm                       <- TypeName | SchemaName | TypeInquiry
256     ParameterIdentifier                 <- Identifier
257     ProceduralParameterSpecification    <- ProcedureHeading
258     FunctionalParameterSpecification    <- FunctionHeading
259 
260 # 6.7.3.7.1
261 #    FormalParameterSection                  <- ConformantArrayParameterSpecification   # BNV Moved to section 6.7.3.1
262     ConformantArrayParameterSpecification   <- ( PROTECTED _ )? ( ValueConformantArraySpecification | VariableConformantArraySpecification )
263     ValueConformantArraySpecification       <- IdentifierList _ ":" _ ConformantArrayForm
264     VariableConformantArraySpecification    <- VAR _ IdentifierList _ ":" _ ConformantArrayForm
265     ConformantArrayForm                     <- PackedConformantArrayForm / UnpackedConformantArrayForm
266     PackedConformantArrayForm               <- PACKED _ ARRAY _ "[" _ IndexTypeSpecification _ "]" _ OF _ TypeName
267     UnpackedConformantArrayForm             <- ARRAY _ "[" _ IndexTypeSpecification ( _ ";" _ IndexTypeSpecification )* _ "]" _ OF _ TypeName
268     IndexTypeSpecification                  <- Identifier _ ".." _ Identifier _ ":" _ OrdinalTypeName
269 # TODO mistake in standard?
270 #    Primary                                 <- BoundIdentifier
271 #    BoundIdentifier                         <- Identifier
272 
273 # 6.7.5 Required procedures TODO
274 
275 # 6.7.5.5 (complete)
276     ReadstrParameterList    <- "(" _ StringExpression _ "," _ VariableAccess ( _ "," _ VariableAccess )* _ ")"
277     StringExpression        <- Expression
278     WritestrParameterList   <- "(" _ StringVariable _ "," _ WriteParameter ( _ "," _ WriteParameter )* _ ")"
279 
280 # 6.7.6 Required functions TODO
281 
282 # 6.8.1 (complete)
283     Expression          <- SimpleExpression ( _ RelationalOperator _ SimpleExpression)?
284     SimpleExpression    <- Sign? _ Term ( _ AddingOperator _ Term )*
285     Term                <- Factor ( _ MultiplyingOperator _ Factor )*
286     Factor              <- Primary ( _ ExponentiatingOperator _ Primary )?
287     Primary             <- VariableAccess
288                          | UnsignedConstant
289                          | SetConstructor
290                          | FunctionAccess
291                          | "(" _ Expression _ ")"
292                          | NOT _ Primary
293                          | ConstantAccess
294                          | SchemaDiscriminant
295                          | StructuredValueConstructor
296                          | DiscriminantIdentifier
297     UnsignedConstant    <- UnsignedNumber | CharacterString | NIL | ExtendedNumber
298     SetConstructor      <- "[" _ ( MemberDesignator ( _ "," _ MemberDesignator )* )? _ "]"
299     MemberDesignator    <- Expression ( _ ".." _ Expression )?
300 
301 # 6.8.2 (complete)
302     ConstantExpression  <- Expression
303 
304 # 6.8.3.1 (complete)
305     ExponentiatingOperator  <- "**" / POW
306     MultiplyingOperator     <- "*" / "/" / DIV / MOD / AND_THEN / AND       # BNV Try to match AND_THEN before AND
307     AddingOperator          <- "+" / "-" / "><" / OR_ELSE / OR              # BNV Try to match OR_ELSE before OR
308     RelationalOperator      <- "=" / "<>" / "<=" / "<" / ">=" / ">" / IN
309 
310 # 6.8.3.2 Arithmetic operators TODO?
311 
312 # 6.8.3.3
313     BooleanExpression       <- Expression
314 
315 # 6.8.3.4 Set operators TODO
316 
317 # 6.8.3.6 String operator TODO
318 
319 # 6.8.4 (complete)
320     SchemaDiscriminant      <- ( VariableAccess / ConstantAccess ) _ "." _ DiscriminantSpecifier | SchemaDiscriminantIdentifier
321     DiscriminantSpecifier   <- DiscriminantIdentifier
322 
323 
324 # 6.8.5 (complete)
325     FunctionDesignator      <- FunctionName ( _ ActualParameterList )?
326     ActualParameterList     <- "(" _ ActualParameter ( _ "," _ ActualParameter )* _ ")"
327     ActualParameter         <- Expression / VariableAccess / ProcedureName / FunctionName
328 
329 # 6.8.6.1 (complete)
330     #FunctionAccess          <- EntireFunctionAccess / ComponentFunctionAccess / SubstringFunctionAccess
331 # Prospero extension: type viewing.
332     FunctionAccess          <- ( EntireFunctionAccess | ComponentFunctionAccess | SubstringFunctionAccess ) ( _ "::" _ TypeName)?
333     ComponentFunctionAccess <- IndexedFunctionAccess / RecordFunctionAccess
334     EntireFunctionAccess    <- FunctionDesignator
335 
336 # 6.8.6.2 (complete)
337     IndexedFunctionAccess   <- ArrayFunction _ "[" _ IndexExpression ( _ "," _ IndexExpression )* _ "]"
338     ArrayFunction           <- FunctionAccess
339     StringFunction          <- FunctionAccess
340 
341 # 6.8.6.3 (complete)
342     RecordFunctionAccess    <- RecordFunction _ "." _ FieldSpecifier
343     RecordFunction          <- FunctionAccess
344 
345 # 6.8.6.4 (complete)
346     FunctionIdentifiedVariable  <- PointerFunction _ "^"
347     PointerFunction             <- FunctionAccess
348 
349 # 6.8.6.5 (complete)
350     SubstringFunctionAccess <- StringFunction _ "[" _ IndexExpression _ ".." _ IndexExpression _ "]"
351 
352 # 6.8.7.1 (complete)
353     StructuredValueConstructor  <- ArrayTypeName _ ArrayValue | RecordTypeName _ RecordValue | SetTypeName _ SetValue
354     ComponentValue  <- Expression | ArrayValue | RecordValue
355 
356 # 6.8.7.2 (complete)
357     ArrayValue          <- "[" _ ( ArrayValueElement ( _ ";" _ ArrayValueElement )* _ ";"? )? ( _ ArrayValueCompleter _ ";"? )? _ "]"
358     ArrayValueElement   <- CaseConstantList _ ":" _ ComponentValue
359     ArrayValueCompleter <- OTHERWISE _ ComponentValue
360 
361 # 6.8.7.3 (complete)
362     RecordValue         <- "[" _ FieldListValue _ "]"
363     FieldListValue      <- ( ( FixedPartValue ( _ ";" _ VariantPartValue )? / VariantPartValue ) _ ";"? )?
364     FixedPartValue      <- FieldValue ( _ ";" _ FieldValue )*
365     FieldValue          <- FieldIdentifier ( _ ";" _ FieldIdentifier )* _ ":" _ ComponentValue
366     VariantPartValue    <- CASE _ ( TagFieldIdentifier _ ":" _)? ConstantTagValue _ OF _ "[" _ FieldListValue _ "]"
367     ConstantTagValue    <- ConstantExpression
368     TagFieldIdentifier  <- FieldIdentifier
369 
370 # 6.8.7.4 (complete)
371     SetValue            <- SetConstructor
372 
373 # 6.8.8.1 (complete)
374     ConstantAccess          <- ConstantAccessComponent / ConstantName
375     ConstantAccessComponent <- IndexedConstant | FieldDesignatedConstant | SubstringConstant
376 
377 # 6.8.8.2 (complete)
378     IndexedConstant <- ArrayConstant _ "[" _ IndexExpression ( _ "," _ IndexExpression )* _ "]" | StringConstant _ "[" _ IndexExpression _ "]"
379     ArrayConstant   <- ConstantAccess
380     StringConstant  <- ConstantAccess
381 
382 # 6.8.8.3 (complete)
383     FieldDesignatedConstant <- RecordConstant _ "." _ FieldSpecifier | ConstantFieldIdentifier
384     RecordConstant          <- ConstantAccess
385 
386 # 6.8.8.4 (complete)
387     SubstringConstant   <- StringConstant _ "[" _ IndexExpression _ ".." _ IndexExpression _ "]"
388 
389 # 6.9.1 (complete)
390 #    Statement   <- ( Label _ ":" _ )? ( SimpleStatement | StructuredStatement )
391 # Need a longest match on the label because of the Prospero extension that labels can be identifiers. Alternatively, maintain a list of defined labels that are in scope.
392     Statement   <- ( SimpleStatement |  StructuredStatement ) | Label _ ":" _ ( SimpleStatement | StructuredStatement )
393 
394 # 6.9.2.1 (complete)
395     SimpleStatement <- EmptyStatement | AssignmentStatement | ProcedureStatement | GotoStatement
396     EmptyStatement  <- eps
397 
398 # 6.9.2.2 (complete)
399     AssignmentStatement <- ( VariableAccess / FunctionIdentifier ) _ ":=" _ Expression
400 
401 # 6.9.2.3 (complete) #BNV Extended for required procedures.
402     ProcedureStatement  <-
403                          / READLN _ ReadlnParameterList
404                          / READSTR _ ReadstrParameterList
405                          / READ _ ReadParameterList
406                          / WRITELN _ WritelnParameterList?
407                          / WRITESTR _ WritestrParameterList
408                          / WRITE _ WriteParameterList
409                          / ProcedureName _ ActualParameterList?
410 
411 # 6.9.2.4 (complete)
412     GotoStatement       <- GOTO _ Label
413 
414 # 6.9.3.1 (complete)
415     StructuredStatement <- CompoundStatement / ConditionalStatement / RepetitiveStatement / WithStatement
416     StatementSequence   <- Statement ( _ ";" _ Statement )*
417 
418 # 6.9.3.2 (complete)
419     CompoundStatement   <- :BEGIN _ StatementSequence _ :END
420 
421 # 6.9.3.3 (complete)
422     ConditionalStatement    <- IfStatement / CaseStatement
423 
424 # 6.9.3.4 (complete)
425     IfStatement <- IF _ BooleanExpression _ THEN _ Statement ( _ ElsePart )?
426     ElsePart    <- ELSE _ Statement
427 
428 # 6.9.3.5 (complete)
429     CaseStatement           <- CASE _ CaseIndex _ OF _ ( CaseListElement ( _ ";" _ CaseListElement )* ( _ ";"? _ CaseStatementCompleter )? | _ CaseStatementCompleter ) _ ";"? _ END
430     CaseIndex               <- Expression
431     CaseListElement         <- CaseConstantList _ ":" _ Statement
432     CaseStatementCompleter  <- OTHERWISE _ StatementSequence
433 
434 # 6.9.3.6 (complete)
435     RepetitiveStatement <- RepeatStatement / WhileStatement / ForStatement
436 
437 # 6.9.3.7 (complete)
438     RepeatStatement <- REPEAT _ StatementSequence _ UNTIL _ BooleanExpression
439 
440 # 6.9.3.8 (complete)
441     WhileStatement  <- WHILE _ BooleanExpression _ DO _ Statement
442 
443 # 6.9.3.9.1 (complete)
444     ForStatement    <- FOR _ ControlVariable _ IterationClause _ DO _ Statement
445     ControlVariable <- EntireVariable
446     IterationClause <- SequenceIteration / SetMemberIteration
447 
448 # 6.9.3.9.2 (complete)
449     SequenceIteration   <- ":=" _ InitialValue _ ( TO / DOWNTO ) _ FinalValue
450     InitialValue        <- Expression
451     FinalValue          <- Expression
452 
453 # 6.9.3.9.3 (complete)
454     SetMemberIteration  <- IN _ SetExpression
455     SetExpression       <- Expression
456 
457 # 6.9.3.10 (complete)
458     WithStatement                   <- WITH _ WithList _ DO _ Statement
459     WithList                        <- WithElement ( _ "," _ WithElement)*
460     WithElement                     <- VariableAccess / ConstantAccess
461     FieldDesignatorIdentifier       <- Identifier
462     ConstantFieldIdentifier         <- Identifier
463     SchemaDiscriminantIdentifier    <- Identifier
464 
465 # 6.9.4 Threats
466 
467 # 6.10.1 (complete)
468     ReadParameterList   <- "(" _ ( FileVariable _ "," _ )? VariableAccess _ ( "," _ VariableAccess _ )* ")"
469 
470 # 6.10.2 (complete)
471     ReadlnParameterList <- ( "(" _ ( FileVariable / VariableAccess ) _ ( "," _ VariableAccess _ )* ")" )?
472 
473 # 6.10.3 (complete)
474     WriteParameterList  <- "(" _ ( FileVariable _ "," _ )? WriteParameter _ ( "," _ WriteParameter _ )* ")"
475     WriteParameter      <- Expression ( _ ":" _ Expression ( _ ":" _ Expression )? )?
476 
477 # 6.10.4 (complete)
478     WritelnParameterList    <- ( "(" _ ( FileVariable | WriteParameter ) _ ( "," _ WriteParameter _ )* ")" )?
479 
480 # 6.11.1 (complete)
481     ModuleDeclaration       <- ModuleHeadeing ( _ ";" _ ModuleBlock )? /
482                                ModuleIdentification _ ";" _ ModuleBlock
483     ModuleHeadeing          <- MODULE Comment? BNVModuleName Comment? InterfaceDirective? Comment? ( "(" ModuleParameterList ")" Comment? )? ";" _ InterfaceSpecificationPart _ ImportPart _ ( ConstantDefinitionPart / TypeDefinitionPart / VariableDeclarationPart / ProcedureAndFunctionHeadingPart)* _ END
484     ModuleParameterList     <- IdentifierList
485     ProcedureAndFunctionHeadingPart <- ( ProcedureHeading / FunctionHeading ) _ ";"
486     ModuleIdentification    <- MODULE Comment? ModuleIdenifier Comment? ImplementationDirective
487     ModuleIdenifier         <- Identifier
488     ModuleBlock             <- ImportPart _ ( ConstantDefinitionPart / TypeDefinitionPart / VariableDeclarationPart / ProcedureAndFunctionDeclarationPart )* _ InitializationPart? _ FinalizationPart? _ END
489     InitializationPart      <- TO _ BEGIN _ DO _ Statement _ ";"
490     FinalizationPart        <- TO _ END _ DO _ Statement _ ";"
491     BNVModuleName           <- Identifier
492 
493 # 6.11.2 (complete)
494     InterfaceSpecificationPart  <- EXPORT _ ( ExportPart _ ";" )+
495     ExportPart                  <- Identifier _ "=" _ "(" _ ExportList _ ")"
496     ExportList                  <- ( ExportClause | ExportRange ) ( _ "," _ ( ExportClause | ExportRange ) )*
497     ExportClause                <- ExportableName | ExportRenamingClause
498     ExportRenamingClause        <- ExportableName _ "=>" _ Identifier
499     ExportableName              <- ConstantName / TypeName / SchemaName / ( ( PROTECTED _ )? VariableName ) / ProcedureName / FunctionName
500     ExportRange                 <- FirstConstantName _ ".." _ LastConstantName
501     FirstConstantName           <- ConstantName
502     LastConstantName            <- ConstantName
503     ConstituentIdentifier       <- Identifier
504     InterfaceIdentifier         <- Identifier
505 
506 # 6.11.3 (complete)
507     ImportSpecification         <- InterfaceIdentifier ( _ AccessQualifier )? _ ImportQualifier?
508     AccessQualifier             <- QUALIFIED
509     ImportQualifier             <- ( SelectiveImportOption _ )? "(" _ ImportList _ ")"
510     SelectiveImportOption       <- ONLY
511     ImportList                  <- ImportClause _ ("," _ ImportClause _)*
512     ImportClause                <- ConstituentIdentifier | ImportRenamingClause
513     ImportRenamingClause        <- ConstituentIdentifier _ "=>" _ Identifier
514     ImportedInterfaceIdentifier <- Identifier
515 
516 # 6.11.4 Required interfaces TODO
517 
518 # 6.12 (complete)
519     MainProgramDeclaration  <- ProgramHeading _ ";" :Spacing? MainProgramBlock # BNV Discarding newlines that have no correspondence in D.
520     ProgramHeading          <- PROGRAM Comment? BNVProgramName ( Comment? "(" _ ProgramParameterList _ ")" )?
521     ProgramParameterList    <- IdentifierList
522     MainProgramBlock        <- _ Block
523     # BNV extensions
524     BNVProgramName          <- Identifier
525 
526 # 6.13
527     Program             <- _ ProgramBlock _
528     ProgramBlock        <- ( ProgramComponent _ )+
529     ProgramComponent    <- ( MainProgramDeclaration _ "." ) / ( ModuleDeclaration _ "." )
530 
531 # Keywords 6.1.2
532     AND         <- "and"i
533     AND_THEN    <- "and_then"i
534     ARRAY       <- "array"i
535     BEGIN       <- "begin"i
536     BINDABLE    <- "bindable"i
537     CASE        <- "case"i
538     CONST       <- "const"i
539     DIV         <- "div"i
540     DO          <- "do"i
541     DOWNTO      <- "downto"i
542     ELSE        <- "else"i
543     END         <- "end"i
544     EXPORT      <- "export"i
545     FILE        <- "file"i
546     FOR         <- "for"i
547     FUNCTION    <- "function"i
548     GOTO        <- "goto"i
549     IF          <- "if"i
550     IMPORT      <- "import"i
551     IN          <- "in"i
552     LABEL       <- "label"i
553     MOD         <- "mod"i
554     MODULE      <- "module"i
555     NIL         <- "nil"i
556     NOT         <- "not"i
557     OF          <- "of"i
558     ONLY        <- "only"i
559     OR          <- "or"i
560     OR_ELSE     <- "or_else"i
561     OTHERWISE   <- "otherwise"i
562     PACKED      <- "packed"i
563     POW         <- "pow"i
564     PROCEDURE   <- "procedure"i
565     PROGRAM     <- "program"i
566     PROTECTED   <- "protected"i
567     QUALIFIED   <- "qualified"i
568     RECORD      <- "record"i
569     REPEAT      <- "repeat"i
570     RESTRICTED  <- "restricted"i
571     SET         <- "set"i
572     THEN        <- "then"i
573     TO          <- "to"i
574     TYPE        <- "type"i
575     UNTIL       <- "until"i
576     VALUE       <- "value"i
577     VAR         <- "var"i
578     WHILE       <- "while"i
579     WITH        <- "with"i
580 
581 # Separators
582     COMMA       <- ","
583     DOT         <- "."
584 
585 # Built-ins
586     READ        <- "read"i
587     READLN      <- "readln"i
588     READSTR     <- "readstr"i
589     WRITE       <- "write"i
590     WRITELN     <- "writeln"i
591     WRITESTR    <- "writestr"i
592 `;