EBNF of GNU Modula-2#

This chapter contains the EBNF of GNU Modula-2. This grammer currently supports both PIM and ISO dialects. The rules here are automatically extracted from the grammer files in GNU Modula-2 and serve to document the syntax of the extensions described earlier and how they fit in with the base language.

Note that the first six productions are built into the lexical analysis phase.

Ident := is a builtin and checks for an identifier
       =:
Ident (ebnf)
Integer := is a builtin and checks for an integer
         =:
Integer (ebnf)
Real := is a builtin and checks for an real constant
      =:
Real (ebnf)
string := is a builtin and checks for an string constant
        =:
string (ebnf)
FileUnit := ( DefinitionModule  |
              ImplementationOrProgramModule  )
          =:
FileUnit (ebnf)
ProgramModule := 'MODULE' Ident [ Priority  ] ';' {
   Import  } Block Ident '.'
               =:
ProgramModule (ebnf)
ImplementationModule := 'IMPLEMENTATION' 'MODULE' Ident
                        [ Priority  ] ';' { Import
                                              } Block
                        Ident '.'
                      =:
ImplementationModule (ebnf)
ImplementationOrProgramModule := ImplementationModule  |
                                 ProgramModule
                               =:
ImplementationOrProgramModule (ebnf)
Number := Integer  | Real
        =:
Number (ebnf)
Qualident := Ident { '.' Ident  }
           =:
Qualident (ebnf)
ConstantDeclaration := Ident '=' ConstExpression
                     =:
ConstantDeclaration (ebnf)
ConstExpression := SimpleConstExpr [ Relation SimpleConstExpr  ]
                 =:
ConstExpression (ebnf)
Relation := '='  | '#'  | '<>'  | '<'  | '<='  |
            '>'  | '>='  | 'IN'
          =:
Relation (ebnf)
SimpleConstExpr := UnaryOrConstTerm { AddOperator
                                       ConstTerm  }
                 =:
SimpleConstExpr (ebnf)
UnaryOrConstTerm := '+' ConstTerm  |
                    '-' ConstTerm  |
                    ConstTerm
                  =:
UnaryOrConstTerm (ebnf)
AddOperator := '+'  | '-'  | 'OR'
             =:
AddOperator (ebnf)
ConstTerm := ConstFactor { MulOperator ConstFactor  }
           =:
ConstTerm (ebnf)
MulOperator := '*'  | '/'  | 'DIV'  | 'MOD'  |
               'REM'  | 'AND'  | '&'
             =:
MulOperator (ebnf)
ConstFactor := Number  | ConstString  |
               ConstSetOrQualidentOrFunction  |
               '(' ConstExpression ')'  |
               'NOT' ConstFactor  |
               ConstAttribute
             =:
ConstFactor (ebnf)
ConstString := string
             =:
ConstString (ebnf)
ComponentElement := ConstExpression [ '..' ConstExpression  ]
                  =:
ComponentElement (ebnf)
ComponentValue := ComponentElement [ 'BY' ConstExpression  ]
                =:
ComponentValue (ebnf)
ArraySetRecordValue := ComponentValue { ',' ComponentValue  }
                     =:
ArraySetRecordValue (ebnf)
Constructor := '{' [ ArraySetRecordValue  ] '}'
             =:
Constructor (ebnf)
ConstSetOrQualidentOrFunction := Constructor  |
                                 Qualident [ Constructor  |
                                             ConstActualParameters  ]
                               =:
ConstSetOrQualidentOrFunction (ebnf)
ConstActualParameters := '(' [ ExpList  ] ')'
                       =:
ConstActualParameters (ebnf)
ConstAttribute := '__ATTRIBUTE__' '__BUILTIN__' '('
                  '(' ConstAttributeExpression ')'
                  ')'
                =:
ConstAttribute (ebnf)
ConstAttributeExpression := Ident  | '<' Qualident
                            ',' Ident '>'
                          =:
ConstAttributeExpression (ebnf)
ByteAlignment := '<*' AttributeExpression '*>'
               =:
ByteAlignment (ebnf)
Alignment := [ ByteAlignment  ]
           =:
Alignment (ebnf)
TypeDeclaration := Ident '=' Type Alignment
                 =:
TypeDeclaration (ebnf)
Type := SimpleType  | ArrayType  | RecordType  |
        SetType  | PointerType  | ProcedureType
      =:
Type (ebnf)
SimpleType := Qualident [ SubrangeType  ]  |
              Enumeration  | SubrangeType
            =:
SimpleType (ebnf)
Enumeration := '(' IdentList ')'
             =:
Enumeration (ebnf)
IdentList := Ident { ',' Ident  }
           =:
IdentList (ebnf)
SubrangeType := '[' ConstExpression '..' ConstExpression
                ']'
              =:
SubrangeType (ebnf)
ArrayType := 'ARRAY' SimpleType { ',' SimpleType  }
             'OF' Type
           =:
ArrayType (ebnf)
RecordType := 'RECORD' [ DefaultRecordAttributes  ]
              FieldListSequence 'END'
            =:
RecordType (ebnf)
DefaultRecordAttributes := '<*' AttributeExpression
                           '*>'
                         =:
DefaultRecordAttributes (ebnf)
RecordFieldPragma := [ '<*' FieldPragmaExpression {
   ',' FieldPragmaExpression  } '*>'  ]
                   =:
RecordFieldPragma (ebnf)
FieldPragmaExpression := Ident [ '(' ConstExpression
                                 ')'  ]
                       =:
FieldPragmaExpression (ebnf)
AttributeExpression := Ident '(' ConstExpression ')'
                     =:
AttributeExpression (ebnf)
FieldListSequence := FieldListStatement { ';' FieldListStatement  }
                   =:
FieldListSequence (ebnf)
FieldListStatement := [ FieldList  ]
                    =:
FieldListStatement (ebnf)
FieldList := IdentList ':' Type RecordFieldPragma  |
             'CASE' CaseTag 'OF' Varient { '|' Varient  }
             [ 'ELSE' FieldListSequence  ] 'END'
           =:
FieldList (ebnf)
TagIdent := [ Ident  ]
          =:
TagIdent (ebnf)
CaseTag := TagIdent [ ':' Qualident  ]
         =:
CaseTag (ebnf)
Varient := [ VarientCaseLabelList ':' FieldListSequence  ]
         =:
Varient (ebnf)
VarientCaseLabelList := VarientCaseLabels { ',' VarientCaseLabels  }
                      =:
VarientCaseLabelList (ebnf)
VarientCaseLabels := ConstExpression [ '..' ConstExpression  ]
                   =:
VarientCaseLabels (ebnf)
CaseLabelList := CaseLabels { ',' CaseLabels  }
               =:
CaseLabelList (ebnf)
CaseLabels := ConstExpression [ '..' ConstExpression  ]
            =:
CaseLabels (ebnf)
SetType := ( 'SET'  | 'PACKEDSET'  ) 'OF' SimpleType
         =:
SetType (ebnf)
PointerType := 'POINTER' 'TO' Type
             =:
PointerType (ebnf)
ProcedureType := 'PROCEDURE' [ FormalTypeList  ]
               =:
ProcedureType (ebnf)
FormalTypeList := '(' ( ')' FormalReturn  |
                        ProcedureParameters ')' FormalReturn  )
                =:
FormalTypeList (ebnf)
FormalReturn := [ ':' OptReturnType  ]
              =:
FormalReturn (ebnf)
OptReturnType := '[' Qualident ']'  |
                 Qualident
               =:
OptReturnType (ebnf)
ProcedureParameters := ProcedureParameter { ',' ProcedureParameter  }
                     =:
ProcedureParameters (ebnf)
ProcedureParameter := '...'  | 'VAR' FormalType  |
                      FormalType
                    =:
ProcedureParameter (ebnf)
VarIdent := Ident [ '[' ConstExpression ']'  ]
          =:
VarIdent (ebnf)
VariableDeclaration := VarIdentList ':' Type Alignment
                     =:
VariableDeclaration (ebnf)
VarIdentList := VarIdent { ',' VarIdent  }
              =:
VarIdentList (ebnf)
Designator := Qualident { SubDesignator  }
            =:
Designator (ebnf)
SubDesignator := '.' Ident  | '[' ExpList ']'  |
                 '^'
               =:
SubDesignator (ebnf)
ExpList := Expression { ',' Expression  }
         =:
