]> git.ipfire.org Git - thirdparty/gcc.git/blame - gcc/m2/gm2-compiler/P3Build.bnf
Update copyright years.
[thirdparty/gcc.git] / gcc / m2 / gm2-compiler / P3Build.bnf
CommitLineData
1eee94d3
GM
1--
2-- m2-3.bnf grammar and associated actions for pass 3.
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 P3Build begin
23(* output from m2-3.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 P3Build ;
46
47FROM M2LexBuf IMPORT currentstring, currenttoken, GetToken, InsertToken,
48 InsertTokenAndRewind, GetTokenNo, PrintTokenNo, MakeVirtualTok,
49 UnknownTokenNo ;
50
51FROM M2Error IMPORT ErrorStringAt, WriteFormat1, WriteFormat2 ;
52FROM NameKey IMPORT NulName, Name, makekey ;
53FROM DynamicStrings IMPORT String, InitString, KillString, Mark, ConCat, ConCatChar ;
54FROM M2Printf IMPORT printf0, printf1 ;
55FROM M2Debug IMPORT Assert ;
56FROM P2SymBuild IMPORT BuildString, BuildNumber ;
57FROM M2MetaError IMPORT MetaErrorT0 ;
89b58667 58FROM M2CaseList IMPORT ElseCase ;
1eee94d3
GM
59
60FROM M2Reserved IMPORT tokToTok, toktype,
61 NulTok, ImportTok, ExportTok, QualifiedTok, UnQualifiedTok,
62 EqualTok, HashTok, LessGreaterTok, LessTok, LessEqualTok,
63 GreaterTok, GreaterEqualTok, InTok, PlusTok, MinusTok,
64 OrTok, TimesTok, DivTok, DivideTok, ModTok, RemTok,
65 AndTok, AmbersandTok, PeriodPeriodTok, ByTok ;
66
67FROM M2Quads IMPORT PushT, PopT, PushTF, PopTF, PopNothing, Annotate,
68 PushTtok, PushTFtok, PopTtok, PopTFtok, OperandTok,
69 BuildModuleStart,
70 StartBuildDefFile, StartBuildModFile,
71 EndBuildFile,
72 StartBuildInit,
73 EndBuildInit,
74 StartBuildFinally,
75 EndBuildFinally,
76 BuildExceptInitial,
77 BuildExceptFinally,
78 BuildExceptProcedure,
79 BuildReThrow,
80 BuildProcedureStart,
81 BuildProcedureBegin,
82 BuildProcedureEnd,
83 BuildScaffold,
84 BuildStmtNote,
85 BuildFunctionCall, BuildConstFunctionCall,
86 BuildBinaryOp, BuildUnaryOp, BuildRelOp, BuildNot,
87 BuildEmptySet, BuildInclRange, BuildInclBit,
88 BuildSetStart, BuildSetEnd,
89 PushLineNo, BuildSizeCheckStart,
90 BuildBuiltinConst, BuildBuiltinTypeInfo,
91 BuildAssignment, BuildAssignConstant,
92 BuildAlignment,
93 BuildRepeat, BuildUntil,
94 BuildWhile, BuildDoWhile, BuildEndWhile,
95 BuildLoop, BuildExit, BuildEndLoop,
96 BuildThenIf, BuildElse, BuildEndIf,
97 BuildForToByDo, BuildPseudoBy, BuildEndFor,
98 BuildElsif1, BuildElsif2,
99 BuildProcedureCall, BuildReturn, BuildNulExpression,
100 CheckBuildFunction,
101 StartBuildWith, EndBuildWith,
c4637cbe 102 BuildAsm,
1eee94d3
GM
103 BuildCaseStart,
104 BuildCaseOr,
105 BuildCaseElse,
106 BuildCaseEnd,
107 BuildCaseCheck,
108 BuildCaseStartStatementSequence,
109 BuildCaseEndStatementSequence,
110 BuildCaseList,
111 BuildCaseRange, BuildCaseEquality,
112 BuildConstructorStart,
113 BuildConstructorEnd,
114 SilentBuildConstructorStart,
115 NextConstructorField, BuildTypeForConstructor,
116 BuildComponentValue,
117 BeginVarient, EndVarient, ElseVarient,
118 BeginVarientList, EndVarientList,
119 RecordOp,
120 BuildNulParam,
121 BuildDesignatorRecord,
122 BuildDesignatorArray,
123 BuildDesignatorPointer,
124 BuildBooleanVariable,
125 CheckWithReference,
126 BuildModulePriority,
127 BuildRetry,
128 DisplayStack,
129 AddVarientRange, AddVarientEquality,
bf470895 130 BuildAsmElement, BuildAsmTrash,
1eee94d3
GM
131 BeginVarient, EndVarient, BeginVarientList, EndVarientList,
132 PushInConstExpression, PopInConstExpression, IsInConstExpression,
133 BuildDefaultFieldAlignment, BuildPragmaField,
134 IsAutoPushOn, PushAutoOff, PushAutoOn, PopAuto ;
135
136FROM P3SymBuild IMPORT P3StartBuildProgModule,
137 P3EndBuildProgModule,
138
139 P3StartBuildDefModule,
140 P3EndBuildDefModule,
141
142 P3StartBuildImpModule,
143 P3EndBuildImpModule,
144
145 StartBuildInnerModule,
146 EndBuildInnerModule,
147
148 CheckImportListOuterModule,
149 CheckCanBeImported,
150 StartBuildProcedure,
151 BuildProcedureHeading,
152 EndBuildProcedure,
153 BuildVarAtAddress,
154 BuildConst,
155 BuildSubrange,
156 BuildNulName,
157 BuildOptArgInitializer ;
158
159FROM SymbolTable IMPORT MakeGnuAsm, PutGnuAsmVolatile, PutGnuAsm, PutGnuAsmInput,
160 PutGnuAsmOutput, PutGnuAsmTrash,
161 PutGnuAsmVolatile, PutGnuAsmSimple,
162 MakeRegInterface,
163 PutRegInterface,
164 IsRegInterface, IsGnuAsmVolatile, IsGnuAsm,
165 GetCurrentModule,
166 GetSymName, GetType, SkipType,
167 NulSym,
168 StartScope, EndScope,
169 PutIncluded,
170 IsVarParam, IsProcedure, IsDefImp, IsModule, IsProcType,
171 IsRecord,
172 RequestSym, IsExported,
173 GetSym, GetLocalSym ;
174
175FROM M2Batch IMPORT IsModuleKnown ;
176
177FROM M2CaseList IMPORT BeginCaseList, EndCaseList ;
178
179IMPORT M2Error ;
180
181CONST
182 Debugging = FALSE ;
1eee94d3
GM
183 DebugAsm = FALSE ;
184
185VAR
186 WasNoError: BOOLEAN ;
187
188
189PROCEDURE ErrorString (s: String) ;
190BEGIN
191 ErrorStringAt(s, GetTokenNo ()) ;
192 WasNoError := FALSE
193END ErrorString ;
194
195
196PROCEDURE ErrorArray (a: ARRAY OF CHAR) ;
197BEGIN
198 ErrorString(InitString(a))
199END ErrorArray ;
200
201
202% declaration P3Build begin
203
204
205(*
206 SyntaxError - after a syntax error we skip all tokens up until we reach
207 a stop symbol.
208*)
209
210PROCEDURE SyntaxError (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
211BEGIN
212 DescribeError ;
213 IF Debugging
214 THEN
215 printf0('\nskipping token *** ')
216 END ;
217 (* --fixme-- this assumes a 32 bit word size. *)
218 WHILE NOT (((ORD(currenttoken)<32) AND (currenttoken IN stopset0)) OR
219 ((ORD(currenttoken)>=32) AND (ORD(currenttoken)<64) AND (currenttoken IN stopset1)) OR
220 ((ORD(currenttoken)>=64) AND (currenttoken IN stopset2)))
221 DO
222 GetToken
223 END ;
224 IF Debugging
225 THEN
226 printf0(' ***\n')
227 END
228END SyntaxError ;
229
230
231(*
232 SyntaxCheck -
233*)
234
235PROCEDURE SyntaxCheck (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
236BEGIN
237 (* --fixme-- this assumes a 32 bit word size. *)
238 IF NOT (((ORD(currenttoken)<32) AND (currenttoken IN stopset0)) OR
239 ((ORD(currenttoken)>=32) AND (ORD(currenttoken)<64) AND (currenttoken IN stopset1)) OR
240 ((ORD(currenttoken)>=64) AND (currenttoken IN stopset2)))
241 THEN
242 SyntaxError(stopset0, stopset1, stopset2)
243 END
244END SyntaxCheck ;
245
246
247(*
248 WarnMissingToken - generates a warning message about a missing token, t.
249*)
250
251PROCEDURE WarnMissingToken (t: toktype) ;
252VAR
253 s0 : SetOfStop0 ;
254 s1 : SetOfStop1 ;
255 s2 : SetOfStop2 ;
256 str: String ;
257BEGIN
258 s0 := SetOfStop0{} ;
259 s1 := SetOfStop1{} ;
260 s2 := SetOfStop2{} ;
261 IF ORD(t)<32
262 THEN
263 s0 := SetOfStop0{t}
264 ELSIF ORD(t)<64
265 THEN
266 s1 := SetOfStop1{t}
267 ELSE
268 s2 := SetOfStop2{t}
269 END ;
270 str := DescribeStop(s0, s1, s2) ;
271
272 str := ConCat(InitString('syntax error,'), Mark(str)) ;
273 ErrorStringAt (str, GetTokenNo ())
274END WarnMissingToken ;
275
276
277(*
278 MissingToken - generates a warning message about a missing token, t.
279*)
280
281PROCEDURE MissingToken (t: toktype) ;
282BEGIN
283 WarnMissingToken(t) ;
284 IF (t#identtok) AND (t#integertok) AND (t#realtok) AND (t#stringtok)
285 THEN
286 IF Debugging
287 THEN
288 printf0('inserting token\n')
289 END ;
290 InsertToken(t)
291 END
292END MissingToken ;
293
294
295(*
296 CheckAndInsert -
297*)
298
299PROCEDURE CheckAndInsert (t: toktype; stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) : BOOLEAN ;
300BEGIN
301 IF ((ORD(t)<32) AND (t IN stopset0)) OR
302 ((ORD(t)>=32) AND (ORD(t)<64) AND (t IN stopset1)) OR
303 ((ORD(t)>=64) AND (t IN stopset2))
304 THEN
305 WarnMissingToken(t) ;
306 InsertTokenAndRewind(t) ;
307 RETURN( TRUE )
308 ELSE
309 RETURN( FALSE )
310 END
311END CheckAndInsert ;
312
313
314(*
315 InStopSet
316*)
317
318PROCEDURE InStopSet (t: toktype; stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) : BOOLEAN ;
319BEGIN
320 IF ((ORD(t)<32) AND (t IN stopset0)) OR
321 ((ORD(t)>=32) AND (ORD(t)<64) AND (t IN stopset1)) OR
322 ((ORD(t)>=64) AND (t IN stopset2))
323 THEN
324 RETURN( TRUE )
325 ELSE
326 RETURN( FALSE )
327 END
328END InStopSet ;
329
330
331(*
332 PeepToken - peep token checks to see whether the stopset is satisfied by currenttoken
333 If it is not then it will insert a token providing the token
334 is one of ; ] ) } . OF END ,
335
336 if the stopset contains <identtok> then we do not insert a token
337*)
338
339PROCEDURE PeepToken (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
340BEGIN
341 (* and again (see above re: ORD)
342 *)
343 IF (NOT (((ORD(currenttoken)<32) AND (currenttoken IN stopset0)) OR
344 ((ORD(currenttoken)>=32) AND (ORD(currenttoken)<64) AND (currenttoken IN stopset1)) OR
345 ((ORD(currenttoken)>=64) AND (currenttoken IN stopset2)))) AND
346 (NOT InStopSet(identtok, stopset0, stopset1, stopset2))
347 THEN
348 (* SyntaxCheck would fail since currentoken is not part of the stopset
349 we check to see whether any of currenttoken might be a commonly omitted token *)
350 IF CheckAndInsert(semicolontok, stopset0, stopset1, stopset2) OR
351 CheckAndInsert(rsbratok, stopset0, stopset1, stopset2) OR
352 CheckAndInsert(rparatok, stopset0, stopset1, stopset2) OR
353 CheckAndInsert(rcbratok, stopset0, stopset1, stopset2) OR
354 CheckAndInsert(periodtok, stopset0, stopset1, stopset2) OR
355 CheckAndInsert(oftok, stopset0, stopset1, stopset2) OR
356 CheckAndInsert(endtok, stopset0, stopset1, stopset2) OR
357 CheckAndInsert(commatok, stopset0, stopset1, stopset2)
358 THEN
359 END
360 END
361END PeepToken ;
362
363
364(*
365 Expect -
366*)
367
368PROCEDURE Expect (t: toktype; stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
8089f26b
GM
369CONST
370 Pass1 = FALSE ;
1eee94d3
GM
371BEGIN
372 IF currenttoken=t
373 THEN
374 GetToken ;
375 IF Pass1
376 THEN
377 PeepToken(stopset0, stopset1, stopset2)
378 END
379 ELSE
380 MissingToken(t)
381 END ;
382 SyntaxCheck(stopset0, stopset1, stopset2)
383END Expect ;
384
385
386(*
387 CompilationUnit - returns TRUE if the input was correct enough to parse
388 in future passes.
389*)
390
391PROCEDURE CompilationUnit () : BOOLEAN ;
392BEGIN
393 WasNoError := TRUE ;
394 FileUnit(SetOfStop0{eoftok}, SetOfStop1{}, SetOfStop2{}) ;
395 RETURN( WasNoError )
396END CompilationUnit ;
397
398
399(*
400 Ident - error checking varient of Ident
401*)
402
403PROCEDURE Ident (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
404BEGIN
405 IF IsAutoPushOn()
406 THEN
407 PushTFtok (makekey (currentstring), identtok, GetTokenNo ())
408 (* ; MetaErrorT0 (GetTokenNo(), "{%W}an ident") *)
409 END ;
410 Expect(identtok, stopset0, stopset1, stopset2)
411END Ident ;
412
413
414(*
415 string -
416*)
417
418PROCEDURE string (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
419BEGIN
420 IF IsAutoPushOn()
421 THEN
422 PushTFtok(makekey(currentstring), stringtok, GetTokenNo ()) ;
423 BuildString
424 END ;
425 Expect(stringtok, stopset0, stopset1, stopset2)
426END string ;
427
428
429(*
430 Integer -
431*)
432
433PROCEDURE Integer (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
434BEGIN
435 IF IsAutoPushOn()
436 THEN
437 PushTFtok (makekey(currentstring), integertok, GetTokenNo ()) ;
438 BuildNumber
439 END ;
440 Expect(integertok, stopset0, stopset1, stopset2)
441END Integer ;
442
443
444(*
445 Real -
446*)
447
448PROCEDURE Real (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
449BEGIN
450 IF IsAutoPushOn()
451 THEN
452 PushTFtok (makekey(currentstring), realtok, GetTokenNo ()) ;
453 BuildNumber
454 END ;
455 Expect(realtok, stopset0, stopset1, stopset2)
456END Real ;
457
458% module P3Build end
459END P3Build.
460% rules
461error 'ErrorArray' 'ErrorString'
462tokenfunc 'currenttoken'
463
464token '' eoftok -- internal token
465token '+' plustok
466token '-' minustok
467token '*' timestok
468token '/' dividetok
469token ':=' becomestok
470token '&' ambersandtok
471token "." periodtok
472token "," commatok
473token ";" semicolontok
474token '(' lparatok
475token ')' rparatok
476token '[' lsbratok -- left square brackets
477token ']' rsbratok -- right square brackets
478token '{' lcbratok -- left curly brackets
479token '}' rcbratok -- right curly brackets
480token '^' uparrowtok
481token "'" singlequotetok
482token '=' equaltok
483token '#' hashtok
484token '<' lesstok
485token '>' greatertok
486token '<>' lessgreatertok
487token '<=' lessequaltok
488token '>=' greaterequaltok
489token '<*' ldirectivetok
490token '*>' rdirectivetok
491token '..' periodperiodtok
492token ':' colontok
493token '"' doublequotestok
494token '|' bartok
495token 'AND' andtok
496token 'ARRAY' arraytok
497token 'BEGIN' begintok
498token 'BY' bytok
499token 'CASE' casetok
500token 'CONST' consttok
501token 'DEFINITION' definitiontok
502token 'DIV' divtok
503token 'DO' dotok
504token 'ELSE' elsetok
505token 'ELSIF' elsiftok
506token 'END' endtok
507token 'EXCEPT' excepttok
508token 'EXIT' exittok
509token 'EXPORT' exporttok
510token 'FINALLY' finallytok
511token 'FOR' fortok
512token 'FROM' fromtok
513token 'IF' iftok
514token 'IMPLEMENTATION' implementationtok
515token 'IMPORT' importtok
516token 'IN' intok
517token 'LOOP' looptok
518token 'MOD' modtok
519token 'MODULE' moduletok
520token 'NOT' nottok
521token 'OF' oftok
522token 'OR' ortok
523token 'PACKEDSET' packedsettok
524token 'POINTER' pointertok
525token 'PROCEDURE' proceduretok
526token 'QUALIFIED' qualifiedtok
527token 'UNQUALIFIED' unqualifiedtok
528token 'RECORD' recordtok
529token 'REM' remtok
530token 'REPEAT' repeattok
531token 'RETRY' retrytok
532token 'RETURN' returntok
533token 'SET' settok
534token 'THEN' thentok
535token 'TO' totok
536token 'TYPE' typetok
537token 'UNTIL' untiltok
538token 'VAR' vartok
539token 'WHILE' whiletok
540token 'WITH' withtok
541token 'ASM' asmtok
542token 'VOLATILE' volatiletok
543token '...' periodperiodperiodtok
544token '__DATE__' datetok
545token '__LINE__' linetok
546token '__FILE__' filetok
547token '__ATTRIBUTE__' attributetok
548token '__BUILTIN__' builtintok
549token '__INLINE__' inlinetok
550token 'integer number' integertok
551token 'identifier' identtok
552token 'real number' realtok
553token 'string' stringtok
554
555special Ident first { < identtok > } follow { }
556special Integer first { < integertok > } follow { }
557special Real first { < realtok > } follow { }
558special string first { < stringtok > } follow { }
559
560BNF
561
562-- the following are provided by the module m2flex and also handbuild procedures below
563-- Ident := Letter { ( Letter | Digit ) } =:
564-- Integer := Digit { Digit } | OctalDigit { OctalDigit } ( " B " | " C " ) |
565-- Digit { HexDigit } " H " =:
566-- Real := Digit { Digit } " . " { Digit } [ ScaleFactor ] =:
567-- ScaleFactor := " E " [ ( " + " | " - " ) ] Digit { Digit } =:
568-- HexDigit := Digit | " A " | " B " | " C " | " D " | " E " | " F " =:
569-- Digit := OctalDigit | " 8 " | " 9 " =:
570-- OctalDigit := "0" | "1" | "2" | "3" | "4" | "5" | "6" | "7" =:
571-- String
572
573FileUnit := % PushAutoOff %
574 ( DefinitionModule |
575 ImplementationOrProgramModule ) % PopAuto %
576 =:
577
578ProgramModule := % VAR modulet, endt: CARDINAL ; %
579 % modulet := GetTokenNo () %
580 "MODULE" % M2Error.DefaultProgramModule %
581 % PushAutoOn %
582 Ident % P3StartBuildProgModule %
583 % StartBuildModFile (modulet) %
584 % BuildModuleStart (modulet) %
585 % PushAutoOff %
586 [ Priority
587 ]
588 ";" % BuildScaffold (modulet,
589 GetCurrentModule ()) %
590 { Import }
591 Block % PushAutoOn %
592 % endt := GetTokenNo () -1 %
593 Ident % EndBuildFile (endt) %
594 % P3EndBuildProgModule %
595 "." % PopAuto ; PopAuto %
596 =:
597
598ImplementationModule := % VAR modulet, endt: CARDINAL ; %
599 % modulet := GetTokenNo () %
600 "IMPLEMENTATION" % M2Error.DefaultImplementationModule %
601 "MODULE" % PushAutoOn %
602 Ident % StartBuildModFile (modulet) %
603 % P3StartBuildImpModule %
604 % BuildModuleStart (modulet) %
605 % PushAutoOff %
606 [ Priority
607 ] ";" % BuildScaffold (modulet,
608 GetCurrentModule ()) %
609 { Import }
610 Block % PushAutoOn %
611 % endt := GetTokenNo () -1 %
612 Ident % EndBuildFile (endt) %
613 % P3EndBuildImpModule %
614 "." % PopAuto ; PopAuto ; PopAuto %
615 =:
616
617ImplementationOrProgramModule := % PushAutoOff %
618 ( ImplementationModule | ProgramModule ) % PopAuto %
619 =:
620
621Number := Integer | Real =:
622
623--
624-- In pass 3 Qualident needs some care as we must only parse module.module.ident
625-- and not ident.recordfield. We leave the ident.recordfield to be parsed by
626-- SubDesignator. Note that Qualident is called by SubDesignator so if
627-- IsAutoPushOff then we just consume tokens.
628--
629
630Qualident := % VAR name : Name ;
631 init, ip1,
632 tokstart, tok : CARDINAL ; %
633 Ident
634 % IF IsAutoPushOn()
635 THEN
636 PopTtok(name, tokstart) ;
637 tok := tokstart ;
638 init := RequestSym (tok, name) ;
639 WHILE IsDefImp (init) OR IsModule (init) DO
640 Expect (periodtok, stopset0, stopset1, stopset2 + SetOfStop2{identtok}) ;
641 StartScope (init) ;
642 Ident (stopset0, stopset1, stopset2) ;
643 PopTtok (name, tok) ;
644 ip1 := RequestSym (tok, name) ;
645 PutIncluded(ip1) ;
646 EndScope ;
647 CheckCanBeImported(init, ip1) ;
648 init := ip1
649 END ;
650 IF tok#tokstart
651 THEN
652 tok := MakeVirtualTok (tokstart, tokstart, tok)
653 END ;
654 IF IsProcedure(init) OR IsProcType(init)
655 THEN
656 PushTtok(init, tok)
657 ELSE
658 PushTFtok(init, GetType(init), tok) ;
659 END
660 ELSE %
661 { "." Ident } % END %
662 =:
663
664ConstantDeclaration := % VAR tokno: CARDINAL ; %
665 % PushAutoOn %
666 ( Ident "=" % tokno := GetTokenNo () -1 %
667 % BuildConst %
668 ConstExpression ) % BuildAssignConstant (tokno) %
669 % PopAuto %
670 =:
671
672ConstExpression := % VAR tokpos: CARDINAL ; %
673 % PushAutoOn %
674 SimpleConstExpr [ Relation % tokpos := GetTokenNo ()-1 %
675 SimpleConstExpr % BuildRelOp (tokpos) %
676 ] % PopAuto %
677 =:
678
679Relation := "=" % PushTtok(EqualTok, GetTokenNo() -1) %
680 | "#" % PushTtok(HashTok, GetTokenNo() -1) %
681 | "<>" % PushTtok(LessGreaterTok, GetTokenNo() -1) %
682 | "<" % PushTtok(LessTok, GetTokenNo() -1) %
683 | "<=" % PushTtok(LessEqualTok, GetTokenNo() -1) %
684 | ">" % PushTtok(GreaterTok, GetTokenNo() -1) %
685 | ">=" % PushTtok(GreaterEqualTok, GetTokenNo() -1) %
686 | "IN" % PushTtok(InTok, GetTokenNo() -1) %
687 =:
688
689SimpleConstExpr := UnaryOrConstTerm { AddOperator ConstTerm % BuildBinaryOp %
690 } =:
691
692UnaryOrConstTerm := "+" % PushTtok(PlusTok, GetTokenNo() -1) %
693 ConstTerm % BuildUnaryOp %
694 |
695 "-" % PushTtok(MinusTok, GetTokenNo() -1) %
696 ConstTerm % BuildUnaryOp %
697 |
698 ConstTerm =:
699
700AddOperator := "+" % PushTtok(PlusTok, GetTokenNo() -1) ;
701 RecordOp %
702 | "-" % PushTtok(MinusTok, GetTokenNo() -1) ;
703 RecordOp %
704 | "OR" % PushTtok(OrTok, GetTokenNo() -1) ;
705 RecordOp %
706 =:
707
708ConstTerm := ConstFactor { MulOperator ConstFactor % BuildBinaryOp %
709 } =:
710
711MulOperator := "*" % PushTtok(TimesTok, GetTokenNo() -1) ;
712 RecordOp %
713 | "/" % PushTtok(DivideTok, GetTokenNo() -1) ;
714 RecordOp %
715 | "DIV" % PushTtok(DivTok, GetTokenNo() -1) ;
716 RecordOp %
717 | "MOD" % PushTtok(ModTok, GetTokenNo() -1) ;
718 RecordOp %
719 | "REM" % PushTtok(RemTok, GetTokenNo() -1) ;
720 RecordOp %
721 | "AND" % PushTtok(AndTok, GetTokenNo() -1) ;
722 RecordOp %
723 | "&" % PushTtok(AmbersandTok, GetTokenNo() -1) ;
724 RecordOp %
725 =:
726
c8f2be5d
GM
727ConstFactor := % VAR tokpos: CARDINAL ; %
728 Number | ConstString | ConstSetOrQualidentOrFunction |
729 "(" ConstExpression ")" | "NOT" % tokpos := GetTokenNo() -1 %
730 ConstFactor % BuildNot (tokpos) %
1eee94d3
GM
731 | ConstAttribute =:
732
733-- to help satisfy LL1
734
735ConstString := string =:
736
737ComponentElement := ConstExpression ( ".." ConstExpression % PushTtok(PeriodPeriodTok, GetTokenNo() -1) %
738 | % PushT(NulTok) %
739 )
740 =:
741
742ComponentValue := ComponentElement ( 'BY' ConstExpression % PushTtok(ByTok, GetTokenNo() -1) %
743
744 | % PushT(NulTok) %
745 )
746 =:
747
748ArraySetRecordValue := ComponentValue % BuildComponentValue %
749 { ',' % NextConstructorField %
750 ComponentValue % BuildComponentValue %
751 }
752 =:
753
754Constructor := % DisplayStack %
755 '{' % BuildConstructorStart (GetTokenNo() -1) %
756 [ ArraySetRecordValue ] % BuildConstructorEnd (GetTokenNo()) %
757 '}' =:
758
759ConstSetOrQualidentOrFunction := Qualident
760 [ Constructor | ConstActualParameters % BuildConstFunctionCall %
761 ]
762 | % BuildTypeForConstructor %
763 Constructor =:
764
765ConstActualParameters := % PushInConstExpression %
766 ActualParameters % PopInConstExpression %
767 =:
768
769ConstAttribute := "__ATTRIBUTE__" "__BUILTIN__" "(" "(" % PushAutoOn %
770 ConstAttributeExpression % PopAuto %
771 ")" ")" =:
772
773ConstAttributeExpression :=
774 Ident % BuildBuiltinConst %
775 | "<" Qualident ',' Ident % BuildBuiltinTypeInfo %
776 ">"
777 =:
778
779ByteAlignment := '<*' % PushAutoOn %
780 AttributeExpression % BuildAlignment %
781 '*>' % PopAuto %
782 =:
783
784Alignment := [ ByteAlignment ] =:
785
786TypeDeclaration := Ident "=" Type Alignment
787 =:
788
789Type :=
790 % PushAutoOff %
791 ( SimpleType | ArrayType
792 | RecordType
793 | SetType
794 | PointerType
795 | ProcedureType ) % PopAuto %
796 =:
797
798SimpleType := Qualident [ SubrangeType ] | Enumeration | SubrangeType =:
799
800Enumeration := "("
801 ( IdentList
802 )
803 ")"
804 =:
805
806IdentList := Ident % VAR
807 on: BOOLEAN ;
808 n : CARDINAL ; %
809 % on := IsAutoPushOn() ;
810 IF on
811 THEN
812 n := 1
813 END %
814 { "," Ident % IF on
815 THEN
816 INC(n)
817 END %
818 } % IF on
819 THEN
820 PushT(n)
821 END %
822 =:
823
824SubrangeType := "[" ConstExpression ".." ConstExpression "]" % BuildSubrange ; %
825 =:
826
827ArrayType := "ARRAY"
828
829 SimpleType
830 { ","
831 SimpleType
832 } "OF"
833 Type
834 =:
835
836RecordType := "RECORD" [ DefaultRecordAttributes ] FieldListSequence "END" =:
837
838DefaultRecordAttributes := '<*' % PushAutoOn %
839 AttributeExpression % BuildDefaultFieldAlignment %
840 % PopAuto %
841 '*>' =:
842
843RecordFieldPragma := [ '<*' FieldPragmaExpression
844 { ',' FieldPragmaExpression } '*>' ] =:
845
846FieldPragmaExpression := % PushAutoOn %
847 Ident PragmaConstExpression % BuildPragmaField %
848 % PopAuto %
849 =:
850
851PragmaConstExpression := ( '(' ConstExpression ')' | % PushT(NulSym) %
852 % Annotate('NulSym||no pragma const') %
853 ) =:
854
855AttributeExpression := Ident '(' ConstExpression ')' =:
856
857FieldListSequence := FieldListStatement { ";" FieldListStatement } =:
858
859-- at present FieldListStatement is as follows:
860FieldListStatement := [ FieldList ] =:
861-- later replace it with FieldList to comply with PIM2
862
863-- sadly the PIM rules are not LL1 as Ident and Qualident have the same first
864-- symbols. We rewrite FieldList to inline qualident
865-- was
866-- FieldList := IdentList ":" % BuildNulName %
867-- Type |
868-- "CASE" [ Ident ":" ] Qualident "OF" Varient { "|" Varient }
869-- [ "ELSE" FieldListSequence ] "END" =:
870
871FieldList := IdentList ":"
872 Type RecordFieldPragma
873 |
874 "CASE" % BeginVarient %
875 CaseTag "OF"
876 Varient { "|" Varient }
877 [ "ELSE" % ElseVarient %
878 FieldListSequence
879 ] "END" % EndVarient %
880 =:
881
882TagIdent := [ Ident ] =:
883
884CaseTag := TagIdent [":" Qualident ] =:
885
886Varient := [ % BeginVarientList %
887 VarientCaseLabelList ":" FieldListSequence % EndVarientList %
888 ] =:
889
890VarientCaseLabelList := VarientCaseLabels { "," VarientCaseLabels } =:
891
892VarientCaseLabels := ConstExpression ( ".." ConstExpression % AddVarientRange %
893 | % AddVarientEquality ; (* epsilon *) %
894 )
895 =:
896
897--
898-- the following rules are a copy of the ConstExpression ebnf rules but without
899-- any actions all prefixed with Silent.
900-- At present they are only used by CaseLabels, if this continues to be true we
901-- might consider restricting the SilentConstExpression. Eg it makes no sence to allow
902-- String in these circumstances!
903--
904
905SilentConstExpression := % PushAutoOff %
906 SilentSimpleConstExpr
907 [ SilentRelation SilentSimpleConstExpr ] % PopAuto %
908 =:
909
910SilentRelation := "=" | "#" | "<>" | "<" | "<=" | ">" | ">=" | "IN" =:
911
912SilentSimpleConstExpr := SilentUnaryOrConstTerm { SilentAddOperator SilentConstTerm } =:
913
914SilentUnaryOrConstTerm := "+" SilentConstTerm | "-" SilentConstTerm | SilentConstTerm =:
915
916SilentAddOperator := "+" | "-" | "OR" =:
917
918SilentConstTerm := SilentConstFactor { SilentMulOperator SilentConstFactor } =:
919
920SilentMulOperator := "*" | "/" | "DIV" | "MOD" | "REM" | "AND" | "&" =:
921
922SilentConstFactor := Number | SilentConstString | SilentConstSetOrQualidentOrFunction |
923 "(" SilentConstExpression ")" | "NOT" SilentConstFactor
924 | SilentConstAttribute =:
925
926SilentConstString := string =:
927
928SilentConstAttribute := "__ATTRIBUTE__" "__BUILTIN__" "(" "(" SilentConstAttributeExpression ")" ")" =:
929
930SilentConstAttributeExpression := Ident | "<" Ident ',' SilentConstString ">" =:
931
932SilentComponentElement := SilentConstExpression [ ".." SilentConstExpression ] =:
933
934SilentComponentValue := SilentComponentElement [ 'BY' SilentConstExpression ] =:
935
936SilentArraySetRecordValue := SilentComponentValue { ',' SilentComponentValue } =:
937
938SilentConstructor := '{' % SilentBuildConstructorStart %
939 [ SilentArraySetRecordValue ] '}' =:
940
941SilentConstSetOrQualidentOrFunction := SilentConstructor | Qualident
942 [ SilentConstructor | SilentActualParameters ] =:
943
944SilentActualParameters := "(" [ SilentExpList ] ")" =:
945
946SilentExpList := SilentConstExpression { "," SilentConstExpression } =:
947
948-- end of the Silent constant rules
949
950SetType := ( "SET" | "PACKEDSET" ) "OF" SimpleType =:
951
952PointerType := "POINTER" "TO"
953 Type
954 =:
955
956ProcedureType := "PROCEDURE"
957 [ FormalTypeList ] =:
958
959FormalTypeList := "(" ( ")" FormalReturn |
960 ProcedureParameters ")" FormalReturn ) =:
961
962FormalReturn := [ ":" OptReturnType ] =:
963
964OptReturnType := "[" Qualident "]" | Qualident =:
965
966ProcedureParameters := ProcedureParameter
967 { "," ProcedureParameter } =:
968
969ProcedureParameter := "..." | "VAR" FormalType | FormalType =:
970
971
972VarIdent := % VAR
973 Sym, Type: CARDINAL ;
974 on: BOOLEAN ; %
975 % on := IsAutoPushOn() %
976 % IF NOT on
977 THEN
978 PushAutoOn
979 END %
980 Ident % IF on
981 THEN
982 PopTF(Sym, Type) ;
983 PushTF(Sym, Type) ;
984 PushTF(Sym, Type)
985 END %
986 [ "[" ConstExpression % BuildVarAtAddress %
987 "]" ]
988 % PopNothing ;
989 PopAuto %
990 =:
991
992VarIdentList := VarIdent % VAR
993 on: BOOLEAN ;
994 n : CARDINAL ; %
995 % on := IsAutoPushOn() ;
996 IF on
997 THEN
998 n := 1
999 END %
1000 { "," VarIdent % IF on
1001 THEN
1002 INC(n)
1003 END %
1004 } % IF on
1005 THEN
1006 PushT(n)
1007 END %
1008 =:
1009
1010VariableDeclaration := VarIdentList ":"
1011 Type Alignment
1012 =:
1013
1014Designator := Qualident % CheckWithReference %
1015 { SubDesignator } =:
1016
1017SubDesignator := "." % VAR Sym, Type, tok,
1018 dotpostok : CARDINAL ;
1019 name, n1 : Name ; %
1020 % dotpostok := GetTokenNo () -1 ;
1021 PopTFtok (Sym, Type, tok) ;
1022 Type := SkipType(Type) ;
1023 PushTFtok(Sym, Type, tok) ;
1024 IF Type=NulSym
1025 THEN
1026 n1 := GetSymName(Sym) ;
1027 IF IsModuleKnown(GetSymName(Sym))
1028 THEN
1029 WriteFormat2('%a looks like a module which has not been globally imported (eg. suggest that you IMPORT %a ;)',
1030 n1, n1)
1031 ELSE
1032 WriteFormat1('%a is not a record variable', n1)
1033 END
1034 ELSIF NOT IsRecord(Type)
1035 THEN
1036 n1 := GetSymName(Type) ;
1037 WriteFormat1('%a is not a record type', n1)
1038 END ;
1039 StartScope(Type) %
1040 Ident
1041 % PopTtok (name, tok) ;
1042 Sym := GetLocalSym(Type, name) ;
1043 IF Sym=NulSym
1044 THEN
1045 n1 := GetSymName(Type) ;
1046 WriteFormat2('field %a does not exist within record %a', name, n1)
1047 END ;
1048 Type := GetType(Sym) ;
1049 PushTFtok (Sym, Type, tok) ;
1050 EndScope ;
1051 PushT(1) ;
1052 BuildDesignatorRecord (dotpostok) %
1053 | "[" ArrayExpList
1054 "]"
1055 | "^" % BuildDesignatorPointer (GetTokenNo () -1) %
1056 =:
1057
1058ArrayExpList :=
1059 Expression % BuildBooleanVariable %
1060 % BuildDesignatorArray %
1061 { ","
1062 Expression % BuildBooleanVariable %
1063 % BuildDesignatorArray %
1064 }
1065 =:
1066
1067ExpList := % VAR n: CARDINAL ; %
1068 Expression % BuildBooleanVariable %
1069 % n := 1 %
1070 { ","
1071 Expression % BuildBooleanVariable %
1072 % INC(n) %
1073 }
1074 % PushT(n) %
1075 =:
1076
1077Expression := % VAR tokpos: CARDINAL ; %
1078 % PushAutoOn %
1079 SimpleExpression [ Relation % tokpos := GetTokenNo ()-1 %
1080 SimpleExpression % BuildRelOp (tokpos) %
1081 ] % PopAuto %
1082 =:
1083
1084SimpleExpression := UnaryOrTerm { AddOperator Term % BuildBinaryOp %
1085 } =:
1086
1087UnaryOrTerm := "+" % PushTtok(PlusTok, GetTokenNo() -1) %
1088 Term % BuildUnaryOp %
1089 | "-" % PushTtok(MinusTok, GetTokenNo() -1) %
1090 Term % BuildUnaryOp %
1091 | Term =:
1092
c8f2be5d
GM
1093Term := Factor
1094 { MulOperator Factor % BuildBinaryOp %
1eee94d3
GM
1095 } =:
1096
c8f2be5d
GM
1097Factor := % VAR tokpos: CARDINAL ; %
1098 Number | string | SetOrDesignatorOrFunction |
1099 "(" Expression ")" | "NOT" % tokpos := GetTokenNo ()-1 %
1100 ( Factor % BuildNot (tokpos) %
1eee94d3
GM
1101 | ConstAttribute
1102 ) =:
1103
1104SetOrDesignatorOrFunction := Qualident
1105 % Assert (OperandTok(1) # UnknownTokenNo) %
1106 % CheckWithReference %
1107 % Assert (OperandTok(1) # UnknownTokenNo) %
1108 [ Constructor |
1109 SimpleDes % (* Assert (OperandTok(1) # UnknownTokenNo) *) %
1110 [ ActualParameters % IF IsInConstExpression()
1111 THEN
1112 BuildConstFunctionCall
1113 ELSE
81d5ca0b 1114 BuildFunctionCall (FALSE)
1eee94d3
GM
1115 END %
1116 ]
1117 ] |
1118 % BuildTypeForConstructor %
1119 Constructor =:
1120
1121-- SimpleDes := { "." Ident | "[" ExpList "]" | "^" } =:
1122SimpleDes := { SubDesignator } =:
1123
1124ActualParameters := "(" % BuildSizeCheckStart %
1125 ( ExpList | % BuildNulParam %
1126 ) ")" =:
1127
1128ExitStatement := "EXIT" % BuildExit %
1129 =:
1130
1131ReturnStatement := "RETURN" % VAR tokno: CARDINAL ; %
1132 % tokno := GetTokenNo () -1 %
1133 ( Expression | % BuildNulExpression (* in epsilon *) %
1134 ) % BuildReturn (tokno) %
1135 =:
1136
1137Statement := % BuildStmtNote (0) %
1138 % PushAutoOn ; DisplayStack %
1139 [ AssignmentOrProcedureCall | IfStatement | CaseStatement |
1140 WhileStatement | RepeatStatement | LoopStatement |
1141 ForStatement | WithStatement | AsmStatement |
1142 ExitStatement | ReturnStatement | RetryStatement
1143 ] % PopAuto ; %
1144 =:
1145
1146RetryStatement := "RETRY" % BuildRetry (GetTokenNo () -1) %
1147 =:
1148
1149AssignmentOrProcedureCall := % VAR isFunc: BOOLEAN ;
1150 tokno : CARDINAL ; %
1151 % DisplayStack %
1152 Designator
1153 % tokno := GetTokenNo () %
1154 ( ":="
1155 % (* PrintTokenNo (tokno) *) %
1156 Expression % BuildAssignment (tokno) %
1157 | % isFunc := CheckBuildFunction() %
1158 ( ActualParameters | % BuildNulParam (* in epsilon *) %
1159 ) % IF isFunc
1160 THEN
81d5ca0b 1161 BuildFunctionCall (FALSE) ;
1eee94d3
GM
1162 BuildAssignment (tokno)
1163 ELSE
1164 BuildProcedureCall (tokno - 1)
1165 END %
1166 ) % DisplayStack %
1167 =:
1168
1169-- these two break LL1 as both start with a Designator
1170-- ProcedureCall := Designator [ ActualParameters ] =:
1171-- Assignment := Designator ":=" Expression =:
1172
1173StatementSequence :=
1174 Statement
1175 { ";"
1176 Statement }
1177 =:
1178
1179IfStatement := "IF"
1180 Expression
1181 "THEN" % BuildThenIf %
1182 % BuildStmtNote (-1) %
1183 StatementSequence
1184 { "ELSIF"
1185 % BuildElsif1 %
1186 % BuildStmtNote (-1) %
1187 Expression
1188 "THEN" % BuildThenIf %
1189 % BuildStmtNote (-1) %
1190 StatementSequence % BuildElsif2 %
1191 }
1192 [
1193 "ELSE" % BuildElse %
1194 % BuildStmtNote (-1) %
1195 StatementSequence ] "END" % BuildEndIf %
1196 % BuildStmtNote (-1) %
1197 =:
1198
1199CaseStatement := "CASE"
1200 Expression % BuildCaseStart %
1201 "OF" Case { "|" Case }
1202 CaseEndStatement
1203 =:
1204
1205CaseEndStatement := "END" % BuildStmtNote (-1) %
1206 % BuildCaseElse %
1207 % BuildCaseCheck %
1208 % BuildCaseEnd %
1209 | "ELSE" % BuildStmtNote (-1) %
1210 % BuildCaseElse %
89b58667 1211 % ElseCase (NulSym) %
1eee94d3
GM
1212 StatementSequence % BuildStmtNote (0) %
1213 "END"
1214 % BuildCaseEnd %
1215 =:
1216
1217Case := [ % BuildStmtNote (-1) %
1218 CaseLabelList % BuildCaseStartStatementSequence %
1219 ":"
1220 StatementSequence % BuildCaseEndStatementSequence %
1221 % EndCaseList %
1222 ]
1223 =:
1224
1225CaseLabelList := % BeginCaseList(NulSym) %
1226 CaseLabels { "," % BuildCaseOr %
1227 CaseLabels } =:
1228
1229CaseLabels := ConstExpression ( ".." ConstExpression % BuildCaseRange ;
1230 BuildCaseList %
1231 | % BuildCaseEquality ; (* epsilon *)
1232 BuildCaseList %
1233 ) =:
1234
1235WhileStatement := "WHILE" % BuildWhile %
1236 % BuildStmtNote (0) %
1237 Expression
1238 % BuildStmtNote (0) %
1239 "DO" % BuildDoWhile %
1240 StatementSequence % BuildStmtNote (0) %
1241 "END" % DisplayStack ; BuildEndWhile %
1242 =:
1243
1244RepeatStatement := "REPEAT"
1245 % BuildRepeat %
1246 StatementSequence % BuildStmtNote (0) %
1247 "UNTIL"
1248 Expression % BuildUntil %
1249 =:
1250
1251ForStatement := % VAR endpostok: CARDINAL ; %
1252 % PushLineNo %
1253 "FOR" Ident ":=" Expression "TO" Expression
1254 ( "BY" ConstExpression | % BuildPseudoBy (* epsilon *) %
1255 ) % PushLineNo %
1256 % BuildStmtNote (0) %
1257 "DO" % BuildForToByDo %
1258 StatementSequence % BuildStmtNote (0) %
1259 % endpostok := GetTokenNo () %
1260 "END" % BuildEndFor (endpostok) %
1261 =:
1262
1263LoopStatement := "LOOP"
1264 % BuildLoop %
1265 StatementSequence % BuildStmtNote (0) %
1266 "END" % BuildEndLoop %
1267 =:
1268
1269WithStatement := % VAR
1270 tok: CARDINAL ; %
1271 "WITH" % tok := GetTokenNo () -1 %
1272 Designator % StartBuildWith (tok) %
1273 % BuildStmtNote (0) %
1274 "DO"
1275 StatementSequence
1276 % BuildStmtNote (0) %
1277 "END" % EndBuildWith %
1278 =:
1279
1280ProcedureDeclaration := ProcedureHeading ";" ProcedureBlock % BuildProcedureEnd ;
1281 PushAutoOn %
1282
1283 Ident % EndBuildProcedure ;
1284 PopAuto %
1285 =:
1286
1287DefineBuiltinProcedure := [ "__ATTRIBUTE__" "__BUILTIN__"
1288 "(" "(" % PushAutoOff %
1289 Ident % PopAuto %
1290 ")" ")" | "__INLINE__" ]
1291 =:
1292
1293ProcedureHeading := "PROCEDURE" % M2Error.DefaultProcedure %
1294 % PushAutoOn %
1295 DefineBuiltinProcedure
1296 ( Ident
1297 % StartBuildProcedure ;
1298 PushAutoOff %
1299 [ FormalParameters ] AttributeNoReturn
1300 % BuildProcedureHeading ;
1301 PopAuto %
1302 ) % PopAuto %
1303 =:
1304
1305Builtin := [ "__BUILTIN__" | "__INLINE__" ] =:
1306
1307DefProcedureHeading := "PROCEDURE" % M2Error.DefaultProcedure %
1308 % PushAutoOn %
1309 Builtin
1310 ( Ident
1311 % StartBuildProcedure ;
1312 PushAutoOff %
1313 [ DefFormalParameters ] AttributeNoReturn
1314 % BuildProcedureHeading ;
1315 PopAuto %
1316 ) % PopAuto %
1317 % M2Error.LeaveErrorScope %
1318 =:
1319
1320AttributeNoReturn := [ "<*" Ident "*>" ] =:
1321
1322AttributeUnused := [ "<*" Ident "*>" ] =:
1323
1324-- introduced procedure block so we can produce more informative
1325-- error messages
1326
1327ProcedureBlock := % BuildProcedureStart %
1328 { Declaration } % BuildProcedureBegin %
1329 [ "BEGIN" % BuildStmtNote (-1) %
1330 ProcedureBlockBody ] % BuildStmtNote (0) %
1331 "END"
1332 =:
1333
1334Block := { Declaration }
1335 % StartBuildInit (GetTokenNo ()) %
1336 InitialBlock % EndBuildInit (GetTokenNo ()) ;
1337 StartBuildFinally (GetTokenNo ()) %
1338 FinalBlock % EndBuildFinally (GetTokenNo ()) %
1339 "END"
1340 =:
1341
1342InitialBlock := [ "BEGIN" % BuildStmtNote (-1) %
1343 InitialBlockBody ] =:
1344
1345FinalBlock := [ "FINALLY" % BuildStmtNote (-1) %
1346 FinalBlockBody ] =:
1347
1348InitialBlockBody := NormalPart [
1349 "EXCEPT" % BuildStmtNote (-1) %
1350 % BuildExceptInitial (GetTokenNo() -1) %
1351 ExceptionalPart ] =:
1352
1353FinalBlockBody := NormalPart [
1354 "EXCEPT" % BuildStmtNote (-1) %
1355 % BuildExceptFinally (GetTokenNo() -1) %
1356 ExceptionalPart ] =:
1357
1358ProcedureBlockBody := NormalPart [
1359 "EXCEPT" % BuildStmtNote (-1) %
1360 % BuildExceptProcedure (GetTokenNo() -1) %
1361 ExceptionalPart ] =:
1362
1363NormalPart := StatementSequence =:
1364
1365ExceptionalPart := StatementSequence % BuildReThrow (GetTokenNo()) %
1366 =:
1367
1368Declaration := "CONST" { ConstantDeclaration ";" } |
1369 "TYPE" { TypeDeclaration ";" } |
1370 "VAR" { VariableDeclaration ";" } |
1371 ProcedureDeclaration ";" |
1372 ModuleDeclaration ";" =:
1373
1374DefFormalParameters := "(" [ DefMultiFPSection ] ")" FormalReturn =:
1375
1376DefMultiFPSection := DefExtendedFP |
1377 FPSection [ ";" DefMultiFPSection ] =:
1378
1379FormalParameters := "(" [ MultiFPSection ] ")" FormalReturn =:
1380
1381MultiFPSection := ExtendedFP |
1382 FPSection [ ";" MultiFPSection ] =:
1383
1384FPSection := NonVarFPSection | VarFPSection =:
1385
1386DefExtendedFP := DefOptArg | "..." =:
1387
1388ExtendedFP := OptArg | "..." =:
1389
1390VarFPSection := "VAR" IdentList ":" FormalType [ AttributeUnused ] =:
1391
1392NonVarFPSection := IdentList ":" FormalType [ AttributeUnused ] =:
1393
1394OptArg := "[" Ident ":" FormalType [ "=" ConstExpression % BuildOptArgInitializer %
1395 ] "]" =:
1396
1397DefOptArg := "[" Ident ":" FormalType "=" ConstExpression % BuildOptArgInitializer %
1398 "]" =:
1399
1400FormalType := { "ARRAY" "OF" } Qualident =:
1401
1402ModuleDeclaration := % VAR modulet: CARDINAL ; %
1403 % modulet := GetTokenNo () %
1404 "MODULE" % M2Error.DefaultInnerModule %
1405 % PushAutoOn %
1406 Ident % StartBuildInnerModule %
1407 % BuildModuleStart (modulet) ;
1408 PushAutoOff %
1409 [ Priority ] ";"
1410 { Import } [ Export ]
1411 Block % PushAutoOn %
1412 Ident % EndBuildInnerModule %
1413 % PopAuto ; PopAuto ; PopAuto %
1414 =:
1415
1416Priority := "[" % PushAutoOn %
1417 ConstExpression % BuildModulePriority ;
1418 PopAuto %
1419 "]" =:
1420
1421Export := "EXPORT" ( "QUALIFIED"
1422 IdentList |
1423 "UNQUALIFIED"
1424 IdentList |
1425 IdentList ) ";" =:
1426
1427FromImport := % PushAutoOn %
1428 "FROM" Ident "IMPORT" IdentList ";" % CheckImportListOuterModule %
1429 % PopAuto %
1430 =:
1431
1432WithoutFromImport := % PushAutoOff %
1433 "IMPORT" IdentList ";"
1434 % PopAuto %
1435 =:
1436
1437Import := FromImport | WithoutFromImport =:
1438
1439DefinitionModule := % VAR deft, endt: CARDINAL ; %
1440 % deft := GetTokenNo () %
1441 "DEFINITION" % M2Error.DefaultDefinitionModule %
1442 "MODULE" % PushAutoOn %
1443 [ "FOR" string ]
1444 Ident % StartBuildDefFile (deft) ;
1445 P3StartBuildDefModule ;
1446 PushAutoOff %
1447 ";"
1448 { Import } [ Export
1449 ]
1450 { Definition } % endt := GetTokenNo () %
1451 "END" % PushAutoOn %
1452 Ident % EndBuildFile (endt) ;
1453 P3EndBuildDefModule %
1454 "." % PopAuto ; PopAuto ; PopAuto %
1455 =:
1456
1457Definition := "CONST" { ConstantDeclaration ";" } |
1458 "TYPE"
1459 { Ident ( ";"
1460 | "=" Type Alignment ";" )
1461 }
1462 |
1463 "VAR" { VariableDeclaration ";" } |
1464 DefProcedureHeading ";" =:
1465
c4637cbe
GM
1466AsmStatement := % VAR CurrentAsm: CARDINAL ;
1467 tok: CARDINAL ; %
1468 % tok := GetTokenNo () %
8089f26b 1469 'ASM' % PushAutoOn ;
c4637cbe
GM
1470 PushT (0) ; (* operand count *)
1471 PushT (MakeGnuAsm ())
1eee94d3 1472 %
c4637cbe
GM
1473 [ 'VOLATILE' % PopT (CurrentAsm) ;
1474 PutGnuAsmVolatile (CurrentAsm) ;
1475 PushT (CurrentAsm)
1eee94d3 1476 %
8089f26b 1477 ] '(' AsmOperands % PopNothing ; (* throw away interface sym *)
c4637cbe 1478 BuildAsm (tok) ;
8089f26b
GM
1479 PopNothing ; (* throw away count *)
1480 PopAuto
1eee94d3
GM
1481 %
1482 ')' =:
1483
1484AsmOperands := % VAR CurrentAsm, count: CARDINAL ;
1485 str: CARDINAL ;
1486 %
c4637cbe
GM
1487 ConstExpression % PopT (str) ;
1488 PopT (CurrentAsm) ;
1489 Assert (IsGnuAsm (CurrentAsm) OR IsGnuAsmVolatile (CurrentAsm)) ;
1490 PopT (count) ;
8089f26b 1491 IF DebugAsm
1eee94d3 1492 THEN
c4637cbe 1493 printf1 ('1: count of asm operands: %d\n', count)
8089f26b 1494 END ;
c4637cbe 1495 PushT (count) ;
8089f26b 1496 (* adds the name/instruction for this asm *)
c4637cbe
GM
1497 PutGnuAsm (CurrentAsm, str) ;
1498 PushT (CurrentAsm) ;
1499 PushT (NulSym) (* the InterfaceSym *)
1eee94d3
GM
1500 %
1501 ( AsmOperandSpec | % (* epsilon *)
c4637cbe 1502 PutGnuAsmSimple (CurrentAsm)
1eee94d3
GM
1503 %
1504 )
1505 =:
1506
1507AsmOperandSpec := % VAR CurrentAsm, outputs, inputs, trash, count: CARDINAL ;
1508 %
8089f26b
GM
1509 ':' AsmOutputList % PopT(outputs) ;
1510 PopT(CurrentAsm) ;
1511 Assert(IsGnuAsm(CurrentAsm) OR IsGnuAsmVolatile(CurrentAsm)) ;
1512 PopT(count) ;
1513 IF DebugAsm
1eee94d3 1514 THEN
8089f26b
GM
1515 printf1('2: output count of asm operands: %d\n', count)
1516 END ;
1517 PutGnuAsmOutput(CurrentAsm, outputs) ;
1518 PushT(0) ; (* reset count *)
1519 PushT(CurrentAsm) ;
1520 PushT(NulSym) (* the InterfaceSym *)
1eee94d3 1521 %
8089f26b
GM
1522 [ ':' AsmInputList % PopT(inputs) ;
1523 PopT(CurrentAsm) ;
1524 Assert(IsGnuAsm(CurrentAsm) OR IsGnuAsmVolatile(CurrentAsm)) ;
1525 PopT(count) ;
1526 IF DebugAsm
1eee94d3 1527 THEN
8089f26b
GM
1528 printf1('3: input count of asm operands: %d\n', count)
1529 END ;
1530 PutGnuAsmInput(CurrentAsm, inputs) ;
1531 PushT(0) ; (* reset count *)
1532 PushT(CurrentAsm) ;
1533 PushT(NulSym) (* the InterfaceSym *)
1eee94d3 1534 %
8089f26b
GM
1535 [ ':' AsmTrashList % PopT(trash) ;
1536 PopT(CurrentAsm) ;
1537 Assert(IsGnuAsm(CurrentAsm) OR IsGnuAsmVolatile(CurrentAsm)) ;
1538 PopT(count) ;
1539 IF DebugAsm
1eee94d3 1540 THEN
8089f26b
GM
1541 printf1('4: trash count of asm operands: %d\n', count)
1542 END ;
1543 PutGnuAsmTrash(CurrentAsm, trash) ;
1544 PushT(0) ; (* reset count *)
1545 PushT(CurrentAsm) ;
1546 PushT(NulSym) (* the InterfaceSym *)
1eee94d3 1547 %
990d10ab 1548 ] ]
1eee94d3
GM
1549 =:
1550
990d10ab
GM
1551AsmOutputList := [ AsmOutputElement ] { ',' AsmOutputElement } =:
1552
1553AsmInputList := [ AsmInputElement ] { ',' AsmInputElement } =:
1eee94d3
GM
1554
1555NamedOperand := '[' Ident ']' =:
1556
1557AsmOperandName := ( NamedOperand
1558 | % IF IsAutoPushOn()
1559 THEN
8089f26b 1560 PushTF (NulName, identtok)
1eee94d3
GM
1561 END
1562 %
1563 )
1564 =:
1565
990d10ab 1566AsmInputElement := AsmOperandName
8089f26b 1567 ConstExpression '(' Expression % BuildAsmElement (TRUE, FALSE)
990d10ab
GM
1568 %
1569 ')'
1570 =:
1eee94d3 1571
990d10ab 1572AsmOutputElement := AsmOperandName
8089f26b 1573 ConstExpression '(' Expression % BuildAsmElement (FALSE, TRUE)
1eee94d3 1574 %
990d10ab
GM
1575 ')'
1576 =:
1eee94d3 1577
8089f26b 1578AsmTrashList := [ ConstExpression % BuildAsmTrash
1eee94d3 1579 %
8089f26b 1580 ] { ',' ConstExpression % BuildAsmTrash
1eee94d3 1581 %
990d10ab 1582 } =:
1eee94d3
GM
1583
1584FNB