Skip -fwhole-program when merging LTO options.
[official-gcc.git] / gcc / m2 / gm2-compiler / PHBuild.bnf
blob7cb97421956aadbffce79e6a805cbed25757d96c
1 --
2 -- m2-h.bnf grammar and associated actions for pass h.
3 --
4 -- Copyright (C) 2001-2022 Free Software Foundation, Inc.
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.
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.
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 PHBuild begin
23 (* output from m2-h.bnf, automatically generated do not edit if these
24 are the top two lines in the file.
26 Copyright (C) 2001-2022 Free Software Foundation, Inc.
27 Contributed by Gaius Mulley <gaius.mulley@southwales.ac.uk>.
29 This file is part of GNU Modula-2.
31 GNU Modula-2 is free software; you can redistribute it and/or modify
32 it under the terms of the GNU General Public License as published by
33 the Free Software Foundation; either version 3, or (at your option)
34 any later version.
36 GNU Modula-2 is distributed in the hope that it will be useful, but
37 WITHOUT ANY WARRANTY; without even the implied warranty of
38 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
39 General Public License for more details.
41 You should have received a copy of the GNU General Public License
42 along with GNU Modula-2; see the file COPYING. If not,
43 see <https://www.gnu.org/licenses/>. *)
45 IMPLEMENTATION MODULE PHBuild ;
47 FROM M2LexBuf IMPORT currentstring, currenttoken, GetToken, InsertToken, InsertTokenAndRewind, GetTokenNo ;
48 FROM M2Error IMPORT ErrorStringAt ;
49 FROM NameKey IMPORT NulName, Name, makekey ;
50 FROM M2Reserved IMPORT NulTok, ByTok, PeriodPeriodTok, tokToTok, toktype ;
51 FROM DynamicStrings IMPORT String, InitString, KillString, Mark, ConCat, ConCatChar ;
52 FROM M2Printf IMPORT printf0 ;
53 FROM M2Debug IMPORT Assert ;
54 FROM P2SymBuild IMPORT BuildString, BuildNumber ;
56 FROM M2Quads IMPORT PushT, PopT, PushTF, PopTF, PopNothing, PushTFtok, PopTFtok, PopTtok,
57 StartBuildDefFile, StartBuildModFile,
58 BuildModuleStart,
59 EndBuildFile,
60 StartBuildInit,
61 EndBuildInit,
62 BuildProcedureStart,
63 BuildProcedureEnd,
64 BuildAssignment, BuildAssignConstant,
65 BuildFunctionCall, BuildConstFunctionCall,
66 BuildBinaryOp, BuildUnaryOp, BuildRelOp, BuildNot,
67 BuildEmptySet, BuildInclRange, BuildInclBit,
68 BuildSetStart, BuildSetEnd,
69 BuildSizeCheckStart,
70 BuildRepeat, BuildUntil,
71 BuildWhile, BuildDoWhile, BuildEndWhile,
72 BuildLoop, BuildExit, BuildEndLoop,
73 BuildThenIf, BuildElse, BuildEndIf,
74 BuildForToByDo, BuildPseudoBy, BuildEndFor,
75 BuildElsif1, BuildElsif2,
76 BuildProcedureCall, BuildReturn, BuildNulExpression,
77 StartBuildWith, EndBuildWith,
78 BuildInline,
79 BuildCaseStart,
80 BuildCaseOr,
81 BuildCaseElse,
82 BuildCaseEnd,
83 BuildCaseStartStatementSequence,
84 BuildCaseEndStatementSequence,
85 BuildCaseList,
86 BuildCaseRange, BuildCaseEquality,
87 BuildConstructorStart,
88 BuildConstructorEnd,
89 SilentBuildConstructorStart,
90 BuildComponentValue, BuildTypeForConstructor,
91 BuildBooleanVariable, BuildAlignment,
92 RecordOp,
93 BuildNulParam,
94 BuildDesignatorRecord,
95 BuildDesignatorArray,
96 BuildDesignatorPointer,
97 BeginVarient, EndVarient, ElseVarient,
98 BeginVarientList, EndVarientList,
99 AddVarientRange, AddVarientEquality,
100 CheckWithReference,
101 IsAutoPushOn, PushAutoOff, PushAutoOn, PopAuto ;
103 FROM P3SymBuild IMPORT P3StartBuildProgModule,
104 P3EndBuildProgModule,
106 P3StartBuildDefModule,
107 P3EndBuildDefModule,
109 P3StartBuildImpModule,
110 P3EndBuildImpModule,
112 StartBuildInnerModule,
113 EndBuildInnerModule,
115 StartBuildProcedure,
116 BuildProcedureHeading,
117 EndBuildProcedure,
118 BuildConst,
119 BuildSubrange,
120 BuildNulName ;
122 FROM SymbolTable IMPORT MakeGnuAsm, PutGnuAsmVolatile, PutGnuAsm, PutGnuAsmInput,
123 PutGnuAsmOutput, PutGnuAsmTrash, PutGnuAsmVolatile,
124 MakeRegInterface,
125 PutRegInterface, GetRegInterface,
126 GetSymName, GetType,
127 NulSym,
128 StartScope, EndScope,
129 PutIncluded,
130 IsVarParam, IsProcedure, IsDefImp, IsModule,
131 IsRecord,
132 RequestSym,
133 GetSym, GetLocalSym ;
135 FROM M2Batch IMPORT IsModuleKnown ;
137 FROM M2CaseList IMPORT BeginCaseList, EndCaseList, ElseCase ;
139 FROM M2Reserved IMPORT NulTok, ImportTok, ExportTok, QualifiedTok, UnQualifiedTok,
140 EqualTok, HashTok, LessGreaterTok, LessTok, LessEqualTok,
141 GreaterTok, GreaterEqualTok, InTok, PlusTok, MinusTok,
142 OrTok, TimesTok, DivTok, DivideTok, ModTok, RemTok, AndTok, AmbersandTok ;
144 IMPORT M2Error ;
147 CONST
148 Debugging = FALSE ;
149 Pass1 = FALSE ; (* permanently disabled for the time being *)
150 Pass2 = FALSE ; (* permanently disabled for the time being *)
151 Pass3 = FALSE ;
154 WasNoError: BOOLEAN ;
157 PROCEDURE ErrorString (s: String) ;
158 BEGIN
159 ErrorStringAt(s, GetTokenNo()) ;
160 WasNoError := FALSE
161 END ErrorString ;
164 PROCEDURE ErrorArray (a: ARRAY OF CHAR) ;
165 BEGIN
166 ErrorString(InitString(a))
167 END ErrorArray ;
170 % declaration PHBuild begin
174 SyntaxError - after a syntax error we skip all tokens up until we reach
175 a stop symbol.
178 PROCEDURE SyntaxError (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
179 BEGIN
180 DescribeError ;
181 IF Debugging
182 THEN
183 printf0('\nskipping token *** ')
184 END ;
185 (* --fixme-- this assumes a 32 bit word size. *)
186 WHILE NOT (((ORD(currenttoken)<32) AND (currenttoken IN stopset0)) OR
187 ((ORD(currenttoken)>=32) AND (ORD(currenttoken)<64) AND (currenttoken IN stopset1)) OR
188 ((ORD(currenttoken)>=64) AND (currenttoken IN stopset2)))
190 GetToken
191 END ;
192 IF Debugging
193 THEN
194 printf0(' ***\n')
196 END SyntaxError ;
200 SyntaxCheck -
203 PROCEDURE SyntaxCheck (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
204 BEGIN
205 (* --fixme-- this assumes a 32 bit word size. *)
206 IF NOT (((ORD(currenttoken)<32) AND (currenttoken IN stopset0)) OR
207 ((ORD(currenttoken)>=32) AND (ORD(currenttoken)<64) AND (currenttoken IN stopset1)) OR
208 ((ORD(currenttoken)>=64) AND (currenttoken IN stopset2)))
209 THEN
210 SyntaxError(stopset0, stopset1, stopset2)
212 END SyntaxCheck ;
216 WarnMissingToken - generates a warning message about a missing token, t.
219 PROCEDURE WarnMissingToken (t: toktype) ;
221 s0 : SetOfStop0 ;
222 s1 : SetOfStop1 ;
223 s2 : SetOfStop2 ;
224 str: String ;
225 BEGIN
226 s0 := SetOfStop0{} ;
227 s1 := SetOfStop1{} ;
228 s2 := SetOfStop2{} ;
229 IF ORD(t)<32
230 THEN
231 s0 := SetOfStop0{t}
232 ELSIF ORD(t)<64
233 THEN
234 s1 := SetOfStop1{t}
235 ELSE
236 s2 := SetOfStop2{t}
237 END ;
238 str := DescribeStop(s0, s1, s2) ;
240 str := ConCat(InitString('syntax error,'), Mark(str)) ;
241 ErrorStringAt(str, GetTokenNo())
242 END WarnMissingToken ;
246 MissingToken - generates a warning message about a missing token, t.
249 PROCEDURE MissingToken (t: toktype) ;
250 BEGIN
251 WarnMissingToken(t) ;
252 IF (t#identtok) AND (t#integertok) AND (t#realtok) AND (t#stringtok)
253 THEN
254 IF Debugging
255 THEN
256 printf0('inserting token\n')
257 END ;
258 InsertToken(t)
260 END MissingToken ;
264 CheckAndInsert -
267 PROCEDURE CheckAndInsert (t: toktype; stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) : BOOLEAN ;
268 BEGIN
269 IF ((ORD(t)<32) AND (t IN stopset0)) OR
270 ((ORD(t)>=32) AND (ORD(t)<64) AND (t IN stopset1)) OR
271 ((ORD(t)>=64) AND (t IN stopset2))
272 THEN
273 WarnMissingToken(t) ;
274 InsertTokenAndRewind(t) ;
275 RETURN( TRUE )
276 ELSE
277 RETURN( FALSE )
279 END CheckAndInsert ;
283 InStopSet
286 PROCEDURE InStopSet (t: toktype; stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) : BOOLEAN ;
287 BEGIN
288 IF ((ORD(t)<32) AND (t IN stopset0)) OR
289 ((ORD(t)>=32) AND (ORD(t)<64) AND (t IN stopset1)) OR
290 ((ORD(t)>=64) AND (t IN stopset2))
291 THEN
292 RETURN( TRUE )
293 ELSE
294 RETURN( FALSE )
296 END InStopSet ;
300 PeepToken - peep token checks to see whether the stopset is satisfied by currenttoken
301 If it is not then it will insert a token providing the token
302 is one of ; ] ) } . OF END ,
304 if the stopset contains <identtok> then we do not insert a token
307 PROCEDURE PeepToken (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
308 BEGIN
309 (* and again (see above re: ORD)
311 IF (NOT (((ORD(currenttoken)<32) AND (currenttoken IN stopset0)) OR
312 ((ORD(currenttoken)>=32) AND (ORD(currenttoken)<64) AND (currenttoken IN stopset1)) OR
313 ((ORD(currenttoken)>=64) AND (currenttoken IN stopset2)))) AND
314 (NOT InStopSet(identtok, stopset0, stopset1, stopset2))
315 THEN
316 (* SyntaxCheck would fail since currentoken is not part of the stopset
317 we check to see whether any of currenttoken might be a commonly omitted token *)
318 IF CheckAndInsert(semicolontok, stopset0, stopset1, stopset2) OR
319 CheckAndInsert(rsbratok, stopset0, stopset1, stopset2) OR
320 CheckAndInsert(rparatok, stopset0, stopset1, stopset2) OR
321 CheckAndInsert(rcbratok, stopset0, stopset1, stopset2) OR
322 CheckAndInsert(periodtok, stopset0, stopset1, stopset2) OR
323 CheckAndInsert(oftok, stopset0, stopset1, stopset2) OR
324 CheckAndInsert(endtok, stopset0, stopset1, stopset2) OR
325 CheckAndInsert(commatok, stopset0, stopset1, stopset2)
326 THEN
329 END PeepToken ;
333 Expect -
336 PROCEDURE Expect (t: toktype; stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
337 BEGIN
338 IF currenttoken=t
339 THEN
340 GetToken ;
341 IF Pass1
342 THEN
343 PeepToken(stopset0, stopset1, stopset2)
345 ELSE
346 MissingToken(t)
347 END ;
348 SyntaxCheck(stopset0, stopset1, stopset2)
349 END Expect ;
353 CompilationUnit - returns TRUE if the input was correct enough to parse
354 in future passes.
357 PROCEDURE CompilationUnit () : BOOLEAN ;
358 BEGIN
359 WasNoError := TRUE ;
360 FileUnit(SetOfStop0{eoftok}, SetOfStop1{}, SetOfStop2{}) ;
361 RETURN( WasNoError )
362 END CompilationUnit ;
366 Ident - error checking varient of Ident
369 PROCEDURE Ident (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
370 BEGIN
371 IF IsAutoPushOn()
372 THEN
373 PushTF(makekey(currentstring), identtok)
374 END ;
375 Expect(identtok, stopset0, stopset1, stopset2)
376 END Ident ;
380 string -
383 PROCEDURE string (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
384 BEGIN
385 IF IsAutoPushOn()
386 THEN
387 PushTF(makekey(currentstring), stringtok) ;
388 BuildString
389 END ;
390 Expect(stringtok, stopset0, stopset1, stopset2)
391 END string ;
395 Integer -
398 PROCEDURE Integer (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
399 BEGIN
400 IF IsAutoPushOn()
401 THEN
402 PushTFtok (makekey(currentstring), integertok, GetTokenNo ()) ;
403 BuildNumber
404 END ;
405 Expect(integertok, stopset0, stopset1, stopset2)
406 END Integer ;
410 Real -
413 PROCEDURE Real (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
414 BEGIN
415 IF IsAutoPushOn()
416 THEN
417 PushTFtok (makekey(currentstring), realtok, GetTokenNo ()) ;
418 BuildNumber
419 END ;
420 Expect(realtok, stopset0, stopset1, stopset2)
421 END Real ;
423 % module PHBuild end
424 END PHBuild.
425 % rules
426 error 'ErrorArray' 'ErrorString'
427 tokenfunc 'currenttoken'
429 token '' eoftok -- internal token
430 token '+' plustok
431 token '-' minustok
432 token '*' timestok
433 token '/' dividetok
434 token ':=' becomestok
435 token '&' ambersandtok
436 token "." periodtok
437 token "," commatok
438 token ";" semicolontok
439 token '(' lparatok
440 token ')' rparatok
441 token '[' lsbratok -- left square brackets
442 token ']' rsbratok -- right square brackets
443 token '{' lcbratok -- left curly brackets
444 token '}' rcbratok -- right curly brackets
445 token '^' uparrowtok
446 token "'" singlequotetok
447 token '=' equaltok
448 token '#' hashtok
449 token '<' lesstok
450 token '>' greatertok
451 token '<>' lessgreatertok
452 token '<=' lessequaltok
453 token '>=' greaterequaltok
454 token '<*' ldirectivetok
455 token '*>' rdirectivetok
456 token '..' periodperiodtok
457 token ':' colontok
458 token '"' doublequotestok
459 token '|' bartok
460 token 'AND' andtok
461 token 'ARRAY' arraytok
462 token 'BEGIN' begintok
463 token 'BY' bytok
464 token 'CASE' casetok
465 token 'CONST' consttok
466 token 'DEFINITION' definitiontok
467 token 'DIV' divtok
468 token 'DO' dotok
469 token 'ELSE' elsetok
470 token 'ELSIF' elsiftok
471 token 'END' endtok
472 token 'EXCEPT' excepttok
473 token 'EXIT' exittok
474 token 'EXPORT' exporttok
475 token 'FINALLY' finallytok
476 token 'FOR' fortok
477 token 'FROM' fromtok
478 token 'IF' iftok
479 token 'IMPLEMENTATION' implementationtok
480 token 'IMPORT' importtok
481 token 'IN' intok
482 token 'LOOP' looptok
483 token 'MOD' modtok
484 token 'MODULE' moduletok
485 token 'NOT' nottok
486 token 'OF' oftok
487 token 'OR' ortok
488 token 'PACKEDSET' packedsettok
489 token 'POINTER' pointertok
490 token 'PROCEDURE' proceduretok
491 token 'QUALIFIED' qualifiedtok
492 token 'UNQUALIFIED' unqualifiedtok
493 token 'RECORD' recordtok
494 token 'REM' remtok
495 token 'REPEAT' repeattok
496 token 'RETRY' retrytok
497 token 'RETURN' returntok
498 token 'SET' settok
499 token 'THEN' thentok
500 token 'TO' totok
501 token 'TYPE' typetok
502 token 'UNTIL' untiltok
503 token 'VAR' vartok
504 token 'WHILE' whiletok
505 token 'WITH' withtok
506 token 'ASM' asmtok
507 token 'VOLATILE' volatiletok
508 token '...' periodperiodperiodtok
509 token '__DATE__' datetok
510 token '__LINE__' linetok
511 token '__FILE__' filetok
512 token '__ATTRIBUTE__' attributetok
513 token '__BUILTIN__' builtintok
514 token '__INLINE__' inlinetok
515 token 'integer number' integertok
516 token 'identifier' identtok
517 token 'real number' realtok
518 token 'string' stringtok
520 special Ident first { < identtok > } follow { }
521 special Integer first { < integertok > } follow { }
522 special Real first { < realtok > } follow { }
523 special string first { < stringtok > } follow { }
527 -- the following are provided by the module m2flex and also handbuild procedures below
528 -- Ident := Letter { ( Letter | Digit ) } =:
529 -- Integer := Digit { Digit } | OctalDigit { OctalDigit } ( " B " | " C " ) |
530 -- Digit { HexDigit } " H " =:
531 -- Real := Digit { Digit } " . " { Digit } [ ScaleFactor ] =:
532 -- ScaleFactor := " E " [ ( " + " | " - " ) ] Digit { Digit } =:
533 -- HexDigit := Digit | " A " | " B " | " C " | " D " | " E " | " F " =:
534 -- Digit := OctalDigit | " 8 " | " 9 " =:
535 -- OctalDigit := "0" | "1" | "2" | "3" | "4" | "5" | "6" | "7" =:
536 -- String
538 FileUnit := % PushAutoOff %
539 ( DefinitionModule |
540 ImplementationOrProgramModule ) % PopAuto %
543 ProgramModule := % VAR begint, endt: CARDINAL ; %
544 % begint := GetTokenNo () %
545 "MODULE" % M2Error.DefaultProgramModule %
546 % PushAutoOn %
547 Ident % P3StartBuildProgModule %
548 % BuildModuleStart (begint) %
549 % PushAutoOff %
550 [ Priority
553 { Import
554 } % begint := GetTokenNo () %
555 % StartBuildInit (begint) %
556 Block % PushAutoOn %
557 % endt := GetTokenNo () -1 %
558 Ident % EndBuildFile (endt) %
559 % P3EndBuildProgModule %
560 "." % PopAuto ;
561 EndBuildInit (endt) ;
562 PopAuto %
565 ImplementationModule := % VAR begint, endt: CARDINAL ; %
566 % begint := GetTokenNo () %
567 "IMPLEMENTATION" % M2Error.DefaultImplementationModule %
568 "MODULE" % PushAutoOn %
569 Ident % StartBuildModFile (begint) %
570 % P3StartBuildImpModule %
571 % BuildModuleStart (begint) %
572 % PushAutoOff %
573 [ Priority
574 ] ";"
575 { Import
576 } % begint := GetTokenNo () %
577 % StartBuildInit (begint) %
578 Block % PushAutoOn %
579 % endt := GetTokenNo () -1 %
580 Ident % EndBuildFile (endt) %
581 % P3EndBuildImpModule %
582 "." % PopAuto ;
583 EndBuildInit (endt) ;
584 PopAuto ;
585 PopAuto %
588 ImplementationOrProgramModule := % PushAutoOff %
589 ( ImplementationModule | ProgramModule ) % PopAuto %
592 Number := Integer | Real =:
594 Qualident := % VAR name: Name ;
595 Type, Sym, tok: CARDINAL ; %
596 Ident
597 % IF IsAutoPushOn()
598 THEN
599 PopTtok(name, tok) ;
600 Sym := RequestSym (tok, name) ;
601 IF IsDefImp(Sym) OR IsModule(Sym)
602 THEN
603 Expect(periodtok, stopset0, stopset1, stopset2 + SetOfStop2{identtok}) ;
604 StartScope(Sym) ;
605 Qualident(stopset0, stopset1, stopset2) ;
606 (* should we test for lack of ident? *)
607 PopTFtok(Sym, Type, tok) ;
608 PushTFtok(Sym, Type, tok) ;
609 EndScope ;
610 PutIncluded(Sym)
611 ELSE
612 PushTFtok(Sym, GetType(Sym), tok) ;
614 ELSE (* just parse qualident *) %
615 { "." Ident } % END %
618 ConstantDeclaration := % PushAutoOn %
619 % VAR tokno: CARDINAL ; %
620 ( Ident "=" % tokno := GetTokenNo () %
621 % BuildConst %
622 ConstExpression ) % BuildAssignConstant (tokno) %
623 % PopAuto %
626 ConstExpression := % VAR tokpos: CARDINAL ; %
627 % PushAutoOn %
628 SimpleConstExpr [ Relation % tokpos := GetTokenNo ()-1 %
629 SimpleConstExpr % BuildRelOp (tokpos) %
630 ] % PopAuto %
633 Relation := "=" % PushT(EqualTok) %
634 | "#" % PushT(HashTok) %
635 | "<>" % PushT(LessGreaterTok) %
636 | "<" % PushT(LessTok) %
637 | "<=" % PushT(LessEqualTok) %
638 | ">" % PushT(GreaterTok) %
639 | ">=" % PushT(GreaterEqualTok) %
640 | "IN" % PushT(InTok) %
643 SimpleConstExpr := UnaryOrConstTerm { AddOperator ConstTerm % BuildBinaryOp %
644 } =:
646 UnaryOrConstTerm := "+" % PushT(PlusTok) %
647 ConstTerm % BuildUnaryOp %
649 "-" % PushT(MinusTok) %
650 ConstTerm % BuildUnaryOp %
652 ConstTerm =:
654 AddOperator := "+" % PushT(PlusTok) ;
655 RecordOp %
656 | "-" % PushT(MinusTok) ;
657 RecordOp %
658 | "OR" % PushT(OrTok) ;
659 RecordOp %
662 ConstTerm := ConstFactor { MulOperator ConstFactor % BuildBinaryOp %
663 } =:
665 MulOperator := "*" % PushT(TimesTok) ;
666 RecordOp %
667 | "/" % PushT(DivideTok) ;
668 RecordOp %
669 | "DIV" % PushT(DivTok) ;
670 RecordOp %
671 | "MOD" % PushT(ModTok) ;
672 RecordOp %
673 | "REM" % PushT(RemTok) ;
674 RecordOp %
675 | "AND" % PushT(AndTok) ;
676 RecordOp %
677 | "&" % PushT(AmbersandTok) ;
678 RecordOp %
681 ConstFactor := Number | ConstString | ConstSetOrQualidentOrFunction |
682 "(" ConstExpression ")" | "NOT" ConstFactor % BuildNot %
683 | ConstAttribute =:
685 -- to help satisfy LL1
687 ConstString := string =:
689 ComponentElement := ConstExpression ( ".." ConstExpression % PushT(PeriodPeriodTok) %
690 | % PushT(NulTok) %
694 ComponentValue := ComponentElement ( 'BY' ConstExpression % PushT(ByTok) %
696 | % PushT(NulTok) %
700 ArraySetRecordValue := ComponentValue % BuildComponentValue %
701 { ',' ComponentValue % BuildComponentValue %
705 Constructor := '{' % BuildConstructorStart (GetTokenNo() -1) %
706 [ ArraySetRecordValue ] % BuildConstructorEnd (GetTokenNo()) %
707 '}' =:
709 ConstSetOrQualidentOrFunction := Qualident
710 [ Constructor | ConstActualParameters % BuildConstFunctionCall %
712 | % BuildTypeForConstructor %
713 Constructor =:
715 ConstAttribute := "__ATTRIBUTE__" "__BUILTIN__" "(" "(" ConstAttributeExpression ")" ")" =:
717 ConstAttributeExpression := Ident | "<" Qualident ',' Ident ">" =:
719 ByteAlignment := '<*' % PushAutoOn %
720 AttributeExpression % BuildAlignment %
721 '*>' % PopAuto %
724 -- OptAlignmentExpression := [ AlignmentExpression ] =:
726 -- AlignmentExpression := "(" ConstExpression ")" =:
728 Alignment := [ ByteAlignment ] =:
730 TypeDeclaration := Ident "=" Type Alignment
733 Type :=
734 % PushAutoOff %
735 ( SimpleType | ArrayType
736 | RecordType
737 | SetType
738 | PointerType
739 | ProcedureType ) % PopAuto %
742 SimpleType := Qualident [ SubrangeType ] | Enumeration | SubrangeType =:
744 Enumeration := "("
745 ( IdentList
750 IdentList := Ident % VAR
751 on: BOOLEAN ;
752 n : CARDINAL ; %
753 % on := IsAutoPushOn() ;
754 IF on
755 THEN
756 n := 1
757 END %
758 { "," Ident % IF on
759 THEN
760 INC(n)
761 END %
762 } % IF on
763 THEN
764 PushT(n)
765 END %
768 SubrangeType := "[" ConstExpression ".." ConstExpression "]" % BuildSubrange ; %
771 ArrayType := "ARRAY"
773 SimpleType
774 { ","
775 SimpleType
776 } "OF"
777 Type
780 RecordType := "RECORD" [ DefaultRecordAttributes ] FieldListSequence "END" =:
782 DefaultRecordAttributes := '<*' AttributeExpression '*>' =:
784 RecordFieldPragma := [ '<*' FieldPragmaExpression
785 { ',' FieldPragmaExpression } '*>' ] =:
787 FieldPragmaExpression := % PushAutoOff %
788 Ident [ '(' ConstExpression ')' ] % PopAuto %
791 AttributeExpression := % PushAutoOff %
792 Ident '(' ConstExpression ')' % PopAuto %
795 FieldListSequence := FieldListStatement { ";" FieldListStatement } =:
797 -- at present FieldListStatement is as follows:
798 FieldListStatement := [ FieldList ] =:
799 -- later replace it with FieldList to comply with PIM2
801 -- sadly the PIM rules are not LL1 as Ident and Qualident have the same first
802 -- symbols. We rewrite FieldList to inline qualident
803 -- was
804 -- FieldList := IdentList ":" % BuildNulName %
805 -- Type |
806 -- "CASE" [ Ident ] [ ":" Qualident ] "OF" Varient { "|" Varient }
807 -- [ "ELSE" FieldListSequence ] "END" =:
809 FieldList := IdentList ":"
810 Type RecordFieldPragma
812 "CASE" % BeginVarient %
813 CaseTag "OF"
814 Varient { "|" Varient }
815 [ "ELSE" % ElseVarient %
816 FieldListSequence
817 ] "END" % EndVarient %
820 TagIdent := [ Ident ] =:
822 CaseTag := TagIdent [":" Qualident ] =:
824 Varient := [ % BeginVarientList %
825 VarientCaseLabelList ":" FieldListSequence % EndVarientList %
826 ] =:
828 VarientCaseLabelList := VarientCaseLabels { "," VarientCaseLabels } =:
830 VarientCaseLabels := ConstExpression ( ".." ConstExpression % AddVarientRange %
831 | % AddVarientEquality ; (* epsilon *) %
835 SilentCaseLabelList := SilentCaseLabels { "," SilentCaseLabels } =:
837 SilentCaseLabels := SilentConstExpression [ ".." SilentConstExpression ] =:
840 -- the following rules are a copy of the ConstExpression ebnf rules but without
841 -- any actions all prefixed with Silent.
844 SilentConstExpression := % PushAutoOff %
845 SilentSimpleConstExpr
846 [ SilentRelation SilentSimpleConstExpr ] % PopAuto %
849 SilentRelation := "=" | "#" | "<>" | "<" | "<=" | ">" | ">=" | "IN" =:
851 SilentSimpleConstExpr := SilentUnaryOrConstTerm { SilentAddOperator SilentConstTerm } =:
853 SilentUnaryOrConstTerm := "+" SilentConstTerm | "-" SilentConstTerm | SilentConstTerm =:
855 SilentAddOperator := "+" | "-" | "OR" =:
857 SilentConstTerm := SilentConstFactor { SilentMulOperator SilentConstFactor } =:
859 SilentMulOperator := "*" | "/" | "DIV" | "MOD" | "REM" | "AND" | "&" =:
861 SilentConstFactor := Number | SilentConstString | SilentConstSetOrQualidentOrFunction |
862 "(" SilentConstExpression ")" | "NOT" SilentConstFactor
863 | SilentConstAttribute =:
865 SilentConstString := string =:
867 SilentConstAttribute := "__ATTRIBUTE__" "__BUILTIN__" "(" "(" SilentConstAttributeExpression ")" ")" =:
869 SilentConstAttributeExpression := Ident | "<" Ident ',' SilentConstString ">" =:
871 SilentConstSetOrQualidentOrFunction := Qualident [ SilentConstructor | SilentActualParameters ] |
872 SilentConstructor =:
874 SilentSetOrDesignatorOrFunction := ( Qualident
875 [ SilentConstructor |
876 SilentSimpleDes [ SilentActualParameters ]
877 ] | SilentConstructor )
880 SilentSimpleDes := { SilentSubDesignator } =:
882 SilentConstructor := "{" % SilentBuildConstructorStart %
883 [ SilentElement { "," SilentElement } ] "}" =:
885 SilentElement := SilentConstExpression [ ".." SilentConstExpression ] =:
887 SilentActualParameters := "(" [ SilentExpList ] ")" =:
889 SilentSubDesignator := "." Ident | "[" SilentExpList "]" | "^"
892 SilentExpList := SilentExpression { "," SilentExpression } =:
894 SilentDesignator := Qualident { SilentSubDesignator } =:
896 SilentExpression :=
897 SilentSimpleExpression
898 [ SilentRelation
899 SilentSimpleExpression ]
902 SilentSimpleExpression := SilentUnaryOrTerm { SilentAddOperator SilentTerm } =:
904 SilentUnaryOrTerm := "+"
905 SilentTerm
906 | "-"
907 SilentTerm
908 | SilentTerm =:
910 SilentTerm := SilentFactor { SilentMulOperator SilentFactor
911 } =:
913 SilentFactor := Number | string | SilentSetOrDesignatorOrFunction |
914 "(" SilentExpression ")" | "NOT" SilentFactor | ConstAttribute =:
916 -- end of the Silent constant rules
918 SetType := ( "SET" | "PACKEDSET" ) "OF" SimpleType =:
920 PointerType := "POINTER" "TO" Type
923 ProcedureType := "PROCEDURE"
924 [ FormalTypeList ] =:
926 FormalTypeList := "(" ( ")" FormalReturn |
927 ProcedureParameters ")" FormalReturn ) =:
929 FormalReturn := [ ":" OptReturnType ] =:
931 OptReturnType := "[" Qualident "]" | Qualident =:
933 ProcedureParameters := ProcedureParameter
934 { "," ProcedureParameter } =:
936 ProcedureParameter := "..." | "VAR" FormalType | FormalType =:
938 VarIdent := % VAR Sym, Type: CARDINAL ; %
939 Ident [ "[" ConstExpression % PopTF(Sym, Type) %
940 "]" ]
943 VarIdentList := VarIdent % VAR
944 on: BOOLEAN ;
945 n : CARDINAL ; %
946 % on := IsAutoPushOn() ;
947 IF on
948 THEN
949 n := 1
950 END %
951 { "," VarIdent % IF on
952 THEN
953 INC(n)
954 END %
955 } % IF on
956 THEN
957 PushT(n)
958 END %
961 VariableDeclaration := VarIdentList ":" Type Alignment
964 Designator := Qualident
965 { SubDesignator } =:
967 SubDesignator := "."
968 Ident
969 | "[" ExpList
971 | "^"
974 ExpList :=
975 Expression
976 { ","
977 Expression
982 Expression :=
983 SimpleExpression [ SilentRelation SimpleExpression
987 SimpleExpression := UnaryOrTerm { SilentAddOperator Term
988 } =:
990 UnaryOrTerm := "+"
991 Term
992 | "-"
993 Term
994 | Term =:
996 Term := Factor { SilentMulOperator Factor
997 } =:
999 Factor := Number | string | SetOrDesignatorOrFunction |
1000 "(" Expression ")" | "NOT" Factor | ConstAttribute =:
1002 -- again Set | Designator causes problems as both has a first symbol, ident or Qualident
1004 SetOrDesignatorOrFunction := ( Qualident [ Constructor |
1005 SimpleDes [ ActualParameters ]
1006 ] | Constructor
1010 -- SimpleDes := { "." Ident | "[" ExpList "]" | "^" } =:
1011 SimpleDes := { SubDesignator } =:
1013 ActualParameters := "("
1014 ( ExpList | % (* epsilon *) %
1015 ) ")" =:
1017 ConstActualParameters := "(" % BuildSizeCheckStart %
1018 ( ConstExpList | % BuildNulParam %
1019 ) ")" =:
1021 ConstExpList := % VAR n: CARDINAL ; %
1022 ConstExpression % BuildBooleanVariable %
1023 % n := 1 %
1024 { ","
1025 ConstExpression % BuildBooleanVariable %
1026 % INC(n) %
1028 % PushT(n) %
1031 Statement :=
1032 [ AssignmentOrProcedureCall | IfStatement | CaseStatement |
1033 WhileStatement | RepeatStatement | LoopStatement |
1034 ForStatement | WithStatement | AsmStatement |
1035 "EXIT"
1036 | "RETURN"
1037 ( Expression | % (* in epsilon *) %
1038 ) | RetryStatement
1042 RetryStatement := "RETRY" =:
1044 AssignmentOrProcedureCall := Designator ( ":=" SilentExpression |
1045 SilentActualParameters | % (* in epsilon *) %
1046 ) =:
1048 -- these two break LL1 as both start with a Designator
1049 -- ProcedureCall := Designator [ ActualParameters ] =:
1050 -- Assignment := Designator ":=" Expression =:
1052 StatementSequence :=
1053 Statement
1054 { ";"
1055 Statement }
1058 IfStatement :=
1059 "IF"
1060 SilentExpression "THEN"
1061 StatementSequence
1062 { "ELSIF"
1063 Expression "THEN"
1064 StatementSequence
1066 [ "ELSE"
1067 StatementSequence ] "END"
1070 CaseStatement := "CASE"
1071 SilentExpression
1072 "OF" Case { "|" Case }
1073 [ "ELSE"
1074 StatementSequence ] "END"
1077 Case := [ SilentCaseLabelList ":" StatementSequence ] =:
1079 WhileStatement := "WHILE"
1080 SilentExpression
1081 "DO"
1082 StatementSequence
1083 "END"
1086 RepeatStatement := "REPEAT"
1087 StatementSequence
1088 "UNTIL"
1089 SilentExpression
1092 ForStatement := "FOR"
1093 Ident ":=" SilentExpression "TO" SilentExpression
1094 ( "BY" SilentConstExpression | % (* epsilon *) %
1095 ) "DO"
1096 StatementSequence "END"
1099 LoopStatement := "LOOP"
1100 StatementSequence
1101 "END"
1104 WithStatement := "WITH"
1105 SilentDesignator "DO"
1106 StatementSequence
1107 "END"
1110 ProcedureDeclaration := ProcedureHeading ";" ( ProcedureBlock % PushAutoOn %
1111 Ident ) % EndBuildProcedure %
1112 % PopAuto %
1115 DefineBuiltinProcedure := [ "__ATTRIBUTE__" "__BUILTIN__" "(" "(" Ident ")" ")" |
1116 "__INLINE__" ]
1119 ProcedureHeading := "PROCEDURE" % M2Error.DefaultProcedure %
1120 DefineBuiltinProcedure % PushAutoOn %
1121 ( Ident % StartBuildProcedure %
1122 % PushAutoOff %
1123 [ FormalParameters ] AttributeNoReturn
1124 % PopAuto %
1125 ) % PopAuto %
1128 Builtin := [ "__BUILTIN__" | "__INLINE__" ] =:
1130 DefProcedureHeading := "PROCEDURE" % M2Error.DefaultProcedure %
1131 Builtin
1132 ( Ident
1133 [ DefFormalParameters ] AttributeNoReturn
1134 ) % M2Error.LeaveErrorScope %
1137 AttributeNoReturn := [ "<*" Ident "*>" ] =:
1139 AttributeUnused := [ "<*" Ident "*>" ] =:
1141 -- introduced procedure block so we can produce more informative
1142 -- error messages
1144 ProcedureBlock := { Declaration } [ "BEGIN" BlockBody ] "END"
1147 Block := { Declaration } InitialBlock FinalBlock "END" =:
1149 InitialBlock := [ "BEGIN" BlockBody ] =:
1151 FinalBlock := [ "FINALLY" BlockBody ] =:
1153 BlockBody := NormalPart [ "EXCEPT" ExceptionalPart ] =:
1155 NormalPart := StatementSequence =:
1157 ExceptionalPart := StatementSequence =:
1159 Declaration := "CONST" { ConstantDeclaration ";" } |
1160 "TYPE" { TypeDeclaration ";" } |
1161 "VAR" { VariableDeclaration ";" } |
1162 ProcedureDeclaration ";" |
1163 ModuleDeclaration ";" =:
1165 DefFormalParameters := "(" [ DefMultiFPSection ] ")" FormalReturn =:
1167 DefMultiFPSection := DefExtendedFP |
1168 FPSection [ ";" DefMultiFPSection ] =:
1170 FormalParameters := "(" [ MultiFPSection ] ")" FormalReturn =:
1172 MultiFPSection := ExtendedFP |
1173 FPSection [ ";" MultiFPSection ] =:
1175 FPSection := NonVarFPSection | VarFPSection =:
1177 DefExtendedFP := DefOptArg | "..." =:
1179 ExtendedFP := OptArg | "..." =:
1181 VarFPSection := "VAR" IdentList ":" FormalType [ AttributeUnused ] =:
1183 NonVarFPSection := IdentList ":" FormalType [ AttributeUnused ] =:
1185 OptArg := "[" Ident ":" FormalType [ "=" SilentConstExpression ] "]" =:
1187 DefOptArg := "[" Ident ":" FormalType "=" SilentConstExpression "]" =:
1189 FormalType := { "ARRAY" "OF" } Qualident =:
1191 ModuleDeclaration := % VAR begint: CARDINAL ; %
1192 % begint := GetTokenNo () %
1193 "MODULE" % M2Error.DefaultInnerModule %
1194 % PushAutoOn %
1195 Ident % StartBuildInnerModule ;
1196 BuildModuleStart (begint) ;
1198 PushAutoOff %
1199 [ Priority ] ";"
1200 { Import
1201 } [ Export
1203 Block % PushAutoOn %
1204 Ident % EndBuildInnerModule %
1205 % PopAuto ; PopAuto ; PopAuto %
1208 Priority := "[" SilentConstExpression "]" =:
1210 Export := "EXPORT" ( "QUALIFIED"
1211 IdentList |
1212 "UNQUALIFIED"
1213 IdentList |
1214 IdentList ) ";" =:
1216 Import := "FROM" Ident "IMPORT" IdentList ";" |
1217 "IMPORT"
1218 IdentList ";" =:
1220 DefinitionModule := % VAR begint, endt: CARDINAL ; %
1221 % begint := GetTokenNo () %
1222 "DEFINITION" % M2Error.DefaultDefinitionModule %
1223 "MODULE" % PushAutoOn %
1224 [ "FOR" string ]
1225 Ident % StartBuildDefFile (begint) ;
1226 P3StartBuildDefModule ;
1227 PushAutoOff %
1229 { Import
1230 } [ Export
1232 { Definition } % endt := GetTokenNo () %
1233 "END" % PushAutoOn %
1234 Ident % EndBuildFile (endt) ;
1235 P3EndBuildDefModule %
1236 "." % PopAuto ; PopAuto ; PopAuto %
1239 Definition := "CONST" { ConstantDeclaration ";" } |
1240 "TYPE"
1241 { Ident ( ";"
1242 | "=" Type Alignment ";" )
1245 "VAR" { VariableDeclaration ";" } |
1246 DefProcedureHeading ";" =:
1248 AsmStatement := 'ASM' [ 'VOLATILE' ] '(' AsmOperands ')' =:
1250 NamedOperand := '[' Ident ']' =:
1252 AsmOperandName := [ NamedOperand ] =:
1254 AsmOperands := AsmOperandName string [ ':' AsmList [ ':' AsmList [ ':' TrashList ] ] ]
1257 AsmList := [ AsmElement ] { ',' AsmElement } =:
1259 AsmElement := string '(' Expression ')'
1262 TrashList := [ string ] { ',' string } =: