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