The GNU Modula-2 front end to GCC

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
       =: 

Integer := is a builtin and checks for an integer
         =: 

Real := is a builtin and checks for an real constant
      =: 

string := is a builtin and checks for an string constant
        =: 

FileUnit := ( DefinitionModule  | ImplementationOrProgramModule  ) 
            
          =: 

ProgramModule := 'MODULE' Ident [ Priority  ] ';' { Import  } 
                 Block Ident '.' 
               =: 

ImplementationModule := 'IMPLEMENTATION' 'MODULE' Ident [ Priority  ] 
                        ';' { Import  } Block Ident '.' 
                      =: 

ImplementationOrProgramModule := ImplementationModule  | 
                                 ProgramModule 
                               =: 

Number := Integer  | Real 
        =: 

Qualident := Ident { '.' Ident  } 
           =: 

ConstantDeclaration := Ident '=' ConstExpression 
                     =: 

ConstExpression := SimpleConstExpr [ Relation SimpleConstExpr  ] 
                 =: 

Relation := '='  | '#'  | '<>'  | '<'  | '<='  | '>'  | '>='  | 
            'IN' 
          =: 

SimpleConstExpr := UnaryOrConstTerm { AddOperator ConstTerm  } 
                 =: 

UnaryOrConstTerm := '+' ConstTerm  | '-' ConstTerm  | 
                    ConstTerm 
                  =: 

AddOperator := '+'  | '-'  | 'OR' 
             =: 

ConstTerm := ConstFactor { MulOperator ConstFactor  } 
           =: 

MulOperator := '*'  | '/'  | 'DIV'  | 'MOD'  | 'REM'  | 
               'AND'  | '&' 
             =: 

ConstFactor := Number  | ConstString  | ConstSetOrQualidentOrFunction  | 
               '(' ConstExpression ')'  | 
               'NOT' ConstFactor  | ConstAttribute 
             =: 

ConstString := string 
             =: 

ComponentElement := ConstExpression [ '..' ConstExpression  ] 
                  =: 

ComponentValue := ComponentElement [ 'BY' ConstExpression  ] 
                =: 

ArraySetRecordValue := ComponentValue { ',' ComponentValue  } 
                     =: 

Constructor := '{' [ ArraySetRecordValue  ] '}' 
             =: 

ConstSetOrQualidentOrFunction := Constructor  | Qualident [ Constructor  | 
                                                            ConstActualParameters  ] 
                               =: 

ConstActualParameters := '(' [ ExpList  ] ')' 
                       =: 

ConstAttribute := '__ATTRIBUTE__' '__BUILTIN__' '(' '(' ConstAttributeExpression 
                  ')' ')' 
                =: 

ConstAttributeExpression := Ident  | '<' Qualident ',' Ident 
                            '>' 
                          =: 

ByteAlignment := '<*' AttributeExpression '*>' 
               =: 

Alignment := [ ByteAlignment  ] 
           =: 

TypeDeclaration := Ident '=' Type Alignment 
                 =: 

Type := SimpleType  | ArrayType  | RecordType  | SetType  | 
        PointerType  | ProcedureType 
      =: 

SimpleType := Qualident [ SubrangeType  ]  | 
              Enumeration  | SubrangeType 
            =: 

Enumeration := '(' IdentList ')' 
             =: 

IdentList := Ident { ',' Ident  } 
           =: 

SubrangeType := '[' ConstExpression '..' ConstExpression ']' 
              =: 

ArrayType := 'ARRAY' SimpleType { ',' SimpleType  } 'OF' Type 
           =: 

RecordType := 'RECORD' [ DefaultRecordAttributes  ] FieldListSequence 
              'END' 
            =: 

DefaultRecordAttributes := '<*' AttributeExpression '*>' 
                         =: 

RecordFieldPragma := [ '<*' FieldPragmaExpression { ',' FieldPragmaExpression  } 
                       '*>'  ] 
                   =: 

FieldPragmaExpression := Ident [ '(' ConstExpression ')'  ] 
                       =: 

AttributeExpression := Ident '(' ConstExpression ')' 
                     =: 

FieldListSequence := FieldListStatement { ';' FieldListStatement  } 
                   =: 

FieldListStatement := [ FieldList  ] 
                    =: 

FieldList := IdentList ':' Type RecordFieldPragma  | 
             'CASE' CaseTag 'OF' Varient { '|' Varient  } [ 
   'ELSE' FieldListSequence  ] 'END' 
           =: 

TagIdent := [ Ident  ] 
          =: 

CaseTag := TagIdent [ ':' Qualident  ] 
         =: 

Varient := [ VarientCaseLabelList ':' FieldListSequence  ] 
         =: 

VarientCaseLabelList := VarientCaseLabels { ',' VarientCaseLabels  } 
                      =: 

VarientCaseLabels := ConstExpression [ '..' ConstExpression  ] 
                   =: 

CaseLabelList := CaseLabels { ',' CaseLabels  } 
               =: 

CaseLabels := ConstExpression [ '..' ConstExpression  ] 
            =: 

SetType := ( 'SET'  | 'PACKEDSET'  ) 'OF' SimpleType 
         =: 

PointerType := 'POINTER' 'TO' Type 
             =: 

ProcedureType := 'PROCEDURE' [ FormalTypeList  ] 
               =: 

FormalTypeList := '(' ( ')' FormalReturn  | 
                        ProcedureParameters ')' FormalReturn  ) 
                =: 

FormalReturn := [ ':' OptReturnType  ] 
              =: 

OptReturnType := '[' Qualident ']'  | Qualident 
               =: 

ProcedureParameters := ProcedureParameter { ',' ProcedureParameter  } 
                     =: 

ProcedureParameter := '...'  | 'VAR' FormalType  | 
                      FormalType 
                    =: 

VarIdent := Ident [ '[' ConstExpression ']'  ] 
          =: 

VariableDeclaration := VarIdentList ':' Type Alignment 
                     =: 

VarIdentList := VarIdent { ',' VarIdent  } 
              =: 

Designator := Qualident { SubDesignator  } 
            =: 

SubDesignator := '.' Ident  | '[' ExpList ']'  | 
                 '^' 
               =: 

ExpList := Expression { ',' Expression  } 
         =: 

Expression := SimpleExpression [ Relation SimpleExpression  ] 
            =: 

SimpleExpression := [ '+'  | '-'  ] Term { AddOperator Term  } 
                  =: 

Term := Factor { MulOperator Factor  } 
      =: 

Factor := Number  | string  | SetOrDesignatorOrFunction  | 
          '(' Expression ')'  | 'NOT' Factor  | 
          ConstAttribute 
        =: 

SetOrDesignatorOrFunction := ( Qualident [ Constructor  | 
                                           SimpleDes [ ActualParameters  ]  ]  | 
                               Constructor  ) 
                           =: 

SimpleDes := { '.' Ident  | '[' ExpList ']'  | 
                '^'  } 
           =: 

ActualParameters := '(' [ ExpList  ] ')' 
                  =: 

Statement := [ AssignmentOrProcedureCall  | 
               IfStatement  | CaseStatement  | 
               WhileStatement  | RepeatStatement  | 
               LoopStatement  | ForStatement  | 
               WithStatement  | AsmStatement  | 
               'EXIT'  | 'RETURN' [ Expression  ]  | 
               RetryStatement  ] 
           =: 

RetryStatement := 'RETRY' 
                =: 

AssignmentOrProcedureCall := Designator ( ':=' Expression  | 
                                          ActualParameters  | 
                                           ) 
                           =: 

StatementSequence := Statement { ';' Statement  } 
                   =: 

IfStatement := 'IF' Expression 'THEN' StatementSequence { 'ELSIF' 
                                                           Expression 
                                                           'THEN' 
                                                           StatementSequence  } 
               [ 'ELSE' StatementSequence  ] 'END' 
             =: 

CaseStatement := 'CASE' Expression 'OF' Case { '|' Case  } 
                 [ 'ELSE' StatementSequence  ] 'END' 
               =: 

Case := [ CaseLabelList ':' StatementSequence  ] 
      =: 

WhileStatement := 'WHILE' Expression 'DO' StatementSequence 'END' 
                =: 

RepeatStatement := 'REPEAT' StatementSequence 'UNTIL' Expression 
                 =: 

ForStatement := 'FOR' Ident ':=' Expression 'TO' Expression [ 
   'BY' ConstExpression  ] 'DO' StatementSequence 'END' 
              =: 

LoopStatement := 'LOOP' StatementSequence 'END' 
               =: 

WithStatement := 'WITH' Designator 'DO' StatementSequence 'END' 
               =: 

ProcedureDeclaration := ProcedureHeading ';' ( ProcedureBlock 
                                               Ident  ) 
                      =: 

DefineBuiltinProcedure := [ '__ATTRIBUTE__' '__BUILTIN__' '(' 
                            '(' Ident ')' ')'  | 
                            '__INLINE__'  ] 
                        =: 

ProcedureHeading := 'PROCEDURE' DefineBuiltinProcedure ( Ident 
                                                         [ FormalParameters  ] 
                                                         AttributeNoReturn  ) 
                  =: 

AttributeNoReturn := [ '<*' Ident '*>'  ] 
                   =: 

Builtin := [ '__BUILTIN__'  | '__INLINE__'  ] 
         =: 

DefProcedureHeading := 'PROCEDURE' Builtin ( Ident [ DefFormalParameters  ] 
                                             AttributeNoReturn  ) 
                     =: 

ProcedureBlock := { Declaration  } [ 'BEGIN' BlockBody  ] 'END' 
                =: 

Block := { Declaration  } InitialBlock FinalBlock 'END' 
       =: 

InitialBlock := [ 'BEGIN' BlockBody  ] 
              =: 

FinalBlock := [ 'FINALLY' BlockBody  ] 
            =: 

BlockBody := NormalPart [ 'EXCEPT' ExceptionalPart  ] 
           =: 

NormalPart := StatementSequence 
            =: 

ExceptionalPart := StatementSequence 
                 =: 

Declaration := 'CONST' { ConstantDeclaration ';'  }  | 
               'TYPE' { TypeDeclaration ';'  }  | 
               'VAR' { VariableDeclaration ';'  }  | 
               ProcedureDeclaration ';'  | 
               ModuleDeclaration ';' 
             =: 

DefFormalParameters := '(' [ DefMultiFPSection  ] ')' FormalReturn 
                     =: 

DefMultiFPSection := DefExtendedFP  | FPSection [ ';' DefMultiFPSection  ] 
                   =: 

FormalParameters := '(' [ MultiFPSection  ] ')' FormalReturn 
                  =: 

MultiFPSection := ExtendedFP  | FPSection [ ';' MultiFPSection  ] 
                =: 

FPSection := NonVarFPSection  | VarFPSection 
           =: 

DefExtendedFP := DefOptArg  | '...' 
               =: 

ExtendedFP := OptArg  | '...' 
            =: 

VarFPSection := 'VAR' IdentList ':' FormalType 
              =: 

NonVarFPSection := IdentList ':' FormalType 
                 =: 

OptArg := '[' Ident ':' FormalType [ '=' ConstExpression  ] ']' 
        =: 

DefOptArg := '[' Ident ':' FormalType '=' ConstExpression ']' 
           =: 

FormalType := { 'ARRAY' 'OF'  } Qualident 
            =: 

ModuleDeclaration := 'MODULE' Ident [ Priority  ] ';' { Import 
                                                          } 
                     [ Export  ] Block Ident 
                   =: 

Priority := '[' ConstExpression ']' 
          =: 

Export := 'EXPORT' ( 'QUALIFIED' IdentList  | 
                     'UNQUALIFIED' IdentList  | 
                     IdentList  ) ';' 
        =: 

Import := 'FROM' Ident 'IMPORT' IdentList ';'  | 
          'IMPORT' IdentList ';' 
        =: 

DefinitionModule := 'DEFINITION' 'MODULE' [ 'FOR' string  ] Ident 
                    ';' { Import  } [ Export  ] { Definition  } 
                    'END' Ident '.' 
                  =: 

Definition := 'CONST' { ConstantDeclaration ';'  }  | 
              'TYPE' { Ident ( ';'  | '=' Type Alignment ';'  )  }  | 
              'VAR' { VariableDeclaration ';'  }  | 
              DefProcedureHeading ';' 
            =: 

AsmStatement := 'ASM' [ 'VOLATILE'  ] '(' AsmOperands ')' 
              =: 

NamedOperand := '[' Ident ']' 
              =: 

AsmOperandName := [ NamedOperand  ] 
                =: 

AsmOperands := string [ ':' AsmList [ ':' AsmList [ ':' TrashList  ]  ]  ] 
             =: 

AsmList := [ AsmElement  ] { ',' AsmElement  } 
         =: 

AsmElement := AsmOperandName string '(' Expression ')' 
            =: 

TrashList := [ string  ] { ',' string  } 
           =: