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