]> git.ipfire.org Git - thirdparty/gcc.git/blame - gcc/m2/gm2-compiler/P0SyntaxCheck.bnf
Update copyright years.
[thirdparty/gcc.git] / gcc / m2 / gm2-compiler / P0SyntaxCheck.bnf
CommitLineData
1eee94d3
GM
1--
2-- m2.bnf grammar and associated actions for pass 0.
3--
83ffe9cd 4-- Copyright (C) 2001-2023 Free Software Foundation, Inc.
1eee94d3
GM
5-- Contributed by Gaius Mulley <gaius.mulley@southwales.ac.uk>.
6--
7-- This file is part of GNU Modula-2.
8--
9-- GNU Modula-2 is free software; you can redistribute it and/or modify
10-- it under the terms of the GNU General Public License as published by
11-- the Free Software Foundation; either version 3, or (at your option)
12-- any later version.
13--
14-- GNU Modula-2 is distributed in the hope that it will be useful, but
15-- WITHOUT ANY WARRANTY; without even the implied warranty of
16-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
17-- General Public License for more details.
18--
19-- You should have received a copy of the GNU General Public License
20-- along with GNU Modula-2; see the file COPYING3. If not see
21-- <http://www.gnu.org/licenses/>.
22% module P0SyntaxCheck begin
23(* output from m2.bnf, automatically generated do not edit if these
24 are the top two lines in the file.
25
83ffe9cd 26Copyright (C) 2001-2023 Free Software Foundation, Inc.
1eee94d3
GM
27Contributed by Gaius Mulley <gaius.mulley@southwales.ac.uk>.
28
29This file is part of GNU Modula-2.
30
31GNU Modula-2 is free software; you can redistribute it and/or modify
32it under the terms of the GNU General Public License as published by
33the Free Software Foundation; either version 3, or (at your option)
34any later version.
35
36GNU Modula-2 is distributed in the hope that it will be useful, but
37WITHOUT ANY WARRANTY; without even the implied warranty of
38MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
39General Public License for more details.
40
41You should have received a copy of the GNU General Public License
42along with GNU Modula-2; see the file COPYING. If not,
43see <https://www.gnu.org/licenses/>. *)
44
45IMPLEMENTATION MODULE P0SyntaxCheck ;
46
47FROM M2LexBuf IMPORT currentstring, currenttoken, GetToken, InsertToken,
48 InsertTokenAndRewind, GetTokenNo, DisplayToken, DumpTokens ;
49
50FROM M2MetaError IMPORT MetaErrorStringT0 ;
51FROM M2Quads IMPORT PushT, PushTF, IsAutoPushOn, PushAutoOff, PushAutoOn, PopAuto, DisplayStack, PushTFtok, PushTtok ;
52FROM M2Reserved IMPORT tokToTok, toktype, NulTok, ImportTok, ExportTok, QualifiedTok, UnQualifiedTok, BuiltinTok, InlineTok ;
53FROM P2SymBuild IMPORT BuildString, BuildNumber ;
54FROM NameKey IMPORT Name, NulName, makekey ;
55FROM StrLib IMPORT StrCopy, StrConCat, StrEqual ;
56FROM M2Batch IMPORT MakeProgramSource, MakeDefinitionSource, MakeImplementationSource ;
57FROM DynamicStrings IMPORT String, InitString, KillString, Mark, ConCat, ConCatChar ;
58FROM M2Debug IMPORT Assert ;
59FROM M2Printf IMPORT printf0 ;
60
61(* imports for Pass0 *)
62
63FROM P0SymBuild IMPORT RegisterImports, RegisterInnerImports,
64 RegisterProgramModule,
65 RegisterImplementationModule, RegisterDefinitionModule,
66 RegisterInnerModule, EndModule,
67 RegisterProcedure, EndProcedure ;
68
69FROM SymbolTable IMPORT NulSym, PutModuleContainsBuiltin, PutHiddenTypeDeclared ;
70
71IMPORT M2Error ;
72
73
74CONST
75 Debugging = FALSE ;
76 DebugRecover = FALSE ;
77 Pass0 = TRUE ;
78 Pass1 = FALSE ;
79 Pass2 = FALSE ; (* permanently disabled for the time being *)
80 Pass3 = FALSE ; (* permanently disabled for the time being *)
81 MaxInsert = 10 ; (* allow 10 tokens to be inserted before *)
82 (* giving up. *)
83
84VAR
85 seenError : BOOLEAN ;
86 LastIdent : Name ;
87 InsertCount: CARDINAL ;
88
89
90PROCEDURE ErrorString (s: String) ;
91BEGIN
92 MetaErrorStringT0 (GetTokenNo (), s) ;
93 seenError := TRUE
94END ErrorString ;
95
96
97PROCEDURE ErrorArray (a: ARRAY OF CHAR) ;
98BEGIN
99 ErrorString (InitString (a))
100END ErrorArray ;
101
102
103% declaration P0SyntaxCheck begin
104
105(*
106 SyntaxError - after a syntax error we skip all tokens up until we reach
107 a stop symbol.
108*)
109
110PROCEDURE SyntaxError (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
111BEGIN
112 DescribeError ;
113 IF Debugging
114 THEN
115 printf0('\nskipping token *** ')
116 END ;
117 (* --fixme-- this assumes a 32 bit word size. *)
118 WHILE NOT (((ORD(currenttoken)<32) AND (currenttoken IN stopset0)) OR
119 ((ORD(currenttoken)>=32) AND (ORD(currenttoken)<64) AND (currenttoken IN stopset1)) OR
120 ((ORD(currenttoken)>=64) AND (currenttoken IN stopset2)))
121 DO
122 GetToken
123 END ;
124 IF Debugging
125 THEN
126 printf0(' ***\n')
127 END
128END SyntaxError ;
129
130
131(*
132 SyntaxCheck -
133*)
134
135PROCEDURE SyntaxCheck (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
136BEGIN
137 (* --fixme-- this assumes a 32 bit word size. *)
138 IF NOT (((ORD(currenttoken)<32) AND (currenttoken IN stopset0)) OR
139 ((ORD(currenttoken)>=32) AND (ORD(currenttoken)<64) AND (currenttoken IN stopset1)) OR
140 ((ORD(currenttoken)>=64) AND (currenttoken IN stopset2)))
141 THEN
142 SyntaxError (stopset0, stopset1, stopset2)
143 END
144END SyntaxCheck ;
145
146
147(*
148 GetMissingTokenMessage - generates and returns a string about a missing token, t.
149*)
150
151PROCEDURE GetMissingTokenMessage (t: toktype) : String ;
152VAR
153 s0 : SetOfStop0 ;
154 s1 : SetOfStop1 ;
155 s2 : SetOfStop2 ;
156 str: String ;
157BEGIN
158 s0 := SetOfStop0{} ;
159 s1 := SetOfStop1{} ;
160 s2 := SetOfStop2{} ;
161 IF ORD(t)<32
162 THEN
163 s0 := SetOfStop0{t}
164 ELSIF ORD(t)<64
165 THEN
166 s1 := SetOfStop1{t}
167 ELSE
168 s2 := SetOfStop2{t}
169 END ;
170 str := DescribeStop (s0, s1, s2) ;
171 RETURN str
172END GetMissingTokenMessage ;
173
174
175(*
176 ErrorMissingToken - generates an error message about a missing token, t.
177*)
178
179PROCEDURE ErrorMissingToken (t: toktype) ;
180VAR
181 str: String ;
182BEGIN
183 str := GetMissingTokenMessage (t) ;
184 str := ConCat (InitString ('syntax error,'), Mark (str)) ;
185 MetaErrorStringT0 (GetTokenNo (), str)
186END ErrorMissingToken ;
187
188
189(*
190 WarnMissingToken - generates a warning message about a missing token, t.
191*)
192
193PROCEDURE WarnMissingToken (t: toktype) ;
194VAR
195 str: String ;
196BEGIN
197 str := GetMissingTokenMessage (t) ;
198 str := ConCat (InitString ('{%W}syntax warning,'), Mark (str)) ;
199 MetaErrorStringT0 (GetTokenNo (), str) ;
200 IF DebugRecover
201 THEN
202 printf0 ("warning note created\n")
203 END
204END WarnMissingToken ;
205
206
207(*
208 MissingToken - generates a warning message about a missing token, t.
209*)
210
211PROCEDURE MissingToken (t: toktype) ;
212BEGIN
213 IF (InsertCount<MaxInsert) AND
214 ((t#identtok) AND (t#integertok) AND (t#realtok) AND (t#stringtok))
215 THEN
216 IF DebugRecover
217 THEN
218 printf0 ("missing token detected and going to be inserted: ");
219 DisplayToken (t)
220 END ;
221 WarnMissingToken (t) ;
222 INC (InsertCount) ;
223 IF DebugRecover
224 THEN
225 printf0 ('inserting token\n')
226 END ;
227 InsertToken (t)
228 ELSE
229 IF DebugRecover
230 THEN
231 printf0 ("missing token detected but cannot be inserted: ");
232 DisplayToken (t)
233 END ;
234 ErrorMissingToken (t)
235 END
236END MissingToken ;
237
238
239(*
240 CheckInsertCandidate -
241*)
242
243PROCEDURE CheckInsertCandidate (t: toktype; stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) : BOOLEAN ;
244BEGIN
245 IF ((ORD(t)<32) AND (t IN stopset0)) OR
246 ((ORD(t)>=32) AND (ORD(t)<64) AND (t IN stopset1)) OR
247 ((ORD(t)>=64) AND (t IN stopset2))
248 THEN
249 INC (InsertCount) ;
250 IF InsertCount < MaxInsert
251 THEN
252 WarnMissingToken (t) ;
253 IF DebugRecover
254 THEN
255 printf0 ('buffer before\n') ;
256 DumpTokens ;
257 printf0 ('inserting token: buffer after\n') ;
258 DumpTokens ;
259 printf0 ('inserting token\n')
260 END ;
261 InsertTokenAndRewind (t) ;
262 RETURN TRUE
263 END
264 END ;
265 RETURN FALSE
266END CheckInsertCandidate ;
267
268
269(*
270 InStopSet
271*)
272
273PROCEDURE InStopSet (t: toktype; stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) : BOOLEAN ;
274BEGIN
275 IF ((ORD(t)<32) AND (t IN stopset0)) OR
276 ((ORD(t)>=32) AND (ORD(t)<64) AND (t IN stopset1)) OR
277 ((ORD(t)>=64) AND (t IN stopset2))
278 THEN
279 RETURN( TRUE )
280 ELSE
281 RETURN( FALSE )
282 END
283END InStopSet ;
284
285
286(*
287 PeepToken - peep token checks to see whether the stopset is satisfied by currenttoken
288 If it is not then it will insert a token providing the token
289 is one of ; ] ) } . OF END ,
290
291 if the stopset contains <identtok> then we do not insert a token
292*)
293
294PROCEDURE PeepToken (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
295BEGIN
296 (* and again (see above re: ORD)
297 *)
298 IF (NOT (((ORD(currenttoken)<32) AND (currenttoken IN stopset0)) OR
299 ((ORD(currenttoken)>=32) AND (ORD(currenttoken)<64) AND (currenttoken IN stopset1)) OR
300 ((ORD(currenttoken)>=64) AND (currenttoken IN stopset2)))) AND
301 (NOT InStopSet(identtok, stopset0, stopset1, stopset2))
302 THEN
303 (* SyntaxCheck will fail since currentoken is not part of the stopset
304 we check to see whether one of the following is in the stopset and
305 if not emit a warning and also the token. *)
306 IF CheckInsertCandidate (semicolontok, stopset0, stopset1, stopset2) OR
307 CheckInsertCandidate (rsbratok, stopset0, stopset1, stopset2) OR
308 CheckInsertCandidate (rparatok, stopset0, stopset1, stopset2) OR
309 CheckInsertCandidate (rcbratok, stopset0, stopset1, stopset2) OR
310 CheckInsertCandidate (periodtok, stopset0, stopset1, stopset2) OR
311 CheckInsertCandidate (oftok, stopset0, stopset1, stopset2) OR
312 CheckInsertCandidate (endtok, stopset0, stopset1, stopset2) OR
313 CheckInsertCandidate (commatok, stopset0, stopset1, stopset2)
314 THEN
315 END
316 END
317END PeepToken ;
318
319
320(*
321 Expect -
322*)
323
324PROCEDURE Expect (t: toktype; stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
325BEGIN
326 IF currenttoken=t
327 THEN
328 GetToken ;
329 IF Pass0
330 THEN
331 PeepToken (stopset0, stopset1, stopset2)
332 END
333 ELSE
334 MissingToken (t)
335 END ;
336 SyntaxCheck (stopset0, stopset1, stopset2)
337END Expect ;
338
339
340(*
341 CompilationUnit - returns TRUE if the input was correct enough to parse
342 in future passes.
343*)
344
345PROCEDURE CompilationUnit () : BOOLEAN ;
346BEGIN
347 seenError := FALSE ;
348 InsertCount := 0 ;
349 FileUnit (SetOfStop0{eoftok}, SetOfStop1{}, SetOfStop2{}) ;
350 RETURN NOT seenError
351END CompilationUnit ;
352
353
354(*
355 Ident - error checking varient of Ident
356*)
357
358PROCEDURE Ident (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
359BEGIN
360 LastIdent := makekey (currentstring) ;
361 IF IsAutoPushOn ()
362 THEN
363 PushTFtok (LastIdent, identtok, GetTokenNo())
364 END ;
365 Expect (identtok, stopset0, stopset1, stopset2)
366END Ident ;
367
368
369(*
370 string -
371*)
372
373PROCEDURE string (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
374BEGIN
375 IF IsAutoPushOn ()
376 THEN
377 PushTF (makekey (currentstring), stringtok) ;
378 BuildString
379 END ;
380 Expect (stringtok, stopset0, stopset1, stopset2)
381END string ;
382
383
384(*
385 Integer -
386*)
387
388PROCEDURE Integer (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
389BEGIN
390 IF IsAutoPushOn()
391 THEN
392 PushTFtok (makekey (currentstring), integertok, GetTokenNo ()) ;
393 BuildNumber
394 END ;
395 Expect(integertok, stopset0, stopset1, stopset2)
396END Integer ;
397
398
399(*
400 Real -
401*)
402
403PROCEDURE Real (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
404BEGIN
405 IF IsAutoPushOn()
406 THEN
407 PushTFtok (makekey (currentstring), realtok, GetTokenNo ()) ;
408 BuildNumber
409 END ;
410 Expect(realtok, stopset0, stopset1, stopset2)
411END Real ;
412
413% module P0SyntaxCheck end
414END P0SyntaxCheck.
415% rules
416error 'ErrorArray' 'ErrorString'
417tokenfunc 'currenttoken'
418
419token '' eoftok -- internal token
420token '+' plustok
421token '-' minustok
422token '*' timestok
423token '/' dividetok
424token ':=' becomestok
425token '&' ambersandtok
426token "." periodtok
427token "," commatok
428token ";" semicolontok
429token '(' lparatok
430token ')' rparatok
431token '[' lsbratok -- left square brackets
432token ']' rsbratok -- right square brackets
433token '{' lcbratok -- left curly brackets
434token '}' rcbratok -- right curly brackets
435token '^' uparrowtok
436token "'" singlequotetok
437token '=' equaltok
438token '#' hashtok
439token '<' lesstok
440token '>' greatertok
441token '<>' lessgreatertok
442token '<=' lessequaltok
443token '>=' greaterequaltok
444token '<*' ldirectivetok
445token '*>' rdirectivetok
446token '..' periodperiodtok
447token ':' colontok
448token '"' doublequotestok
449token '|' bartok
450token 'AND' andtok
451token 'ARRAY' arraytok
452token 'BEGIN' begintok
453token 'BY' bytok
454token 'CASE' casetok
455token 'CONST' consttok
456token 'DEFINITION' definitiontok
457token 'DIV' divtok
458token 'DO' dotok
459token 'ELSE' elsetok
460token 'ELSIF' elsiftok
461token 'END' endtok
462token 'EXCEPT' excepttok
463token 'EXIT' exittok
464token 'EXPORT' exporttok
465token 'FINALLY' finallytok
466token 'FOR' fortok
467token 'FROM' fromtok
468token 'IF' iftok
469token 'IMPLEMENTATION' implementationtok
470token 'IMPORT' importtok
471token 'IN' intok
472token 'LOOP' looptok
473token 'MOD' modtok
474token 'MODULE' moduletok
475token 'NOT' nottok
476token 'OF' oftok
477token 'OR' ortok
478token 'PACKEDSET' packedsettok
479token 'POINTER' pointertok
480token 'PROCEDURE' proceduretok
481token 'QUALIFIED' qualifiedtok
482token 'UNQUALIFIED' unqualifiedtok
483token 'RECORD' recordtok
484token 'REM' remtok
485token 'REPEAT' repeattok
486token 'RETRY' retrytok
487token 'RETURN' returntok
488token 'SET' settok
489token 'THEN' thentok
490token 'TO' totok
491token 'TYPE' typetok
492token 'UNTIL' untiltok
493token 'VAR' vartok
494token 'WHILE' whiletok
495token 'WITH' withtok
496token 'ASM' asmtok
497token 'VOLATILE' volatiletok
498token '...' periodperiodperiodtok
499token '__DATE__' datetok
500token '__LINE__' linetok
501token '__FILE__' filetok
502token '__ATTRIBUTE__' attributetok
503token '__BUILTIN__' builtintok
504token '__INLINE__' inlinetok
505token 'integer number' integertok
506token 'identifier' identtok
507token 'real number' realtok
508token 'string' stringtok
509
510special Ident first { < identtok > } follow { }
511 '@i{is a builtin and checks for an identifier}'
512special Integer first { < integertok > } follow { }
513 '@i{is a builtin and checks for an integer}'
514special Real first { < realtok > } follow { }
515 '@i{is a builtin and checks for an real constant}'
516special string first { < stringtok > } follow { }
517 '@i{is a builtin and checks for an string constant}'
518BNF
519
520-- the following are provided by the module m2flex and also hand built procedures below
521-- Ident := Letter { ( Letter | Digit ) } =:
522-- Integer := Digit { Digit } | OctalDigit { OctalDigit } ( " B " | " C " ) |
523-- Digit { HexDigit } " H " =:
524-- Real := Digit { Digit } " . " { Digit } [ ScaleFactor ] =:
525-- ScaleFactor := " E " [ ( " + " | " - " ) ] Digit { Digit } =:
526-- HexDigit := Digit | " A " | " B " | " C " | " D " | " E " | " F " =:
527-- Digit := OctalDigit | " 8 " | " 9 " =:
528-- OctalDigit := "0" | "1" | "2" | "3" | "4" | "5" | "6" | "7" =:
529-- String
530
531FileUnit := % PushAutoOff %
532 ( DefinitionModule | ImplementationOrProgramModule ) % PopAuto %
533 =:
534
535ProgramModule := "MODULE" % PushAutoOn ; %
536 % M2Error.DefaultProgramModule %
537 Ident % RegisterProgramModule ; %
538 % PushAutoOff ; %
539 [ Priority ]
540 ";"
541 % PushAutoOn ; %
542 { Import % RegisterImports %
543 } % PopAuto %
544 Block % PopAuto %
545 Ident "." % EndModule %
546 % PopAuto %
547 =:
548
549ImplementationModule := "IMPLEMENTATION" % M2Error.DefaultImplementationModule %
550 "MODULE" % PushAutoOn ; %
551 Ident % RegisterImplementationModule ; %
552 % PushAutoOff ; %
553 [ Priority ] ";" % PushAutoOn ; %
554 { Import % RegisterImports %
555 } % PopAuto %
556 Block % PopAuto %
557
558 Ident % EndModule %
559 % PopAuto %
560 "." =:
561
562ImplementationOrProgramModule := ImplementationModule | ProgramModule =:
563
564Number := Integer | Real =:
565
566Qualident := Ident { "." Ident } =:
567
568ConstantDeclaration := Ident "=" ConstExpression =:
569
570ConstExpression := SimpleConstExpr [ Relation SimpleConstExpr ] =:
571
572Relation := "=" | "#" | "<>" | "<" | "<=" | ">" | ">=" | "IN" =:
573
574SimpleConstExpr := UnaryOrConstTerm { AddOperator ConstTerm } =:
575
576UnaryOrConstTerm := "+" ConstTerm | "-" ConstTerm | ConstTerm =:
577
578AddOperator := "+" | "-" | "OR" =:
579
580ConstTerm := ConstFactor { MulOperator ConstFactor } =:
581
582MulOperator := "*" | "/" | "DIV" | "MOD" | "REM" | "AND" | "&" =:
583
584ConstFactor := Number | ConstString | ConstSetOrQualidentOrFunction |
585 "(" ConstExpression ")" | "NOT" ConstFactor |
586 ConstAttribute =:
587
588-- to help satisfy LL1
589
590ConstString := string =:
591
592ComponentElement := ConstExpression [ ".." ConstExpression ] =:
593
594ComponentValue := ComponentElement [ 'BY' ConstExpression ] =:
595
596ArraySetRecordValue := ComponentValue { ',' ComponentValue } =:
597
598Constructor := '{' [ ArraySetRecordValue ] '}' =:
599
600ConstSetOrQualidentOrFunction := Constructor | Qualident
601 [ Constructor | ConstActualParameters ] =:
602
603ConstActualParameters := "(" [ ExpList ] ")" =:
604
605ConstAttribute := "__ATTRIBUTE__" "__BUILTIN__" "(" "(" ConstAttributeExpression ")" ")" =:
606
607ConstAttributeExpression := Ident | "<" Qualident ',' Ident ">" =:
608
609ByteAlignment := '<*' AttributeExpression '*>' =:
610
611-- AlignmentExpression := "(" ConstExpression ")" =:
612
613Alignment := [ ByteAlignment ] =:
614
615TypeDeclaration := Ident "=" Type Alignment =:
616
617Type := SimpleType | ArrayType | RecordType | SetType |
618 PointerType | ProcedureType =:
619
620SimpleType := Qualident [ SubrangeType ] | Enumeration | SubrangeType =:
621
622Enumeration := "(" IdentList ")" =:
623
624IdentList := Ident % VAR
625 on: BOOLEAN ;
626 n : CARDINAL ; %
627 % on := IsAutoPushOn() ;
628 IF on
629 THEN
630 n := 1
631 END %
632 { "," Ident % IF on
633 THEN
634 INC(n)
635 END %
636 } % IF on
637 THEN
638 PushT(n)
639 END %
640 =:
641
642SubrangeType := "[" ConstExpression ".." ConstExpression "]" =:
643
644ArrayType := "ARRAY" SimpleType { "," SimpleType } "OF" Type =:
645
646RecordType := "RECORD" [ DefaultRecordAttributes ] FieldListSequence "END" =:
647
648DefaultRecordAttributes := '<*' AttributeExpression '*>' =:
649
650RecordFieldPragma := [ '<*' FieldPragmaExpression
651 { ',' FieldPragmaExpression } '*>' ] =:
652
653FieldPragmaExpression := Ident [ '(' ConstExpression ')' ] =:
654
655AttributeExpression := Ident '(' ConstExpression ')' =:
656
657FieldListSequence := FieldListStatement { ";" FieldListStatement } =:
658
659FieldListStatement := [ FieldList ] =:
660
661FieldList := IdentList ":" Type RecordFieldPragma
662 |
663 "CASE" CaseTag "OF" Varient { "|" Varient }
664 [ "ELSE" FieldListSequence ] "END"
665 =:
666
667TagIdent := [ Ident ] =:
668
669CaseTag := TagIdent [ ":" Qualident ] =:
670
671Varient := [ VarientCaseLabelList ":" FieldListSequence ] =:
672
673VarientCaseLabelList := VarientCaseLabels { "," VarientCaseLabels } =:
674
675VarientCaseLabels := ConstExpression [ ".." ConstExpression ] =:
676
677CaseLabelList := CaseLabels { "," CaseLabels } =:
678
679CaseLabels := ConstExpression [ ".." ConstExpression ] =:
680
681SetType := ( "SET" | "PACKEDSET" ) "OF" SimpleType =:
682
683PointerType := "POINTER" "TO" Type =:
684
685ProcedureType := "PROCEDURE" [ FormalTypeList ] =:
686
687FormalTypeList := "(" ( ")" FormalReturn |
688 ProcedureParameters ")" FormalReturn ) =:
689
690FormalReturn := [ ":" OptReturnType ] =:
691
692OptReturnType := "[" Qualident "]" | Qualident =:
693
694ProcedureParameters := ProcedureParameter
695 { "," ProcedureParameter } =:
696
697ProcedureParameter := "..." | "VAR" FormalType | FormalType =:
698
699VarIdent := Ident [ "[" ConstExpression "]" ]
700 =:
701
702VariableDeclaration := VarIdentList ":" Type Alignment =:
703
704VarIdentList := VarIdent % VAR
705 on: BOOLEAN ;
706 n : CARDINAL ; %
707 % on := IsAutoPushOn() ;
708 IF on
709 THEN
710 n := 1
711 END %
712 { "," VarIdent % IF on
713 THEN
714 INC(n)
715 END %
716 } % IF on
717 THEN
718 PushT(n)
719 END %
720 =:
721
722Designator := Qualident { SubDesignator } =:
723
724SubDesignator := "." Ident | "[" ExpList "]" | "^" =:
725
726ExpList := Expression { "," Expression } =:
727
728Expression := SimpleExpression [ Relation SimpleExpression ] =:
729
730SimpleExpression := [ "+" | "-" ] Term { AddOperator Term } =:
731
732Term := Factor { MulOperator Factor } =:
733
734Factor := Number | string | SetOrDesignatorOrFunction |
735 "(" Expression ")" | "NOT" Factor | ConstAttribute =:
736
737SetOrDesignatorOrFunction := ( Qualident [ Constructor |
738 SimpleDes [ ActualParameters ]
739 ] | Constructor
740 )
741 =:
742
743SimpleDes := { "." Ident | "[" ExpList "]" | "^" } =:
744
745ActualParameters := "(" [ ExpList ] ")" =:
746
747Statement := [ AssignmentOrProcedureCall | IfStatement | CaseStatement |
748 WhileStatement | RepeatStatement | LoopStatement |
749 ForStatement | WithStatement | AsmStatement |
750 "EXIT" | "RETURN" [ Expression ] | RetryStatement ] =:
751
752RetryStatement := "RETRY" =:
753
754AssignmentOrProcedureCall := Designator ( ":=" Expression |
755 ActualParameters | % (* epsilon *) %
756 ) =:
757
758-- these two break LL1 as both start with a Designator
759-- ProcedureCall := Designator [ ActualParameters ] =:
760-- Assignment := Designator ":=" Expression =:
761
762StatementSequence := Statement { ";" Statement } =:
763
764IfStatement := "IF" Expression "THEN" StatementSequence
765 { "ELSIF" Expression "THEN" StatementSequence }
766 [ "ELSE" StatementSequence ] "END" =:
767
768CaseStatement := "CASE" Expression "OF" Case { "|" Case }
769 [ "ELSE" StatementSequence ] "END" =:
770
771Case := [ CaseLabelList ":" StatementSequence ] =:
772
773WhileStatement := "WHILE" Expression "DO" StatementSequence "END" =:
774
775RepeatStatement := "REPEAT" StatementSequence "UNTIL" Expression =:
776
777ForStatement := "FOR" Ident ":=" Expression "TO" Expression
778 [ "BY" ConstExpression ] "DO"
779 StatementSequence "END" =:
780
781LoopStatement := "LOOP" StatementSequence "END" =:
782
783WithStatement := "WITH" Designator "DO" StatementSequence "END" =:
784
785ProcedureDeclaration :=
786 ProcedureHeading ";" ( ProcedureBlock % PushAutoOn %
787 Ident % EndProcedure %
788 % PopAuto %
789 ) =:
790
791DefineBuiltinProcedure := [ "__ATTRIBUTE__" "__BUILTIN__" "(" "(" Ident ")" ")" |
792 "__INLINE__" ] =:
793
794ProcedureHeading := "PROCEDURE" % M2Error.DefaultProcedure %
795 DefineBuiltinProcedure
796 ( % PushAutoOn %
797 Ident % RegisterProcedure %
798 % PopAuto %
799 [ FormalParameters ] AttributeNoReturn ) =:
800
801AttributeNoReturn := [ "<*" Ident "*>" ] =:
802
803AttributeUnused := [ "<*" Ident "*>" ] =:
804
805-- note that we do need to know whether builtins are used as they
806-- determine whether we need to parse the implementation module
807-- the same is true for hidden types
808
809Builtin := [ "__BUILTIN__" % PutModuleContainsBuiltin %
810 | "__INLINE__" ] =:
811
812DefProcedureHeading := "PROCEDURE" % M2Error.DefaultProcedure %
813 Builtin
814 ( Ident [ DefFormalParameters ] AttributeNoReturn )
815 % M2Error.LeaveErrorScope %
816 =:
817
818-- introduced procedure block so we can produce more informative
819-- error messages
820
821ProcedureBlock := { Declaration } [ "BEGIN" BlockBody ] "END" =:
822
823Block := { Declaration } InitialBlock FinalBlock "END" =:
824
825InitialBlock := [ "BEGIN" BlockBody ] =:
826
827FinalBlock := [ "FINALLY" BlockBody ] =:
828
829BlockBody := NormalPart [ "EXCEPT" ExceptionalPart ] =:
830
831NormalPart := StatementSequence =:
832
833ExceptionalPart := StatementSequence =:
834
835Declaration := "CONST" { ConstantDeclaration ";" } |
836 "TYPE" { TypeDeclaration ";" } |
837 "VAR" { VariableDeclaration ";" } |
838 ProcedureDeclaration ";" |
839 ModuleDeclaration ";" =:
840
841DefFormalParameters := "(" [ DefMultiFPSection ] ")" FormalReturn =:
842
843DefMultiFPSection := DefExtendedFP |
844 FPSection [ ";" DefMultiFPSection ] =:
845
846FormalParameters := "(" [ MultiFPSection ] ")" FormalReturn =:
847
848MultiFPSection := ExtendedFP |
849 FPSection [ ";" MultiFPSection ] =:
850
851FPSection := NonVarFPSection | VarFPSection =:
852
853DefExtendedFP := DefOptArg | "..." =:
854
855ExtendedFP := OptArg | "..." =:
856
857VarFPSection := "VAR" IdentList ":" FormalType [ AttributeUnused ] =:
858
859NonVarFPSection := IdentList ":" FormalType [ AttributeUnused ] =:
860
861OptArg := "[" Ident ":" FormalType [ "=" ConstExpression ] "]" =:
862
863DefOptArg := "[" Ident ":" FormalType "=" ConstExpression "]" =:
864
865FormalType := { "ARRAY" "OF" } Qualident =:
866
867ModuleDeclaration := "MODULE" % PushAutoOn %
868 % M2Error.DefaultInnerModule %
869 Ident % RegisterInnerModule %
870 % PushAutoOff %
871 [ Priority ] ";" % PushAutoOn %
872 { Import % RegisterInnerImports %
873 } % PopAuto %
874 [ Export ] Block % PopAuto %
875 Ident % EndModule %
876 % PopAuto %
877 =:
878
879Priority := "[" ConstExpression "]" =:
880
881Export := "EXPORT" ( "QUALIFIED" IdentList |
882 "UNQUALIFIED" IdentList |
883 IdentList
884 ) ";" =:
885
886Import := "FROM" Ident "IMPORT" IdentList ";" |
887 "IMPORT" % PushTtok (ImportTok, GetTokenNo () -1)
888 (* determines whether Ident or Module *) %
889 IdentList ";" =:
890
891DefinitionModule := % VAR forC: BOOLEAN ; %
892 % forC := FALSE %
893 "DEFINITION" % M2Error.DefaultDefinitionModule %
894 "MODULE" [ "FOR" string % forC := TRUE %
895 ] % PushAutoOn %
896 Ident % RegisterDefinitionModule (forC) %
897 ";"
898 { Import % RegisterImports %
899 } % PushAutoOff %
900 [ Export
901 ]
902 { Definition } % PopAuto %
903 "END" Ident % EndModule %
904 "." % PopAuto %
905 =:
906
907Definition := "CONST" { ConstantDeclaration ";" } |
908 "TYPE" { Ident
909 ( ";" % PutHiddenTypeDeclared %
910 | "=" Type Alignment ";" ) }
911 |
912 "VAR" { VariableDeclaration ";" } |
913 DefProcedureHeading ";" =:
914
915AsmStatement := 'ASM' [ 'VOLATILE' ] '(' AsmOperands ')' =:
916
917NamedOperand := '[' Ident ']' =:
918
919AsmOperandName := [ NamedOperand ] =:
920
921AsmOperands := string [ ':' AsmList [ ':' AsmList [ ':' TrashList ] ] ]
922 =:
923
924AsmList := [ AsmElement ] { ',' AsmElement } =:
925
926AsmElement := AsmOperandName string '(' Expression ')'
927 =:
928
929TrashList := [ string ] { ',' string } =:
930
931FNB