Modula-2 Reloaded

A Modern Typesafe & Literate Programming Notation

Site Menu

Project

Specification

Implementation

Recommendations

Reference

Needs Updating

Work in Progress

Wastebasket

Wiki Manual

edit SideBar

Spec EBNF

EBNF

Spec.EBNF History

Hide minor edits - Show changes to output

2015-09-16 01:47 by trijezdci -
Changed line 77 from:
   Uppercase-Letter ( UppercaseLetter | Digit | “-” | “_” )* ;
to:
   Uppercase-Letter ( Uppercase-Letter | Digit | “-” | “_” )* ;
2015-09-16 01:45 by trijezdci -
Changed lines 4-5 from:
Each EBNF rule defines exactly one symbol and is terminated by a semicolon.  Names of symbols start with a letter which may be followed by letters, digits, hyphens and low lines.  Names may not contain whitespace.  Terminal symbols are denoted by names whose letters are all uppercase. Non-terminal symbols are denoted by names which start with a lowercase letter.  Literals are enclosed in double or single quotes.  EBNF production rules take the following general forms:
to:
Each EBNF rule defines exactly one symbol and is terminated by a semicolon.  Names of symbols start with a letter which may be followed by letters, digits, hyphens and low lines.  Names may not contain whitespace.  Terminal symbols are denoted by names which start with an uppercase letter.  Non-terminal symbols are denoted by names which start with a lowercase letter.  Literals are enclosed in double or single quotes.  By convention, reserved words of the target language are denoted in all-uppercase letters.

EBNF production rules take the following general forms:
Changed lines 77-78 from:
   UPPERCASE-LETTER ( UPPERCASE-LETTER | DIGIT | “-” | “_” )* ;
to:
   Uppercase-Letter ( UppercaseLetter | Digit | “-” | “_” )* ;
Changed lines 80-81 from:
   LOWERCASE-LETTER ( LETTER | DIGIT | “-” | “_” )* ;
to:
   Lowercase-Letter ( Letter | Digit | “-” | “_” )* ;
Changed lines 83-85 from:
   ( ‘“‘ ( CHARACTER | “‘” )+ ‘“‘ ) |

    ( “‘“ ( CHARACTER | ‘“’ )+ “‘“ ) ;
to:
   ( ‘“‘ ( Character | “‘” )+ ‘“‘ ) |

    ( “‘“ ( Character | ‘“’ )+ “‘“ ) ;
Changed lines 89-92 from:
LETTER :=
    UPPERCASE-LETTER | LOWERCASE-LETTER ;

UPPERCASE-LETTER :=
to:
Letter :=
    Uppercase-Letter | Lowercase-Letter ;

Uppercase-Letter :=
Changed line 95 from:
LOWERCASE-LETTER :=
to:
Lowercase-Letter :=
Changed line 98 from:
DIGIT :=
to:
Digit :=
Changed lines 101-102 from:
CHARACTER :=

    LETTER | DIGIT |

to:
Character :=

    Letter | Digit |

Added lines 106-108:

Reserved-Word :=
  Uppercase-Letter* ;
2010-01-25 19:40 by benjk -
Changed line 2 from:
The syntax of Modula-2 was formally defined in an extended version of Backus-Naur Formalism, known as Wirth EBNF, in which brackets and braces are used to denote optional and repeating syntactic entities.  For the formal definition of the revised Modula-2 language we use a slightly different version of EBNF which employs parentheses and modifier suffixes instead.
to:
The syntax of PIM Modula-2 was formally defined in an extended version of Backus-Naur Formalism, known as Wirth EBNF, in which brackets and braces are used to denote optional and repeating syntactic entities.  For the formal definition of the revised Modula-2 language we use a slightly different version of EBNF which employs parentheses and modifier suffixes instead.
2010-01-25 19:39 by benjk -
Changed lines 90-94 from:
UPPERCASE-LETTER := “A” .. “Z” ;

LOWERCASE-LETTER := “a”
.. “z” ;

DIGIT := “0” .. “9” ;
to:
UPPERCASE-LETTER :=
    “A” .. “Z” ;

LOWERCASE-LETTER :=
    “a” .. “z” ;

DIGIT :=
 
“0” .. “9” ;
2010-01-25 19:38 by benjk -
Deleted line 9:
Deleted line 15:
Deleted line 21:
Deleted line 27:
Deleted line 33:
Deleted line 39:
Deleted line 47:
2010-01-25 19:37 by benjk -
Changed lines 10-11 from:
Symbol @@foo@@ is defined as a synonym for symbol @@bar@@.
to:

[-
Symbol @@foo@@ is defined as a synonym for symbol @@bar@@.-]
Changed lines 17-18 from:
Symbol @@foo@@ is defined as a sequence of symbol @@bar@@ followed by symbol @@baz@@.
to:

[-
Symbol @@foo@@ is defined as a sequence of symbol @@bar@@ followed by symbol @@baz@@.-]
Changed lines 24-25 from:
Symbol @@foo@@ is defined as an alternative, either symbol @@bar@@ or symbol @@baz@@, but not both.
to:

[-
Symbol @@foo@@ is defined as an alternative, either symbol @@bar@@ or symbol @@baz@@, but not both.-]
Changed lines 31-32 from:
Symbol @@foo@@ is defined by zero or one occurrence of symbol @@bar@@.
to:

[-
Symbol @@foo@@ is defined by zero or one occurrence of symbol @@bar@@.-]
Changed lines 38-39 from:
Symbol @@foo@@ is defined by one or more occurrences of symbol @@bar@@.
to:

[-
Symbol @@foo@@ is defined by one or more occurrences of symbol @@bar@@.-]
Changed lines 45-46 from:
Symbol @@foo@@ is defined by zero or more occurrences of symbol @@bar@@.
to:

[-
Symbol @@foo@@ is defined by zero or more occurrences of symbol @@bar@@.-]
Changed lines 54-55 from:
Symbol @@foo@@ is defined by an occurrence of symbol @@bar@@ followed by an alternative of symbol @@baz@@, or symbol @@bam@@ followed by zero or more occurrences of literal @@“,”@@ and symbol @@boo@@.
to:

[-
Symbol @@foo@@ is defined by an occurrence of symbol @@bar@@ followed by an alternative of symbol @@baz@@, or symbol @@bam@@ followed by zero or more occurrences of literal @@“,”@@ and symbol @@boo@@.-]
2010-01-25 19:36 by benjk -
Changed line 8 from:
 foo := bar ;
to:
foo := bar ;
Changed line 14 from:
 foo := bar baz ;
to:
foo := bar baz ;
Changed line 20 from:
 foo := bar | baz ;
to:
foo := bar | baz ;
Changed line 26 from:
 foo := bar? ;
to:
foo := bar? ;
Changed line 32 from:
 foo := bar+ ;
to:
foo := bar+ ;
Changed line 38 from:
 foo := bar* ;
to:
foo := bar* ;
Changed line 46 from:
 foo := bar ( baz | bam ) ( “,” boo )* ;
to:
foo := bar ( baz | bam ) ( “,” boo )* ;
Changed lines 52-72 from:
 syntax := statement* ;
 statement := symbol-id “:=” expression “;” ;
 expression := term ( “|” term )* ;
 term := factor+ ;
 factor := 
    ( symbol-id | literal | literal-range | group )

( “?” | “+” | “*” )* ;
 group : = “(“ expression “)” ;
 symbol-id := terminal-id | non-terminal-id ;
 terminal-id :=
    UPPERCASE-LETTER ( UPPERCASE-LETTER | DIGIT | “-” | “_” )* ;
 non-terminal-id :=
    LOWERCASE-LETTER ( LETTER | DIGIT | “-” | “_” )* ;
 literal :=
    ( ‘“‘ ( CHARACTER | “‘” )+ ‘“‘ ) |

( “‘“ ( CHARACTER | ‘“’ )+ “‘“ ) ;
 literal-range := literal “..” literal ;
 LETTER := UPPERCASE-LETTER | LOWERCASE-LETTER ;
 UPPERCASE-LETTER := “A” .. “Z” ;
 LOWERCASE-LETTER := “a” .. “z” ;
 DIGIT := “0” .. “9” ;
 CHARACTER :=
    LETTER | DIGIT |

“ “ | “!” | “#” | “$” | “%” | “&” | “(“ | “)” | “*” | “+” |

“,” | “-” | “.” | “/” | “:” | “;” | “<“ | “=” | “>” | “?” |

“@” | “[“ | “]” | “^” | “_” | “`” | “{“ | “|” | “}” | “~” ;
to:
syntax :=
    statement* ;

statement :=
    symbol-id “:=” expression “;” ;

expression :=
    term ( “|” term )* ;

term :=
    factor+ ;

factor :=
    ( symbol-id | literal | literal-range | group )

    ( “?” | “+” | “*” )* ;

group : =
    “(“ expression “)” ;

symbol-id :=
    terminal-id | non-terminal-id ;

terminal-id :=

    UPPERCASE-LETTER ( UPPERCASE-LETTER | DIGIT | “-” | “_” )* ;

non-terminal-id :=

    LOWERCASE-LETTER ( LETTER | DIGIT | “-” | “_” )* ;

literal :=

    ( ‘“‘ ( CHARACTER | “‘” )+ ‘“‘ ) |

    ( “‘“ ( CHARACTER | ‘“’ )+ “‘“ ) ;

literal-range :=
    literal “..” literal ;

LETTER :=
    UPPERCASE-LETTER | LOWERCASE-LETTER ;

UPPERCASE-LETTER := “A” .. “Z” ;

LOWERCASE-LETTER := “a” .. “z” ;

DIGIT := “0” .. “9” ;

CHARACTER :=

    LETTER | DIGIT |

    “ “ | “!” | “#” | “$” | “%” | “&” | “(“ | “)” | “*” | “+” |

    “,” | “-” | “.” | “/” | “:” | “;” | “<“ | “=” | “>” | “?” |

    “@” | “[“ | “]” | “^” | “_” | “`” | “{“ | “|” | “}” | “~” ;
2010-01-25 19:32 by benjk -
Added line 44:
2010-01-25 19:31 by benjk -
Changed lines 10-11 from:
Symbol foo is defined as a synonym for symbol bar.
to:
Symbol @@foo@@ is defined as a synonym for symbol @@bar@@.
Changed lines 16-17 from:
Symbol foo is defined as a sequence of symbol bar followed by symbol baz.
to:
Symbol @@foo@@ is defined as a sequence of symbol @@bar@@ followed by symbol @@baz@@.
Changed lines 22-23 from:
Symbol foo is defined as an alternative, either symbol bar or symbol baz, but not both.
to:
Symbol @@foo@@ is defined as an alternative, either symbol @@bar@@ or symbol @@baz@@, but not both.
Changed lines 28-29 from:
Symbol foo is defined by zero or one occurrence of symbol bar.5
to:
Symbol @@foo@@ is defined by zero or one occurrence of symbol @@bar@@.
Changed lines 34-35 from:
Symbol foo is defined by one or more occurrences of symbol bar.
to:
Symbol @@foo@@ is defined by one or more occurrences of symbol @@bar@@.
Changed lines 40-41 from:
Symbol foo is defined by zero or more occurrences of symbol bar.6
to:
Symbol @@foo@@ is defined by zero or more occurrences of symbol @@bar@@.
Changed lines 47-48 from:
Symbol foo is defined by an occurrence of symbol bar followed by an alternative of symbol baz, or symbol bam followed by zero or more occurrences of literal @@“,”@@ and symbol boo.
to:
Symbol @@foo@@ is defined by an occurrence of symbol @@bar@@ followed by an alternative of symbol @@baz@@, or symbol @@bam@@ followed by zero or more occurrences of literal @@“,”@@ and symbol @@boo@@.
Changed lines 55-56 from:
 factor := 
    ( symbol-id | literal | literal-range | group )
   ( “?” | “+” | “*” )* ;
to:
 factor := 
    ( symbol-id | literal | literal-range | group )

( “?” | “+” | “*” )* ;
Changed lines 61-62 from:
 literal :=
    ( ‘“‘ ( CHARACTER | “‘” )+ ‘“‘ ) |
   ( “‘“ ( CHARACTER | ‘“’ )+ “‘“ ) ;
to:
 literal :=
    ( ‘“‘ ( CHARACTER | “‘” )+ ‘“‘ ) |

( “‘“ ( CHARACTER | ‘“’ )+ “‘“ ) ;
2010-01-25 19:29 by benjk -
Changed lines 66-69 from:
 CHARACTER :=
    LETTER | DIGIT |
    “ “ | “!” | “#” | “$” | “%” | “&” | “(“ | “)” | *” | “+” |   ,” | “-” | “.” | “/” | “:” | “;” | “<“ | “=” | “>” | “?” |
    “@” | “[“ | “]” | “^” | “_” | “`” | “{“ | “|” | “}” | “~” ;
to:
 CHARACTER :=
    LETTER | DIGIT |

“ “ |!” | #” | “$” | “%” | “&” | “(“ | “)” | “*” | “+” |
,” | “-” | “.” |/” | “:” | “;” | “<“ | “=” | “>” | “?” |
“@” | “[“ | “]” | “^” | “_” | “`” | “{“ | “|” | “}” | “~” ;
2010-01-25 19:28 by benjk -
Changed lines 1-17 from:
!!! Reserved Words
* 42 reserved words

@@AND@@, @@ARRAY@@, @@BEGIN@@, @@BY@@, @@CASE@@, @@CONST@@,
@@DEFINITION@@, @@DIV@@, @@DO@@, @@ELSE@@, @@ELSIF@@, @@END@@
,
@@ENUM@@, @@EXIT@@, @@FOR@@, @@FROM@@, @@IF@@, @@IMMUTABLE@@,
@@IMPLEMENTATION@@, @@IMPORT@@, @@IN@@, @@IS@@, @@LOOP@@, @@MOD@@,
@@MODULE@@, @@NOT@@, @@OF@@, @@OPAQUE@@, @@OR@@, @@POINTER@@,
@@PROCEDURE@@, @@RECORD@@, @@REPEAT@@, @@RETURN@@, @@SET@@,
@@THEN@@, @@TO@@, @@TYPE@@, @@UNTIL@@, @@VAR@@, @@VARIADIC@@,
@@WHILE@@

!!! Non
-Terminal Symbols
* 62 productions
* 16 aliases

!!!!Compilation Units
to:
!!!A Notation to Describe the Syntax of Modula-2
The syntax of Modula-2 was formally defined in an extended version of Backus-Naur Formalism
, known as Wirth EBNF, in which brackets and braces are used to denote optional and repeating syntactic entities.  For the formal definition of the revised Modula-2 language we use a slightly different version of EBNF which employs parentheses and modifier suffixes instead.

Each EBNF rule defines exactly one symbol and is terminated by a semicolon.  Names of symbols start with a letter which may be followed by letters, digits, hyphens and low lines.  Names may not contain whitespace.  Terminal symbols are denoted by names whose letters are all uppercase.  Non-terminal symbols are denoted by names which start with a lowercase letter.  Literals are enclosed in double or single quotes.  EBNF production rules take the following general forms:

!!!!Synonym
Changed lines 8-25 from:
 (1) compilationUnit :
      programModule | definitionOfModule | implementationOfModule ;

 (2) programModule :
      MODULE moduleId ( '[' priority ']' )? ';'
      importList* block moduleId '.' ;

 (3) definitionOfModule :
      DEFINITION MODULE moduleId ';'
      importList* definition*
      END moduleId '.' ;

 (4) implementationOfModule :
      IMPLEMENTATION programModule ;

    moduleId : ident ;

    priority : constExpression
;
to:
 foo := bar ;
Changed lines 10-12 from:
!!!!Import Lists, Blocks, Declarations, Definitions
to:
Symbol foo is defined as a synonym for symbol bar.

!!!!Sequence
Changed lines 14-31 from:
 (5) importList :
       ( FROM moduleId IMPORT ( identList | '*' ) | IMPORT identList ) ';' ;

 (6) block :
      declaration*
      ( BEGIN statementSequence )? END ;

 (7) declaration :
      CONST ( constantDeclaration ';' )* |
      TYPE ( typeDeclaration ';' )* |
      VAR ( variableDeclaration ';' )* |
      procedureDeclaration ';'  ;

 (8) definition :
      CONST ( constantDeclaration ';' )* |
      TYPE ( ident ( IS namedType | '=' ( type | OPAQUE recordType? ) ) ';' )* |
      VAR ( variableDeclaration ';' )* |
      procedureHeader ';'
;
to:
 foo := bar baz ;
Changed lines 16-18 from:
!!!!Constant Declarations
to:
Symbol foo is defined as a sequence of symbol bar followed by symbol baz.

!!!!Alternative
Changed lines 20-21 from:
 (9) constantDeclaration :
 
     ident '=' ( constExpression | structuredValue ) ;
to:
 foo := bar | baz ;
Changed lines 22-24 from:
!!!!Type Declaration
to:
Symbol foo is defined as an alternative, either symbol bar or symbol baz, but not both.

!!!!Option
Changed lines 26-81 from:
(10) typeDeclaration :
      ident ( IS namedType | '=' type ) ;

(11) type :
      namedType | anonymousType | enumerationType | setType ;

    namedType : qualident ;

(12) anonymousType :
      arrayType | recordType | pointerType | procedureType ;

(13) enumerationType :
      ENUM ( '(' baseType ')' )? identList? END |
      '(' identList ')' // simple notation ;

    baseType : qualident ;

(14) arrayType :
      ARRAY arrayIndex ( ',' arrayIndex )*
      OF ( namedType | recordType | procedureType ) ;

    arrayIndex : ordinalConstExpression ;

    ordinalConstExpression : constExpression ;

(15) recordType :
      RECORD ( '(' baseType ')' )? fieldListSequence? END ;

(16) fieldListSequence :
      fieldList ( ';' fieldList )* ;

(17) fieldList :
      identList ':'
      ( namedType | arrayType | recordType | procedureType ) ;

(18) setType :
      SET OF ( namedType | '(' identList ')' ) ;

(19) pointerType :
      POINTER TO IMMUTABLE? namedType ;

(20) procedureType :
      PROCEDURE
      ( '(' formalTypeList ')' )?
      ( ':' returnedType )? ;

(21) formalTypeList :
      attributedFormalType ( ',' attributedFormalType )* ;

(22) attributedFormalType :
      IMMUTABLE? VAR? formalType ;

(23) formalType :
      ( ARRAY OF )? namedType ;

    returnedType : namedType ;
to:
 foo := bar? ;
Changed lines 28-30 from:
!!!!Variable Declarations
to:
Symbol foo is defined by zero or one occurrence of symbol bar.5

!!!!Repetition
Changed lines 32-36 from:
(24) variableDeclaration :
       ident ( '[' machineAddress ']' | ',' identList )?
      ':' ( namedType | anonymousType ) ;

    machineAddress : constExpression
;
to:
 foo := bar+ ;
Changed lines 34-36 from:
!!!!Procedure Declarations
to:
Symbol foo is defined by one or more occurrences of symbol bar.

!!!!Optional Repetition
Changed lines 38-60 from:
(25) procedureDeclaration :
      procedureHeader ';' block ident ;

(26) procedureHeader :
      PROCEDURE
      ( '(' ident ':' receiverType ')' )?
      ident ( '(' formalParamList ')' )? ( ':' returnedType )? ;

    receiverType : ident ;

(27) formalParamList :
      formalParams ( ';' ( formalParams | variadicParams ) )* ;

(28) formalParams :
      IMMUTABLE? VAR? identList ':' formalType ;

(29) variadicParams :
      VARIADIC handle ( '[' indexParam ']' )? OF
      IMMUTABLE? VAR? ident ( ( '.' ident )* | ( ',' ident )* ':' formalType ) ;

    handle : ident ;

    indexParam : ident ;
to:
 foo := bar* ;
Changed lines 40-43 from:
!!!!Statements
to:
Symbol foo is defined by zero or more occurrences of symbol bar.6

!!!!Grouping
Parentheses may be used to group syntactic entities on the right hand side of an EBNF rule. A group may be followed by a @@?@@, @@+@@ or @@*@@ modifier which then applies to the group as a whole.
Changed lines 45-88 from:
(30) statement :
      ( assignmentOrProcedureCall | ifStatement | caseStatement |
        whileStatement | repeatStatement | loopStatement |
        forStatement | RETURN expression? | EXIT )? ;

(31) statementSequence :
      statement ( ';' statement )* ;

(32) assignmentOrProcedureCall :
      designator
      ( ':=' ( expression | structuredValue ) | '++' | '--' | actualParameters )? ;

(33) ifStatement :
      IF expression THEN statementSequence
      ( ELSIF expression THEN statementSequence )*
      ( ELSE statementSequence )?
      END ;

(34) caseStatement :
      CASE expression OF case ( '|' case )*
      ( ELSE statementSequence )?
      END ;

(35) case :
      caseLabelList ':' statementSequence ;

(36) caseLabelList :
      caseLabels ( ',' caseLabels )* ;

(37) caseLabels :
      constExpression ( '..' constExpression )? ;

(38) whileStatement :
      WHILE expression DO statementSequence END ;

(39) repeatStatement :
      REPEAT statementSequence UNTIL expression ;

(40) loopStatement :
      LOOP statementSequence END ;

(41) forStatement :
      FOR ident ':=' expression TO expression ( BY constExpression )?
      DO statementSequence END ;
to:
 foo := bar ( baz | bam ) ( “,” boo )* ;
Changed lines 47-49 from:
!!!!Expressions
to:
Symbol foo is defined by an occurrence of symbol bar followed by an alternative of symbol baz, or symbol bam followed by zero or more occurrences of literal @@“,”@@ and symbol boo.

!!!EBNF defined in EBNF
Changed lines 51-229 from:
(42) constExpression :
      simpleConstExpr ( relation simpleConstExpr | '::' namedType )? ;

(43) relation :
      '=' | '#' | '<' | '<=' | '>' | '>=' | IN | IS ;

(44) simpleConstExpr :
      ( '+' | '-' )? constTerm ( addOperator constTerm )* ;

(45) addOperator :
      '+' | '-' | OR ;

(46) constTerm :
      constFactor ( mulOperator constFactor )* ;

(47) mulOperator :
      '*' | '/' | DIV | MOD | AND | '&' ;

(48) constFactor :
      number | string | qualident |
      '(' constExpression ')' | ( NOT | '~' ) constFactor ;

(49) designator :
      qualident ( designatorTail )? ;

(50) designatorTail :
      ( ( '[' expressionList ']' | '^' ) ( '.' ident )* )+ ;

(51) expressionList :
      expression ( ',' expression )* ;

(52) expression :
      simpleExpression ( relation simpleExpression | '::' namedType )? ;

(53) simpleExpression :
      ( '+' | '-' )? term ( addOperator term )* ;

(54) term :
      factor ( mulOperator factor )* ;

(55) factor :
      number |
      string |
      designatorOrProcedureCall |
      '(' expression ')' | ( NOT | '~' ) factor ;

(56) designatorOrProcedureCall :
      qualident ( designatorTail? actualParameters? ) ;

(57) actualParameters :
      '(' expressionList? ')' ;
@]
!!!!Value Constructors
[@
(58) structuredValue :
      '{' ( valueComponent ( ',' valueComponent )* )? '}' ;

(59) valueComponent :
      constExpression ( ( BY | '..' ) constExpression  )? |
      structuredValue ;
@]
!!!!Identifiers
[@
(60) qualident :
      ident ( '.' ident )* ;

(61) identList :
      ident ( ',' ident )* ;

    ident : IDENT ;
@]
!!!!Literals
[@
    number : NUMBER ;

    string : STRING ;
@]
!!!!Pragmas
[@
(62) pragma :
      '<*' (

      // conditional compilation pragmas
      ( IF | ELSIF ) constExpression | ELSE | ENDIF |

      // console message pragmas
      ( INFO | WARN | ERROR | FATAL ) compileTimeMessage |

      // other language defined pragmas
      FOREIGN ( '=' string )? | INLINE | NOINLINE |

      // implementation defined pragmas
      implementationDefinedPragma ( '+' | '-' | '=' ( ident | number ) )?

      ) '*>' ;

    compileTimeMessage : string ;

    implementationDefinedPragma : ident ;
@]
!!!Terminal Symbols
* 9 productions
[@

 (1) IDENT :
      ( '_' | '$' | LETTER ) ( '_' | '$' | LETTER | DIGIT )* ;

 (2) NUMBER :
      // Decimal integer
      DIGIT+ |

      // Binary integer
      BINARY_DIGIT+ 'B' |

      // Sedecimal integer
      DIGIT SEDECIMAL_DIGIT* ( 'C' | 'H' ) |

      // Real number
      DIGIT+ '.' DIGIT+ ( 'E' ( '+' | '-' )? DIGIT+ )? ;

 (3) STRING :
      SINGLE_QUOTE ( CHARACTER | DOUBLE_QUOTE )* SINGLE_QUOTE |
      DOUBLE_QUOTE ( CHARACTER | SINGLE_QUOTE )* DOUBLE_QUOTE ;

 (4) LETTER :
      'A' .. 'Z' | 'a' .. 'z' ;

 (5) DIGIT :
      BINARY_DIGIT | '2' | '3' | '4' | '5' | '6' | '7' | '8' | '9' ;

 (6) BINARY_DIGIT :
      '0' | '1' ;

 (7) SEDECIMAL_DIGIT :
      DIGIT | 'A' | 'B' | 'C' | 'D' | 'E' | 'F' ;

 (8) CHARACTER :
      DIGIT | LETTER |
      // any printable characters other than single and double quote
      ' ' | '!' | '#' | '$' | '%' | '&' | '(' | ')' | '*' | '+' |
      ',' | '-' | '.' | ':' | ';' | '<' | '=' | '>' | '?' | '@' |
      '[' | ']' | '^' | '_' | '`' | '{' | '|' | '}' | '~' |
      ESCAPE_SEQUENCE  ;

 (8) ESCAPE_SEQUENCE :
      BACKSLASH
      ( '0' | 'n' | 'r' | 't' | BACKSLASH | SINGLE_QUOTE | DOUBLE_QUOTE ) ;
@]
!!!Ignore Symbols
* 6 productions

