]> git.ipfire.org Git - thirdparty/gcc.git/blob - gcc/m2/gm2-compiler/PCBuild.bnf
ddbe2f1b2fc076e86d8f9001134c894c7ae21441
[thirdparty/gcc.git] / gcc / m2 / gm2-compiler / PCBuild.bnf
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
26 Copyright (C) 2001-2025 Free Software Foundation, Inc.
27 Contributed by Gaius Mulley <gaius.mulley@southwales.ac.uk>.
28
29 This file is part of GNU Modula-2.
30
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.
35
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.
40
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/>. *)
44
45 IMPLEMENTATION MODULE PCBuild ;
46
47 FROM M2LexBuf IMPORT currentstring, currenttoken, GetToken, InsertToken,
48 InsertTokenAndRewind, GetTokenNo, MakeVirtualTok ;
49
50 FROM M2MetaError IMPORT MetaErrorStringT0 ;
51 FROM NameKey IMPORT NulName, Name, makekey ;
52 FROM DynamicStrings IMPORT String, InitString, KillString, Mark, ConCat, ConCatChar ;
53 FROM M2Printf IMPORT printf0 ;
54 FROM M2Debug IMPORT Assert ;
55 FROM P2SymBuild IMPORT BuildString, BuildNumber ;
56
57 FROM 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
64 FROM 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
74 FROM P3SymBuild IMPORT CheckCanBeImported ;
75
76 FROM 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
111 FROM 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
125 FROM M2Batch IMPORT IsModuleKnown ;
126
127 FROM M2StateCheck IMPORT StateCheck,
128 InitState, PushState, PopState, InclConst, ExclConst,
129 InclConstructor, ExclConstructor,
130 InclConstFunc, CheckQualident ;
131
132 IMPORT M2Error ;
133
134
135 CONST
136 Debugging = FALSE ;
137 Pass1 = FALSE ;
138
139 VAR
140 BlockState: StateCheck ;
141 seenError : BOOLEAN ;
142
143
144 PROCEDURE ErrorString (s: String) ;
145 BEGIN
146 MetaErrorStringT0 (GetTokenNo (), s) ;
147 seenError := TRUE
148 END ErrorString ;
149
150
151 PROCEDURE ErrorArray (a: ARRAY OF CHAR) ;
152 BEGIN
153 ErrorString (InitString (a))
154 END ErrorArray ;
155
156
157 PROCEDURE ErrorArrayAt (a: ARRAY OF CHAR; tok: CARDINAL) ;
158 BEGIN
159 MetaErrorStringT0 (tok, InitString (a))
160 END 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
171 PROCEDURE SyntaxError (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
172 BEGIN
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
189 END SyntaxError ;
190
191
192 (*
193 SyntaxCheck -
194 *)
195
196 PROCEDURE SyntaxCheck (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
197 BEGIN
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
205 END SyntaxCheck ;
206
207
208 (*
209 WarnMissingToken - generates a warning message about a missing token, t.
210 *)
211
212 PROCEDURE WarnMissingToken (t: toktype) ;
213 VAR
214 s0 : SetOfStop0 ;
215 s1 : SetOfStop1 ;
216 s2 : SetOfStop2 ;
217 str: String ;
218 BEGIN
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)
235 END WarnMissingToken ;
236
237
238 (*
239 MissingToken - generates a warning message about a missing token, t.
240 *)
241
242 PROCEDURE MissingToken (t: toktype) ;
243 BEGIN
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
253 END MissingToken ;
254
255
256 (*
257 CheckAndInsert -
258 *)
259
260 PROCEDURE CheckAndInsert (t: toktype; stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) : BOOLEAN ;
261 BEGIN
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
272 END CheckAndInsert ;
273
274
275 (*
276 InStopSet
277 *)
278
279 PROCEDURE InStopSet (t: toktype; stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) : BOOLEAN ;
280 BEGIN
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
289 END 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
300 PROCEDURE PeepToken (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
301 BEGIN
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
322 END PeepToken ;
323
324
325 (*
326 Expect -
327 *)
328
329 PROCEDURE Expect (t: toktype; stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
330 BEGIN
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)
342 END Expect ;
343
344
345 (*
346 CompilationUnit - returns TRUE if the input was correct enough to parse
347 in future passes.
348 *)
349
350 PROCEDURE CompilationUnit () : BOOLEAN ;
351 BEGIN
352 seenError := FALSE ;
353 FileUnit(SetOfStop0{eoftok}, SetOfStop1{}, SetOfStop2{}) ;
354 RETURN NOT seenError
355 END CompilationUnit ;
356
357
358 (*
359 Ident - error checking varient of Ident
360 *)
361
362 PROCEDURE Ident (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
363 BEGIN
364 IF IsAutoPushOn()
365 THEN
366 PushTFtok (makekey (currentstring), identtok, GetTokenNo ())
367 END ;
368 Expect(identtok, stopset0, stopset1, stopset2)
369 END Ident ;
370
371
372 (*
373 string -
374 *)
375
376 PROCEDURE string (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
377 BEGIN
378 IF IsAutoPushOn()
379 THEN
380 PushTF(makekey(currentstring), stringtok) ;
381 BuildString
382 END ;
383 Expect(stringtok, stopset0, stopset1, stopset2)
384 END string ;
385
386
387 (*
388 Integer -
389 *)
390
391 PROCEDURE Integer (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
392 BEGIN
393 IF IsAutoPushOn()
394 THEN
395 PushTFtok (makekey(currentstring), integertok, GetTokenNo ()) ;
396 BuildNumber
397 END ;
398 Expect(integertok, stopset0, stopset1, stopset2)
399 END Integer ;
400
401
402 (*
403 Real -
404 *)
405
406 PROCEDURE Real (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
407 BEGIN
408 IF IsAutoPushOn()
409 THEN
410 PushTFtok (makekey(currentstring), realtok, GetTokenNo ()) ;
411 BuildNumber
412 END ;
413 Expect(realtok, stopset0, stopset1, stopset2)
414 END 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
424 PROCEDURE PushTFQualident (tok, tokstart: CARDINAL;
425 init: CARDINAL) ;
426 BEGIN
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
439 END PushTFQualident ;
440
441
442 (*
443 CheckModuleQualident - check to see if the beginning ident of the qualident is an
444 imported module.
445 *)
446
447 PROCEDURE CheckModuleQualident (stopset0: SetOfStop0;
448 stopset1: SetOfStop1;
449 stopset2: SetOfStop2) ;
450 VAR
451 name : Name ;
452 init,
453 nextLevel,
454 tok, tokstart: CARDINAL ;
455 BEGIN
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
476 END CheckModuleQualident ;
477
478 % module PCBuild end
479 BEGIN
480 BlockState := InitState ()
481 END PCBuild.
482 % rules
483 error 'ErrorArray' 'ErrorString'
484 tokenfunc 'currenttoken'
485
486 token '' eoftok -- internal token
487 token '+' plustok
488 token '-' minustok
489 token '*' timestok
490 token '/' dividetok
491 token ':=' becomestok
492 token '&' ambersandtok
493 token "." periodtok
494 token "," commatok
495 token ";" semicolontok
496 token '(' lparatok
497 token ')' rparatok
498 token '[' lsbratok -- left square brackets
499 token ']' rsbratok -- right square brackets
500 token '{' lcbratok -- left curly brackets
501 token '}' rcbratok -- right curly brackets
502 token '^' uparrowtok
503 token "'" singlequotetok
504 token '=' equaltok
505 token '#' hashtok
506 token '<' lesstok
507 token '>' greatertok
508 token '<>' lessgreatertok
509 token '<=' lessequaltok
510 token '>=' greaterequaltok
511 token '<*' ldirectivetok
512 token '*>' rdirectivetok
513 token '..' periodperiodtok
514 token ':' colontok
515 token '"' doublequotestok
516 token '|' bartok
517 token 'AND' andtok
518 token 'ARRAY' arraytok
519 token 'BEGIN' begintok
520 token 'BY' bytok
521 token 'CASE' casetok
522 token 'CONST' consttok
523 token 'DEFINITION' definitiontok
524 token 'DIV' divtok
525 token 'DO' dotok
526 token 'ELSE' elsetok
527 token 'ELSIF' elsiftok
528 token 'END' endtok
529 token 'EXCEPT' excepttok
530 token 'EXIT' exittok
531 token 'EXPORT' exporttok
532 token 'FINALLY' finallytok
533 token 'FOR' fortok
534 token 'FORWARD' forwardtok
535 token 'FROM' fromtok
536 token 'IF' iftok
537 token 'IMPLEMENTATION' implementationtok
538 token 'IMPORT' importtok
539 token 'IN' intok
540 token 'LOOP' looptok
541 token 'MOD' modtok
542 token 'MODULE' moduletok
543 token 'NOT' nottok
544 token 'OF' oftok
545 token 'OR' ortok
546 token 'PACKEDSET' packedsettok
547 token 'POINTER' pointertok
548 token 'PROCEDURE' proceduretok
549 token 'QUALIFIED' qualifiedtok
550 token 'UNQUALIFIED' unqualifiedtok
551 token 'RECORD' recordtok
552 token 'REM' remtok
553 token 'REPEAT' repeattok
554 token 'RETRY' retrytok
555 token 'RETURN' returntok
556 token 'SET' settok
557 token 'THEN' thentok
558 token 'TO' totok
559 token 'TYPE' typetok
560 token 'UNTIL' untiltok
561 token 'VAR' vartok
562 token 'WHILE' whiletok
563 token 'WITH' withtok
564 token 'ASM' asmtok
565 token 'VOLATILE' volatiletok
566 token '...' periodperiodperiodtok
567 token '__DATE__' datetok
568 token '__LINE__' linetok
569 token '__FILE__' filetok
570 token '__ATTRIBUTE__' attributetok
571 token '__BUILTIN__' builtintok
572 token '__INLINE__' inlinetok
573 token 'integer number' integertok
574 token 'identifier' identtok
575 token 'real number' realtok
576 token 'string' stringtok
577
578 special Ident first { < identtok > } follow { }
579 special Integer first { < integertok > } follow { }
580 special Real first { < realtok > } follow { }
581 special string first { < stringtok > } follow { }
582
583 BNF
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
596 FileUnit := % PushAutoOff %
597 ( DefinitionModule |
598 ImplementationOrProgramModule ) % PopAuto %
599 =:
600
601 ProgramModule := "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
615 ImplementationModule := "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
629 ImplementationOrProgramModule := % PushAutoOff %
630 ( ImplementationModule | ProgramModule ) % PopAuto %
631 =:
632
633 Number := Integer | Real =:
634
635 Qualident := Ident
636 % IF IsAutoPushOn()
637 THEN
638 CheckModuleQualident (stopset0, stopset1, stopset2)
639 ELSE (* just parse qualident *) %
640 { "." Ident } % END %
641 =:
642
643 ConstantDeclaration := % 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
657 ConstExpression := % 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
667 Relation := "=" % 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
677 SimpleConstExpr := % VAR top: CARDINAL ; %
678 % top := Top() %
679 UnaryOrConstTerm { ConstAddOperator ConstTerm % BuildBinaryConst %
680 } % Assert(top=Top()) %
681 =:
682
683 UnaryOrConstTerm := "+" % PushT(PlusTok) %
684 ConstTerm % BuildUnaryConst %
685 | "-" % PushT(MinusTok) %
686 ConstTerm % BuildUnaryConst %
687 | ConstTerm
688 =:
689
690 ConstAddOperator := "+" % PushT(PlusTok) %
691 | "-" % PushT(MinusTok) %
692 | "OR" % PushT(OrTok) %
693 =:
694
695 AddOperator := "+" | "-" | "OR" =:
696
697 ConstTerm := % 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
705 ConstMulOperator := "*" % 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
714 MulOperator := "*" | "/" | "DIV" | "MOD" | "REM" | "AND" | "&"
715 =:
716
717 ConstFactor := ConstNumber | ConstString |
718 ConstSetOrQualidentOrFunction |
719 "(" ConstExpression ")" |
720 "NOT" ConstFactor
721 | ConstAttribute
722 =:
723
724 ConstNumber := % PushAutoOn %
725 ( Integer % PushIntegerType %
726 | Real % PushRType %
727 ) % PopAuto %
728 =:
729
730 -- to help satisfy LL1
731
732 ConstString := % PushAutoOn %
733 string % PushStringType %
734 % PopAuto %
735 =:
736
737 ComponentElement := ConstExpression [ ".." ConstExpression ] =:
738
739 ComponentValue := ComponentElement [ 'BY' ConstExpression ] =:
740
741 ArraySetRecordValue := ComponentValue { ',' % NextConstructorField %
742 ComponentValue } =:
743
744 Constructor := '{' % 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
754 ConstructorOrConstActualParameters := Constructor | ConstActualParameters % PushConstFunctionType %
755 % PopNothing (* pop function *) %
756 =:
757
758 -- the entry to Constructor
759
760 ConstSetOrQualidentOrFunction := % 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
773 ConstActualParameters := % PushState (BlockState) %
774 % InclConstFunc (BlockState) %
775 % CheckQualident (OperandTok (1), BlockState, OperandT (1)) %
776 % PushT(0) %
777 "(" [ ConstExpList ] ")"
778 % PopState (BlockState) %
779 =:
780
781 ConstExpList := % 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
791 ConstAttribute := % VAR top: CARDINAL ; %
792 % top := Top() %
793 "__ATTRIBUTE__" "__BUILTIN__" "(" "(" % PushAutoOn %
794 ConstAttributeExpression % PopAuto %
795 ")" ")" % Assert(top=Top()) %
796 =:
797
798 ConstAttributeExpression :=
799 Ident % PushConstAttributeType %
800 % PopNothing %
801 | "<" Qualident ',' Ident ">" % PushConstAttributePairType %
802 % PopNothing ; PopNothing %
803 =:
804
805 ByteAlignment := '<*' AttributeExpression '*>' =:
806
807 Alignment := [ ByteAlignment ] =:
808
809 TypeDeclaration := Ident "=" Type Alignment =:
810
811 Type :=
812 % PushAutoOff %
813 ( SimpleType | ArrayType
814 | RecordType
815 | SetType
816 | PointerType
817 | ProcedureType ) % PopAuto %
818 =:
819
820 SimpleType := Qualident [ SubrangeType ] | Enumeration | SubrangeType =:
821
822 Enumeration := "(" IdentList ")" =:
823
824 IdentList := 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
842 SubrangeType := "[" ConstExpression ".." ConstExpression "]" =:
843
844 ArrayType := "ARRAY"
845
846 SimpleType
847 { ","
848 SimpleType
849 } "OF"
850 Type
851 =:
852
853 RecordType := "RECORD" [ DefaultRecordAttributes ] FieldListSequence "END" =:
854
855 DefaultRecordAttributes := '<*' AttributeExpression '*>' =:
856
857 RecordFieldPragma := [ '<*' FieldPragmaExpression
858 { ',' FieldPragmaExpression } '*>' ] =:
859
860 FieldPragmaExpression := % PushAutoOff %
861 Ident [ '(' ConstExpression ')' ]
862 % PopAuto %
863 =:
864
865 AttributeExpression := % PushAutoOff %
866 Ident '(' ConstExpression ')' % PopAuto %
867 =:
868
869 FieldListSequence := FieldListStatement { ";" FieldListStatement } =:
870
871 FieldListStatement := [ FieldList ] =:
872
873 FieldList := IdentList ":"
874 Type RecordFieldPragma
875 |
876 "CASE"
877 CaseTag "OF"
878 Varient { "|" Varient }
879 [ "ELSE"
880 FieldListSequence
881 ] "END"
882 =:
883
884 TagIdent := [ Ident ] =:
885
886 CaseTag := TagIdent [":" Qualident ] =:
887
888 Varient := [ VarientCaseLabelList ":" FieldListSequence ] =:
889
890 VarientCaseLabelList := VarientCaseLabels { "," VarientCaseLabels } =:
891
892 VarientCaseLabels := 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
905 SilentConstExpression := % PushAutoOff %
906 SilentSimpleConstExpr
907 [ SilentRelation SilentSimpleConstExpr ] % PopAuto %
908 =:
909
910 SilentRelation := "=" | "#" | "<>" | "<" | "<=" | ">" | ">=" | "IN" =:
911
912 SilentSimpleConstExpr := SilentUnaryOrConstTerm { SilentAddOperator SilentConstTerm } =:
913
914 SilentUnaryOrConstTerm := "+" SilentConstTerm | "-" SilentConstTerm | SilentConstTerm =:
915
916 SilentAddOperator := "+" | "-" | "OR" =:
917
918 SilentConstTerm := SilentConstFactor { SilentMulOperator SilentConstFactor } =:
919
920 SilentMulOperator := "*" | "/" | "DIV" | "MOD" | "REM" | "AND" | "&" =:
921
922 SilentConstFactor := Number | SilentConstString | SilentConstSetOrQualidentOrFunction |
923 "(" SilentConstExpression ")" | "NOT" SilentConstFactor
924 | SilentConstAttribute =:
925
926 SilentConstString := string =:
927
928 SilentConstAttribute := "__ATTRIBUTE__" "__BUILTIN__" "(" "(" SilentConstAttributeExpression ")" ")" =:
929
930 SilentConstAttributeExpression := Ident | "<" Ident ',' SilentConstString ">" =:
931
932 SilentComponentElement := SilentConstExpression [ ".." SilentConstExpression ] =:
933
934 SilentComponentValue := SilentComponentElement [ 'BY' SilentConstExpression ] =:
935
936 SilentArraySetRecordValue := SilentComponentValue { ',' SilentComponentValue } =:
937
938 SilentConstructor := '{' % SilentBuildConstructor %
939 [ SilentArraySetRecordValue ] '}' =:
940
941 SilentConstSetOrQualidentOrFunction := SilentConstructor | Qualident
942 [ SilentConstructor | SilentActualParameters ] =:
943
944 SilentActualParameters := "(" [ SilentExpList ] ")" =:
945
946 SilentExpList := SilentConstExpression { "," SilentConstExpression } =:
947
948 -- end of the Silent constant rules
949
950 SetType := ( "SET" | "PACKEDSET" ) "OF" SimpleType =:
951
952 PointerType := "POINTER" "TO"
953 Type
954 =:
955
956 ProcedureType := "PROCEDURE"
957 [ FormalTypeList ] =:
958
959 FormalTypeList := "(" ( ")" FormalReturn |
960 ProcedureParameters ")" FormalReturn ) =:
961
962 FormalReturn := [ ":" OptReturnType ] =:
963
964 OptReturnType := "[" Qualident "]" | Qualident =:
965
966 ProcedureParameters := ProcedureParameter
967 { "," ProcedureParameter } =:
968
969 ProcedureParameter := "..." | "VAR" FormalType | FormalType =:
970
971
972 VarIdent := Ident [ "[" ConstExpression "]" ]
973 =:
974
975 VarIdentList := VarIdent { "," VarIdent }
976 =:
977
978 VariableDeclaration := VarIdentList ":" Type Alignment
979 =:
980
981 Designator := Qualident { SubDesignator } =:
982
983 SubDesignator := "." Ident | "[" ArrayExpList "]" | "^"
984 =:
985
986 ArrayExpList := Expression { "," Expression } =:
987
988 ExpList := Expression { "," Expression } =:
989
990 Expression := SimpleExpression [ SilentRelation SimpleExpression ]
991 =:
992
993 SimpleExpression := UnaryOrTerm { AddOperator Term } =:
994
995 UnaryOrTerm := "+" Term | "-" Term | Term =:
996
997 Term := Factor { MulOperator Factor } =:
998
999 Factor := Number | string | SetOrDesignatorOrFunction |
1000 "(" Expression ")" | "NOT" ( Factor | ConstAttribute ) =:
1001
1002 PushQualident := % 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
1067 ConstructorOrSimpleDes := Constructor | % PopNothing %
1068 SimpleDes [ ActualParameters ]
1069 =:
1070
1071 SetOrDesignatorOrFunction := % 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 "]" | "^" } =:
1085 SimpleDes := { SubDesignator } =:
1086
1087 ActualParameters := "(" [ ExpList ] ")" =:
1088
1089 ExitStatement := "EXIT" =:
1090
1091 ReturnStatement := "RETURN" [ Expression ] =:
1092
1093 Statement := % PushAutoOff %
1094 [ AssignmentOrProcedureCall | IfStatement | CaseStatement |
1095 WhileStatement | RepeatStatement | LoopStatement |
1096 ForStatement | WithStatement | AsmStatement |
1097 ExitStatement | ReturnStatement | RetryStatement
1098 ] % PopAuto ; %
1099 =:
1100
1101 RetryStatement := "RETRY" =:
1102
1103 AssignmentOrProcedureCall := % 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
1114 StatementSequence := % VAR top: CARDINAL ; %
1115 % top := Top() %
1116 Statement % Assert(top=Top()) %
1117 { ";"
1118 Statement % Assert(top=Top()) %
1119 }
1120 =:
1121
1122 IfStatement := "IF" Expression "THEN"
1123 StatementSequence
1124 { "ELSIF" Expression "THEN" StatementSequence
1125 }
1126 [ "ELSE" StatementSequence ] "END"
1127 =:
1128
1129 CaseStatement := "CASE" Expression "OF" Case { "|" Case }
1130 CaseEndStatement
1131 =:
1132
1133 CaseEndStatement := "END" | "ELSE" StatementSequence "END"
1134 =:
1135
1136 Case := [ CaseLabelList ":" StatementSequence ]
1137 =:
1138
1139 CaseLabelList := CaseLabels { "," CaseLabels } =:
1140
1141 CaseLabels := ConstExpression [ ".." ConstExpression ] =:
1142
1143 WhileStatement := "WHILE" Expression "DO" StatementSequence "END" =:
1144
1145 RepeatStatement := "REPEAT" StatementSequence "UNTIL" Expression =:
1146
1147 ForStatement := "FOR" Ident ":=" Expression "TO" Expression
1148 [ "BY" ConstExpression ] "DO"
1149 StatementSequence
1150 "END"
1151 =:
1152
1153 LoopStatement := "LOOP" StatementSequence "END" =:
1154
1155 WithStatement := "WITH" Designator "DO"
1156 StatementSequence
1157 "END"
1158 =:
1159
1160 ProcedureDeclaration := % VAR top: CARDINAL ; %
1161 % top := Top () %
1162 ProcedureHeading ";" PostProcedureHeading % Assert (top = Top ()) %
1163 =:
1164
1165 PostProcedureHeading := ProperProcedure | ForwardDeclaration =:
1166
1167 ForwardDeclaration := "FORWARD" % PCEndBuildForward %
1168 =:
1169
1170 ProperProcedure := ProcedureBlock % PushAutoOn %
1171 Ident % PCEndBuildProcedure %
1172 % PopAuto %
1173 =:
1174
1175 DefineBuiltinProcedure := [ "__ATTRIBUTE__" "__BUILTIN__"
1176 "(" "(" % PushAutoOff %
1177 Ident % PopAuto %
1178 ")" ")" | "__INLINE__" ]
1179 =:
1180
1181 ProcedureHeading := "PROCEDURE" % M2Error.DefaultProcedure %
1182 % PushAutoOn %
1183 DefineBuiltinProcedure
1184 ( Ident
1185 % PCStartBuildProcedure %
1186 % PushAutoOff %
1187 [ FormalParameters ] AttributeNoReturn
1188 % PCBuildProcedureHeading %
1189 % PopAuto %
1190 ) % PopAuto %
1191 =:
1192
1193 Builtin := [ "__BUILTIN__" | "__INLINE__" ] =:
1194
1195 DefProcedureHeading := "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
1208 AttributeNoReturn := [ "<*" Ident "*>" ] =:
1209
1210 AttributeUnused := [ "<*" Ident "*>" ] =:
1211
1212 -- introduced procedure block so we can produce more informative
1213 -- error messages
1214
1215 ProcedureBlock := % VAR top: CARDINAL ; %
1216 % top := Top() %
1217 { Declaration % Assert(top=Top()) %
1218 } [ "BEGIN" ProcedureBlockBody % Assert(top=Top()) %
1219 ] "END" % Assert(top=Top()) %
1220 =:
1221
1222 Block := % VAR top: CARDINAL ; %
1223 % top := Top() %
1224 { Declaration } InitialBlock FinalBlock
1225 "END" % Assert(top=Top()) %
1226 =:
1227
1228 InitialBlock := [ "BEGIN" InitialBlockBody ] =:
1229
1230 FinalBlock := [ "FINALLY" FinalBlockBody ] =:
1231
1232 InitialBlockBody := NormalPart [ "EXCEPT" ExceptionalPart ] =:
1233
1234 FinalBlockBody := NormalPart [ "EXCEPT" ExceptionalPart ] =:
1235
1236 ProcedureBlockBody := NormalPart [ "EXCEPT" ExceptionalPart ] =:
1237
1238 NormalPart := StatementSequence =:
1239
1240 ExceptionalPart := StatementSequence =:
1241
1242 Declaration := "CONST" { ConstantDeclaration ";" } |
1243 "TYPE" { TypeDeclaration ";" } |
1244 "VAR" { VariableDeclaration ";" } |
1245 ProcedureDeclaration ";" |
1246 ModuleDeclaration ";" =:
1247
1248 DefFormalParameters := "(" [ DefMultiFPSection ] ")" FormalReturn =:
1249
1250 DefMultiFPSection := DefExtendedFP |
1251 FPSection [ ";" DefMultiFPSection ] =:
1252
1253 FormalParameters := "(" [ MultiFPSection ] ")" FormalReturn =:
1254
1255 MultiFPSection := ExtendedFP |
1256 FPSection [ ";" MultiFPSection ] =:
1257
1258 FPSection := NonVarFPSection | VarFPSection =:
1259
1260 DefExtendedFP := DefOptArg | "..." =:
1261
1262 ExtendedFP := OptArg | "..." =:
1263
1264 VarFPSection := "VAR" IdentList ":" FormalType [ AttributeUnused ] =:
1265
1266 NonVarFPSection := IdentList ":" FormalType [ AttributeUnused ] =:
1267
1268 OptArg := "[" Ident ":" FormalType [ "=" ConstExpression ] "]" =:
1269
1270 DefOptArg := "[" Ident ":" FormalType "=" ConstExpression "]" =:
1271
1272 FormalType := { "ARRAY" "OF" } Qualident =:
1273
1274 ModuleDeclaration := "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
1287 Priority := "[" ConstExpression "]" =:
1288
1289 Export := "EXPORT" ( "QUALIFIED"
1290 IdentList |
1291 "UNQUALIFIED"
1292 IdentList |
1293 IdentList ) ";" =:
1294
1295 Import := % PushAutoOn %
1296 ( "FROM" Ident "IMPORT" IdentList ";" |
1297 "IMPORT" % PushT(ImportTok)
1298 (* determines whether Ident or Module *) %
1299 IdentList ";" ) % PopAuto %
1300 =:
1301
1302 DefinitionModule := "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
1317 Definition := "CONST" { ConstantDeclaration ";" } |
1318 "TYPE"
1319 { Ident ( ";"
1320 | "=" Type Alignment ";" )
1321 }
1322 |
1323 "VAR" { VariableDeclaration ";" } |
1324 DefProcedureHeading ";" =:
1325
1326 AsmStatement := 'ASM' [ 'VOLATILE' ] '(' AsmOperands ')' =:
1327
1328 NamedOperand := '[' Ident ']' =:
1329
1330 AsmOperandName := [ NamedOperand ] =:
1331
1332 AsmOperands := ConstExpression [ ':' AsmList [ ':' AsmList [ ':' TrashList ] ] ]
1333 =:
1334
1335 AsmList := [ AsmElement ] { ',' AsmElement } =:
1336
1337 AsmElement := AsmOperandName ConstExpression '(' Expression ')'
1338 =:
1339
1340 TrashList := [ ConstExpression ] { ',' ConstExpression } =:
1341
1342 FNB