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