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