]> git.ipfire.org Git - thirdparty/gcc.git/blame_incremental - gcc/m2/gm2-compiler/PCBuild.bnf
Daily bump.
[thirdparty/gcc.git] / gcc / m2 / gm2-compiler / PCBuild.bnf
... / ...
CommitLineData
1--
2-- m2-c.bnf grammar and associated actions for pass C.
3--
4-- Copyright (C) 2001-2025 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.
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 PCBuild begin
23(* output from m2-c.bnf, automatically generated do not edit if these
24 are the top two lines in the file.
25
26Copyright (C) 2001-2025 Free Software Foundation, Inc.
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 PCBuild ;
46
47FROM M2LexBuf IMPORT currentstring, currenttoken, GetToken, InsertToken,
48 InsertTokenAndRewind, GetTokenNo, MakeVirtualTok ;
49
50FROM M2MetaError IMPORT MetaErrorStringT0 ;
51FROM NameKey IMPORT NulName, Name, makekey ;
52FROM DynamicStrings IMPORT String, InitString, KillString, Mark, ConCat, ConCatChar ;
53FROM M2Printf IMPORT printf0 ;
54FROM M2Debug IMPORT Assert ;
55FROM P2SymBuild IMPORT BuildString, BuildNumber ;
56
57FROM M2Reserved IMPORT tokToTok, toktype,
58 NulTok, ImportTok, ExportTok, QualifiedTok, UnQualifiedTok,
59 EqualTok, HashTok, LessGreaterTok, LessTok, LessEqualTok,
60 GreaterTok, GreaterEqualTok, InTok, PlusTok, MinusTok,
61 OrTok, TimesTok, DivTok, DivideTok, ModTok, RemTok,
62 AndTok, AmbersandTok, PeriodPeriodTok, ByTok ;
63
64FROM M2Quads IMPORT Top, PushT, PopT, PushTF, PopTF, PopNothing, OperandT, OperandTok,
65 PushTFA,
66 PushTFn, PopTFn, PushTFtok, PopTtok, PopTFtok, PushTtok, PushTFntok,
67 PushT, PushTF, IsAutoPushOn, PushAutoOff, PushAutoOn, PopAuto,
68 DupFrame, Annotate,
69 BuildTypeForConstructor, BuildConstructor, BuildConstructorEnd,
70 PopConstructor,
71 NextConstructorField, SilentBuildConstructor,
72 PushInConstExpression, PopInConstExpression ;
73
74FROM P3SymBuild IMPORT CheckCanBeImported ;
75
76FROM PCSymBuild IMPORT PCStartBuildProgModule,
77 PCEndBuildProgModule,
78
79 PCStartBuildDefModule,
80 PCEndBuildDefModule,
81
82 PCStartBuildImpModule,
83 PCEndBuildImpModule,
84
85 PCStartBuildInnerModule,
86 PCEndBuildInnerModule,
87
88 PCStartBuildProcedure,
89 PCBuildProcedureHeading,
90 PCEndBuildProcedure,
91 PCEndBuildForward,
92 PCBuildImportOuterModule,
93 PCBuildImportInnerModule,
94 StartDesConst,
95 EndDesConst,
96 BuildRelationConst,
97 BuildBinaryConst,
98 BuildUnaryConst,
99 PushIntegerType,
100 PushStringType,
101 PushConstructorCastType,
102 PushInConstructor,
103 PopInConstructor,
104 PushConstFunctionType,
105 PushConstType,
106 PushConstAttributeType,
107 PushConstAttributePairType,
108 PushRType,
109 CheckNotVar ;
110
111FROM SymbolTable IMPORT MakeGnuAsm, PutGnuAsmVolatile, PutGnuAsm, PutGnuAsmInput,
112 PutGnuAsmOutput, PutGnuAsmTrash, PutGnuAsmVolatile,
113 MakeRegInterface,
114 PutRegInterface,
115 GetSymName, GetType, SkipType,
116 NulSym,
117 StartScope, EndScope,
118 PutIncluded,
119 IsVarParam, IsProcedure, IsDefImp, IsModule,
120 IsRecord, IsProcType,
121 GetCurrentModule, IsInnerModule, IsImported,
122 RequestSym,
123 GetSym, GetLocalSym ;
124
125FROM M2Batch IMPORT IsModuleKnown ;
126
127FROM M2StateCheck IMPORT StateCheck,
128 InitState, PushState, PopState, InclConst, ExclConst,
129 InclConstructor, ExclConstructor,
130 InclConstFunc, CheckQualident ;
131
132IMPORT M2Error ;
133
134
135CONST
136 Debugging = FALSE ;
137 Pass1 = FALSE ;
138
139VAR
140 BlockState: StateCheck ;
141 seenError : BOOLEAN ;
142
143
144PROCEDURE ErrorString (s: String) ;
145BEGIN
146 MetaErrorStringT0 (GetTokenNo (), s) ;
147 seenError := TRUE
148END ErrorString ;
149
150
151PROCEDURE ErrorArray (a: ARRAY OF CHAR) ;
152BEGIN
153 ErrorString (InitString (a))
154END ErrorArray ;
155
156
157PROCEDURE ErrorArrayAt (a: ARRAY OF CHAR; tok: CARDINAL) ;
158BEGIN
159 MetaErrorStringT0 (tok, InitString (a))
160END ErrorArrayAt ;
161
162
163% declaration PCBuild begin
164
165
166(*
167 SyntaxError - after a syntax error we skip all tokens up until we reach
168 a stop symbol.
169*)
170
171PROCEDURE SyntaxError (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
172BEGIN
173 DescribeError ;
174 IF Debugging
175 THEN
176 printf0('\nskipping token *** ')
177 END ;
178 (* --fixme-- this assumes a 32 bit word size. *)
179 WHILE NOT (((ORD(currenttoken)<32) AND (currenttoken IN stopset0)) OR
180 ((ORD(currenttoken)>=32) AND (ORD(currenttoken)<64) AND (currenttoken IN stopset1)) OR
181 ((ORD(currenttoken)>=64) AND (currenttoken IN stopset2)))
182 DO
183 GetToken
184 END ;
185 IF Debugging
186 THEN
187 printf0(' ***\n')
188 END
189END SyntaxError ;
190
191
192(*
193 SyntaxCheck -
194*)
195
196PROCEDURE SyntaxCheck (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
197BEGIN
198 (* --fixme-- this assumes a 32 bit word size. *)
199 IF NOT (((ORD(currenttoken)<32) AND (currenttoken IN stopset0)) OR
200 ((ORD(currenttoken)>=32) AND (ORD(currenttoken)<64) AND (currenttoken IN stopset1)) OR
201 ((ORD(currenttoken)>=64) AND (currenttoken IN stopset2)))
202 THEN
203 SyntaxError(stopset0, stopset1, stopset2)
204 END
205END SyntaxCheck ;
206
207
208(*
209 WarnMissingToken - generates a warning message about a missing token, t.
210*)
211
212PROCEDURE WarnMissingToken (t: toktype) ;
213VAR
214 s0 : SetOfStop0 ;
215 s1 : SetOfStop1 ;
216 s2 : SetOfStop2 ;
217 str: String ;
218BEGIN
219 s0 := SetOfStop0{} ;
220 s1 := SetOfStop1{} ;
221 s2 := SetOfStop2{} ;
222 IF ORD(t)<32
223 THEN
224 s0 := SetOfStop0{t}
225 ELSIF ORD(t)<64
226 THEN
227 s1 := SetOfStop1{t}
228 ELSE
229 s2 := SetOfStop2{t}
230 END ;
231 str := DescribeStop(s0, s1, s2) ;
232
233 str := ConCat(InitString('syntax error,'), Mark(str)) ;
234 MetaErrorStringT0 (GetTokenNo (), str)
235END WarnMissingToken ;
236
237
238(*
239 MissingToken - generates a warning message about a missing token, t.
240*)
241
242PROCEDURE MissingToken (t: toktype) ;
243BEGIN
244 WarnMissingToken(t) ;
245 IF (t#identtok) AND (t#integertok) AND (t#realtok) AND (t#stringtok)
246 THEN
247 IF Debugging
248 THEN
249 printf0('inserting token\n')
250 END ;
251 InsertToken(t)
252 END
253END MissingToken ;
254
255
256(*
257 CheckAndInsert -
258*)
259
260PROCEDURE CheckAndInsert (t: toktype; stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) : BOOLEAN ;
261BEGIN
262 IF ((ORD(t)<32) AND (t IN stopset0)) OR
263 ((ORD(t)>=32) AND (ORD(t)<64) AND (t IN stopset1)) OR
264 ((ORD(t)>=64) AND (t IN stopset2))
265 THEN
266 WarnMissingToken(t) ;
267 InsertTokenAndRewind(t) ;
268 RETURN( TRUE )
269 ELSE
270 RETURN( FALSE )
271 END
272END CheckAndInsert ;
273
274
275(*
276 InStopSet
277*)
278
279PROCEDURE InStopSet (t: toktype; stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) : BOOLEAN ;
280BEGIN
281 IF ((ORD(t)<32) AND (t IN stopset0)) OR
282 ((ORD(t)>=32) AND (ORD(t)<64) AND (t IN stopset1)) OR
283 ((ORD(t)>=64) AND (t IN stopset2))
284 THEN
285 RETURN( TRUE )
286 ELSE
287 RETURN( FALSE )
288 END
289END InStopSet ;
290
291
292(*
293 PeepToken - peep token checks to see whether the stopset is satisfied by currenttoken
294 If it is not then it will insert a token providing the token
295 is one of ; ] ) } . OF END ,
296
297 if the stopset contains <identtok> then we do not insert a token
298*)
299
300PROCEDURE PeepToken (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
301BEGIN
302 (* and again (see above re: ORD)
303 *)
304 IF (NOT (((ORD(currenttoken)<32) AND (currenttoken IN stopset0)) OR
305 ((ORD(currenttoken)>=32) AND (ORD(currenttoken)<64) AND (currenttoken IN stopset1)) OR
306 ((ORD(currenttoken)>=64) AND (currenttoken IN stopset2)))) AND
307 (NOT InStopSet(identtok, stopset0, stopset1, stopset2))
308 THEN
309 (* SyntaxCheck would fail since currentoken is not part of the stopset
310 we check to see whether any of currenttoken might be a commonly omitted token *)
311 IF CheckAndInsert(semicolontok, stopset0, stopset1, stopset2) OR
312 CheckAndInsert(rsbratok, stopset0, stopset1, stopset2) OR
313 CheckAndInsert(rparatok, stopset0, stopset1, stopset2) OR
314 CheckAndInsert(rcbratok, stopset0, stopset1, stopset2) OR
315 CheckAndInsert(periodtok, stopset0, stopset1, stopset2) OR
316 CheckAndInsert(oftok, stopset0, stopset1, stopset2) OR
317 CheckAndInsert(endtok, stopset0, stopset1, stopset2) OR
318 CheckAndInsert(commatok, stopset0, stopset1, stopset2)
319 THEN
320 END
321 END
322END PeepToken ;
323
324
325(*
326 Expect -
327*)
328
329PROCEDURE Expect (t: toktype; stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
330BEGIN
331 IF currenttoken=t
332 THEN
333 GetToken ;
334 IF Pass1
335 THEN
336 PeepToken(stopset0, stopset1, stopset2)
337 END
338 ELSE
339 MissingToken(t)
340 END ;
341 SyntaxCheck(stopset0, stopset1, stopset2)
342END Expect ;
343
344
345(*
346 CompilationUnit - returns TRUE if the input was correct enough to parse
347 in future passes.
348*)
349
350PROCEDURE CompilationUnit () : BOOLEAN ;
351BEGIN
352 seenError := FALSE ;
353 FileUnit(SetOfStop0{eoftok}, SetOfStop1{}, SetOfStop2{}) ;
354 RETURN NOT seenError
355END CompilationUnit ;
356
357
358(*
359 Ident - error checking varient of Ident
360*)
361
362PROCEDURE Ident (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
363BEGIN
364 IF IsAutoPushOn()
365 THEN
366 PushTFtok (makekey (currentstring), identtok, GetTokenNo ())
367 END ;
368 Expect(identtok, stopset0, stopset1, stopset2)
369END Ident ;
370
371
372(*
373 string -
374*)
375
376PROCEDURE string (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
377BEGIN
378 IF IsAutoPushOn()
379 THEN
380 PushTF(makekey(currentstring), stringtok) ;
381 BuildString
382 END ;
383 Expect(stringtok, stopset0, stopset1, stopset2)
384END string ;
385
386
387(*
388 Integer -
389*)
390
391PROCEDURE Integer (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
392BEGIN
393 IF IsAutoPushOn()
394 THEN
395 PushTFtok (makekey(currentstring), integertok, GetTokenNo ()) ;
396 BuildNumber
397 END ;
398 Expect(integertok, stopset0, stopset1, stopset2)
399END Integer ;
400
401
402(*
403 Real -
404*)
405
406PROCEDURE Real (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
407BEGIN
408 IF IsAutoPushOn()
409 THEN
410 PushTFtok (makekey(currentstring), realtok, GetTokenNo ()) ;
411 BuildNumber
412 END ;
413 Expect(realtok, stopset0, stopset1, stopset2)
414END Real ;
415
416
417(*
418 PushTFQualident - push the result of the Qualident
419 to the stack. It checks to see if init
420 is a procedure or proc type and if so
421 it does not push the return type.
422*)
423
424PROCEDURE PushTFQualident (tok, tokstart: CARDINAL;
425 init: CARDINAL) ;
426BEGIN
427 IF tok#tokstart
428 THEN
429 tok := MakeVirtualTok (tokstart, tokstart, tok)
430 END ;
431 IF IsProcedure (init) OR IsProcType (init)
432 THEN
433 PushTtok (init, tok) ;
434 Annotate ("%1s(%1d)||qualident procedure/proctype") ;
435 ELSE
436 Annotate ("%1s(%1d)|%1s(%1d)||qualident|type") ;
437 PushTFtok (init, GetType (init), tok) ;
438 END
439END PushTFQualident ;
440
441
442(*
443 CheckModuleQualident - check to see if the beginning ident of the qualident is an
444 imported module.
445*)
446
447PROCEDURE CheckModuleQualident (stopset0: SetOfStop0;
448 stopset1: SetOfStop1;
449 stopset2: SetOfStop2) ;
450VAR
451 name : Name ;
452 init,
453 nextLevel,
454 tok, tokstart: CARDINAL ;
455BEGIN
456 PopTtok (name, tokstart) ;
457 tok := tokstart ;
458 init := RequestSym (tok, name) ;
459 IF IsImported (GetCurrentModule (), init) AND (IsDefImp (init) OR IsModule (init))
460 THEN
461 WHILE IsDefImp (init) OR IsModule (init) DO
462 Expect (periodtok, stopset0, stopset1, stopset2 + SetOfStop2{identtok}) ;
463 StartScope (init) ;
464 Ident (stopset0, stopset1, stopset2) ;
465 PopTtok (name, tok) ;
466 nextLevel := RequestSym (tok, name) ;
467 EndScope ;
468 CheckCanBeImported (init, nextLevel) ;
469 init := nextLevel
470 END ;
471 PushTFQualident (tok, tokstart, init) ;
472 PutIncluded (init)
473 ELSE
474 PushTFQualident (tok, tokstart, init)
475 END
476END CheckModuleQualident ;
477
478% module PCBuild end
479BEGIN
480 BlockState := InitState ()
481END PCBuild.
482% rules
483error 'ErrorArray' 'ErrorString'
484tokenfunc 'currenttoken'
485
486token '' eoftok -- internal token
487token '+' plustok
488token '-' minustok
489token '*' timestok
490token '/' dividetok
491token ':=' becomestok
492token '&' ambersandtok
493token "." periodtok
494token "," commatok
495token ";" semicolontok
496token '(' lparatok
497token ')' rparatok
498token '[' lsbratok -- left square brackets
499token ']' rsbratok -- right square brackets
500token '{' lcbratok -- left curly brackets
501token '}' rcbratok -- right curly brackets
502token '^' uparrowtok
503token "'" singlequotetok
504token '=' equaltok
505token '#' hashtok
506token '<' lesstok
507token '>' greatertok
508token '<>' lessgreatertok
509token '<=' lessequaltok
510token '>=' greaterequaltok
511token '<*' ldirectivetok
512token '*>' rdirectivetok
513token '..' periodperiodtok
514token ':' colontok
515token '"' doublequotestok
516token '|' bartok
517token 'AND' andtok
518token 'ARRAY' arraytok
519token 'BEGIN' begintok
520token 'BY' bytok
521token 'CASE' casetok
522token 'CONST' consttok
523token 'DEFINITION' definitiontok
524token 'DIV' divtok
525token 'DO' dotok
526token 'ELSE' elsetok
527token 'ELSIF' elsiftok
528token 'END' endtok
529token 'EXCEPT' excepttok
530token 'EXIT' exittok
531token 'EXPORT' exporttok
532token 'FINALLY' finallytok
533token 'FOR' fortok
534token 'FORWARD' forwardtok
535token 'FROM' fromtok
536token 'IF' iftok
537token 'IMPLEMENTATION' implementationtok
538token 'IMPORT' importtok
539token 'IN' intok
540token 'LOOP' looptok
541token 'MOD' modtok
542token 'MODULE' moduletok
543token 'NOT' nottok
544token 'OF' oftok
545token 'OR' ortok
546token 'PACKEDSET' packedsettok
547token 'POINTER' pointertok
548token 'PROCEDURE' proceduretok
549token 'QUALIFIED' qualifiedtok
550token 'UNQUALIFIED' unqualifiedtok
551token 'RECORD' recordtok
552token 'REM' remtok
553token 'REPEAT' repeattok
554token 'RETRY' retrytok
555token 'RETURN' returntok
556token 'SET' settok
557token 'THEN' thentok
558token 'TO' totok
559token 'TYPE' typetok
560token 'UNTIL' untiltok
561token 'VAR' vartok
562token 'WHILE' whiletok
563token 'WITH' withtok
564token 'ASM' asmtok
565token 'VOLATILE' volatiletok
566token '...' periodperiodperiodtok
567token '__DATE__' datetok
568token '__LINE__' linetok
569token '__FILE__' filetok
570token '__ATTRIBUTE__' attributetok
571token '__BUILTIN__' builtintok
572token '__INLINE__' inlinetok
573token 'integer number' integertok
574token 'identifier' identtok
575token 'real number' realtok
576token 'string' stringtok
577
578special Ident first { < identtok > } follow { }
579special Integer first { < integertok > } follow { }
580special Real first { < realtok > } follow { }
581special string first { < stringtok > } follow { }
582
583BNF
584
585-- the following are provided by the module m2flex and also handbuild procedures below
586-- Ident := Letter { ( Letter | Digit ) } =:
587-- Integer := Digit { Digit } | OctalDigit { OctalDigit } ( " B " | " C " ) |
588-- Digit { HexDigit } " H " =:
589-- Real := Digit { Digit } " . " { Digit } [ ScaleFactor ] =:
590-- ScaleFactor := " E " [ ( " + " | " - " ) ] Digit { Digit } =:
591-- HexDigit := Digit | " A " | " B " | " C " | " D " | " E " | " F " =:
592-- Digit := OctalDigit | " 8 " | " 9 " =:
593-- OctalDigit := "0" | "1" | "2" | "3" | "4" | "5" | "6" | "7" =:
594-- String
595
596FileUnit := % PushAutoOff %
597 ( DefinitionModule |
598 ImplementationOrProgramModule ) % PopAuto %
599 =:
600
601ProgramModule := "MODULE" % M2Error.DefaultProgramModule %
602 % PushAutoOn %
603 Ident % PCStartBuildProgModule %
604 % PushAutoOff %
605 [ Priority
606 ]
607 ";"
608 { Import % PCBuildImportOuterModule %
609 }
610 Block % PushAutoOn %
611 Ident % PCEndBuildProgModule %
612 "." % PopAuto ; PopAuto %
613 =:
614
615ImplementationModule := "IMPLEMENTATION" % M2Error.DefaultImplementationModule %
616 "MODULE" % PushAutoOn %
617 Ident % PCStartBuildImpModule %
618 % PushAutoOff %
619 [ Priority
620 ] ";"
621 { Import % PCBuildImportOuterModule %
622 }
623 Block % PushAutoOn %
624
625 Ident % PCEndBuildImpModule %
626 "." % PopAuto ; PopAuto ; PopAuto %
627 =:
628
629ImplementationOrProgramModule := % PushAutoOff %
630 ( ImplementationModule | ProgramModule ) % PopAuto %
631 =:
632
633Number := Integer | Real =:
634
635Qualident := Ident
636 % IF IsAutoPushOn()
637 THEN
638 CheckModuleQualident (stopset0, stopset1, stopset2)
639 ELSE (* just parse qualident *) %
640 { "." Ident } % END %
641 =:
642
643ConstantDeclaration := % VAR top: CARDINAL ; %
644 % InclConst (BlockState) %
645 % top := Top() %
646 % PushAutoOn %
647 ( Ident "=" % StartDesConst %
648 % PushAutoOff %
649 ConstExpression % PopAuto %
650 )
651 % EndDesConst %
652 % PopAuto %
653 % Assert(top=Top()) %
654 % ExclConst (BlockState) %
655 =:
656
657ConstExpression := % VAR top: CARDINAL ; %
658 % top := Top() %
659 % PushInConstExpression %
660 % PushAutoOff %
661 SimpleConstExpr [ Relation SimpleConstExpr % BuildRelationConst %
662 ] % PopAuto %
663 % PopInConstExpression %
664 % Assert(top=Top()) %
665 =:
666
667Relation := "=" % PushT(EqualTok) %
668 | "#" % PushT(HashTok) %
669 | "<>" % PushT(LessGreaterTok) %
670 | "<" % PushT(LessTok) %
671 | "<=" % PushT(LessEqualTok) %
672 | ">" % PushT(GreaterTok) %
673 | ">=" % PushT(GreaterEqualTok) %
674 | "IN" % PushT(InTok) %
675 =:
676
677SimpleConstExpr := % VAR top: CARDINAL ; %
678 % top := Top() %
679 UnaryOrConstTerm { ConstAddOperator ConstTerm % BuildBinaryConst %
680 } % Assert(top=Top()) %
681 =:
682
683UnaryOrConstTerm := "+" % PushT(PlusTok) %
684 ConstTerm % BuildUnaryConst %
685 | "-" % PushT(MinusTok) %
686 ConstTerm % BuildUnaryConst %
687 | ConstTerm
688 =:
689
690ConstAddOperator := "+" % PushT(PlusTok) %
691 | "-" % PushT(MinusTok) %
692 | "OR" % PushT(OrTok) %
693 =:
694
695AddOperator := "+" | "-" | "OR" =:
696
697ConstTerm := % VAR top: CARDINAL ; %
698 % top := Top() %
699 ConstFactor % Assert(top=Top()) %
700 { ConstMulOperator ConstFactor % BuildBinaryConst %
701 % Assert(top=Top()) %
702 } % Assert(top=Top()) %
703 =:
704
705ConstMulOperator := "*" % PushT(TimesTok) %
706 | "/" % PushT(DivideTok) %
707 | "DIV" % PushT(DivTok) %
708 | "MOD" % PushT(ModTok) %
709 | "REM" % PushT(RemTok) %
710 | "AND" % PushT(AndTok) %
711 | "&" % PushT(AmbersandTok) %
712 =:
713
714MulOperator := "*" | "/" | "DIV" | "MOD" | "REM" | "AND" | "&"
715 =:
716
717ConstFactor := ConstNumber | ConstString |
718 ConstSetOrQualidentOrFunction |
719 "(" ConstExpression ")" |
720 "NOT" ConstFactor
721 | ConstAttribute
722 =:
723
724ConstNumber := % PushAutoOn %
725 ( Integer % PushIntegerType %
726 | Real % PushRType %
727 ) % PopAuto %
728 =:
729
730-- to help satisfy LL1
731
732ConstString := % PushAutoOn %
733 string % PushStringType %
734 % PopAuto %
735 =:
736
737ComponentElement := ConstExpression [ ".." ConstExpression ] =:
738
739ComponentValue := ComponentElement [ 'BY' ConstExpression ] =:
740
741ArraySetRecordValue := ComponentValue { ',' % NextConstructorField %
742 ComponentValue } =:
743
744Constructor := '{' % InclConstructor (BlockState) %
745 % CheckQualident (OperandTok (1), BlockState, OperandT (1)) %
746 % PushConstructorCastType %
747 % PushInConstructor %
748 % BuildConstructor (GetTokenNo ()-1) %
749 [ ArraySetRecordValue ] % PopConstructor %
750 '}' % PopInConstructor %
751 % ExclConstructor (BlockState) %
752 =:
753
754ConstructorOrConstActualParameters := Constructor | ConstActualParameters % PushConstFunctionType %
755 % PopNothing (* pop function *) %
756 =:
757
758-- the entry to Constructor
759
760ConstSetOrQualidentOrFunction := % PushAutoOff %
761 % VAR tokpos: CARDINAL ; %
762 % tokpos := GetTokenNo () %
763 (
764 PushQualident
765 ( ConstructorOrConstActualParameters | % CheckQualident (OperandTok (1), BlockState, OperandT (1)) %
766 % PushConstType %
767 % PopNothing %
768 )
769 | % BuildTypeForConstructor (tokpos) %
770 Constructor ) % PopAuto %
771 =:
772
773ConstActualParameters := % PushState (BlockState) %
774 % InclConstFunc (BlockState) %
775 % CheckQualident (OperandTok (1), BlockState, OperandT (1)) %
776 % PushT(0) %
777 "(" [ ConstExpList ] ")"
778 % PopState (BlockState) %
779 =:
780
781ConstExpList := % VAR n: CARDINAL ; %
782 ConstExpression % PopT(n) %
783 % INC(n) %
784 % Assert(n=1) %
785 % PushT(n) %
786 { "," ConstExpression % PopT(n) %
787 % INC(n) %
788 % PushT(n) %
789 } =:
790
791ConstAttribute := % VAR top: CARDINAL ; %
792 % top := Top() %
793 "__ATTRIBUTE__" "__BUILTIN__" "(" "(" % PushAutoOn %
794 ConstAttributeExpression % PopAuto %
795 ")" ")" % Assert(top=Top()) %
796 =:
797
798ConstAttributeExpression :=
799 Ident % PushConstAttributeType %
800 % PopNothing %
801 | "<" Qualident ',' Ident ">" % PushConstAttributePairType %
802 % PopNothing ; PopNothing %
803 =:
804
805ByteAlignment := '<*' AttributeExpression '*>' =:
806
807Alignment := [ ByteAlignment ] =:
808
809TypeDeclaration := Ident "=" Type Alignment =:
810
811Type :=
812 % PushAutoOff %
813 ( SimpleType | ArrayType
814 | RecordType
815 | SetType
816 | PointerType
817 | ProcedureType ) % PopAuto %
818 =:
819
820SimpleType := Qualident [ SubrangeType ] | Enumeration | SubrangeType =:
821
822Enumeration := "(" IdentList ")" =:
823
824IdentList := Ident % VAR
825 on: BOOLEAN ;
826 n : CARDINAL ; %
827 % on := IsAutoPushOn() ;
828 IF on
829 THEN
830 n := 1
831 END %
832 { "," Ident % IF on
833 THEN
834 INC(n)
835 END %
836 } % IF on
837 THEN
838 PushT(n)
839 END %
840 =:
841
842SubrangeType := "[" ConstExpression ".." ConstExpression "]" =:
843
844ArrayType := "ARRAY"
845
846 SimpleType
847 { ","
848 SimpleType
849 } "OF"
850 Type
851 =:
852
853RecordType := "RECORD" [ DefaultRecordAttributes ] FieldListSequence "END" =:
854
855DefaultRecordAttributes := '<*' AttributeExpression '*>' =:
856
857RecordFieldPragma := [ '<*' FieldPragmaExpression
858 { ',' FieldPragmaExpression } '*>' ] =:
859
860FieldPragmaExpression := % PushAutoOff %
861 Ident [ '(' ConstExpression ')' ]
862 % PopAuto %
863 =:
864
865AttributeExpression := % PushAutoOff %
866 Ident '(' ConstExpression ')' % PopAuto %
867 =:
868
869FieldListSequence := FieldListStatement { ";" FieldListStatement } =:
870
871FieldListStatement := [ FieldList ] =:
872
873FieldList := IdentList ":"
874 Type RecordFieldPragma
875 |
876 "CASE"
877 CaseTag "OF"
878 Varient { "|" Varient }
879 [ "ELSE"
880 FieldListSequence
881 ] "END"
882 =:
883
884TagIdent := [ Ident ] =:
885
886CaseTag := TagIdent [":" Qualident ] =:
887
888Varient := [ VarientCaseLabelList ":" FieldListSequence ] =:
889
890VarientCaseLabelList := VarientCaseLabels { "," VarientCaseLabels } =:
891
892VarientCaseLabels := ConstExpression ( ".." ConstExpression
893 | % (* epsilon *) %
894 )
895 =:
896
897--
898-- the following rules are a copy of the ConstExpression ebnf rules but without
899-- any actions all prefixed with Silent.
900-- At present they are only used by CaseLabels, if this continues to be true we
901-- might consider restricting the SilentConstExpression. Eg it makes no sence to allow
902-- String in these circumstances!
903--
904
905SilentConstExpression := % PushAutoOff %
906 SilentSimpleConstExpr
907 [ SilentRelation SilentSimpleConstExpr ] % PopAuto %
908 =:
909
910SilentRelation := "=" | "#" | "<>" | "<" | "<=" | ">" | ">=" | "IN" =:
911
912SilentSimpleConstExpr := SilentUnaryOrConstTerm { SilentAddOperator SilentConstTerm } =:
913
914SilentUnaryOrConstTerm := "+" SilentConstTerm | "-" SilentConstTerm | SilentConstTerm =:
915
916SilentAddOperator := "+" | "-" | "OR" =:
917
918SilentConstTerm := SilentConstFactor { SilentMulOperator SilentConstFactor } =:
919
920SilentMulOperator := "*" | "/" | "DIV" | "MOD" | "REM" | "AND" | "&" =:
921
922SilentConstFactor := Number | SilentConstString | SilentConstSetOrQualidentOrFunction |
923 "(" SilentConstExpression ")" | "NOT" SilentConstFactor
924 | SilentConstAttribute =:
925
926SilentConstString := string =:
927
928SilentConstAttribute := "__ATTRIBUTE__" "__BUILTIN__" "(" "(" SilentConstAttributeExpression ")" ")" =:
929
930SilentConstAttributeExpression := Ident | "<" Ident ',' SilentConstString ">" =:
931
932SilentComponentElement := SilentConstExpression [ ".." SilentConstExpression ] =:
933
934SilentComponentValue := SilentComponentElement [ 'BY' SilentConstExpression ] =:
935
936SilentArraySetRecordValue := SilentComponentValue { ',' SilentComponentValue } =:
937
938SilentConstructor := '{' % SilentBuildConstructor %
939 [ SilentArraySetRecordValue ] '}' =:
940
941SilentConstSetOrQualidentOrFunction := SilentConstructor | Qualident
942 [ SilentConstructor | SilentActualParameters ] =:
943
944SilentActualParameters := "(" [ SilentExpList ] ")" =:
945
946SilentExpList := SilentConstExpression { "," SilentConstExpression } =:
947
948-- end of the Silent constant rules
949
950SetType := ( "SET" | "PACKEDSET" ) "OF" SimpleType =:
951
952PointerType := "POINTER" "TO"
953 Type
954 =:
955
956ProcedureType := "PROCEDURE"
957 [ FormalTypeList ] =:
958
959FormalTypeList := "(" ( ")" FormalReturn |
960 ProcedureParameters ")" FormalReturn ) =:
961
962FormalReturn := [ ":" OptReturnType ] =:
963
964OptReturnType := "[" Qualident "]" | Qualident =:
965
966ProcedureParameters := ProcedureParameter
967 { "," ProcedureParameter } =:
968
969ProcedureParameter := "..." | "VAR" FormalType | FormalType =:
970
971
972VarIdent := Ident [ "[" ConstExpression "]" ]
973 =:
974
975VarIdentList := VarIdent { "," VarIdent }
976 =:
977
978VariableDeclaration := VarIdentList ":" Type Alignment
979 =:
980
981Designator := Qualident { SubDesignator } =:
982
983SubDesignator := "." Ident | "[" ArrayExpList "]" | "^"
984 =:
985
986ArrayExpList := Expression { "," Expression } =:
987
988ExpList := Expression { "," Expression } =:
989
990Expression := SimpleExpression [ SilentRelation SimpleExpression ]
991 =:
992
993SimpleExpression := UnaryOrTerm { AddOperator Term } =:
994
995UnaryOrTerm := "+" Term | "-" Term | Term =:
996
997Term := Factor { MulOperator Factor } =:
998
999Factor := Number | string | SetOrDesignatorOrFunction |
1000 "(" Expression ")" | "NOT" ( Factor | ConstAttribute ) =:
1001
1002PushQualident := % VAR name : Name ;
1003 init, ip1 : CARDINAL ;
1004 tok, tokstart: CARDINAL ; %
1005 % PushAutoOn %
1006 Ident % IF IsAutoPushOn()
1007 THEN
1008 PopTtok (name, tokstart) ;
1009 tok := tokstart ;
1010 init := GetSym (name) ;
1011 IF init=NulSym
1012 THEN
1013 PushTFntok (NulSym, NulSym, name, tok)
1014 ELSE
1015 WHILE IsDefImp (init) OR IsModule (init) DO
1016 IF currenttoken # periodtok
1017 THEN
1018 ErrorArrayAt ("expecting '.' after module in the construction of a qualident", tok) ;
1019 IF tok#tokstart
1020 THEN
1021 tok := MakeVirtualTok (tokstart, tokstart, tok)
1022 END ;
1023 PushTtok (init, tok) ;
1024 PopAuto ;
1025 RETURN
1026 ELSE
1027 Expect (periodtok, stopset0, stopset1, stopset2 + SetOfStop2{identtok}) ;
1028 StartScope (init) ;
1029 Ident (stopset0, stopset1, stopset2) ;
1030 PopTtok (name, tok) ;
1031 ip1 := GetSym (name) ;
1032 IF ip1 = NulSym
1033 THEN
1034 ErrorArrayAt ("unknown ident in the construction of a qualident", tok) ;
1035 EndScope ;
1036 IF tok#tokstart
1037 THEN
1038 tok := MakeVirtualTok (tokstart, tokstart, tok)
1039 END ;
1040 PushTFntok (NulSym, NulSym, name, tok) ;
1041 PopAuto ;
1042 RETURN
1043 ELSE
1044 PutIncluded (ip1)
1045 END ;
1046 EndScope ;
1047 CheckCanBeImported (init, ip1) ;
1048 init := ip1
1049 END
1050 END ;
1051 IF tok#tokstart
1052 THEN
1053 tok := MakeVirtualTok (tokstart, tokstart, tok)
1054 END ;
1055 IF IsProcedure (init) OR IsProcType (init)
1056 THEN
1057 PushTtok (init, tok)
1058 ELSE
1059 PushTFtok (init, GetType(init), tok)
1060 END
1061 END
1062 ELSE %
1063 { "." Ident } % END %
1064 % PopAuto %
1065 =:
1066
1067ConstructorOrSimpleDes := Constructor | % PopNothing %
1068 SimpleDes [ ActualParameters ]
1069 =:
1070
1071SetOrDesignatorOrFunction := % VAR tokpos: CARDINAL ; %
1072 % tokpos := GetTokenNo () %
1073 % PushAutoOff %
1074 (
1075 PushQualident
1076 ( ConstructorOrSimpleDes | % PopNothing %
1077 )
1078 |
1079 % BuildTypeForConstructor (tokpos) %
1080 Constructor
1081 ) % PopAuto %
1082 =:
1083
1084-- SimpleDes := { "." Ident | "[" ExpList "]" | "^" } =:
1085SimpleDes := { SubDesignator } =:
1086
1087ActualParameters := "(" [ ExpList ] ")" =:
1088
1089ExitStatement := "EXIT" =:
1090
1091ReturnStatement := "RETURN" [ Expression ] =:
1092
1093Statement := % PushAutoOff %
1094 [ AssignmentOrProcedureCall | IfStatement | CaseStatement |
1095 WhileStatement | RepeatStatement | LoopStatement |
1096 ForStatement | WithStatement | AsmStatement |
1097 ExitStatement | ReturnStatement | RetryStatement
1098 ] % PopAuto ; %
1099 =:
1100
1101RetryStatement := "RETRY" =:
1102
1103AssignmentOrProcedureCall := % VAR top: CARDINAL ; %
1104 % top := Top() %
1105 Designator ( ":=" Expression |
1106 ActualParameters | % (* epsilon *) %
1107 ) % Assert(top=Top()) %
1108 =:
1109
1110-- these two break LL1 as both start with a Designator
1111-- ProcedureCall := Designator [ ActualParameters ] =:
1112-- Assignment := Designator ":=" Expression =:
1113
1114StatementSequence := % VAR top: CARDINAL ; %
1115 % top := Top() %
1116 Statement % Assert(top=Top()) %
1117 { ";"
1118 Statement % Assert(top=Top()) %
1119 }
1120 =:
1121
1122IfStatement := "IF" Expression "THEN"
1123 StatementSequence
1124 { "ELSIF" Expression "THEN" StatementSequence
1125 }
1126 [ "ELSE" StatementSequence ] "END"
1127 =:
1128
1129CaseStatement := "CASE" Expression "OF" Case { "|" Case }
1130 CaseEndStatement
1131 =:
1132
1133CaseEndStatement := "END" | "ELSE" StatementSequence "END"
1134 =:
1135
1136Case := [ CaseLabelList ":" StatementSequence ]
1137 =:
1138
1139CaseLabelList := CaseLabels { "," CaseLabels } =:
1140
1141CaseLabels := ConstExpression [ ".." ConstExpression ] =:
1142
1143WhileStatement := "WHILE" Expression "DO" StatementSequence "END" =:
1144
1145RepeatStatement := "REPEAT" StatementSequence "UNTIL" Expression =:
1146
1147ForStatement := "FOR" Ident ":=" Expression "TO" Expression
1148 [ "BY" ConstExpression ] "DO"
1149 StatementSequence
1150 "END"
1151 =:
1152
1153LoopStatement := "LOOP" StatementSequence "END" =:
1154
1155WithStatement := "WITH" Designator "DO"
1156 StatementSequence
1157 "END"
1158 =:
1159
1160ProcedureDeclaration := % VAR top: CARDINAL ; %
1161 % top := Top () %
1162 ProcedureHeading ";" PostProcedureHeading % Assert (top = Top ()) %
1163 =:
1164
1165PostProcedureHeading := ProperProcedure | ForwardDeclaration =:
1166
1167ForwardDeclaration := "FORWARD" % PCEndBuildForward %
1168 =:
1169
1170ProperProcedure := ProcedureBlock % PushAutoOn %
1171 Ident % PCEndBuildProcedure %
1172 % PopAuto %
1173 =:
1174
1175DefineBuiltinProcedure := [ "__ATTRIBUTE__" "__BUILTIN__"
1176 "(" "(" % PushAutoOff %
1177 Ident % PopAuto %
1178 ")" ")" | "__INLINE__" ]
1179 =:
1180
1181ProcedureHeading := "PROCEDURE" % M2Error.DefaultProcedure %
1182 % PushAutoOn %
1183 DefineBuiltinProcedure
1184 ( Ident
1185 % PCStartBuildProcedure %
1186 % PushAutoOff %
1187 [ FormalParameters ] AttributeNoReturn
1188 % PCBuildProcedureHeading %
1189 % PopAuto %
1190 ) % PopAuto %
1191 =:
1192
1193Builtin := [ "__BUILTIN__" | "__INLINE__" ] =:
1194
1195DefProcedureHeading := "PROCEDURE" % M2Error.DefaultProcedure %
1196 % PushAutoOn %
1197 Builtin
1198 ( Ident
1199 % PCStartBuildProcedure %
1200 % PushAutoOff %
1201 [ DefFormalParameters ] AttributeNoReturn
1202 % PCBuildProcedureHeading %
1203 % PopAuto %
1204 ) % PopAuto %
1205 % M2Error.LeaveErrorScope %
1206 =:
1207
1208AttributeNoReturn := [ "<*" Ident "*>" ] =:
1209
1210AttributeUnused := [ "<*" Ident "*>" ] =:
1211
1212-- introduced procedure block so we can produce more informative
1213-- error messages
1214
1215ProcedureBlock := % VAR top: CARDINAL ; %
1216 % top := Top() %
1217 { Declaration % Assert(top=Top()) %
1218 } [ "BEGIN" ProcedureBlockBody % Assert(top=Top()) %
1219 ] "END" % Assert(top=Top()) %
1220 =:
1221
1222Block := % VAR top: CARDINAL ; %
1223 % top := Top() %
1224 { Declaration } InitialBlock FinalBlock
1225 "END" % Assert(top=Top()) %
1226 =:
1227
1228InitialBlock := [ "BEGIN" InitialBlockBody ] =:
1229
1230FinalBlock := [ "FINALLY" FinalBlockBody ] =:
1231
1232InitialBlockBody := NormalPart [ "EXCEPT" ExceptionalPart ] =:
1233
1234FinalBlockBody := NormalPart [ "EXCEPT" ExceptionalPart ] =:
1235
1236ProcedureBlockBody := NormalPart [ "EXCEPT" ExceptionalPart ] =:
1237
1238NormalPart := StatementSequence =:
1239
1240ExceptionalPart := StatementSequence =:
1241
1242Declaration := "CONST" { ConstantDeclaration ";" } |
1243 "TYPE" { TypeDeclaration ";" } |
1244 "VAR" { VariableDeclaration ";" } |
1245 ProcedureDeclaration ";" |
1246 ModuleDeclaration ";" =:
1247
1248DefFormalParameters := "(" [ DefMultiFPSection ] ")" FormalReturn =:
1249
1250DefMultiFPSection := DefExtendedFP |
1251 FPSection [ ";" DefMultiFPSection ] =:
1252
1253FormalParameters := "(" [ MultiFPSection ] ")" FormalReturn =:
1254
1255MultiFPSection := ExtendedFP |
1256 FPSection [ ";" MultiFPSection ] =:
1257
1258FPSection := NonVarFPSection | VarFPSection =:
1259
1260DefExtendedFP := DefOptArg | "..." =:
1261
1262ExtendedFP := OptArg | "..." =:
1263
1264VarFPSection := "VAR" IdentList ":" FormalType [ AttributeUnused ] =:
1265
1266NonVarFPSection := IdentList ":" FormalType [ AttributeUnused ] =:
1267
1268OptArg := "[" Ident ":" FormalType [ "=" ConstExpression ] "]" =:
1269
1270DefOptArg := "[" Ident ":" FormalType "=" ConstExpression "]" =:
1271
1272FormalType := { "ARRAY" "OF" } Qualident =:
1273
1274ModuleDeclaration := "MODULE" % M2Error.DefaultInnerModule %
1275 % PushAutoOn %
1276 Ident % PCStartBuildInnerModule %
1277 % PushAutoOff %
1278 [ Priority ] ";"
1279 { Import % PCBuildImportInnerModule %
1280 } [ Export
1281 ]
1282 Block % PushAutoOn %
1283 Ident % PCEndBuildInnerModule %
1284 % PopAuto ; PopAuto ; PopAuto %
1285 =:
1286
1287Priority := "[" ConstExpression "]" =:
1288
1289Export := "EXPORT" ( "QUALIFIED"
1290 IdentList |
1291 "UNQUALIFIED"
1292 IdentList |
1293 IdentList ) ";" =:
1294
1295Import := % PushAutoOn %
1296 ( "FROM" Ident "IMPORT" IdentList ";" |
1297 "IMPORT" % PushT(ImportTok)
1298 (* determines whether Ident or Module *) %
1299 IdentList ";" ) % PopAuto %
1300 =:
1301
1302DefinitionModule := "DEFINITION" % M2Error.DefaultDefinitionModule %
1303 "MODULE" % PushAutoOn %
1304 [ "FOR" string ]
1305 Ident % PCStartBuildDefModule ;
1306 PushAutoOff %
1307 ";"
1308 { Import % PCBuildImportOuterModule %
1309 } [ Export
1310 ]
1311 { Definition }
1312 "END" % PushAutoOn %
1313 Ident % PCEndBuildDefModule %
1314 "." % PopAuto ; PopAuto ; PopAuto %
1315 =:
1316
1317Definition := "CONST" { ConstantDeclaration ";" } |
1318 "TYPE"
1319 { Ident ( ";"
1320 | "=" Type Alignment ";" )
1321 }
1322 |
1323 "VAR" { VariableDeclaration ";" } |
1324 DefProcedureHeading ";" =:
1325
1326AsmStatement := 'ASM' [ 'VOLATILE' ] '(' AsmOperands ')' =:
1327
1328NamedOperand := '[' Ident ']' =:
1329
1330AsmOperandName := [ NamedOperand ] =:
1331
1332AsmOperands := ConstExpression [ ':' AsmList [ ':' AsmList [ ':' TrashList ] ] ]
1333 =:
1334
1335AsmList := [ AsmElement ] { ',' AsmElement } =:
1336
1337AsmElement := AsmOperandName ConstExpression '(' Expression ')'
1338 =:
1339
1340TrashList := [ ConstExpression ] { ',' ConstExpression } =:
1341
1342FNB