!!!!Whitespace
[@
 (1) WHITESPACE :
      ' ' | ASCII_TAB ;
@]
!!!!Comments
[@
 (2) COMMENT :
      NESTABLE_COMMENT | NON_NESTABLE_COMMENT | SINGLE_LINE_COMMENT ;

 (3) NESTABLE_COMMENT :
      '(*'
      ( . )* // anything other than '(*' or '*)'
      NESTABLE_COMMENT*
      '*)' ;

 (4) NON_NESTABLE_COMMENT :
      '/*'
      ( . )* // anything other than '*/'
      '*/' ;

 (5) SINGLE_LINE_COMMENT :
      '//'
      ( . )* // anything other than EOL
      END_OF_LINE ;

 (6) END_OF_LINE :
      ASCII_LF ASCII_CR? | ASCII_CR ASCII_LF? ;
to:
 syntax := statement* ;
 statement := symbol-id “:=” expression “;” ;
 expression := term ( “|” term )* ;
 term := factor+ ;
 factor := 
    ( symbol-id | literal | literal-range | group )
    ( “?” | “+” | “*” )* ;
 group : = “(“ expression “)” ;
 symbol-id := terminal-id | non-terminal-id ;
 terminal-id :=
    UPPERCASE-LETTER ( UPPERCASE-LETTER | DIGIT | “-” | “_” )* ;
 non-terminal-id :=
    LOWERCASE-LETTER ( LETTER | DIGIT | “-” | “_” )* ;
 literal :=
    ( ‘“‘ ( CHARACTER | “‘” )+ ‘“‘ ) |
    ( “‘“ ( CHARACTER | ‘“’ )+ “‘“ ) ;
 literal-range := literal “..” literal ;
 LETTER := UPPERCASE-LETTER | LOWERCASE-LETTER ;
 UPPERCASE-LETTER := “A” .. “Z” ;
 LOWERCASE-LETTER := “a” .. “z” ;
 DIGIT := “0” .. “9” ;
 CHARACTER :=
    LETTER | DIGIT |
    “ “ | “!” | “#” | “$” | “%” | “&” | “(“ | “)” | “*” | “+” |
    “,” | “-” | “.” | “/” | “:” | “;” | “<“ | “=” | “>” | “?” |
    “@” | “[“ | “]” | “^” | “_” | “`” | “{“ | “|” | “}” | “~” ;
2010-01-15 13:42 by benjk -
Changed lines 213-214 from:
       ( '+' | '-' {})? constTerm ( addOperator constTerm )* ;
to:
       ( '+' | '-' )? constTerm ( addOperator constTerm )* ;
Changed line 241 from:
       ( '+' | '-' {})? term ( addOperator term )* ;
to:
       ( '+' | '-' )? term ( addOperator term )* ;
2010-01-15 13:04 by benjk -
Added lines 2-3:
* 42 reserved words
2010-01-15 13:03 by benjk -
Added lines 1-10:
!!! Reserved Words
@@AND@@, @@ARRAY@@, @@BEGIN@@, @@BY@@, @@CASE@@, @@CONST@@,
@@DEFINITION@@, @@DIV@@, @@DO@@, @@ELSE@@, @@ELSIF@@, @@END@@,
@@ENUM@@, @@EXIT@@, @@FOR@@, @@FROM@@, @@IF@@, @@IMMUTABLE@@,
@@IMPLEMENTATION@@, @@IMPORT@@, @@IN@@, @@IS@@, @@LOOP@@, @@MOD@@,
@@MODULE@@, @@NOT@@, @@OF@@, @@OPAQUE@@, @@OR@@, @@POINTER@@,
@@PROCEDURE@@, @@RECORD@@, @@REPEAT@@, @@RETURN@@, @@SET@@,
@@THEN@@, @@TO@@, @@TYPE@@, @@UNTIL@@, @@VAR@@, @@VARIADIC@@,
@@WHILE@@

2010-01-15 10:51 by benjk -
Changed lines 11-13 from:
        MODULE moduleId ( '[' priority ']' )? ';'
       importList* block moduleId '.' ;
to:
       MODULE moduleId ( '[' priority ']' )? ';'
      importList* block moduleId '.' ;
Changed lines 15-18 from:
        DEFINITION MODULE moduleId ';'
       importList* definition*
       END moduleId '.' ;
to:
       DEFINITION MODULE moduleId ';'
      importList* definition*
      END moduleId '.' ;
Changed lines 20-21 from:
       IMPLEMENTATION programModule ;
to:
       IMPLEMENTATION programModule ;
Changed line 32 from:
       declaration*
to:
       declaration*
Changed lines 36-40 from:
        CONST ( constantDeclaration ';' )* |
       TYPE ( typeDeclaration ';' )* |
       VAR ( variableDeclaration ';' )* |
       procedureDeclaration ';'  ;
to:
       CONST ( constantDeclaration ';' )* |
      TYPE ( typeDeclaration ';' )* |
      VAR ( variableDeclaration ';' )* |
      procedureDeclaration ';'  ;
Changed lines 42-45 from:
        CONST ( constantDeclaration ';' )* |
       TYPE ( ident ( IS namedType | '=' ( type | OPAQUE recordType? ) ) ';' )* |
       VAR ( variableDeclaration ';' )* |
       procedureHeader ';' ;
to:
       CONST ( constantDeclaration ';' )* |
      TYPE ( ident ( IS namedType | '=' ( type | OPAQUE recordType? ) ) ';' )* |
      VAR ( variableDeclaration ';' )* |
      procedureHeader ';' ;
Changed line 50 from:
       ident '=' ( constExpression | structuredValue ) ;
to:
       ident '=' ( constExpression | structuredValue ) ;
Changed lines 55-56 from:
       ident ( IS namedType | '=' type ) ;
to:
       ident ( IS namedType | '=' type ) ;
Changed lines 58-59 from:
       namedType | anonymousType | enumerationType | setType ;
to:
       namedType | anonymousType | enumerationType | setType ;
Changed lines 63-64 from:
       arrayType | recordType | pointerType | procedureType ;
to:
       arrayType | recordType | pointerType | procedureType ;
Changed line 66 from:
       ENUM ( '(' baseType ')' )? identList? END |
to:
       ENUM ( '(' baseType ')' )? identList? END |
Changed lines 72-74 from:
        ARRAY arrayIndex ( ',' arrayIndex )*
       OF ( namedType | recordType | procedureType ) ;
to:
       ARRAY arrayIndex ( ',' arrayIndex )*
      OF ( namedType | recordType | procedureType ) ;
Changed lines 80-81 from:
       RECORD ( '(' baseType ')' )? fieldListSequence? END ;
to:
       RECORD ( '(' baseType ')' )? fieldListSequence? END ;
Changed lines 83-84 from:
       fieldList ( ';' fieldList )* ;
to:
       fieldList ( ';' fieldList )* ;
Changed line 86 from:
       identList ':'
to:
       identList ':'
Changed lines 90-91 from:
       SET OF ( namedType | '(' identList ')' ) ;
to:
       SET OF ( namedType | '(' identList ')' ) ;
Changed lines 93-94 from:
       POINTER TO IMMUTABLE? namedType ;
to:
       POINTER TO IMMUTABLE? namedType ;
Changed line 96 from:
       PROCEDURE
to:
       PROCEDURE
Changed lines 101-102 from:
       attributedFormalType ( ',' attributedFormalType )* ;
to:
       attributedFormalType ( ',' attributedFormalType )* ;
Changed lines 104-105 from:
       IMMUTABLE? VAR? formalType ;
to:
       IMMUTABLE? VAR? formalType ;
Changed line 114 from:
       ident ( '[' machineAddress ']' | ',' identList )?
to:
       ident ( '[' machineAddress ']' | ',' identList )?
Changed lines 122-123 from:
       procedureHeader ';' block ident ;
to:
       procedureHeader ';' block ident ;
Changed line 125 from:
       PROCEDURE
to:
       PROCEDURE
Changed lines 127-128 from:
       ident ( '(' formalParamList ')' )? ( ':' returnedType )? ;
to:
       ident ( '(' formalParamList ')' )? ( ':' returnedType )? ;
Changed lines 132-133 from:
       formalParams ( ';' ( formalParams | variadicParams ) )* ;
to:
       formalParams ( ';' ( formalParams | variadicParams ) )* ;
Changed lines 135-136 from:
       IMMUTABLE? VAR? identList ':' formalType ;
to:
       IMMUTABLE? VAR? identList ':' formalType ;
Changed lines 138-139 from:
        VARIADIC handle ( '[' indexParam ']' )? OF
       IMMUTABLE? VAR? ident ( ( '.' ident )* | ( ',' ident )* ':' formalType ) ;
to:
       VARIADIC handle ( '[' indexParam ']' )? OF
      IMMUTABLE? VAR? ident ( ( '.' ident )* | ( ',' ident )* ':' formalType ) ;
Changed lines 149-151 from:
          whileStatement | repeatStatement | loopStatement |
         forStatement | RETURN expression? | EXIT )? ;
to:
         whileStatement | repeatStatement | loopStatement |
        forStatement | RETURN expression? | EXIT )? ;
Changed lines 153-154 from:
       statement ( ';' statement )* ;
to:
       statement ( ';' statement )* ;
Changed line 156 from:
       designator
to:
       designator
Changed line 160 from:
       IF expression THEN statementSequence
to:
       IF expression THEN statementSequence
Changed lines 163-164 from:
       END ;
to:
       END ;
Changed line 166 from:
       CASE expression OF case ( '|' case )*
to:
       CASE expression OF case ( '|' case )*
Changed lines 168-169 from:
       END ;
to:
       END ;
Changed lines 171-172 from:
       caseLabelList ':' statementSequence ;
to:
       caseLabelList ':' statementSequence ;
Changed lines 174-175 from:
       caseLabels ( ',' caseLabels )* ;
to:
       caseLabels ( ',' caseLabels )* ;
Changed lines 177-178 from:
       constExpression ( '..' constExpression )? ;
to:
       constExpression ( '..' constExpression )? ;
Changed lines 180-181 from:
       WHILE expression DO statementSequence END ;
to:
       WHILE expression DO statementSequence END ;
Changed lines 183-184 from:
       REPEAT statementSequence UNTIL expression ;
to:
       REPEAT statementSequence UNTIL expression ;
Changed lines 186-187 from:
       LOOP statementSequence END ;
to:
       LOOP statementSequence END ;
Changed lines 189-190 from:
        FOR ident ':=' expression TO expression ( BY constExpression )?
       DO statementSequence END ;
to:
       FOR ident ':=' expression TO expression ( BY constExpression )?
      DO statementSequence END ;
Changed lines 195-196 from:
       simpleConstExpr ( relation simpleConstExpr | '::' namedType )? ;
to:
       simpleConstExpr ( relation simpleConstExpr | '::' namedType )? ;
Changed lines 207-208 from:
       constFactor ( mulOperator constFactor )* ;
to:
       constFactor ( mulOperator constFactor )* ;
Changed line 213 from:
       number | string | qualident |
to:
       number | string | qualident |
Changed lines 217-218 from:
       qualident ( designatorTail )? ;
to:
       qualident ( designatorTail )? ;
Changed lines 223-224 from:
       expression ( ',' expression )* ;
to:
       expression ( ',' expression )* ;
Changed lines 226-227 from:
       simpleExpression ( relation simpleExpression | '::' namedType )? ;
to:
       simpleExpression ( relation simpleExpression | '::' namedType )? ;
Changed lines 232-233 from:
       factor ( mulOperator factor )* ;
to:
       factor ( mulOperator factor )* ;
Changed lines 235-237 from:
        number |
       string |
       designatorOrProcedureCall |
to:
       number |
      string |
      designatorOrProcedureCall |
Changed lines 241-242 from:
       qualident ( designatorTail? actualParameters? ) ;
to:
       qualident ( designatorTail? actualParameters? ) ;
Changed lines 252-253 from:
        constExpression ( ( BY | '..' ) constExpression  )? |
       structuredValue ;
to:
       constExpression ( ( BY | '..' ) constExpression  )? |
      structuredValue ;
Changed lines 258-259 from:
       ident ( '.' ident )* ;
to:
       ident ( '.' ident )* ;
Changed lines 261-262 from:
       ident ( ',' ident )* ;
to:
       ident ( ',' ident )* ;
Changed line 283 from:
       FOREIGN ( '=' string )? | INLINE | NOINLINE |
to:
       FOREIGN ( '=' string )? | INLINE | NOINLINE |
Changed line 286 from:
       implementationDefinedPragma ( '+' | '-' | '=' ( ident | number ) )?
to:
       implementationDefinedPragma ( '+' | '-' | '=' ( ident | number ) )?
Changed line 303 from:
       DIGIT+ |
to:
       DIGIT+ |
Changed line 306 from:
       BINARY_DIGIT+ 'B' |
to:
       BINARY_DIGIT+ 'B' |
Changed line 309 from:
       DIGIT SEDECIMAL_DIGIT* ( 'C' | 'H' ) |
to:
       DIGIT SEDECIMAL_DIGIT* ( 'C' | 'H' ) |
Changed lines 312-313 from:
       DIGIT+ '.' DIGIT+ ( 'E' ( '+' | '-' )? DIGIT+ )? ;
to:
       DIGIT+ '.' DIGIT+ ( 'E' ( '+' | '-' )? DIGIT+ )? ;
Changed lines 315-317 from:
        SINGLE_QUOTE ( CHARACTER | DOUBLE_QUOTE )* SINGLE_QUOTE |
       DOUBLE_QUOTE ( CHARACTER | SINGLE_QUOTE )* DOUBLE_QUOTE ;
to:
       SINGLE_QUOTE ( CHARACTER | DOUBLE_QUOTE )* SINGLE_QUOTE |
      DOUBLE_QUOTE ( CHARACTER | SINGLE_QUOTE )* DOUBLE_QUOTE ;
Changed lines 322-323 from:
       BINARY_DIGIT | '2' | '3' | '4' | '5' | '6' | '7' | '8' | '9' ;
to:
       BINARY_DIGIT | '2' | '3' | '4' | '5' | '6' | '7' | '8' | '9' ;
Changed lines 328-329 from:
       DIGIT | 'A' | 'B' | 'C' | 'D' | 'E' | 'F' ;
to:
       DIGIT | 'A' | 'B' | 'C' | 'D' | 'E' | 'F' ;
Changed line 331 from:
       DIGIT | LETTER |
to:
       DIGIT | LETTER |
Changed lines 336-337 from:
       ESCAPE_SEQUENCE  ;
to:
       ESCAPE_SEQUENCE  ;
Changed line 339 from:
       BACKSLASH
to:
       BACKSLASH
Changed lines 353-354 from:
       NESTABLE_COMMENT | NON_NESTABLE_COMMENT | SINGLE_LINE_COMMENT ;
to:
       NESTABLE_COMMENT | NON_NESTABLE_COMMENT | SINGLE_LINE_COMMENT ;
Changed line 358 from:
       NESTABLE_COMMENT*
to:
       NESTABLE_COMMENT*
Changed lines 369-370 from:
       END_OF_LINE ;
to:
       END_OF_LINE ;
Changed line 372 from:
       ASCII_LF ASCII_CR? | ASCII_CR ASCII_LF? ;
to:
       ASCII_LF ASCII_CR? | ASCII_CR ASCII_LF? ;
2010-01-15 10:45 by benjk -
Changed lines 8-9 from:
programModule | definitionOfModule | implementationOfModule ;
to:
       programModule | definitionOfModule | implementationOfModule ;
Changed lines 11-13 from:
MODULE moduleId ( '[' priority ']' )? ';'
importList* block moduleId '.' ;
to:
      MODULE moduleId ( '[' priority ']' )? ';'
       
importList* block moduleId '.' ;
Changed lines 15-18 from:
DEFINITION MODULE moduleId ';'
importList* definition*
END
moduleId '.' ;
to:
       DEFINITION MODULE moduleId ';'
        importList* definition*
       
END moduleId '.' ;
Changed lines 20-21 from:
IMPLEMENTATION programModule ;
to:
       IMPLEMENTATION programModule ;
Changed lines 29-30 from:
( FROM moduleId IMPORT ( identList | '*' ) | IMPORT identList ) ';' ;
to:
       ( FROM moduleId IMPORT ( identList | '*' ) | IMPORT identList ) ';' ;
Changed lines 32-34 from:
declaration*
( BEGIN statementSequence )? END ;
to:
       declaration*
       ( BEGIN statementSequence )? END ;
Changed lines 36-40 from:
CONST ( constantDeclaration ';' )* |
TYPE ( typeDeclaration ';' )* |
VAR ( variableDeclaration
';' )* |
procedureDeclaration ';'  ;
to:
       CONST ( constantDeclaration ';' )* |
       TYPE ( typeDeclaration ';' )* |
        VAR ( variableDeclaration ';' )* |
       
procedureDeclaration ';'  ;
Changed lines 42-45 from:
CONST ( constantDeclaration ';' )* |
TYPE ( ident ( IS namedType |
'=' ( type | OPAQUE recordType? ) ) ';' )* |
VAR ( variableDeclaration ';' )*
|
procedureHeader ';' ;
to:
       CONST ( constantDeclaration ';' )* |
        TYPE ( ident ( IS namedType | '=' ( type | OPAQUE recordType? ) ) ';' )* |
        VAR ( variableDeclaration ';' )* |
       
procedureHeader ';' ;
Changed line 50 from:
ident '=' ( constExpression | structuredValue ) ;
to:
       ident '=' ( constExpression | structuredValue ) ;
Changed lines 55-56 from:
ident ( IS namedType | '=' type ) ;
to:
       ident ( IS namedType | '=' type ) ;
Changed lines 58-59 from:
namedType | anonymousType | enumerationType | setType ;
to:
       namedType | anonymousType | enumerationType | setType ;
Changed lines 63-64 from:
arrayType | recordType | pointerType | procedureType ;
to:
       arrayType | recordType | pointerType | procedureType ;
Changed lines 66-68 from:
ENUM ( '(' baseType ')' )? identList? END |
'(' identList ')' // simple notation ;
to:
       ENUM ( '(' baseType ')' )? identList? END |
     
'(' identList ')' // simple notation ;
Changed lines 72-74 from:
ARRAY arrayIndex ( ',' arrayIndex )*
OF
( namedType | recordType | procedureType ) ;
to:
      ARRAY arrayIndex ( ',' arrayIndex )*
       
OF ( namedType | recordType | procedureType ) ;
Changed lines 80-81 from:
RECORD ( '(' baseType ')' )? fieldListSequence? END ;
to:
       RECORD ( '(' baseType ')' )? fieldListSequence? END ;
Changed lines 83-84 from:
fieldList ( ';' fieldList )* ;
to:
       fieldList ( ';' fieldList )* ;
Changed lines 86-88 from:
identList ':'
( namedType | arrayType | recordType | procedureType ) ;
to:
        identList ':'
       ( namedType | arrayType | recordType | procedureType ) ;
Changed lines 90-91 from:
SET OF ( namedType | '(' identList ')' ) ;
to:
       SET OF ( namedType | '(' identList ')' ) ;
Changed lines 93-94 from:
POINTER TO IMMUTABLE? namedType ;
to:
       POINTER TO IMMUTABLE? namedType ;
Changed lines 96-99 from:
PROCEDURE
( '(' formalTypeList ')' )?
(
':' returnedType )? ;
to:
       PROCEDURE
      ( '(' formalTypeList ')' )?
     
( ':' returnedType )? ;
Changed lines 101-102 from:
attributedFormalType ( ',' attributedFormalType )* ;
to:
       attributedFormalType ( ',' attributedFormalType )* ;
Changed lines 104-105 from:
IMMUTABLE? VAR? formalType ;
to:
       IMMUTABLE? VAR? formalType ;
Changed lines 107-108 from:
( ARRAY OF )? namedType ;
to:
       ( ARRAY OF )? namedType ;
Changed lines 114-116 from:
ident ( '[' machineAddress ']' | ',' identList )?
':' ( namedType | anonymousType ) ;
to:
        ident ( '[' machineAddress ']' | ',' identList )?
     
':' ( namedType | anonymousType ) ;
Changed lines 122-123 from:
procedureHeader ';' block ident ;
to:
       procedureHeader ';' block ident ;
Changed lines 125-128 from:
PROCEDURE
( '(' ident ':' receiverType ')' )?
ident
( '(' formalParamList ')' )? ( ':' returnedType )? ;
to:
        PROCEDURE
      ( '(' ident ':' receiverType ')' )?
       
ident ( '(' formalParamList ')' )? ( ':' returnedType )? ;
Changed lines 132-133 from:
formalParams ( ';' ( formalParams | variadicParams ) )* ;
to:
       formalParams ( ';' ( formalParams | variadicParams ) )* ;
Changed lines 135-136 from:
IMMUTABLE? VAR? identList ':' formalType ;
to:
       IMMUTABLE? VAR? identList ':' formalType ;
Changed lines 138-139 from:
VARIADIC handle ( '[' indexParam ']' )? OF
IMMUTABLE?
VAR? ident ( ( '.' ident )* | ( ',' ident )* ':' formalType ) ;
to:
      VARIADIC handle ( '[' indexParam ']' )? OF
       
IMMUTABLE? VAR? ident ( ( '.' ident )* | ( ',' ident )* ':' formalType ) ;
Changed lines 148-151 from:
( assignmentOrProcedureCall | ifStatement | caseStatement |
  whileStatement | repeatStatement | loopStatement |
  forStatement | RETURN expression? | EXIT )? ;
to:
       ( assignmentOrProcedureCall | ifStatement | caseStatement |
         whileStatement | repeatStatement | loopStatement |
       
  forStatement | RETURN expression? | EXIT )? ;
Changed lines 153-154 from:
statement ( ';' statement )* ;
to:
       statement ( ';' statement )* ;
Changed lines 156-158 from:
designator
(
':=' ( expression | structuredValue ) | '++' | '--' | actualParameters )? ;
to:
       designator
     
( ':=' ( expression | structuredValue ) | '++' | '--' | actualParameters )? ;
Changed lines 160-164 from:
IF expression THEN statementSequence
( ELSIF expression THEN statementSequence )*
( ELSE
statementSequence )?
END
;
to:
        IF expression THEN statementSequence
       ( ELSIF expression THEN statementSequence )*
      ( ELSE statementSequence )?
       
END ;
Changed lines 166-169 from:
CASE expression OF case ( '|' case )*
( ELSE statementSequence
)?
END
;
to:
       CASE expression OF case ( '|' case )*
      ( ELSE statementSequence )?
       
END ;
Changed lines 171-172 from:
caseLabelList ':' statementSequence ;
to:
       caseLabelList ':' statementSequence ;
Changed lines 174-175 from:
caseLabels ( ',' caseLabels )* ;
to:
       caseLabels ( ',' caseLabels )* ;
Changed lines 177-178 from:
constExpression ( '..' constExpression )? ;
to:
       constExpression ( '..' constExpression )? ;
Changed lines 180-181 from:
WHILE expression DO statementSequence END ;
to:
       WHILE expression DO statementSequence END ;
Changed lines 183-184 from:
REPEAT statementSequence UNTIL expression ;
to:
       REPEAT statementSequence UNTIL expression ;
Changed lines 186-187 from:
LOOP statementSequence END ;
to:
       LOOP statementSequence END ;
Changed lines 189-190 from:
FOR ident ':=' expression TO expression ( BY constExpression )?
DO
statementSequence END ;
to:
        FOR ident ':=' expression TO expression ( BY constExpression )?
       
DO statementSequence END ;
Changed lines 195-196 from:
simpleConstExpr ( relation simpleConstExpr | '::' namedType )? ;
to:
       simpleConstExpr ( relation simpleConstExpr | '::' namedType )? ;
Changed lines 198-199 from:
'=' | '#' | '<' | '<=' | '>' | '>=' | IN | IS ;
to:
       '=' | '#' | '<' | '<=' | '>' | '>=' | IN | IS ;
Changed lines 201-202 from:
( '+' | '-' {})? constTerm ( addOperator constTerm )* ;
to:
       ( '+' | '-' {})? constTerm ( addOperator constTerm )* ;
Changed lines 204-205 from:
'+' | '-' | OR ;
to:
       '+' | '-' | OR ;
Changed lines 207-208 from:
constFactor ( mulOperator constFactor )* ;
to:
       constFactor ( mulOperator constFactor )* ;
Changed lines 210-211 from:
'*' | '/' | DIV | MOD | AND | '&' ;
to:
       '*' | '/' | DIV | MOD | AND | '&' ;
Changed lines 213-215 from:
number | string | qualident |
'(' constExpression ')' | ( NOT | '~' ) constFactor ;
to:
       number | string | qualident |
     
'(' constExpression ')' | ( NOT | '~' ) constFactor ;
Changed lines 217-218 from:
qualident ( designatorTail )? ;
to:
       qualident ( designatorTail )? ;
Changed lines 220-221 from:
( ( '[' expressionList ']' | '^' ) ( '.' ident )* )+ ;
to:
       ( ( '[' expressionList ']' | '^' ) ( '.' ident )* )+ ;
Changed lines 223-224 from:
expression ( ',' expression )* ;
to:
       expression ( ',' expression )* ;
Changed lines 226-227 from:
simpleExpression ( relation simpleExpression | '::' namedType )? ;
to:
       simpleExpression ( relation simpleExpression | '::' namedType )? ;
Changed lines 229-230 from:
( '+' | '-' {})? term ( addOperator term )* ;
to:
       ( '+' | '-' {})? term ( addOperator term )* ;
Changed lines 232-233 from:
factor ( mulOperator factor )* ;
to:
       factor ( mulOperator factor )* ;
Changed lines 235-239 from:
number |
string |
designatorOrProcedureCall
|
'(' expression ')' | ( NOT | '~' ) factor ;
to:
        number |
       string |
        designatorOrProcedureCall |
     
'(' expression ')' | ( NOT | '~' ) factor ;
Changed lines 241-242 from:
qualident ( designatorTail? actualParameters? ) ;
to:
       qualident ( designatorTail? actualParameters? ) ;
Changed line 244 from:
'(' expressionList? ')' ;
to:
       '(' expressionList? ')' ;
Changed lines 249-250 from:
'{' ( valueComponent ( ',' valueComponent )* )? '}' ;
to:
       '{' ( valueComponent ( ',' valueComponent )* )? '}' ;
Changed lines 252-253 from:
constExpression ( ( BY | '..' ) constExpression  )? |
structuredValue ;
to:
        constExpression ( ( BY | '..' ) constExpression  )? |
       
structuredValue ;
Changed lines 258-259 from:
ident ( '.' ident )* ;
to:
       ident ( '.' ident )* ;
Changed lines 261-262 from:
ident ( ',' ident )* ;
to:
       ident ( ',' ident )* ;
Changed line 274 from:
'<*' (
to:
       '<*' (
Changed lines 276-277 from:
// conditional compilation pragmas
(
IF | ELSIF ) constExpression | ELSE | ENDIF |
to:
      // conditional compilation pragmas
     
( IF | ELSIF ) constExpression | ELSE | ENDIF |
Changed lines 279-280 from:
// console message pragmas
(
INFO | WARN | ERROR | FATAL ) compileTimeMessage |
to:
      // console message pragmas
     
( INFO | WARN | ERROR | FATAL ) compileTimeMessage |
Changed lines 282-283 from:
// other language defined pragmas
FOREIGN ( '=' string )? | INLINE | NOINLINE |
to:
      // other language defined pragmas
     
FOREIGN ( '=' string )? | INLINE | NOINLINE |
Changed lines 285-286 from:
// implementation defined pragmas
implementationDefinedPragma
( '+' | '-' | '=' ( ident | number ) )?
to:
      // implementation defined pragmas
       
implementationDefinedPragma ( '+' | '-' | '=' ( ident | number ) )?
Changed lines 288-289 from:
) '*>' ;
to:
       ) '*>' ;
Changed lines 299-300 from:
( '_' | '$' | LETTER ) ( '_' | '$' | LETTER | DIGIT )* ;
to:
       ( '_' | '$' | LETTER ) ( '_' | '$' | LETTER | DIGIT )* ;
Changed lines 302-303 from:
// Decimal integer
DIGIT+
|
to:
      // Decimal integer
       
DIGIT+ |
Changed lines 305-306 from:
// Binary integer
BINARY_DIGIT+
'B' |
to:
      // Binary integer
       
BINARY_DIGIT+ 'B' |
Changed lines 308-309 from:
// Sedecimal integer
DIGIT
SEDECIMAL_DIGIT* ( 'C' | 'H' ) |
to:
      // Sedecimal integer
       
DIGIT SEDECIMAL_DIGIT* ( 'C' | 'H' ) |
Changed lines 311-313 from:
// Real number
DIGIT+
'.' DIGIT+ ( 'E' ( '+' | '-' )? DIGIT+ )? ;
to:
      // Real number
       
DIGIT+ '.' DIGIT+ ( 'E' ( '+' | '-' )? DIGIT+ )? ;
Changed lines 315-317 from:
   SINGLE_QUOTE ( CHARACTER | DOUBLE_QUOTE )* SINGLE_QUOTE |
    DOUBLE_QUOTE ( CHARACTER | SINGLE_QUOTE )* DOUBLE_QUOTE ;
to:
       SINGLE_QUOTE ( CHARACTER | DOUBLE_QUOTE )* SINGLE_QUOTE |
   
    DOUBLE_QUOTE ( CHARACTER | SINGLE_QUOTE )* DOUBLE_QUOTE ;
Changed lines 319-320 from:
'A' .. 'Z' | 'a' .. 'z' ;
to:
       'A' .. 'Z' | 'a' .. 'z' ;
Changed lines 322-323 from:
BINARY_DIGIT | '2' | '3' | '4' | '5' | '6' | '7' | '8' | '9' ;
to:
       BINARY_DIGIT | '2' | '3' | '4' | '5' | '6' | '7' | '8' | '9' ;
Changed lines 325-326 from:
'0' | '1' ;
to:
       '0' | '1' ;
Changed lines 328-329 from:
DIGIT | 'A' | 'B' | 'C' | 'D' | 'E' | 'F' ;
to:
       DIGIT | 'A' | 'B' | 'C' | 'D' | 'E' | 'F' ;
Changed lines 331-337 from:
DIGIT | LETTER |
// any printable characters other than single and double quote
' ' | '!' | '#' | '$' | '%' | '&' | '(' | ')' | '*' | '+' |
',' |
'-' | '.' | ':' | ';' | '<' | '=' | '>' | '?' | '@' |
'[' | ']' | '^' | '_' | '`' | '{' | '|' | '}' | '~' |
ESCAPE_SEQUENCE  ;
to:
       DIGIT | LETTER |
      // any printable characters other than single and double quote
       ' ' | '!' | '#' | '$' | '%' | '&' | '(' | ')' | '*' | '+' |
      ',' | '-' | '.' | ':' | ';' | '<' | '=' | '>' | '?' | '@' |
      '[' | ']' | '^' | '_' | '`' | '{' | '|' | '}' | '~' |
       
ESCAPE_SEQUENCE  ;
Changed lines 339-340 from:
BACKSLASH
(
'0' | 'n' | 'r' | 't' | BACKSLASH | SINGLE_QUOTE | DOUBLE_QUOTE ) ;
to:
       BACKSLASH
     
( '0' | 'n' | 'r' | 't' | BACKSLASH | SINGLE_QUOTE | DOUBLE_QUOTE ) ;
Changed line 348 from:
' ' | ASCII_TAB ;
to:
       ' ' | ASCII_TAB ;
Changed lines 353-354 from:
NESTABLE_COMMENT | NON_NESTABLE_COMMENT | SINGLE_LINE_COMMENT ;
to:
       NESTABLE_COMMENT | NON_NESTABLE_COMMENT | SINGLE_LINE_COMMENT ;
Changed lines 356-360 from:
'(*'
( . )* // anything other than
'(*' or '*)'
NESTABLE_COMMENT*
'*)' ;
to:
     '(*'
       ( . )* // anything other than '(*' or '*)'
        NESTABLE_COMMENT*
     
'*)' ;
Changed lines 362-365 from:
'/*'
( . )* // anything other than
'*/'
'*/' ;
to:
     '/*'
       ( . )* // anything other than '*/'
     
'*/' ;
Changed lines 367-370 from:
'//'
( . )* // anything other than EOL
END_OF_LINE
;
to:
      '//'
      ( . )* // anything other than EOL
       
END_OF_LINE ;
Changed line 372 from:
ASCII_LF ASCII_CR? | ASCII_CR ASCII_LF? ;
to:
       ASCII_LF ASCII_CR? | ASCII_CR ASCII_LF? ;
2010-01-15 10:35 by benjk -
Changed line 192 from:
!!!!Expressions ***
to:
!!!!Expressions
2010-01-15 10:34 by benjk -
Changed line 246 from:
!!!!Value Constructors ***
to:
!!!!Value Constructors
Added line 297:
2010-01-15 10:32 by benjk -
Changed line 25 from:
to:
@]
Changed line 27 from:
to:
[@
Changed line 46 from:
to:
@]
Changed line 48 from:
to:
[@
Changed line 51 from:
to:
@]
Changed line 53 from:
to:
[@
Changed line 110 from:
to:
@]
Changed line 112 from:
to:
[@
Changed line 118 from:
to:
@]
Changed line 120 from:
to:
[@
Changed line 144 from:
to:
@]
Changed line 146 from:
to:
[@
Changed line 191 from:
to:
@]
Changed line 193 from:
to:
[@
Changed line 245 from:
to:
@]
Changed line 247 from:
to:
[@
Changed line 254 from:
to:
@]
Changed line 256 from:
to:
[@
Changed line 264 from:
to:
@]
Changed line 266 from:
to:
[@
Changed line 270 from:
to:
@]
Changed line 272 from:
to:
[@
Changed line 293 from:
to:
@]
Changed line 296 from:
to:
[@
Changed line 340 from:
to:
@]
Changed line 345 from:
to:
[@
Changed line 348 from:
to:
@]
Changed line 350 from:
to:
[@
2010-01-15 10:29 by benjk -
Added lines 1-372:
!!! Non-Terminal Symbols
* 62 productions
* 16 aliases

!!!!Compilation Units
[@
 (1) compilationUnit :
programModule | definitionOfModule | implementationOfModule ;

 (2) programModule :
MODULE moduleId ( '[' priority ']' )? ';'
importList* block moduleId '.' ;

 (3) definitionOfModule :
DEFINITION MODULE moduleId ';'
importList* definition*
END moduleId '.' ;

 (4) implementationOfModule :
IMPLEMENTATION programModule ;

    moduleId : ident ;

    priority : constExpression ;

!!!!Import Lists, Blocks, Declarations, Definitions

 (5) importList :
( FROM moduleId IMPORT ( identList | '*' ) | IMPORT identList ) ';' ;

 (6) block :
declaration*
( BEGIN statementSequence )? END ;

 (7) declaration :
CONST ( constantDeclaration ';' )* |
TYPE ( typeDeclaration ';' )* |
VAR ( variableDeclaration ';' )* |
procedureDeclaration ';'  ;

 (8) definition :
CONST ( constantDeclaration ';' )* |
TYPE ( ident ( IS namedType | '=' ( type | OPAQUE recordType? ) ) ';' )* |
VAR ( variableDeclaration ';' )* |
procedureHeader ';' ;

!!!!Constant Declarations

 (9) constantDeclaration :
ident '=' ( constExpression | structuredValue ) ;

!!!!Type Declaration

(10) typeDeclaration :
ident ( IS namedType | '=' type ) ;

(11) type :
namedType | anonymousType | enumerationType | setType ;

    namedType : qualident ;

(12) anonymousType :
arrayType | recordType | pointerType | procedureType ;

(13) enumerationType :
ENUM ( '(' baseType ')' )? identList? END |
'(' identList ')' // simple notation ;

    baseType : qualident ;

(14) arrayType :
ARRAY arrayIndex ( ',' arrayIndex )*
OF ( namedType | recordType | procedureType ) ;

    arrayIndex : ordinalConstExpression ;

    ordinalConstExpression : constExpression ;

(15) recordType :
RECORD ( '(' baseType ')' )? fieldListSequence? END ;

(16) fieldListSequence :
fieldList ( ';' fieldList )* ;

(17) fieldList :
identList ':'
( namedType | arrayType | recordType | procedureType ) ;

(18) setType :
SET OF ( namedType | '(' identList ')' ) ;

(19) pointerType :
POINTER TO IMMUTABLE? namedType ;

(20) procedureType :
PROCEDURE
( '(' formalTypeList ')' )?
( ':' returnedType )? ;

(21) formalTypeList :
attributedFormalType ( ',' attributedFormalType )* ;

(22) attributedFormalType :
IMMUTABLE? VAR? formalType ;

(23) formalType :
( ARRAY OF )? namedType ;

    returnedType : namedType ;

!!!!Variable Declarations

(24) variableDeclaration :
ident ( '[' machineAddress ']' | ',' identList )?
':' ( namedType | anonymousType ) ;

    machineAddress : constExpression ;

!!!!Procedure Declarations

(25) procedureDeclaration :
procedureHeader ';' block ident ;

(26) procedureHeader :
PROCEDURE
( '(' ident ':' receiverType ')' )?
ident ( '(' formalParamList ')' )? ( ':' returnedType )? ;

    receiverType : ident ;

(27) formalParamList :
formalParams ( ';' ( formalParams | variadicParams ) )* ;

(28) formalParams :
IMMUTABLE? VAR? identList ':' formalType ;

(29) variadicParams :
VARIADIC handle ( '[' indexParam ']' )? OF
IMMUTABLE? VAR? ident ( ( '.' ident )* | ( ',' ident )* ':' formalType ) ;

    handle : ident ;

    indexParam : ident ;

!!!!Statements

(30) statement :
( assignmentOrProcedureCall | ifStatement | caseStatement |
  whileStatement | repeatStatement | loopStatement |
  forStatement | RETURN expression? | EXIT )? ;

(31) statementSequence :
statement ( ';' statement )* ;

(32) assignmentOrProcedureCall :
designator
( ':=' ( expression | structuredValue ) | '++' | '--' | actualParameters )? ;

(33) ifStatement :
IF expression THEN statementSequence
( ELSIF expression THEN statementSequence )*
( ELSE statementSequence )?
END ;

(34) caseStatement :
CASE expression OF case ( '|' case )*
( ELSE statementSequence )?
END ;

(35) case :
caseLabelList ':' statementSequence ;

(36) caseLabelList :
caseLabels ( ',' caseLabels )* ;

(37) caseLabels :
constExpression ( '..' constExpression )? ;

(38) whileStatement :
WHILE expression DO statementSequence END ;

(39) repeatStatement :
REPEAT statementSequence UNTIL expression ;

(40) loopStatement :
LOOP statementSequence END ;

(41) forStatement :
FOR ident ':=' expression TO expression ( BY constExpression )?
DO statementSequence END ;

!!!!Expressions ***

(42) constExpression :
simpleConstExpr ( relation simpleConstExpr | '::' namedType )? ;

(43) relation :
'=' | '#' | '<' | '<=' | '>' | '>=' | IN | IS ;

(44) simpleConstExpr :
( '+' | '-' {})? constTerm ( addOperator constTerm )* ;

(45) addOperator :
'+' | '-' | OR ;

(46) constTerm :
constFactor ( mulOperator constFactor )* ;

(47) mulOperator :
'*' | '/' | DIV | MOD | AND | '&' ;

(48) constFactor :
number | string | qualident |
'(' constExpression ')' | ( NOT | '~' ) constFactor ;

(49) designator :
qualident ( designatorTail )? ;

(50) designatorTail :
( ( '[' expressionList ']' | '^' ) ( '.' ident )* )+ ;

(51) expressionList :
expression ( ',' expression )* ;

(52) expression :
simpleExpression ( relation simpleExpression | '::' namedType )? ;

(53) simpleExpression :
( '+' | '-' {})? term ( addOperator term )* ;

(54) term :
factor ( mulOperator factor )* ;

(55) factor :
number |
string |
designatorOrProcedureCall |
'(' expression ')' | ( NOT | '~' ) factor ;

(56) designatorOrProcedureCall :
qualident ( designatorTail? actualParameters? ) ;

(57) actualParameters :
'(' expressionList? ')' ;

!!!!Value Constructors ***

(58) structuredValue :
'{' ( valueComponent ( ',' valueComponent )* )? '}' ;

(59) valueComponent :
constExpression ( ( BY | '..' ) constExpression  )? |
structuredValue ;

!!!!Identifiers

(60) qualident :
ident ( '.' ident )* ;

(61) identList :
ident ( ',' ident )* ;

    ident : IDENT ;

!!!!Literals

    number : NUMBER ;

    string : STRING ;

!!!!Pragmas

(62) pragma :
'<*' (

// conditional compilation pragmas
( IF | ELSIF ) constExpression | ELSE | ENDIF |

// console message pragmas
( INFO | WARN | ERROR | FATAL ) compileTimeMessage |

// other language defined pragmas
FOREIGN ( '=' string )? | INLINE | NOINLINE |

// implementation defined pragmas
implementationDefinedPragma ( '+' | '-' | '=' ( ident | number ) )?

) '*>' ;

    compileTimeMessage : string ;

    implementationDefinedPragma : ident ;

!!!Terminal Symbols
* 9 productions

 (1) IDENT :
( '_' | '$' | LETTER ) ( '_' | '$' | LETTER | DIGIT )* ;

 (2) NUMBER :
// Decimal integer
DIGIT+ |

// Binary integer
BINARY_DIGIT+ 'B' |

// Sedecimal integer
DIGIT SEDECIMAL_DIGIT* ( 'C' | 'H' ) |

// Real number
DIGIT+ '.' DIGIT+ ( 'E' ( '+' | '-' )? DIGIT+ )? ;

 (3) STRING :
    SINGLE_QUOTE ( CHARACTER | DOUBLE_QUOTE )* SINGLE_QUOTE |
    DOUBLE_QUOTE ( CHARACTER | SINGLE_QUOTE )* DOUBLE_QUOTE ;

 (4) LETTER :
'A' .. 'Z' | 'a' .. 'z' ;

 (5) DIGIT :
BINARY_DIGIT | '2' | '3' | '4' | '5' | '6' | '7' | '8' | '9' ;

 (6) BINARY_DIGIT :
'0' | '1' ;

 (7) SEDECIMAL_DIGIT :
DIGIT | 'A' | 'B' | 'C' | 'D' | 'E' | 'F' ;

 (8) CHARACTER :
DIGIT | LETTER |
// any printable characters other than single and double quote
' ' | '!' | '#' | '$' | '%' | '&' | '(' | ')' | '*' | '+' |
',' | '-' | '.' | ':' | ';' | '<' | '=' | '>' | '?' | '@' |
'[' | ']' | '^' | '_' | '`' | '{' | '|' | '}' | '~' |
ESCAPE_SEQUENCE  ;

 (8) ESCAPE_SEQUENCE :
BACKSLASH
( '0' | 'n' | 'r' | 't' | BACKSLASH | SINGLE_QUOTE | DOUBLE_QUOTE ) ;

!!!Ignore Symbols
* 6 productions

!!!!Whitespace

 (1) WHITESPACE :
' ' | ASCII_TAB ;

!!!!Comments

 (2) COMMENT :
NESTABLE_COMMENT | NON_NESTABLE_COMMENT | SINGLE_LINE_COMMENT ;

 (3) NESTABLE_COMMENT :
'(*'
( . )* // anything other than '(*' or '*)'
NESTABLE_COMMENT*
'*)' ;

 (4) NON_NESTABLE_COMMENT :
'/*'
( . )* // anything other than '*/'
'*/' ;

 (5) SINGLE_LINE_COMMENT :
'//'
( . )* // anything other than EOL
END_OF_LINE ;

 (6) END_OF_LINE :
ASCII_LF ASCII_CR? | ASCII_CR ASCII_LF? ;
@]