ExpList (ebnf)
Expression := SimpleExpression [ Relation SimpleExpression  ]
            =:
Expression (ebnf)
SimpleExpression := [ '+'  | '-'  ] Term { AddOperator
                                            Term  }
                  =:
SimpleExpression (ebnf)
Term := Factor { MulOperator Factor  }
      =:
Term (ebnf)
Factor := Number  | string  | SetOrDesignatorOrFunction  |
          '(' Expression ')'  |
          'NOT' Factor  | ConstAttribute
        =:
Factor (ebnf)
SetOrDesignatorOrFunction := ( Qualident [ Constructor  |
                                           SimpleDes
                                           [ ActualParameters  ]  ]  |
                               Constructor  )
                           =:
SetOrDesignatorOrFunction (ebnf)
SimpleDes := { '.' Ident  | '[' ExpList ']'  |
                '^'  }
           =:
SimpleDes (ebnf)
ActualParameters := '(' [ ExpList  ] ')'
                  =:
ActualParameters (ebnf)
Statement := [ AssignmentOrProcedureCall  |
               IfStatement  | CaseStatement  |
               WhileStatement  | RepeatStatement  |
               LoopStatement  | ForStatement  |
               WithStatement  | AsmStatement  |
               'EXIT'  | 'RETURN' [ Expression  ]  |
               RetryStatement  ]
           =:
Statement (ebnf)
RetryStatement := 'RETRY'
                =:
RetryStatement (ebnf)
AssignmentOrProcedureCall := Designator ( ':=' Expression  |
                                          ActualParameters  |
                                           )
                           =:
AssignmentOrProcedureCall (ebnf)
StatementSequence := Statement { ';' Statement  }
                   =:
StatementSequence (ebnf)
IfStatement := 'IF' Expression 'THEN' StatementSequence
               { 'ELSIF' Expression 'THEN' StatementSequence  }
               [ 'ELSE' StatementSequence  ] 'END'
             =:
IfStatement (ebnf)
CaseStatement := 'CASE' Expression 'OF' Case { '|'
                                                Case  }
                 [ 'ELSE' StatementSequence  ] 'END'
               =:
CaseStatement (ebnf)
Case := [ CaseLabelList ':' StatementSequence  ]
      =:
Case (ebnf)
WhileStatement := 'WHILE' Expression 'DO' StatementSequence
                  'END'
                =:
WhileStatement (ebnf)
RepeatStatement := 'REPEAT' StatementSequence 'UNTIL'
                   Expression
                 =:
RepeatStatement (ebnf)
ForStatement := 'FOR' Ident ':=' Expression 'TO' Expression
                [ 'BY' ConstExpression  ] 'DO' StatementSequence
                'END'
              =:
ForStatement (ebnf)
LoopStatement := 'LOOP' StatementSequence 'END'
               =:
LoopStatement (ebnf)
WithStatement := 'WITH' Designator 'DO' StatementSequence
                 'END'
               =:
WithStatement (ebnf)
ProcedureDeclaration := ProcedureHeading ';' ( ProcedureBlock
                                               Ident
                                                )
                      =:
ProcedureDeclaration (ebnf)
DefineBuiltinProcedure := [ '__ATTRIBUTE__' '__BUILTIN__'
                            '(' '(' Ident ')' ')'  |
                            '__INLINE__'  ]
                        =:
DefineBuiltinProcedure (ebnf)
ProcedureHeading := 'PROCEDURE' DefineBuiltinProcedure
                    ( Ident [ FormalParameters  ] AttributeNoReturn  )
                  =:
ProcedureHeading (ebnf)
AttributeNoReturn := [ '<*' Ident '*>'  ]
                   =:
AttributeNoReturn (ebnf)
Builtin := [ '__BUILTIN__'  | '__INLINE__'  ]
         =:
Builtin (ebnf)
DefProcedureHeading := 'PROCEDURE' Builtin ( Ident
                                             [ DefFormalParameters  ]
                                             AttributeNoReturn  )

                     =:
DefProcedureHeading (ebnf)
ProcedureBlock := { Declaration  } [ 'BEGIN' BlockBody  ]
                  'END'
                =:
ProcedureBlock (ebnf)
Block := { Declaration  } InitialBlock FinalBlock
         'END'
       =:
Block (ebnf)
InitialBlock := [ 'BEGIN' BlockBody  ]
              =:
InitialBlock (ebnf)
FinalBlock := [ 'FINALLY' BlockBody  ]
            =:
FinalBlock (ebnf)
BlockBody := NormalPart [ 'EXCEPT' ExceptionalPart  ]
           =:
BlockBody (ebnf)
NormalPart := StatementSequence
            =:
NormalPart (ebnf)
ExceptionalPart := StatementSequence
                 =:
ExceptionalPart (ebnf)
Declaration := 'CONST' { ConstantDeclaration ';'  }  |
               'TYPE' { TypeDeclaration ';'  }  |
               'VAR' { VariableDeclaration ';'  }  |
               ProcedureDeclaration ';'  |
               ModuleDeclaration ';'
             =:
Declaration (ebnf)
DefFormalParameters := '(' [ DefMultiFPSection  ] ')'
                       FormalReturn
                     =:
DefFormalParameters (ebnf)
DefMultiFPSection := DefExtendedFP  |
                     FPSection [ ';' DefMultiFPSection  ]
                   =:
DefMultiFPSection (ebnf)
FormalParameters := '(' [ MultiFPSection  ] ')' FormalReturn
                  =:
FormalParameters (ebnf)
MultiFPSection := ExtendedFP  | FPSection [ ';' MultiFPSection  ]
                =:
MultiFPSection (ebnf)
FPSection := NonVarFPSection  | VarFPSection
           =:
FPSection (ebnf)
DefExtendedFP := DefOptArg  | '...'
               =:
DefExtendedFP (ebnf)
ExtendedFP := OptArg  | '...'
            =:
ExtendedFP (ebnf)
VarFPSection := 'VAR' IdentList ':' FormalType
              =:
VarFPSection (ebnf)
NonVarFPSection := IdentList ':' FormalType
                 =:
NonVarFPSection (ebnf)
OptArg := '[' Ident ':' FormalType [ '=' ConstExpression  ]
          ']'
        =:
OptArg (ebnf)
DefOptArg := '[' Ident ':' FormalType '=' ConstExpression
             ']'
           =:
DefOptArg (ebnf)
FormalType := { 'ARRAY' 'OF'  } Qualident
            =:
FormalType (ebnf)
ModuleDeclaration := 'MODULE' Ident [ Priority  ] ';'
                     { Import  } [ Export  ] Block
                     Ident
                   =:
ModuleDeclaration (ebnf)
Priority := '[' ConstExpression ']'
          =:
Priority (ebnf)
Export := 'EXPORT' ( 'QUALIFIED' IdentList  |
                     'UNQUALIFIED' IdentList  |
                     IdentList  ) ';'
        =:
Export (ebnf)
Import := 'FROM' Ident 'IMPORT' IdentList ';'  |
          'IMPORT' IdentList ';'
        =:
Import (ebnf)
DefinitionModule := 'DEFINITION' 'MODULE' [ 'FOR' string
                                             ] Ident
                    ';' { Import  } [ Export  ] {
   Definition  } 'END' Ident '.'
                  =:
DefinitionModule (ebnf)
Definition := 'CONST' { ConstantDeclaration ';'  }  |
              'TYPE' { Ident ( ';'  | '=' Type Alignment
                                ';'  )  }  |
              'VAR' { VariableDeclaration ';'  }  |
              DefProcedureHeading ';'
            =:
Definition (ebnf)
AsmStatement := 'ASM' [ 'VOLATILE'  ] '(' AsmOperands
                ')'
              =:
AsmStatement (ebnf)
NamedOperand := '[' Ident ']'
              =:
NamedOperand (ebnf)
AsmOperandName := [ NamedOperand  ]
                =:
AsmOperandName (ebnf)
AsmOperands := string [ ':' AsmList [ ':' AsmList [
   ':' TrashList  ]  ]  ]
             =:
AsmOperands (ebnf)
AsmList := [ AsmElement  ] { ',' AsmElement  }
         =:
AsmList (ebnf)
AsmElement := AsmOperandName string '(' Expression
              ')'
            =:
AsmElement (ebnf)
TrashList := [ string  ] { ',' string  }
           =:
TrashList (ebnf)