2 -- m2-c.bnf grammar and associated actions for pass C.
4 -- Copyright (C) 2001-2025 Free Software Foundation, Inc.
5 -- Contributed by Gaius Mulley <gaius.mulley@southwales.ac.uk>.
7 -- This file is part of GNU Modula-2.
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)
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.
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.
26 Copyright (C) 2001-2025 Free Software Foundation, Inc.
27 Contributed by Gaius Mulley <gaius.mulley@southwales.ac.uk>.
29 This file is part of GNU Modula-2.
31 GNU Modula-2 is free software; you can redistribute it and/or modify
32 it under the terms of the GNU General Public License as published by
33 the Free Software Foundation; either version 3, or (at your option)
36 GNU Modula-2 is distributed in the hope that it will be useful, but
37 WITHOUT ANY WARRANTY; without even the implied warranty of
38 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
39 General Public License for more details.
41 You should have received a copy of the GNU General Public License
42 along with GNU Modula-2; see the file COPYING. If not,
43 see <https://www.gnu.org/licenses/>. *)
45 IMPLEMENTATION MODULE PCBuild ;
47 FROM M2LexBuf IMPORT currentstring, currenttoken, GetToken, InsertToken,
48 InsertTokenAndRewind, GetTokenNo, MakeVirtualTok ;
50 FROM M2MetaError IMPORT MetaErrorStringT0 ;
51 FROM NameKey IMPORT NulName, Name, makekey ;
52 FROM DynamicStrings IMPORT String, InitString, KillString, Mark, ConCat, ConCatChar ;
53 FROM M2Printf IMPORT printf0 ;
54 FROM M2Debug IMPORT Assert ;
55 FROM P2SymBuild IMPORT BuildString, BuildNumber ;
57 FROM 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 ;
64 FROM M2Quads IMPORT Top, PushT, PopT, PushTF, PopTF, PopNothing, OperandT, OperandTok,
66 PushTFn, PopTFn, PushTFtok, PopTtok, PopTFtok, PushTtok, PushTFntok,
67 PushT, PushTF, IsAutoPushOn, PushAutoOff, PushAutoOn, PopAuto,
69 BuildTypeForConstructor, BuildConstructor, BuildConstructorEnd,
71 NextConstructorField, SilentBuildConstructor,
72 PushInConstExpression, PopInConstExpression ;
74 FROM P3SymBuild IMPORT CheckCanBeImported ;
76 FROM PCSymBuild IMPORT PCStartBuildProgModule,
79 PCStartBuildDefModule,
82 PCStartBuildImpModule,
85 PCStartBuildInnerModule,
86 PCEndBuildInnerModule,
88 PCStartBuildProcedure,
89 PCBuildProcedureHeading,
92 PCBuildImportOuterModule,
93 PCBuildImportInnerModule,
101 PushConstructorCastType,
104 PushConstFunctionType,
106 PushConstAttributeType,
107 PushConstAttributePairType,
111 FROM SymbolTable IMPORT MakeGnuAsm, PutGnuAsmVolatile, PutGnuAsm, PutGnuAsmInput,
112 PutGnuAsmOutput, PutGnuAsmTrash, PutGnuAsmVolatile,
115 GetSymName, GetType, SkipType,
117 StartScope, EndScope,
119 IsVarParam, IsProcedure, IsDefImp, IsModule,
120 IsRecord, IsProcType,
121 GetCurrentModule, IsInnerModule, IsImported,
123 GetSym, GetLocalSym ;
125 FROM M2Batch IMPORT IsModuleKnown ;
127 FROM M2StateCheck IMPORT StateCheck,
128 InitState, PushState, PopState, InclConst, ExclConst,
129 InclConstructor, ExclConstructor,
130 InclConstFunc, CheckQualident ;
140 BlockState: StateCheck ;
141 seenError : BOOLEAN ;
144 PROCEDURE ErrorString (s: String) ;
146 MetaErrorStringT0 (GetTokenNo (), s) ;
151 PROCEDURE ErrorArray (a: ARRAY OF CHAR) ;
153 ErrorString (InitString (a))
157 PROCEDURE ErrorArrayAt (a: ARRAY OF CHAR; tok: CARDINAL) ;
159 MetaErrorStringT0 (tok, InitString (a))
163 % declaration PCBuild begin
167 SyntaxError - after a syntax error we skip all tokens up until we reach
171 PROCEDURE SyntaxError (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
176 printf0('\nskipping token *** ')
178 (* --fixme-- this assumes a 32 bit word size. *)
179 WHILE NOT (((ORD(currenttoken)<32) AND (currenttoken IN stopset0)) OR
180 ((ORD(currenttoken)>=32) AND (ORD(currenttoken)<64) AND (currenttoken IN stopset1)) OR
181 ((ORD(currenttoken)>=64) AND (currenttoken IN stopset2)))
196 PROCEDURE SyntaxCheck (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
198 (* --fixme-- this assumes a 32 bit word size. *)
199 IF NOT (((ORD(currenttoken)<32) AND (currenttoken IN stopset0)) OR
200 ((ORD(currenttoken)>=32) AND (ORD(currenttoken)<64) AND (currenttoken IN stopset1)) OR
201 ((ORD(currenttoken)>=64) AND (currenttoken IN stopset2)))
203 SyntaxError(stopset0, stopset1, stopset2)
209 WarnMissingToken - generates a warning message about a missing token, t.
212 PROCEDURE WarnMissingToken (t: toktype) ;
231 str := DescribeStop(s0, s1, s2) ;
233 str := ConCat(InitString('syntax error,'), Mark(str)) ;
234 MetaErrorStringT0 (GetTokenNo (), str)
235 END WarnMissingToken ;
239 MissingToken - generates a warning message about a missing token, t.
242 PROCEDURE MissingToken (t: toktype) ;
244 WarnMissingToken(t) ;
245 IF (t#identtok) AND (t#integertok) AND (t#realtok) AND (t#stringtok)
249 printf0('inserting token\n')
260 PROCEDURE CheckAndInsert (t: toktype; stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) : BOOLEAN ;
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))
266 WarnMissingToken(t) ;
267 InsertTokenAndRewind(t) ;
279 PROCEDURE InStopSet (t: toktype; stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) : BOOLEAN ;
281 IF ((ORD(t)<32) AND (t IN stopset0)) OR
282 ((ORD(t)>=32) AND (ORD(t)<64) AND (t IN stopset1)) OR
283 ((ORD(t)>=64) AND (t IN stopset2))
293 PeepToken - peep token checks to see whether the stopset is satisfied by currenttoken
294 If it is not then it will insert a token providing the token
295 is one of ; ] ) } . OF END ,
297 if the stopset contains <identtok> then we do not insert a token
300 PROCEDURE PeepToken (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
302 (* and again (see above re: ORD)
304 IF (NOT (((ORD(currenttoken)<32) AND (currenttoken IN stopset0)) OR
305 ((ORD(currenttoken)>=32) AND (ORD(currenttoken)<64) AND (currenttoken IN stopset1)) OR
306 ((ORD(currenttoken)>=64) AND (currenttoken IN stopset2)))) AND
307 (NOT InStopSet(identtok, stopset0, stopset1, stopset2))
309 (* SyntaxCheck would fail since currentoken is not part of the stopset
310 we check to see whether any of currenttoken might be a commonly omitted token *)
311 IF CheckAndInsert(semicolontok, stopset0, stopset1, stopset2) OR
312 CheckAndInsert(rsbratok, stopset0, stopset1, stopset2) OR
313 CheckAndInsert(rparatok, stopset0, stopset1, stopset2) OR
314 CheckAndInsert(rcbratok, stopset0, stopset1, stopset2) OR
315 CheckAndInsert(periodtok, stopset0, stopset1, stopset2) OR
316 CheckAndInsert(oftok, stopset0, stopset1, stopset2) OR
317 CheckAndInsert(endtok, stopset0, stopset1, stopset2) OR
318 CheckAndInsert(commatok, stopset0, stopset1, stopset2)
329 PROCEDURE Expect (t: toktype; stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
336 PeepToken(stopset0, stopset1, stopset2)
341 SyntaxCheck(stopset0, stopset1, stopset2)
346 CompilationUnit - returns TRUE if the input was correct enough to parse
350 PROCEDURE CompilationUnit () : BOOLEAN ;
353 FileUnit(SetOfStop0{eoftok}, SetOfStop1{}, SetOfStop2{}) ;
355 END CompilationUnit ;
359 Ident - error checking varient of Ident
362 PROCEDURE Ident (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
366 PushTFtok (makekey (currentstring), identtok, GetTokenNo ())
368 Expect(identtok, stopset0, stopset1, stopset2)
376 PROCEDURE string (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
380 PushTF(makekey(currentstring), stringtok) ;
383 Expect(stringtok, stopset0, stopset1, stopset2)
391 PROCEDURE Integer (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
395 PushTFtok (makekey(currentstring), integertok, GetTokenNo ()) ;
398 Expect(integertok, stopset0, stopset1, stopset2)
406 PROCEDURE Real (stopset0: SetOfStop0; stopset1: SetOfStop1; stopset2: SetOfStop2) ;
410 PushTFtok (makekey(currentstring), realtok, GetTokenNo ()) ;
413 Expect(realtok, stopset0, stopset1, stopset2)
418 PushTFQualident - push the result of the Qualident
419 to the stack. It checks to see if init
420 is a procedure or proc type and if so
421 it does not push the return type.
424 PROCEDURE PushTFQualident (tok, tokstart: CARDINAL;
429 tok := MakeVirtualTok (tokstart, tokstart, tok)
431 IF IsProcedure (init) OR IsProcType (init)
433 PushTtok (init, tok) ;
434 Annotate ("%1s(%1d)||qualident procedure/proctype") ;
436 Annotate ("%1s(%1d)|%1s(%1d)||qualident|type") ;
437 PushTFtok (init, GetType (init), tok) ;
439 END PushTFQualident ;
443 CheckModuleQualident - check to see if the beginning ident of the qualident is an
447 PROCEDURE CheckModuleQualident (stopset0: SetOfStop0;
448 stopset1: SetOfStop1;
449 stopset2: SetOfStop2) ;
454 tok, tokstart: CARDINAL ;
456 PopTtok (name, tokstart) ;
458 init := RequestSym (tok, name) ;
459 IF IsImported (GetCurrentModule (), init) AND (IsDefImp (init) OR IsModule (init))
461 WHILE IsDefImp (init) OR IsModule (init) DO
462 Expect (periodtok, stopset0, stopset1, stopset2 + SetOfStop2{identtok}) ;
464 Ident (stopset0, stopset1, stopset2) ;
465 PopTtok (name, tok) ;
466 nextLevel := RequestSym (tok, name) ;
468 CheckCanBeImported (init, nextLevel) ;
471 PushTFQualident (tok, tokstart, init) ;
474 PushTFQualident (tok, tokstart, init)
476 END CheckModuleQualident ;
480 BlockState := InitState ()
483 error 'ErrorArray' 'ErrorString'
484 tokenfunc 'currenttoken'
486 token '' eoftok -- internal token
491 token ':=' becomestok
492 token '&' ambersandtok
495 token ";" semicolontok
498 token '[' lsbratok -- left square brackets
499 token ']' rsbratok -- right square brackets
500 token '{' lcbratok -- left curly brackets
501 token '}' rcbratok -- right curly brackets
503 token "'" singlequotetok
508 token '<>' lessgreatertok
509 token '<=' lessequaltok
510 token '>=' greaterequaltok
511 token '<*' ldirectivetok
512 token '*>' rdirectivetok
513 token '..' periodperiodtok
515 token '"' doublequotestok
518 token 'ARRAY' arraytok
519 token 'BEGIN' begintok
522 token 'CONST' consttok
523 token 'DEFINITION' definitiontok
527 token 'ELSIF' elsiftok
529 token 'EXCEPT' excepttok
531 token 'EXPORT' exporttok
532 token 'FINALLY' finallytok
534 token 'FORWARD' forwardtok
537 token 'IMPLEMENTATION' implementationtok
538 token 'IMPORT' importtok
542 token 'MODULE' moduletok
546 token 'PACKEDSET' packedsettok
547 token 'POINTER' pointertok
548 token 'PROCEDURE' proceduretok
549 token 'QUALIFIED' qualifiedtok
550 token 'UNQUALIFIED' unqualifiedtok
551 token 'RECORD' recordtok
553 token 'REPEAT' repeattok
554 token 'RETRY' retrytok
555 token 'RETURN' returntok
560 token 'UNTIL' untiltok
562 token 'WHILE' whiletok
565 token 'VOLATILE' volatiletok
566 token '...' periodperiodperiodtok
567 token '__DATE__' datetok
568 token '__LINE__' linetok
569 token '__FILE__' filetok
570 token '__ATTRIBUTE__' attributetok
571 token '__BUILTIN__' builtintok
572 token '__INLINE__' inlinetok
573 token 'integer number' integertok
574 token 'identifier' identtok
575 token 'real number' realtok
576 token 'string' stringtok
578 special Ident first { < identtok > } follow { }
579 special Integer first { < integertok > } follow { }
580 special Real first { < realtok > } follow { }
581 special string first { < stringtok > } follow { }
585 -- the following are provided by the module m2flex and also handbuild procedures below
586 -- Ident := Letter { ( Letter | Digit ) } =:
587 -- Integer := Digit { Digit } | OctalDigit { OctalDigit } ( " B " | " C " ) |
588 -- Digit { HexDigit } " H " =:
589 -- Real := Digit { Digit } " . " { Digit } [ ScaleFactor ] =:
590 -- ScaleFactor := " E " [ ( " + " | " - " ) ] Digit { Digit } =:
591 -- HexDigit := Digit | " A " | " B " | " C " | " D " | " E " | " F " =:
592 -- Digit := OctalDigit | " 8 " | " 9 " =:
593 -- OctalDigit := "0" | "1" | "2" | "3" | "4" | "5" | "6" | "7" =:
596 FileUnit := % PushAutoOff %
598 ImplementationOrProgramModule ) % PopAuto %
601 ProgramModule := "MODULE" % M2Error.DefaultProgramModule %
603 Ident % PCStartBuildProgModule %
608 { Import % PCBuildImportOuterModule %
611 Ident % PCEndBuildProgModule %
612 "." % PopAuto ; PopAuto %
615 ImplementationModule := "IMPLEMENTATION" % M2Error.DefaultImplementationModule %
616 "MODULE" % PushAutoOn %
617 Ident % PCStartBuildImpModule %
621 { Import % PCBuildImportOuterModule %
625 Ident % PCEndBuildImpModule %
626 "." % PopAuto ; PopAuto ; PopAuto %
629 ImplementationOrProgramModule := % PushAutoOff %
630 ( ImplementationModule | ProgramModule ) % PopAuto %
633 Number := Integer | Real =:
638 CheckModuleQualident (stopset0, stopset1, stopset2)
639 ELSE (* just parse qualident *) %
640 { "." Ident } % END %
643 ConstantDeclaration := % VAR top: CARDINAL ; %
644 % InclConst (BlockState) %
647 ( Ident "=" % StartDesConst %
649 ConstExpression % PopAuto %
653 % Assert(top=Top()) %
654 % ExclConst (BlockState) %
657 ConstExpression := % VAR top: CARDINAL ; %
659 % PushInConstExpression %
661 SimpleConstExpr [ Relation SimpleConstExpr % BuildRelationConst %
663 % PopInConstExpression %
664 % Assert(top=Top()) %
667 Relation := "=" % PushT(EqualTok) %
668 | "#" % PushT(HashTok) %
669 | "<>" % PushT(LessGreaterTok) %
670 | "<" % PushT(LessTok) %
671 | "<=" % PushT(LessEqualTok) %
672 | ">" % PushT(GreaterTok) %
673 | ">=" % PushT(GreaterEqualTok) %
674 | "IN" % PushT(InTok) %
677 SimpleConstExpr := % VAR top: CARDINAL ; %
679 UnaryOrConstTerm { ConstAddOperator ConstTerm % BuildBinaryConst %
680 } % Assert(top=Top()) %
683 UnaryOrConstTerm := "+" % PushT(PlusTok) %
684 ConstTerm % BuildUnaryConst %
685 | "-" % PushT(MinusTok) %
686 ConstTerm % BuildUnaryConst %
690 ConstAddOperator := "+" % PushT(PlusTok) %
691 | "-" % PushT(MinusTok) %
692 | "OR" % PushT(OrTok) %
695 AddOperator := "+" | "-" | "OR" =:
697 ConstTerm := % VAR top: CARDINAL ; %
699 ConstFactor % Assert(top=Top()) %
700 { ConstMulOperator ConstFactor % BuildBinaryConst %
701 % Assert(top=Top()) %
702 } % Assert(top=Top()) %
705 ConstMulOperator := "*" % PushT(TimesTok) %
706 | "/" % PushT(DivideTok) %
707 | "DIV" % PushT(DivTok) %
708 | "MOD" % PushT(ModTok) %
709 | "REM" % PushT(RemTok) %
710 | "AND" % PushT(AndTok) %
711 | "&" % PushT(AmbersandTok) %
714 MulOperator := "*" | "/" | "DIV" | "MOD" | "REM" | "AND" | "&"
717 ConstFactor := ConstNumber | ConstString |
718 ConstSetOrQualidentOrFunction |
719 "(" ConstExpression ")" |
724 ConstNumber := % PushAutoOn %
725 ( Integer % PushIntegerType %
730 -- to help satisfy LL1
732 ConstString := % PushAutoOn %
733 string % PushStringType %
737 ComponentElement := ConstExpression [ ".." ConstExpression ] =:
739 ComponentValue := ComponentElement [ 'BY' ConstExpression ] =:
741 ArraySetRecordValue := ComponentValue { ',' % NextConstructorField %
744 Constructor := '{' % InclConstructor (BlockState) %
745 % CheckQualident (OperandTok (1), BlockState, OperandT (1)) %
746 % PushConstructorCastType %
747 % PushInConstructor %
748 % BuildConstructor (GetTokenNo ()-1) %
749 [ ArraySetRecordValue ] % PopConstructor %
750 '}' % PopInConstructor %
751 % ExclConstructor (BlockState) %
754 ConstructorOrConstActualParameters := Constructor | ConstActualParameters % PushConstFunctionType %
755 % PopNothing (* pop function *) %
758 -- the entry to Constructor
760 ConstSetOrQualidentOrFunction := % PushAutoOff %
761 % VAR tokpos: CARDINAL ; %
762 % tokpos := GetTokenNo () %
765 ( ConstructorOrConstActualParameters | % CheckQualident (OperandTok (1), BlockState, OperandT (1)) %
769 | % BuildTypeForConstructor (tokpos) %
770 Constructor ) % PopAuto %
773 ConstActualParameters := % PushState (BlockState) %
774 % InclConstFunc (BlockState) %
775 % CheckQualident (OperandTok (1), BlockState, OperandT (1)) %
777 "(" [ ConstExpList ] ")"
778 % PopState (BlockState) %
781 ConstExpList := % VAR n: CARDINAL ; %
782 ConstExpression % PopT(n) %
786 { "," ConstExpression % PopT(n) %
791 ConstAttribute := % VAR top: CARDINAL ; %
793 "__ATTRIBUTE__" "__BUILTIN__" "(" "(" % PushAutoOn %
794 ConstAttributeExpression % PopAuto %
795 ")" ")" % Assert(top=Top()) %
798 ConstAttributeExpression :=
799 Ident % PushConstAttributeType %
801 | "<" Qualident ',' Ident ">" % PushConstAttributePairType %
802 % PopNothing ; PopNothing %
805 ByteAlignment := '<*' AttributeExpression '*>' =:
807 Alignment := [ ByteAlignment ] =:
809 TypeDeclaration := Ident "=" Type Alignment =:
813 ( SimpleType | ArrayType
817 | ProcedureType ) % PopAuto %
820 SimpleType := Qualident [ SubrangeType ] | Enumeration | SubrangeType =:
822 Enumeration := "(" IdentList ")" =:
824 IdentList := Ident % VAR
827 % on := IsAutoPushOn() ;
842 SubrangeType := "[" ConstExpression ".." ConstExpression "]" =:
853 RecordType := "RECORD" [ DefaultRecordAttributes ] FieldListSequence "END" =:
855 DefaultRecordAttributes := '<*' AttributeExpression '*>' =:
857 RecordFieldPragma := [ '<*' FieldPragmaExpression
858 { ',' FieldPragmaExpression } '*>' ] =:
860 FieldPragmaExpression := % PushAutoOff %
861 Ident [ '(' ConstExpression ')' ]
865 AttributeExpression := % PushAutoOff %
866 Ident '(' ConstExpression ')' % PopAuto %
869 FieldListSequence := FieldListStatement { ";" FieldListStatement } =:
871 FieldListStatement := [ FieldList ] =:
873 FieldList := IdentList ":"
874 Type RecordFieldPragma
878 Varient { "|" Varient }
884 TagIdent := [ Ident ] =:
886 CaseTag := TagIdent [":" Qualident ] =:
888 Varient := [ VarientCaseLabelList ":" FieldListSequence ] =:
890 VarientCaseLabelList := VarientCaseLabels { "," VarientCaseLabels } =:
892 VarientCaseLabels := ConstExpression ( ".." ConstExpression
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!
905 SilentConstExpression := % PushAutoOff %
906 SilentSimpleConstExpr
907 [ SilentRelation SilentSimpleConstExpr ] % PopAuto %
910 SilentRelation := "=" | "#" | "<>" | "<" | "<=" | ">" | ">=" | "IN" =:
912 SilentSimpleConstExpr := SilentUnaryOrConstTerm { SilentAddOperator SilentConstTerm } =:
914 SilentUnaryOrConstTerm := "+" SilentConstTerm | "-" SilentConstTerm | SilentConstTerm =:
916 SilentAddOperator := "+" | "-" | "OR" =:
918 SilentConstTerm := SilentConstFactor { SilentMulOperator SilentConstFactor } =:
920 SilentMulOperator := "*" | "/" | "DIV" | "MOD" | "REM" | "AND" | "&" =:
922 SilentConstFactor := Number | SilentConstString | SilentConstSetOrQualidentOrFunction |
923 "(" SilentConstExpression ")" | "NOT" SilentConstFactor
924 | SilentConstAttribute =:
926 SilentConstString := string =:
928 SilentConstAttribute := "__ATTRIBUTE__" "__BUILTIN__" "(" "(" SilentConstAttributeExpression ")" ")" =:
930 SilentConstAttributeExpression := Ident | "<" Ident ',' SilentConstString ">" =:
932 SilentComponentElement := SilentConstExpression [ ".." SilentConstExpression ] =:
934 SilentComponentValue := SilentComponentElement [ 'BY' SilentConstExpression ] =:
936 SilentArraySetRecordValue := SilentComponentValue { ',' SilentComponentValue } =:
938 SilentConstructor := '{' % SilentBuildConstructor %
939 [ SilentArraySetRecordValue ] '}' =:
941 SilentConstSetOrQualidentOrFunction := SilentConstructor | Qualident
942 [ SilentConstructor | SilentActualParameters ] =:
944 SilentActualParameters := "(" [ SilentExpList ] ")" =:
946 SilentExpList := SilentConstExpression { "," SilentConstExpression } =:
948 -- end of the Silent constant rules
950 SetType := ( "SET" | "PACKEDSET" ) "OF" SimpleType =:
952 PointerType := "POINTER" "TO"
956 ProcedureType := "PROCEDURE"
957 [ FormalTypeList ] =:
959 FormalTypeList := "(" ( ")" FormalReturn |
960 ProcedureParameters ")" FormalReturn ) =:
962 FormalReturn := [ ":" OptReturnType ] =:
964 OptReturnType := "[" Qualident "]" | Qualident =:
966 ProcedureParameters := ProcedureParameter
967 { "," ProcedureParameter } =:
969 ProcedureParameter := "..." | "VAR" FormalType | FormalType =:
972 VarIdent := Ident [ "[" ConstExpression "]" ]
975 VarIdentList := VarIdent { "," VarIdent }
978 VariableDeclaration := VarIdentList ":" Type Alignment
981 Designator := Qualident { SubDesignator } =:
983 SubDesignator := "." Ident | "[" ArrayExpList "]" | "^"
986 ArrayExpList := Expression { "," Expression } =:
988 ExpList := Expression { "," Expression } =:
990 Expression := SimpleExpression [ SilentRelation SimpleExpression ]
993 SimpleExpression := UnaryOrTerm { AddOperator Term } =:
995 UnaryOrTerm := "+" Term | "-" Term | Term =:
997 Term := Factor { MulOperator Factor } =:
999 Factor := Number | string | SetOrDesignatorOrFunction |
1000 "(" Expression ")" | "NOT" ( Factor | ConstAttribute ) =:
1002 PushQualident := % VAR name : Name ;
1003 init, ip1 : CARDINAL ;
1004 tok, tokstart: CARDINAL ; %
1006 Ident % IF IsAutoPushOn()
1008 PopTtok (name, tokstart) ;
1010 init := GetSym (name) ;
1013 PushTFntok (NulSym, NulSym, name, tok)
1015 WHILE IsDefImp (init) OR IsModule (init) DO
1016 IF currenttoken # periodtok
1018 ErrorArrayAt ("expecting '.' after module in the construction of a qualident", tok) ;
1021 tok := MakeVirtualTok (tokstart, tokstart, tok)
1023 PushTtok (init, tok) ;
1027 Expect (periodtok, stopset0, stopset1, stopset2 + SetOfStop2{identtok}) ;
1029 Ident (stopset0, stopset1, stopset2) ;
1030 PopTtok (name, tok) ;
1031 ip1 := GetSym (name) ;
1034 ErrorArrayAt ("unknown ident in the construction of a qualident", tok) ;
1038 tok := MakeVirtualTok (tokstart, tokstart, tok)
1040 PushTFntok (NulSym, NulSym, name, tok) ;
1047 CheckCanBeImported (init, ip1) ;
1053 tok := MakeVirtualTok (tokstart, tokstart, tok)
1055 IF IsProcedure (init) OR IsProcType (init)
1057 PushTtok (init, tok)
1059 PushTFtok (init, GetType(init), tok)
1063 { "." Ident } % END %
1067 ConstructorOrSimpleDes := Constructor | % PopNothing %
1068 SimpleDes [ ActualParameters ]
1071 SetOrDesignatorOrFunction := % VAR tokpos: CARDINAL ; %
1072 % tokpos := GetTokenNo () %
1076 ( ConstructorOrSimpleDes | % PopNothing %
1079 % BuildTypeForConstructor (tokpos) %
1084 -- SimpleDes := { "." Ident | "[" ExpList "]" | "^" } =:
1085 SimpleDes := { SubDesignator } =:
1087 ActualParameters := "(" [ ExpList ] ")" =:
1089 ExitStatement := "EXIT" =:
1091 ReturnStatement := "RETURN" [ Expression ] =:
1093 Statement := % PushAutoOff %
1094 [ AssignmentOrProcedureCall | IfStatement | CaseStatement |
1095 WhileStatement | RepeatStatement | LoopStatement |
1096 ForStatement | WithStatement | AsmStatement |
1097 ExitStatement | ReturnStatement | RetryStatement
1101 RetryStatement := "RETRY" =:
1103 AssignmentOrProcedureCall := % VAR top: CARDINAL ; %
1105 Designator ( ":=" Expression |
1106 ActualParameters | % (* epsilon *) %
1107 ) % Assert(top=Top()) %
1110 -- these two break LL1 as both start with a Designator
1111 -- ProcedureCall := Designator [ ActualParameters ] =:
1112 -- Assignment := Designator ":=" Expression =:
1114 StatementSequence := % VAR top: CARDINAL ; %
1116 Statement % Assert(top=Top()) %
1118 Statement % Assert(top=Top()) %
1122 IfStatement := "IF" Expression "THEN"
1124 { "ELSIF" Expression "THEN" StatementSequence
1126 [ "ELSE" StatementSequence ] "END"
1129 CaseStatement := "CASE" Expression "OF" Case { "|" Case }
1133 CaseEndStatement := "END" | "ELSE" StatementSequence "END"
1136 Case := [ CaseLabelList ":" StatementSequence ]
1139 CaseLabelList := CaseLabels { "," CaseLabels } =:
1141 CaseLabels := ConstExpression [ ".." ConstExpression ] =:
1143 WhileStatement := "WHILE" Expression "DO" StatementSequence "END" =:
1145 RepeatStatement := "REPEAT" StatementSequence "UNTIL" Expression =:
1147 ForStatement := "FOR" Ident ":=" Expression "TO" Expression
1148 [ "BY" ConstExpression ] "DO"
1153 LoopStatement := "LOOP" StatementSequence "END" =:
1155 WithStatement := "WITH" Designator "DO"
1160 ProcedureDeclaration := % VAR top: CARDINAL ; %
1162 ProcedureHeading ";" PostProcedureHeading % Assert (top = Top ()) %
1165 PostProcedureHeading := ProperProcedure | ForwardDeclaration =:
1167 ForwardDeclaration := "FORWARD" % PCEndBuildForward %
1170 ProperProcedure := ProcedureBlock % PushAutoOn %
1171 Ident % PCEndBuildProcedure %
1175 DefineBuiltinProcedure := [ "__ATTRIBUTE__" "__BUILTIN__"
1176 "(" "(" % PushAutoOff %
1178 ")" ")" | "__INLINE__" ]
1181 ProcedureHeading := "PROCEDURE" % M2Error.DefaultProcedure %
1183 DefineBuiltinProcedure
1185 % PCStartBuildProcedure %
1187 [ FormalParameters ] AttributeNoReturn
1188 % PCBuildProcedureHeading %
1193 Builtin := [ "__BUILTIN__" | "__INLINE__" ] =:
1195 DefProcedureHeading := "PROCEDURE" % M2Error.DefaultProcedure %
1199 % PCStartBuildProcedure %
1201 [ DefFormalParameters ] AttributeNoReturn
1202 % PCBuildProcedureHeading %
1205 % M2Error.LeaveErrorScope %
1208 AttributeNoReturn := [ "<*" Ident "*>" ] =:
1210 AttributeUnused := [ "<*" Ident "*>" ] =:
1212 -- introduced procedure block so we can produce more informative
1215 ProcedureBlock := % VAR top: CARDINAL ; %
1217 { Declaration % Assert(top=Top()) %
1218 } [ "BEGIN" ProcedureBlockBody % Assert(top=Top()) %
1219 ] "END" % Assert(top=Top()) %
1222 Block := % VAR top: CARDINAL ; %
1224 { Declaration } InitialBlock FinalBlock
1225 "END" % Assert(top=Top()) %
1228 InitialBlock := [ "BEGIN" InitialBlockBody ] =:
1230 FinalBlock := [ "FINALLY" FinalBlockBody ] =:
1232 InitialBlockBody := NormalPart [ "EXCEPT" ExceptionalPart ] =:
1234 FinalBlockBody := NormalPart [ "EXCEPT" ExceptionalPart ] =:
1236 ProcedureBlockBody := NormalPart [ "EXCEPT" ExceptionalPart ] =:
1238 NormalPart := StatementSequence =:
1240 ExceptionalPart := StatementSequence =:
1242 Declaration := "CONST" { ConstantDeclaration ";" } |
1243 "TYPE" { TypeDeclaration ";" } |
1244 "VAR" { VariableDeclaration ";" } |
1245 ProcedureDeclaration ";" |
1246 ModuleDeclaration ";" =:
1248 DefFormalParameters := "(" [ DefMultiFPSection ] ")" FormalReturn =:
1250 DefMultiFPSection := DefExtendedFP |
1251 FPSection [ ";" DefMultiFPSection ] =:
1253 FormalParameters := "(" [ MultiFPSection ] ")" FormalReturn =:
1255 MultiFPSection := ExtendedFP |
1256 FPSection [ ";" MultiFPSection ] =:
1258 FPSection := NonVarFPSection | VarFPSection =:
1260 DefExtendedFP := DefOptArg | "..." =:
1262 ExtendedFP := OptArg | "..." =:
1264 VarFPSection := "VAR" IdentList ":" FormalType [ AttributeUnused ] =:
1266 NonVarFPSection := IdentList ":" FormalType [ AttributeUnused ] =:
1268 OptArg := "[" Ident ":" FormalType [ "=" ConstExpression ] "]" =:
1270 DefOptArg := "[" Ident ":" FormalType "=" ConstExpression "]" =:
1272 FormalType := { "ARRAY" "OF" } Qualident =:
1274 ModuleDeclaration := "MODULE" % M2Error.DefaultInnerModule %
1276 Ident % PCStartBuildInnerModule %
1279 { Import % PCBuildImportInnerModule %
1282 Block % PushAutoOn %
1283 Ident % PCEndBuildInnerModule %
1284 % PopAuto ; PopAuto ; PopAuto %
1287 Priority := "[" ConstExpression "]" =:
1289 Export := "EXPORT" ( "QUALIFIED"
1295 Import := % PushAutoOn %
1296 ( "FROM" Ident "IMPORT" IdentList ";" |
1297 "IMPORT" % PushT(ImportTok)
1298 (* determines whether Ident or Module *) %
1299 IdentList ";" ) % PopAuto %
1302 DefinitionModule := "DEFINITION" % M2Error.DefaultDefinitionModule %
1303 "MODULE" % PushAutoOn %
1305 Ident % PCStartBuildDefModule ;
1308 { Import % PCBuildImportOuterModule %
1312 "END" % PushAutoOn %
1313 Ident % PCEndBuildDefModule %
1314 "." % PopAuto ; PopAuto ; PopAuto %
1317 Definition := "CONST" { ConstantDeclaration ";" } |
1320 | "=" Type Alignment ";" )
1323 "VAR" { VariableDeclaration ";" } |
1324 DefProcedureHeading ";" =:
1326 AsmStatement := 'ASM' [ 'VOLATILE' ] '(' AsmOperands ')' =:
1328 NamedOperand := '[' Ident ']' =:
1330 AsmOperandName := [ NamedOperand ] =:
1332 AsmOperands := ConstExpression [ ':' AsmList [ ':' AsmList [ ':' TrashList ] ] ]
1335 AsmList := [ AsmElement ] { ',' AsmElement } =:
1337 AsmElement := AsmOperandName ConstExpression '(' Expression ')'
1340 TrashList := [ ConstExpression ] { ',' ConstExpression } =: