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

Grammar

Spec.Grammar History

Hide minor edits - Show changes to output

2015-09-15 06:29 by trijezdci -
Changed line 1 from:
!!! (1) Non-Terminals
to:
!!! Non-Terminals
Changed line 5 from:
!!! (2) Terminals
to:
!!! Terminals
Changed line 9 from:
!!! (3) Ignore Symbols
to:
!!! Ignore Symbols
Changed line 13 from:
!!! (4) Pragmas
to:
!!! Pragmas
2015-09-15 06:04 by trijezdci -
Changed lines 15-19 from:
*[[SyntaxDiagrams.Pragmas|Syntax Diagrams]]
to:
*[[SyntaxDiagrams.Pragmas|Syntax Diagrams]]

!!! Downloads
*[[https://bitbucket.org/trijezdci/m2r10/raw/tip/_GRAMMAR/Modula2.g|EBNF Grammar (ANTLR)]]
*[[https://bitbucket.org/trijezdci/m2r10/downloads/SyntaxDiagrams.pdf|Syntax Diagrams (PDF)
]]
2015-09-14 13:03 by trijezdci -
Changed lines 3-4 from:
*[[Grammar.SyntaxDiagrams.NonTerminals|Syntax Diagrams]]
to:
*[[SyntaxDiagrams.NonTerminals|Syntax Diagrams]]
Changed lines 7-8 from:
*[[Grammar.SyntaxDiagrams.Terminals|Syntax Diagrams]]
to:
*[[SyntaxDiagrams.Terminals|Syntax Diagrams]]
Changed lines 11-12 from:
*[[Grammar.SyntaxDiagrams.IgnoreSymbols|Syntax Diagrams]]
to:
*[[SyntaxDiagrams.IgnoreSymbols|Syntax Diagrams]]
Changed line 15 from:
*[[Grammar.SyntaxDiagrams.Pragmas|Syntax Diagrams]]
to:
*[[SyntaxDiagrams.Pragmas|Syntax Diagrams]]
2015-09-14 13:02 by trijezdci -
Changed lines 3-4 from:
*[[Spec.Grammar.SyntaxDiagrams.NonTerminals|Syntax Diagrams]]
to:
*[[Grammar.SyntaxDiagrams.NonTerminals|Syntax Diagrams]]
Changed lines 7-8 from:
*[[Spec.Grammar.SyntaxDiagrams.Terminals|Syntax Diagrams]]
to:
*[[Grammar.SyntaxDiagrams.Terminals|Syntax Diagrams]]
Changed lines 11-12 from:
*[[Spec.Grammar.SyntaxDiagrams.IgnoreSymbols|Syntax Diagrams]]
to:
*[[Grammar.SyntaxDiagrams.IgnoreSymbols|Syntax Diagrams]]
Changed line 15 from:
*[[Spec.Grammar.SyntaxDiagrams.Pragmas|Syntax Diagrams]]
to:
*[[Grammar.SyntaxDiagrams.Pragmas|Syntax Diagrams]]
2015-09-14 13:02 by trijezdci -
Changed lines 3-4 from:
*[[Diagrams.NonTerminals|Syntax Diagrams]]
to:
*[[Spec.Grammar.SyntaxDiagrams.NonTerminals|Syntax Diagrams]]
Changed lines 7-8 from:
*[[Diagrams.Terminals|Syntax Diagrams]]
to:
*[[Spec.Grammar.SyntaxDiagrams.Terminals|Syntax Diagrams]]
Changed lines 11-12 from:
*[[Diagrams.IgnoreSymbols|Syntax Diagrams]]
to:
*[[Spec.Grammar.SyntaxDiagrams.IgnoreSymbols|Syntax Diagrams]]
Changed line 15 from:
*[[Diagrams.Pragmas|Syntax Diagrams]]
to:
*[[Spec.Grammar.SyntaxDiagrams.Pragmas|Syntax Diagrams]]
2015-09-14 12:54 by trijezdci - restructured
Changed lines 2-4 from:
!!!!![[EBNF.NonTerminals|EBNF Notation]]
!!!!![[Diagrams.NonTerminals|Syntax Diagrams]]
to:
*[[EBNF.NonTerminals|EBNF Notation]]
*[[Diagrams.NonTerminals|Syntax Diagrams]]
Changed lines 6-8 from:
!!!!![[EBNF.Terminals|EBNF Notation]]
!!!!![[Diagrams.Terminals|Syntax Diagrams]]
to:
*[[EBNF.Terminals|EBNF Notation]]
*[[Diagrams.Terminals|Syntax Diagrams]]
Changed lines 10-12 from:
!!!!![[EBNF.IgnoreSymbols|EBNF Notation]]
!!!!![[Diagrams.IgnoreSymbols|Syntax Diagrams]]
to:
*[[EBNF.IgnoreSymbols|EBNF Notation]]
*[[Diagrams.IgnoreSymbols|Syntax Diagrams]]
Changed lines 14-1661 from:
!!!!![[EBNF.Pragmas|EBNF Notation]]
!!!!![[Diagrams.Pragmas|Syntax Diagrams]]



!!! (1) Non-Terminals

!!!!!#1 Compilation Unit
[@
compilationUnit :
  definitionModule | implOrPrgmModule | blueprint
  ;
@]

!!!!Definition Module Syntax

!!!!!#2 Definition Module
[@
definitionModule :
  DEFINITION MODULE moduleIdent
  ( '[' blueprintToObey ']' )? ( FOR typeToExtend )? ';'
  (importList ';')* definition*
  END moduleIdent '.'
  ;
@]

!!!!!#2.1 Module Identifier, Blueprint Identifier, Type To Extend
[@
moduleIdent : Ident ;

blueprintIdent : Ident ;

typeToExtend : Ident ;
@]

!!!!!#2.2 Blueprint To Obey
[@
blueprintToObey : blueprintIdent ;
@]

!!!!!#3 Import List
[@
importList :
  libGenDirective | importDirective
  ;
@]

!!!!!#4 Library Generation Directive
[@
libGenDirective :
  GENLIB libIdent FROM template FOR templateParamList END
  ;
@]

!!!!!#4.1 Library Identifier, Template, Placeholder
[@
libIdent : Ident ;

template : Ident ;

placeholder : Ident ;
@]

!!!!!#4.2 Replacement
[@
replacement :
  NumberLiteral | StringLiteral | ChevronText
  ;
@]

!!!!!#5 Import Directive
[@
importDirective :
  FROM ( moduleIdent | ENUM enumTypeIdent )
    IMPORT ( identifiersToImport | importAll ) |
  IMPORT modulesToImport
  ;
@]

!!!!!#5.1 Enumeration Type Identifier
[@
enumTypeIdent : typeIdent ;
@]

!!!!!#5.2 Type Identifier
[@
typeIdent : qualident ;
@]

!!!!!#5.3 Identifiers To Import, Modules To Import
[@
identifiersToImport :
  Ident reExport? ( ',' Ident reExport? )*
  ;

modulesToImport : identifiersToImport ;
@]

!!!!!#5.4 Re-Export
[@
reExport : '+' ;
@]

!!!!!#5.5 Import All
[@
importAll : '*' ;
@]

!!!!!#6 Qualified Identifier
[@
qualident :
  Ident ( '.' Ident )*
  ;
@]

!!!!!#7 Definition
[@
definition :
  CONST ( constDefinition ';' )+ |
  TYPE ( typeDefinition ';' )+ |
  VAR ( variableDeclaration ';' )+ |
  procedureHeader ';'
  ;
@]

!!!!!#8 Constant Definition
[@
constDefinition :
  ( '[' propertyToBindTo ']' | restrictedExport )?
  Ident '=' constExpression
  ;
@]

!!!!!#8.1 Constant Expression
[@
constExpression : expression ;
@]

!!!!!#8.2 Constant Expression
[@
restrictedExport : '*' ;
@]

!!!!!#9 Type Definition
[@
typeDefinition :
  restrictedExport? Ident '=' ( OPAQUE | type )
  ;
@]

!!!!!#10 Variable Declaration
[@
variableDeclaration :
  identList ':' ( range OF )? typeIdent
  ;
@]

!!!!!#11 Identifier List
[@
identList :
    Ident ( ',' Ident )*
    ;
@]

!!!!!#12 Range
[@
range :
  '[' greaterThan? constExpression '..' lessThan? constExpression ']'
  ;
@]

!!!!!#12.1 Greater Than
[@
greaterThan : '>' ;
@]

!!!!!#12.2 Less Than
[@
lessThan : '<' ;
@]

!!!!!#13 Type
[@
type :
  typeIdent | derivedSubType | enumType | setType | arrayType |
  recordType | pointerType | coroutineType | procedureType
  ;
@]

!!!!!#13.1 Derived Sub-Type
[@
derivedSubType :
  ALIAS OF typeIdent |
  range OF ordinalOrScalarType |
  CONST dynamicTypeIdent
  ;
@]

!!!!!#13.2 Ordinal Or Scalar Type, Dynamic Type Identifier
[@
ordinalOrScalarType : typeIdent ;

dynamicTypeIdent : typeIdent ;
@]

!!!!!#14 Enumeration Type
[@
enumType :
  '(' ( '+' enumTypeToExtend )? identList ')'
  ;
@]

!!!!!#14.1 Enumeration Type To Extend
[@
enumTypeToExtend : typeIdent ;
@]

!!!!!#15 Set Type
[@
setType :
  SET OF enumTypeIdent
  ;
@]

!!!!!#16 Array Type
[@
arrayType :
  ARRAY componentCount ( ',' componentCount )* OF typeIdent
  ;
@]

!!!!!#16.1 Component Count
[@
componentCount : constExpression ;
@]

!!!!!#17 Record Type
[@
recordType :
  RECORD
    ( fieldList ( ';' fieldList )* indeterminateField? |
      '(' recTypeToExtend ')' fieldList ( ';' fieldList )* )
  ;
@]

!!!!!#17.1 Field List
[@
fieldList :
  restrictedExport? variableDeclaration
  ;
@]

!!!!!#17.2 Record Type To Extend
[@
recTypeToExtend : typeIdent ;
@]

!!!!!#17.3 Indeterminate Field
[@
indeterminateField :
  '~' Ident ':' ARRAY discriminantFieldIdent OF typeIdent
  ;
@]

!!!!!#17.4 Discriminant Field Ident
[@
discriminantFieldIdent : Ident ;
@]

!!!!!#18 Pointer Type
[@
pointerType :
  POINTER TO CONST? typeIdent
  ;
@]

!!!!!#19 Coroutine Type
[@
coroutineType :
  COROUTINE '(' assocProcType ')'
  ;
@]

!!!!!#19.1 Associated Procedure Type
[@
assocProcType : typeIdent ;
@]

!!!!!#20 Procedure Type
[@
procedureType :
  PROCEDURE ( formalType ( ',' formalType )* )? ( ':' returnedType )?
  ;
@]

!!!!!#20.1 Formal Type
[@
formalType :
  simpleFormalType | attributedFormalType | variadicFormalType
  ;
@]

!!!!!#21 Simple Formal Type
[@
simpleFormalType :
  ( ARRAY OF )? typeIdent | castingFormalType
  ;
@]

!!!!!#21.1 Casting Formal Type
[@
castingFormalType :
  CAST ( ARRAY OF OCTET | addressTypeIdent )
  ;
@]

!!!!!#21.2 Address Type Identifier
[@
addressTypeIdent :
  ( UNSAFE '.' )? ADDRESS
  ;
@]

!!!!!#22 Attributed Formal Type
[@
attributedFormalType :
  ( CONST | NEW | VAR ) ( simpleFormalType | simpleVariadicFormalType )
  ;
@]

!!!!!#23 Simple Variadic Formal Type
[@
simpleVariadicFormalType :
  ARGLIST reqNumOfArgs? OF simpleFormalType terminator?
  ;
@]

!!!!!#23.1 Required Number Of Arguments
[@
reqNumOfArgs :
  greaterThan? constExpression
  ;
@]

!!!!!#23.2 Argument List Terminator
[@
terminator :
  '|' constQualident
  ;
@]

!!!!!#23.2 Constant Qualified Identifier
[@
constQualident : qualident ;
@]

!!!!!#24 Variadic Formal Type
[@
variadicFormalType :
  ARGLIST reqNumOfArgs? OF
    ( '{' nonVariadicFormalType ( ';' nonVariadicFormalType )* '}' |
      simpleFormalType ) terminator?
  ;
@]

!!!!!#25 Non-Variadic Formal Type
[@
nonVariadicFormalType :
  ( CONST | NEW | VAR )? simpleFormalType
  ;
@]

!!!!!#26 Procedure Header
[@
procedureHeader :
  PROCEDURE ( '[' ( entityToBindTo | COROUTINE ) ']' | restrictedExport )?
  procedureSignature
  ;
@]

!!!!!#27 Procedure Signature
[@
procedureSignature :
  Ident ( '(' formalParams ( ';' formalParams )* ')' )? ( ':' returnedType )?
  ;
@]

!!!!!#28 Formal Parameters
[@
formalParams :
  identList ':' ( simpleFormalType | variadicFormalParams ) |
  attributedFormalParams
  ;
@]

!!!!!#29 Attributed Formal Parameters
[@
attributedFormalParams :
  ( CONST | NEW | VAR ) identList ':'
  ( simpleFormalType | simpleVariadicFormalType )
  ;
@]

!!!!!#30 Variadic Formal Parameters
[@
variadicFormalParams :
  ARGLIST reqNumOfArgs? OF
    ( ( '{' nonVariadicFormalParams ( ';' nonVariadicFormalParams )* '}') |
      simpleFormalType ) terminator?
  ;
@]

!!!!!#31 Non-Variadic Formal Parameters
[@
nonVariadicFormalParams :
  ( CONST | NEW | VAR )? identList ':' simpleFormalType
  ;
@]

!!!!Implementation And Program Module Syntax

!!!!!#32 Implementation Or Program Module
[@
implOrPrgmModule :
  IMPLEMENTATION? MODULE moduleIdent ';'
  ( importList ';' )* block moduleIdent '.'
  ;
@]

!!!!!#33 Block
[@
block :
  declaration* ( BEGIN statementSequence )? END
  ;
@]

!!!!!#34 Declaration
[@
declaration :
  CONST ( Ident '=' constExpression ';' )+ |
  TYPE ( Ident '=' type ';' )+ |
  VAR ( variableDeclaration ';' )+ |
  procedureHeader ';' block Ident ';'
  ;
@]

!!!!!#35 Statement Sequence
[@
statementSequence :
  statement ( ';' statement )*
  ;
@]

!!!!!#36 Statement
[@
statement :
  memMgtOperation | updateOrProcCall | ifStatement | caseStatement |
  loopStatement | whileStatement | repeatStatement | forStatement |
  ( RETURN | YIELD ) expression? | EXIT
  ;
@]

!!!!!#37 Memory Management Operation
[@
memMgtOperation :
  NEW designator ( OF initSize | := initValue )? |
  RETAIN designator |
  RELEASE designator
  ;
@]

!!!!!#37.1 Initial Size, Initial Value
[@
initSize : expression ;

initValue : expression ;
@]

!!!!!#38 Update Or Procedure Call
[@
updateOrProcCall :
  designator ( ':=' expression | incOrDecSuffix | actualParameters )? |
  COPY designator ':=' expression
  ;
@]

!!!!!#38.1 Increment Or Decrement Suffix
[@
incOrDecSuffix :
  '++' | '--'
  ;
@]

!!!!!#39 IF Statement
[@
ifStatement :
  IF boolExpression THEN statementSequence
  ( ELSIF boolExpression THEN statementSequence )?
  ( ELSE statementSequence )?
  END
  ;
@]

!!!!!#39.1 Boolean Expression
[@
boolExpression : expression ;
@]

!!!!!#40 CASE Statement
[@
caseStatement :
  CASE expression OF ( '|' case  )+ ( ELSE statementSequence )? END
  ;
@]

!!!!!#40.1 Case
[@
case :
  caseLabels ( ',' caseLabels )* ':' statementSequence
  ;
@]

!!!!!#40.2 Case Labels
[@
caseLabels :
  constExpression ( '..' constExpression )?
  ;
@]

!!!!!#41 LOOP Statement
[@
loopStatement :
  LOOP statementSequence END
  ;
@]

!!!!!#42 WHILE Statement
[@
whileStatement :
  WHILE boolExpression DO statementSequence END
  ;
@]

!!!!!#43 REPEAT Statement
[@
repeatStatement :
  REPEAT statementSequence UNTIL boolExpression
  ;
@]

!!!!!#44 FOR Statement
[@
forStatement :
  FOR forLoopVariants IN iterableEntity DO statementSequence END
  ;
@]

!!!!!#44.1 FOR Loop Variants
[@
forLoopVariants :
  accessor ascOrDesc? ( ',' value )? |
  VALUE value ascOrDesc?
  ;
@]

!!!!!#44.2 Accessor, Value
[@
accessor : Ident ;

value : Ident ;
@]

!!!!!#44.3 Iterable Entity
[@
iterableEntity :
  designator | range OF ordinalType
  ;
@]

!!!!!#44.4 Ascender Or Descender
[@
ascOrDesc : incOrDecSuffix ;
@]

!!!!!#44.5 Ordinal Type
[@
ordinalType : typeIdent ;
@]

!!!!!#45 Designator
[@
designator :
  qualident designatorTail?
  ;
@]

!!!!!#45.1 Designator Tail
[@
designatorTail :
  ( ( '[' exprListOrSlice ']' | '^' ) ( '.' Ident )* )+
  ;
@]

!!!!!#45.2 Expression List Or Slice
[@
exprListOrSlice :
  expression ( ( ',' expression )* | '..' expression? )
  ;
@]

!!!!!#46 Expression
[@
expression :
  simpleExpression ( operL1 simpleExpression )?
  ;
@]

!!!!!#46.1 Level-1 Operator
[@
operL1 :
  '=' | '#' | '<' | '<=' | '>' | '>=' | IN | concatOp | identityOp
  ;
@]

!!!!!#46.2 Concatenation Operator
[@
concatOp : '&' ;
@]

!!!!!#46.3 Identity Operator
[@
identityOp : '==' ;
@]

!!!!!#47 Simple Expression
[@
simpleExpression :
  ( '+' | '-' )? term ( operL2 term )*
  ;
@]

!!!!!#47.1 Level-2 Operator
[@
operL2 :
  '+' | '-' | OR
  ;
@]

!!!!!#48 Term
[@
term :
  factorOrNegation ( operL3 factorOrNegation )*
  ;
@]

!!!!!#48.1 Level-3 Operator
[@
operL3 :
  '*' | '/' | DIV | MOD | AND | setDiffOp | dotProductOp
  ;
@]

!!!!!#48.2 Set Difference Operator
[@
setDiffOp : '\' ;
@]

!!!!!#48.3 Dot Product Operator
[@
dotProductOp : '*.' ;
@]

!!!!!#49 Factor Or Negation
[@
factorOrNegation :
  NOT? factorOrTypeConv
  ;
@]

!!!!!#50 Factor Or Type Conversion
[@
factorOrTypeConv :
  factor ( '::' typeIdent )?
  ;
@]

!!!!!#51 Factor
[@
factor :
  NumberLiteral | StringLiteral | structuredValue |
  '(' expression ')' | designator actualParameters?
  ;
@]

!!!!!#52 Actual Parameters
[@
actualParameters :
  '(' expressionList ')'
  ;
@]

!!!!!#53 Expression List
[@
expressionList :
  expression ( ',' expression )*
  ;
@]

!!!!!#54 Structured Value
[@
structuredValue :
  '{' valueComponent ( ',' valueComponent )* '}'
  ;
@]

!!!!!#54.1 Value Component
[@
valueComponent :
  constExpression (( BY | '..' )? constExpression )? | runtimeExpression
  ;
@]

!!!!!#54.2 Runtime Expression
[@
runtimeExpression : expression ;
@]

!!!!Blueprint Syntax

!!!!!#55 Blueprint
[@
blueprint :
  BLUEPRINT blueprintIdent ( '[' blueprintToRefine ']' )?
  ( FOR blueprintForTypeToExtend )? ';' ( REFERENTIAL identList ';' )?
  MODULE TYPE '=' ( typeClassification ( ';' literalCompatibility)? | NONE ) ';'
  ( constraint ';' )* ( requirement ';' )* END blueprintIdent '.'
  ;
@]

!!!!!#55.1 Blueprint Identifier
[@
blueprintIdent : Ident ;
@]

!!!!!#55.2 Blueprint To Refine, Blueprint For Type To Extend
[@
blueprintToRefine : blueprintIdent ;

blueprintForTypeToExtend : blueprintIdent ;
@]

!!!!!#56 Type Classification
[@
typeClassification :
  '{' determinedClassification ( ';' refinableClassification )? ( ';' '*' )? '}'
  | '*'
  ;
@]

!!!!!#56.1 Determined Classification
[@
determinedClassification :
  classificationIdent ( ',' classificationIdent )*
  ;
@]

!!!!!#56.2 Refinable Classification
[@
refinableClassification :
  '~' classificationIdent ( ',' '~' classificationIdent )*
  ;
@]

!!!!!#56.3 Classification Identifier
[@
classificationIdent : Ident ;
@]

!!!!!#57 Literal Compatibility
[@
literalCompatibility :
  TLITERAL '=' protoLiteral ( '|' protoLiteral )*
  ;
@]

!!!!!#57.1 Proto-Literal
[@
protoLiteral :
  protoLiteralIdent | structuredProtoLiteral
  ;
@]

!!!!!#57.2 Proto-Literal Identifier
[@
protoLiteralIdent : Ident ;
@]

!!!!!#58 Structured Proto-Literal
[@
structuredProtoLiteral :
  '{'
    ( ARGLIST reqValueCount? OF
        ( '{' builtinOrReferential ( ',' builtinOrReferential )* '}' |
          builtinOrReferential ) ) |
    builtinOrReferential '}'
  ;
@]

!!!!!#58.1 Required Value Count
[@
reqValueCount :
  greaterThan? wholeNumber
  ;
@]

!!!!!#58.2 Greater Than
[@
greaterThan : '>' ;
@]

!!!!!#58.3 Whole Number
[@
wholeNumber : NumberLiteral ;
@]

!!!!!#58.4 Built-in Type Or Referential Identifier
[@
builtinOrReferential : Ident ;
@]

!!!!!#59 Constraint
[@
constraint :
  constraintTerm ( oneWayDependency | mutualDependencyOrExclusion )
  ;
@]

!!!!!#59.1 Constraint Term
[@
constraintTerm :
  '(' classificationOrFlagIdent ')' |
  '[' bindableEntityOrProperty ']'
  ;
@]

!!!!!#59.2 Bindable Entity Or Property
[@
bindableEntityOrProperty :
  entityToBindTo | propertyToBindTo
  ;
@]

!!!!!#59.3 One-Way Dependency
[@
oneWayDependency :
  '->' termList ( '|' termList )*
  ;
@]

!!!!!#59.4 Mutual Dependency Or Exclusion
[@
mutualDependencyOrExclusion :
  ( '<>' | '><' ) termList
  ;
@]

!!!!!#59.5 Term List
[@
termList :
  constraintTerm ( ',' constraintTerm )*
  ;
@]

!!!!!#59.6 Classification Or Flag Identifier
[@
classificationOrFlagIdent : Ident ;
@]

!!!!!#60 Requirement
[@
requirement :
  condition '->' ( typeRequirement | constRequirement | procRequirement )
  ;
@]

!!!!!#60.1 Condition
[@
condition :
  NOT? boolConstIdent
  ;
@]

!!!!!#60.2 Boolean Constant Identifier
[@
boolConstIdent : Ident ;
@]

!!!!!#60.3 Type Requirement
[@
typeRequirement :
  TYPE typeDefinition
  ;
@]

!!!!!#61 Constant Requirement
[@
constRequirement :
  CONST
    ( '[' propertyToBindTo ']' ( simpleConstRequirement | '=' NONE ) |
      restrictedExport? simpleConstRequirement )
  ;
@]

!!!!!#61.1 Simple Constant Requirement
[@
simpleConstRequirement :
  Ident ( '=' constExpression | ':' builtinTypeIdent )
  ;
@]

!!!!!#61.2 Constant Expression
[@
constExpression : expression ;
@]

!!!!!#61.3 Built-in Type Identifier
[@
builtinTypeIdent : Ident ;
@]

!!!!!#61.4 Restricted Export
[@
restrictedExport : '*' ;
@]

!!!!!#62 Property To Bind To
[@
propertyToBindTo :
  memMgtProperty | collectionProperty | scalarProperty | TFLAGS
  ;
@]

!!!!!#62.1 Memory Management Property
[@
memMgtProperty :
  TDYN | TREFC
  ;
@]

!!!!!#62.2 Collection Property
[@
collectionProperty :
  TORDERED | TSORTED | TLIMIT
  ;
@]

!!!!!#62.3 Scalar Property
[@
scalarProperty :
  TSCALAR | TMAX | TMIN
  ;
@]

!!!!!#63 Procedure Requirement
[@
procedureRequirement :
  PROCEDURE
    ( '[' ( entityToBindTo | COROUTINE ) ']' ( procedureSignature | '=' NONE ) |
      restrictedExport? procedureSignature )
  ;
@]

!!!!!#64 Entity To Bind To
[@
entityToBindTo :
  bindableResWord | bindableOperator | bindableMacro
  ;
@]

!!!!!#64.1 Bindable Reserved Word
[@
bindableResWord :
  NEW | RETAIN | RELEASE | COPY | bindableFor
  ;
@]

!!!!!#64.2 Bindable FOR
[@
bindableFor :
  FOR forBindingDifferentiator?
  ;
@]

!!!!!#64.3 FOR Binding Differentiator
[@
forBindingDifferentiator :
  '|' ( '++' | '--' )
  ;
@]

!!!!!#64.4 Bindable Operator
[@
bindableOperator :
  '+' | '-' | '*' | '/' | '\' | '=' | '<' | '>' | '*.' | '::'
  IN | DIV | MOD | unaryMinus
  ;
@]

!!!!!#64.5 Unary Minus
[@
unaryMinus : '+/-' ;
@]

!!!!!#64.6 Bindable Macro
[@
bindableMacro :
  ABS | LENGTH | EXISTS | SEEK | SUBSET | READ | READNEW | WRITE | WRITEF |
  SXF | VAL | multiBindableMacro1 | multiBindableMacro2 | multiBindableMacro3
  ;
@]

!!!!!#64.7 Multi-Bindable Macro 1
[@
multiBindableMacro1 :
  ( COUNT | VALUE ) bindingDifferentiator1?
  ;
@]

!!!!!#64.8 Binding Differentiator 1
[@
bindingDifferentiator1 :
  '|' '#'
  ;
@]

!!!!!#64.9 Multi-Bindable Macro 2
[@
multiBindableMacro2 :
  ( STORE | INSERT | REMOVE ) bindingDifferentiator2?
  ;
@]

!!!!!#64.10 Binding Differentiator 2
[@
bindingDifferentiator2 :
  '|' ( ',' | '#' | '*' )
  ;
@]

!!!!!#64.11 Multi-Bindable Macro 3
[@
multiBindableMacro3 :
  APPEND bindingDifferentiator3?
  ;
@]

!!!!!#64.12 Binding Differentiator 3
[@
bindingDifferentiator3 :
  '|' ( ',' | '*' )
  ;
@]

!!! (2) Terminals

!!!!!#1 Reserved Words

@@ALIAS@@, @@AND@@, @@ARGLIST@@, @@ARRAY@@, @@BEGIN@@, @@BLUEPRINT@@,
@@BY@@,@@CASE@@, @@CONST@@, @@COPY@@, @@DEFINITION@@, @@DIV@@, @@DO@@,
@@ELSE@@, @@ELSIF@@, @@END@@, @@ENUM@@, @@EXIT@@, @@FOR@@, @@FROM@@,
@@IF@@, @@IMPLEMENTATION@@, @@IMPORT@@, @@IN@@, @@LOOP@@, @@MOD@@,
@@MODULE@@, @@NEW@@, @@NONE@@, @@NOT@@, @@OF@@, @@OPAQUE@@, @@OR@@,
@@POINTER@@, @@PROCEDURE@@, @@RECORD@@, @@REFERENTIAL@@, @@RELEASE@@,
@@REPEAT@@, @@RETAIN@@, @@RETURN@@, @@SET@@, @@THEN@@, @@TO@@, @@TYPE@@,
@@UNTIL@@, @@VAR@@, @@WHILE@@, @@YIELD@@

!!!!!#2 Dual-Use Identifiers (Schrödinger's Tokens)

@@ABS@@, @@ADDRESS@@, @@APPEND@@, @@CAST@@, @@COUNT@@, @@COROUTINE@@,
@@EXISTS@@, @@INSERT@@, @@LENGTH@@, @@OCTET@@, @@READ@@, @@READNEW@@,
@@REMOVE@@, @@SEEK@@, @@STORE@@, @@SUBSET@@, @@SXF@@, @@TDYN@@,
@@TFLAGS@@, @@TLIMIT@@, @@TLITERAL@@, @@TMAX@@, @@TMIN@@, @@TORDERED@@,
@@TREFC@@, @@TSCALAR@@, @@TSORTED@@, @@UNSAFE@@, @@VAL@@, @@VALUE@@,
@@WRITE@@, @@WRITEF@@

!!!!!#3 Special Symbols

[@.@] &nbsp; [@,@] &nbsp; [@:@] &nbsp; [@;@] &nbsp; [@|@] &nbsp; [@^@] &nbsp;
[@~@] &nbsp; [@..@] &nbsp; [@:=@] &nbsp; [@++@] &nbsp; [@--@] &nbsp; [@::@] &nbsp;
[@+@] &nbsp; [@-@] &nbsp; [@*@] &nbsp; [@*.@] &nbsp; [@/@] &nbsp; [@\@] &nbsp;
[@=@] &nbsp; [@#@] &nbsp; [@>@] &nbsp; [@>=@] &nbsp; [@<@] &nbsp; [@<=@] &nbsp;
[@==@] &nbsp; [@&@] &nbsp; [@->@] &nbsp; [@<>@] &nbsp; [@><@] &nbsp; [@+/-@] &nbsp;
[@(@] &nbsp; [@)@] &nbsp; [@[@] &nbsp; [@]@] &nbsp; [@{@] &nbsp; [@}@] &nbsp;

!!!!!#3.1 Quoted Text Delimiters

[@'@] &nbsp; [@"@] &nbsp; [@<<@] &nbsp; [@>>@] &nbsp;

!!!!!#3.2 Comment Delimiters

[@!@] &nbsp; [@(*@] &nbsp; [@*)@] &nbsp;

!!!!!#3.3 Pragma Affix and Delimiters

[@?@] &nbsp; [@<*@] &nbsp; [@*>@] &nbsp;

!!!!!#3.3 Template Language Symbols

[@##@] &nbsp; [@<#@] &nbsp; [@#>@] &nbsp; [@@@@] &nbsp; [@//@] &nbsp; [@/*@] &nbsp;  [@*/@] &nbsp;

!!!!!#3.5 Reserved Symbols

[@`@] &nbsp; for use as a token by Objective Modula-2 [[<<]]
[@@@] &nbsp; for use as a lead character in identifiers and reserved words by language supersets [[<<]]
[@%@] &nbsp; for use as a character in identifiers and reserved words by implementations targeting[=OpenVMS=]

!!!!!#4 Identifier
[@
Ident :
  ( Letter | ForeignIdentChar+ LetterOrDigit+ ) IdentTailChar*
  ;
@]

!!!!!#4.1 Standard Library Identifier
[@
StdLibIdent :
  Letter LetterOrDigit*
  ;
@]

!!!!!#4.2 Letter Or Digit
[@
LetterOrDigit :
  Letter | Digit
  ;
@]

!!!!!#4.3 Foreign Identifier Character
[@
ForeignIdentChar :
  '_' | '$'
  ;
@]

!!!!!#4.4 Identifier Tail Character
[@
IdentTailChar :
  LetterOrDigit | ForeignIdentChar
  ;
@]

!!!!!#5 Number Literal
[@
NumberLiteral :
  /* number literals starting with digit 0 ... */
  '0' (
    /* without prefix are real numbers */
    RealNumberTail |
    /* with prefix 0b are base-2 numbers */
    'b' Base2DigitSeq |
    /* with prefix 0x are base-16 numbers */
    'x' Base16DigitSeq |
    /* with prefix 0u are unicode code points */
    'u' Base16DigitSeq
  )?
  /* number literals starting with digits 1 to 9 ... */
  | '1'..'9' DecimalNumberTail? /* are always decimal numbers */
  ;
@]

!!!!!#5.1 Decimal Number Tail
[@
DecimalNumberTail :
  DigitSep? DigitSeq RealNumberTail? | RealNumberTail
  ;
@]

!!!!!#5.2 Real Number Tail
[@
RealNumberTail :
  '.' DigitSeq ( 'e' ( '+' | '-' )? DigitSeq )?
  ;
@]

!!!!!#5.3 Digit Sequence
[@
DigitSeq :
  Digit+ ( DigitSep Digit+ )*
  ;
@]

!!!!!#5.4 Base-16 Digit Sequence
[@
Base16DigitSeq :
    Base16Digit+ ( DigitSep Base16Digit+ )*
    ;
@]

!!!!!#5.5 Base-2 Digit Sequence
[@
Base2DigitSeq :
  Base2Digit+ ( DigitSep Base2Digit+ )*
  ;
@]

!!!!!#5.6 Digit
[@
Digit :
  Base2Digit | '2' | '3' | '4' | '5' | '6' | '7' | '8' | '9'
  ;
@]

!!!!!#5.7 Base-16 Digit
[@
Base16Digit :
  Digit | 'A' | 'B' | 'C' | 'D' | 'E' | 'F'
  ;
@]

!!!!!#5.8 Base-2 Digit
[@
Base2Digit :
  '0' | '1'
  ;
@]

!!!!!#5.9 Digit Separator
[@
DigitSep : "'" ;
@]

!!!!!#6 String Literal
[@
StringLiteral :
  SingleQuotedString | DoubleQuotedString
  ;
@]

!!!!!#6.1 Single Quoted String
[@
SingleQuotedString :
  "'" ( QuotableCharacter | '"' )* "'"
  ;
@]

!!!!!#6.2 Double Quoted String
[@
DoubleQuotedString :
  '"' ( QuotableCharacter | "'" )* '"'
  ;
@]

!!!!!#6.3 Quotable Character
[@
QuotableCharacter :
  Digit | Letter | Space | NonAlphaNumQuotable | EscapedCharacter
  ;
@]

!!!!!#6.4 Letter
[@
Letter :
  'A' .. 'Z' | 'a' .. 'z'
  ;
@]

!!!!!#6.5 Space
[@
Space : ' ' ;
@]

!!!!!#6.6 Non-Alphanumeric Quotable
[@
NonAlphaNumQuotable :
  '!' | '#' | '$' | '%' | '&' | '(' | ')' | '*' | '+' | ',' |
  '-' | '.' | '/' | ':' | ';' | '<' | '=' | '>' | '?' | '@' |
  '[' | ']' | '^' | '_' | '`' | '{' | '|' | '}' | '~'
@]

!!!!!#6.7 Escaped Character
[@
EscapedCharacter :
  '\' ( 'n' | 't' | '\' )
  ;
@]

!!!!!#7 Chevron Text
[@
ChevronText :
  '<<' ( QuotableCharacter | "'" | '"' )* '>>'
  ;
@]

!!! (3) Ignore Symbols

!!!!!#1 Whitespace
[@
Whitespace :
  Space | ASCII_TAB
  ;
@]

!!!!!#1.1 ASCII Tabulator
[@
ASCII_TAB : CHR(8) ;
@]

!!!!!#2 Line Comment
[@
LineComment :
  '!' CommentCharacter* EndOfLine
  ;
@]

!!!!!#3 Block Comment
[@
BlockComment :
  '(*' ( CommentCharacter | BlockComment | EndOfLine )* '*)'
  ;
@]

!!!!!#3.1 Comment Character
[@
BlockComment :
  Digit | Letter | Whitespace | NonAlphaNumQuotable | '\' | "'" | '"'
  ;
@]

!!!!!#4 End Of Line Marker
[@
EndOfLine :
  ASCII_LF | ASCII_CR ASCII_LF?
  ;
@]

!!!!!#4.1 ASCII Line Feed
[@
ASCII_LF : CHR(10) ;
@]

!!!!!#4.2 ASCII Carriage Return
[@
ASCII_LF : CHR(13) ;
@]

!!! (4) Pragmas

!!!!!#1 Pragma
[@
pragma :
  '<*' pragmaBody '*>'
  ;
@]

!!!!!#1.1 Pragma Body
[@
pragmaBody :
  pragmaMSG | pragmaIF | procDeclAttrPragma | pragmaOUT | pragmaFORWARD |
  pragmaENCODING | pragmaALIGN | pragmaPADBITS | pragmaPURITY |
  varDeclAttrPragma | pragmaDEPRECATED | pragmaGENERATED |
  pragmaADDR | pragmaFFI | pragmaFFIDENT | implDefinedPragma
 ;
@]

!!!!!#2 Body Of Compile Time Message Pragma
[@
pragmaMSG :
  MSG '=' ctMsgMode ':' ctMsgComponentList
  ;
@]

!!!!!#2.1 Message Mode
[@
ctMsgMode :
  INFO | WARN | ERROR | FATAL
  ;
@]

!!!!!#2.2 Message Component List
[@
ctMsgComponentList :
  ctMsgComponent ( ',' ctMsgComponent )*
  ;
@]

!!!!!#2.3 Message Component
[@
compileTimeMsgComponent :
    StringLiteral | constQualident | '?' valuePragma
    ;
@]

!!!!!#2.4 Constant Qualified Identifier
[@
constQualident : qualident ;
@]

!!!!!#2.5 Value Pragma
[@
valuePragma :
    ALIGN | ENCODING | valuePragmaSymbol
    ;
@]

!!!!!#2.6 Value Pragma Symbol
[@
valuePragmaSymbol : PragmaSymbol ;
@]

!!!!!#2.7 Pragma Symbol
[@
PragmaSymbol :
  Letter+
  ;
@]

!!!!!#3 Body Of Conditional Compilation Pragma
[@
pragmaIF :
  ( IF | ELSIF ) inPragmaExpression | ELSE | END
  ;
@]

!!!!!#4 Body Of Procedure Declaration Attribute Pragma
[@
procDeclAttrPragma :
  INLINE | NOINLINE | BLOCKING | NORETURN
  ;
@]

!!!!!#5 Body Of Promise-To-Write Pragma
[@
pragmaOUT :
  OUT
  ;
@]

!!!!!#6 Body Of Forward Declaration Pragma
[@
pragmaFORWARD :
  FORWARD ( TYPE identList | procedureHeader )
  ;
@]

!!!!!#7 Body Of Character Encoding Pragma
[@
pragmaENCODING :
  ENCODING '=' StringLiteral /* "ASCII" or "UTF8" */
  ( ':' codePointSampleList )?
  ;
@]

!!!!!#7.1a Code Point Sample List
[@
codePointSampleList :
  codePointSample ( ',' codePointSample )*
  ;
@]

!!!!!#7.1b Code Point Sample
[@
codePointSample :
  quotedCharacterLiteral '=' characterCodeLiteral
  ;
@]

!!!!!#7.2 Quoted Character Literal
[@
quotedCharacterLiteral : StringLiteral ; /* single character only */
@]

!!!!!#7.3 Character Code Literal
[@
characterCodeLiteral : NumberLiteral ; /* whole number only */
@]

!!!!!#8 Body Of Memory Alignment Pragma
[@
pragmaALIGN :
  ALIGN '=' inPragmaExpression
  ;
@]

!!!!!#9 Body Of Bit Padding Pragma
[@
pragmaPADBITS :
  PADBITS '=' inPragmaExpression
  ;
@]

!!!!!#10 Body Of Purity Attribute Pragma
[@
pragmaPURITY :
  PURITY '=' inPragmaExpression /* values 0 .. 3 */
  ;
@]

!!!!!#11 Body Of Variable Declaration Attribute Pragma
[@
varDeclAttrPragma :
  SINGLEASSIGN | LOWLATENCY | VOLATILE
  ;
@]

!!!!!#12 Body Of Deprecation Pragma
[@
pragmaDEPRECATED :
  DEPRECATED
  ;
@]

!!!!!#13 Body Of Library Generation Timestamp Pragma
[@
pragmaGENERATED :
  GENERATED template ',' datestamp ',' timestamp
  ;
@]

!!!!!#13.1 Datestamp
[@
datestamp :
  year '-' month '-' day
  ;
@]

!!!!!#13.2 Timestamp
[@
timestamp :
  hours ':' minutes ':' seconds '+' timezone
  ;
@]

!!!!!#13.3 Year, Month, Day, Hours, Minutes, Seconds, Timezone
[@
year : wholeNumber ;

month : wholeNumber ;

day : wholeNumber ;

hours : wholeNumber ;

minutes : wholeNumber ;

seconds : wholeNumber ;

timezone : wholeNumber ;
@]

!!!!!#14 Body Of Memory Mapping Pragma
[@
pragmaADDR :
  ADDR '=' inPragmaExpression
  ;
@]

!!!!!#15 Body Of Foreign Function Interface Pragma
[@
pragmaFFI :
  FFI '=' StringLiteral /* "C", "Fortran", "CLR" or "JVM" */
  ;
@]

!!!!!#16 Body Of Foreign Function Identifier Mapping Pragma
[@
pragmaFFIDENT :
  FFIDENT '=' StringLiteral /* foreign library identifier */
  ;
@]

!!!!!#17 Body Of Implementation Defined Pragma
[@
implDefinedPragma :
  ( implPrefix '.' )? PragmaSymbol ( '=' inPragmaExpression )? '|' ctMsgMode
  ;
@]

!!!!!#17.1 Implementation Prefix
[@
implPrefix :
  Letter LetterOrDigit*
  ;
@]

!!!!!#18 In-Pragma Expression
[@
inPragmaExpression :
  inPragmaSimpleExpression ( inPragmaOperL1 inPragmaSimpleExpression )?
  ;
@]

!!!!!#18.1 In-Pragma Level-1 Operator
[@
inPragmaOperL1 :
  '=' | '#' | '<' | '<=' | '>' | '>='
  ;
@]

!!!!!#19 In-Pragma Simple Expression
[@
inPragmaSimpleExpression :
  ( '+' | '-' )? inPragmaTerm ( inPragmaOperL2 inPragmaTerm )*
  ;
@]

!!!!!#19.1 In-Pragma Level-2 Operator
[@
inPragmaOperL2 :
  '+' | '-' | OR
  ;
@]

!!!!!#20 In-Pragma Term
[@
inPragmaTerm :
  inPragmaFactorOrNegation ( inPragmaOperL3 inPragmaFactorOrNegation )*
  ;
@]

!!!!!#20.1 In-Pragma Level-3 Operator
[@
inPragmaOperL3 :
  '*' | DIV | MOD | AND
  ;
@]

!!!!!#21 In-Pragma Factor Or Negation
[@
inPragmaFactorOrNegation :
  NOT? inPragmaFactor
  ;
@]

!!!!!#22 In-Pragma Factor
[@
inPragmaFactor :
  WholeNumber |
  /* constQualident is covered by inPragmaCompileTimeFunctionCall */
  '(' inPragmaExpression ')' | inPragmaCompileTimeFunctionCall
  ;
@]

!!!!!#23 In-Pragma Compile Time Function Call
[@
inPragmaCompileTimeFunctionCall :
  qualident ( '(' inPragmaExpression ( ',' inPragmaExpression )* ')' )?
  ;
@]
to:
*[[EBNF.Pragmas|EBNF Notation]]
*[[Diagrams.Pragmas|Syntax Diagrams]]
2015-09-14 12:45 by trijezdci - split page
Changed lines 2-20 from:
to:
!!!!![[EBNF.NonTerminals|EBNF Notation]]
!!!!![[Diagrams.NonTerminals|Syntax Diagrams]]

!!! (2) Terminals
!!!!![[EBNF.Terminals|EBNF Notation]]
!!!!![[Diagrams.Terminals|Syntax Diagrams]]

!!! (3) Ignore Symbols
!!!!![[EBNF.IgnoreSymbols|EBNF Notation]]
!!!!![[Diagrams.IgnoreSymbols|Syntax Diagrams]]

!!! (4) Pragmas
!!!!![[EBNF.Pragmas|EBNF Notation]]
!!!!![[Diagrams.Pragmas|Syntax Diagrams]]



!!! (1) Non-Terminals

Changed line 1661 from:
@]
to:
@]
2015-09-14 12:29 by trijezdci - update to latest grammar (2015-08-31)
Changed lines 1507-1511 from:




to:
!!!!!#13 Body Of Library Generation Timestamp Pragma
[@
pragmaGENERATED :
  GENERATED template ',' datestamp ',' timestamp
  ;
@]

!!!!!#13.1 Datestamp
[@
datestamp :
  year '-' month '-' day
  ;
@]

!!!!!#13.2 Timestamp
[@
timestamp :
  hours ':' minutes ':' seconds '+' timezone
  ;
@]

!!!!!#13.3 Year, Month, Day, Hours, Minutes, Seconds, Timezone
[@
year : wholeNumber ;

month : wholeNumber ;

day : wholeNumber ;

hours : wholeNumber ;

minutes : wholeNumber ;

seconds : wholeNumber ;

timezone : wholeNumber ;
@]

!!!!!#14 Body Of Memory Mapping Pragma
[@
pragmaADDR :
  ADDR '=' inPragmaExpression
  ;
@]

!!!!!#15 Body Of Foreign Function Interface Pragma
[@
pragmaFFI :
  FFI '=' StringLiteral /* "C", "Fortran", "CLR" or "JVM" */
  ;
@]

!!!!!#16 Body Of Foreign Function Identifier Mapping Pragma
[@
pragmaFFIDENT :
  FFIDENT '=' StringLiteral /* foreign library identifier */
  ;
@]

!!!!!#17 Body Of Implementation Defined Pragma
[@
implDefinedPragma :
  ( implPrefix '.' )? PragmaSymbol ( '=' inPragmaExpression )? '|' ctMsgMode
  ;
@]

!!!!!#17.1 Implementation Prefix
[@
implPrefix :
  Letter LetterOrDigit*
  ;
@]

!!!!!#18 In-Pragma Expression
[@
inPragmaExpression :
  inPragmaSimpleExpression ( inPragmaOperL1 inPragmaSimpleExpression )?
  ;
@]

!!!!!#18.1 In-Pragma Level-1 Operator
[@
inPragmaOperL1 :
  '=' | '#' | '<' | '<=' | '>' | '>='
  ;
@]

!!!!!#19 In-Pragma Simple Expression
[@
inPragmaSimpleExpression :
  ( '+' | '-' )? inPragmaTerm ( inPragmaOperL2 inPragmaTerm )*
  ;
@]

!!!!!#19.1 In-Pragma Level-2 Operator
[@
inPragmaOperL2 :
  '+' | '-' | OR
  ;
@]

!!!!!#20 In-Pragma Term
[@
inPragmaTerm :
  inPragmaFactorOrNegation ( inPragmaOperL3 inPragmaFactorOrNegation )*
  ;
@]

!!!!!#20.1 In-Pragma Level-3 Operator
[@
inPragmaOperL3 :
  '*' | DIV | MOD | AND
  ;
@]

!!!!!#21 In-Pragma Factor Or Negation
[@
inPragmaFactorOrNegation :
  NOT? inPragmaFactor
  ;
@]

!!!!!#22 In-Pragma Factor
[@
inPragmaFactor :
  WholeNumber |
  /* constQualident is covered by inPragmaCompileTimeFunctionCall */
  '(' inPragmaExpression ')' | inPragmaCompileTimeFunctionCall
  ;
@]

!!!!!#23 In-Pragma Compile Time Function Call
[@
inPragmaCompileTimeFunctionCall :
  qualident ( '(' inPragmaExpression ( ',' inPragmaExpression )* ')' )?
  ;
@]
2015-09-14 12:00 by trijezdci - update to latest grammar (work in progress)
Changed line 1370 from:
  ( INFO | WARN | ERROR | FATAL )
to:
  INFO | WARN | ERROR | FATAL
2015-09-14 12:00 by trijezdci - update to latest grammar (work in progress)
2015-09-14 12:00 by trijezdci - update to latest grammar (work in progress)
Changed line 1370 from:
  ( INFO | WARN | ERROR | FATAL {})
to:
  ( INFO | WARN | ERROR | FATAL )
2015-09-14 11:59 by trijezdci - update to latest grammar (work in progress)
2015-09-14 11:59 by trijezdci - update to latest grammar (work in progress)
Added lines 1340-1509:

!!! (4) Pragmas

!!!!!#1 Pragma
[@
pragma :
  '<*' pragmaBody '*>'
  ;
@]

!!!!!#1.1 Pragma Body
[@
pragmaBody :
  pragmaMSG | pragmaIF | procDeclAttrPragma | pragmaOUT | pragmaFORWARD |
  pragmaENCODING | pragmaALIGN | pragmaPADBITS | pragmaPURITY |
  varDeclAttrPragma | pragmaDEPRECATED | pragmaGENERATED |
  pragmaADDR | pragmaFFI | pragmaFFIDENT | implDefinedPragma
 ;
@]

!!!!!#2 Body Of Compile Time Message Pragma
[@
pragmaMSG :
  MSG '=' ctMsgMode ':' ctMsgComponentList
  ;
@]

!!!!!#2.1 Message Mode
[@
ctMsgMode :
  ( INFO | WARN | ERROR | FATAL {})
  ;
@]

!!!!!#2.2 Message Component List
[@
ctMsgComponentList :
  ctMsgComponent ( ',' ctMsgComponent )*
  ;
@]

!!!!!#2.3 Message Component
[@
compileTimeMsgComponent :
    StringLiteral | constQualident | '?' valuePragma
    ;
@]

!!!!!#2.4 Constant Qualified Identifier
[@
constQualident : qualident ;
@]

!!!!!#2.5 Value Pragma
[@
valuePragma :
    ALIGN | ENCODING | valuePragmaSymbol
    ;
@]

!!!!!#2.6 Value Pragma Symbol
[@
valuePragmaSymbol : PragmaSymbol ;
@]

!!!!!#2.7 Pragma Symbol
[@
PragmaSymbol :
  Letter+
  ;
@]

!!!!!#3 Body Of Conditional Compilation Pragma
[@
pragmaIF :
  ( IF | ELSIF ) inPragmaExpression | ELSE | END
  ;
@]

!!!!!#4 Body Of Procedure Declaration Attribute Pragma
[@
procDeclAttrPragma :
  INLINE | NOINLINE | BLOCKING | NORETURN
  ;
@]

!!!!!#5 Body Of Promise-To-Write Pragma
[@
pragmaOUT :
  OUT
  ;
@]

!!!!!#6 Body Of Forward Declaration Pragma
[@
pragmaFORWARD :
  FORWARD ( TYPE identList | procedureHeader )
  ;
@]

!!!!!#7 Body Of Character Encoding Pragma
[@
pragmaENCODING :
  ENCODING '=' StringLiteral /* "ASCII" or "UTF8" */
  ( ':' codePointSampleList )?
  ;
@]

!!!!!#7.1a Code Point Sample List
[@
codePointSampleList :
  codePointSample ( ',' codePointSample )*
  ;
@]

!!!!!#7.1b Code Point Sample
[@
codePointSample :
  quotedCharacterLiteral '=' characterCodeLiteral
  ;
@]

!!!!!#7.2 Quoted Character Literal
[@
quotedCharacterLiteral : StringLiteral ; /* single character only */
@]

!!!!!#7.3 Character Code Literal
[@
characterCodeLiteral : NumberLiteral ; /* whole number only */
@]

!!!!!#8 Body Of Memory Alignment Pragma
[@
pragmaALIGN :
  ALIGN '=' inPragmaExpression
  ;
@]

!!!!!#9 Body Of Bit Padding Pragma
[@
pragmaPADBITS :
  PADBITS '=' inPragmaExpression
  ;
@]

!!!!!#10 Body Of Purity Attribute Pragma
[@
pragmaPURITY :
  PURITY '=' inPragmaExpression /* values 0 .. 3 */
  ;
@]

!!!!!#11 Body Of Variable Declaration Attribute Pragma
[@
varDeclAttrPragma :
  SINGLEASSIGN | LOWLATENCY | VOLATILE
  ;
@]

!!!!!#12 Body Of Deprecation Pragma
[@
pragmaDEPRECATED :
  DEPRECATED
  ;
@]



2015-09-14 11:31 by trijezdci - update to latest grammar (work in progress)
2015-09-14 11:31 by trijezdci - update to latest grammar (work in progress)
Changed lines 1289-1302 from:

!!! Reserved Pragmas
* 14 reserved pragmas

@@IF@@, @@ELSE@@, @@ELSIF@@, @@ENDIF@@, @@INFO@@, @@WARN@@,
@@ERROR@@, @@FATAL@@, @@ALIGN@@, @@FOREIGN@@, @@MAKE@@,
@@INLINE@@, @@NOINLINE@@, @@VOLATILE@@

!!! Non-Terminal Symbols
* 65 productions
* 15 aliases


!!!!Literals
to:
!!! (3) Ignore Symbols

!!!!!#1 Whitespace
Changed lines 1293-1295 from:
    number : NUMBER ;

    string : STRING
;
to:
Whitespace :
  Space | ASCII_TAB
  ;
Changed lines 1297-1300 from:
!!!Pragma Symbols
* 5 productions
* 2 aliases

to:

!!!!!#1.1 ASCII Tabulator
Changed lines 1300-1321 from:
 (1) pragma :
      '<*'
      ( conditionalPragma | consoleMessagePragma | codeGenerationPragma |
        implementationDefinedPragma )
      '*>' ;

 (2) conditionalPragma :
      ( IF | ELSIF ) constExpression | ELSE | ENDIF ;

 (3) consoleMessagePragma :
      ( INFO | WARN | ERROR | FATAL ) compileTimeMessage ;

 (4) codeGenerationPragma :
      ALIGN '=' constExpression | FOREIGN ( '=' string )? | MAKE '=' string |
      INLINE | NOINLINE | VOLATILE ;

 (5) implementationDefinedPragma :
      pragmaName ( '+' | '-' | '=' ( ident | number ) )? ;

    compileTimeMessage : string ;

    pragmaName : ident ;
to:
ASCII_TAB : CHR(8) ;
Changed lines 1303-1304 from:
!!!Terminal Symbols
* 9 productions
to:
!!!!!#2 Line Comment
Changed lines 1305-1348 from:

 (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 ) ;
to:
LineComment :
  '!' CommentCharacter* EndOfLine
  ;
Changed lines 1309-1312 from:
!!!Ignore Symbols
* 6 productions

!!!!Whitespace
to:

!!!!!#3 Block Comment
Changed lines 1312-1313 from:
 (1) WHITESPACE :
      ' ' | ASCII_TAB ;
to:
BlockComment :
  '(*' ( CommentCharacter | BlockComment | EndOfLine )*
'*)'
  ;
Changed lines 1316-1317 from:
!!!!Comments
to:

!!!!!#3.1 Comment Character
Changed lines 1319-1340 from:
 (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:
BlockComment :
  Digit | Letter | Whitespace | NonAlphaNumQuotable
| '\' | "'" | '"'
  ;
@]

!!!!!#4 End Of Line Marker
[@
EndOfLine :
  ASCII_LF | ASCII_CR ASCII_LF?
  ;
@]

!!!!!#4.1 ASCII Line Feed
[@
ASCII_LF : CHR(10
) ;
@]

!!!!!#4.2 ASCII Carriage Return
[@
ASCII_LF : CHR
(13) ;
@]

2015-09-14 11:14 by trijezdci - update to latest grammar (work in progress)
2015-09-14 11:14 by trijezdci - update to latest grammar (work in progress)
Changed line 1176 from:
  '.' DigitSeq ( 'e' ( '+' | '-' {})? DigitSeq )?
to:
  '.' DigitSeq ( 'e' ( '+' | '-' )? DigitSeq )?
2015-09-14 11:12 by trijezdci - update to latest grammar (work in progress)
2015-09-14 11:12 by trijezdci - update to latest grammar (work in progress)
Changed lines 1112-1132 from:
!!!!!#4 Identifiers

!!!!!#4 Number Literals

!!!!!#5 String Literals



!!! Reserved Pragmas
* 14 reserved pragmas

@@IF@@, @@ELSE@@, @@ELSIF@@, @@ENDIF@@, @@INFO@@, @@WARN@@,
@@ERROR@@, @@FATAL@@, @@ALIGN@@, @@FOREIGN@@, @@MAKE@@,
@@INLINE@@, @@NOINLINE@@, @@VOLATILE@@

!!! Non-Terminal Symbols
* 65 productions
* 15 aliases


!!!!Literals
to:
!!!!!#4 Identifier
[@
Ident :
  ( Letter | ForeignIdentChar+ LetterOrDigit+ ) IdentTailChar*
  ;
@]

!!!!!#4.1 Standard Library Identifier
[@
StdLibIdent :
  Letter LetterOrDigit*
  ;
@]

!!!!!#4.2 Letter Or Digit
[@
LetterOrDigit :
  Letter | Digit
  ;
@]

!!!!!#4.3 Foreign Identifier Character
[@
ForeignIdentChar :
  '_' | '$'
  ;
@]

!!!!!#4.4 Identifier Tail Character
[@
IdentTailChar :
  LetterOrDigit | ForeignIdentChar
  ;
@]

!!!!!#5 Number Literal
[@
NumberLiteral :
  /* number literals starting with digit 0 ... */
  '0' (
    /* without prefix are real numbers */
    RealNumberTail |
    /* with prefix 0b are base-2 numbers */
    'b' Base2DigitSeq |
    /* with prefix 0x are base-16 numbers */
    'x' Base16DigitSeq |
    /* with prefix 0u are unicode code points */
    'u' Base16DigitSeq
  )?
  /* number literals starting with digits 1 to 9 ... */
  | '1'..'9' DecimalNumberTail? /* are always decimal numbers */
  ;
@]

!!!!!#5.1 Decimal Number Tail
[@
DecimalNumberTail :
  DigitSep? DigitSeq RealNumberTail? | RealNumberTail
  ;
@]

!!!!!#5.2 Real Number Tail
[@
RealNumberTail :
  '.' DigitSeq ( 'e' ( '+' | '-' {})? DigitSeq )?
  ;
@]

!!!!!#5.3 Digit Sequence
[@
DigitSeq :
  Digit+ ( DigitSep Digit+ )*
  ;
@]

!!!!!#5.4 Base-16 Digit Sequence
[@
Base16DigitSeq :
    Base16Digit+ ( DigitSep Base16Digit+ )*
    ;
@]

!!!!!#5.5 Base-2 Digit Sequence
[@
Base2DigitSeq :
  Base2Digit+ ( DigitSep Base2Digit+ )*
  ;
@]

!!!!!#5.6 Digit
[@
Digit :
  Base2Digit | '2' | '3' | '4' | '5' | '6' | '7' | '8' | '9'
  ;
@]

!!!!!#5.7 Base-16 Digit
[@
Base16Digit :
  Digit | 'A' | 'B' | 'C' | 'D' | 'E' | 'F'
  ;
@]

!!!!!#5.8 Base-2 Digit
[@
Base2Digit :
  '0' | '1'
  ;
@]

!!!!!#5.9 Digit Separator
[@
DigitSep : "'" ;
@]

!!!!!#6 String Literal
[@
StringLiteral :
  SingleQuotedString | DoubleQuotedString
  ;
@]

!!!!!#6.1 Single Quoted String
[@
SingleQuotedString :
  "'" ( QuotableCharacter | '"' )* "'"
  ;
@]

!!!!!#6.2 Double Quoted String
[@
DoubleQuotedString :
  '"' ( QuotableCharacter | "'" )* '"'
  ;
@]

!!!!!#6.3 Quotable Character
[@
QuotableCharacter :
  Digit | Letter | Space | NonAlphaNumQuotable | EscapedCharacter
  ;
@]

!!!!!#6.4 Letter
[@
Letter :
  'A' .. 'Z' | 'a' .. 'z'
  ;
@]

!!!!!#6.5 Space
[@
Space : ' ' ;
@]

!!!!!#6.6 Non-Alphanumeric Quotable
[@
NonAlphaNumQuotable :
  '!' | '#' | '$' | '%' | '&' | '(' | ')' | '*' | '+' | ',' |
  '-' | '.' | '/' | ':' | ';' | '<' | '=' | '>' | '?' | '@' |
  '[' | ']' | '^' | '_' | '`' | '{' | '|' | '}' | '~'
@]

!!!!!#6.7 Escaped Character
[@
EscapedCharacter :
  '\' ( 'n' | 't' | '\' )
  ;
@]

!!!!!#7 Chevron Text
[@
ChevronText :
  '<<' ( QuotableCharacter | "'" | '"' )* '>>'
  ;
@]
2015-09-14 10:48 by trijezdci - update to latest grammar (work in progress)
2015-09-14 10:48 by trijezdci - update to latest grammar (work in progress)
Changed lines 1108-1109 from:
[@`@] &nbsp; for use as a token by Objective Modula-2 (:nl:)
[@@@] &nbsp; for use as a lead character in identifiers and reserved words by language supersets (:nl:)
to:
[@`@] &nbsp; for use as a token by Objective Modula-2 [[<<]]
[@@@]
&nbsp; for use as a lead character in identifiers and reserved words by language supersets [[<<]]
2015-09-14 10:47 by trijezdci - update to latest grammar (work in progress)
Changed lines 1108-1112 from:
[@`@] &nbsp; for use as a token by Objective Modula-2

[@@@]
&nbsp; for use as a lead character in identifiers and reserved words by language supersets

[@%@]
&nbsp; for use as a character in identifiers and reserved words by implementations targeting [=OpenVMS=]
to:
[@`@] &nbsp; for use as a token by Objective Modula-2 (:nl:)
[@@@]
&nbsp; for use as a lead character in identifiers and reserved words by language supersets (:nl:)
[@%@]
&nbsp; for use as a character in identifiers and reserved words by implementations targeting[=OpenVMS=] 
2015-09-14 10:28 by trijezdci - update to latest grammar (work in progress)
Changed line 931 from:
!!!!!#62 PropertyToBindTo
to:
!!!!!#62 Property To Bind To
Added line 1109:
Changed lines 1111-1112 from:
[@%@] &nbsp; for use as a character in identifiers and reserved words by implementations targeting OpenVMS
to:

[@%@] &nbsp; for use as a character in identifiers and reserved words by implementations targeting [=OpenVMS=]
2015-09-14 10:26 by trijezdci - update to latest grammar (work in progress)e
Changed lines 1062-1063 from:
* 50 reserved words
to:
Changed lines 1073-1074 from:
* 32 identifiers
to:
Changed lines 1082-1083 from:
* 36 special symbols
to:
Changed lines 1090-1092 from:
!!!Quoted Text Delimiters
* 4 symbols
to:
!!!!!#3.1 Quoted Text Delimiters
Changed lines 1094-1096 from:
!!!Comment Delimiters
* 3 symbols
to:
!!!!!#3.2 Comment Delimiters
Changed lines 1098-1100 from:
!!!Pragma Affix and Delimiters
* 3 symbols
to:
!!!!!#3.3 Pragma Affix and Delimiters
Changed lines 1102-1104 from:
!!!Template Language Symbols
* 7 symbols
to:
!!!!!#3.3 Template Language Symbols
Added lines 1105-1117:

!!!!!#3.5 Reserved Symbols

[@`@] &nbsp; for use as a token by Objective Modula-2
[@@@] &nbsp; for use as a lead character in identifiers and reserved words by language supersets
[@%@] &nbsp; for use as a character in identifiers and reserved words by implementations targeting OpenVMS

!!!!!#4 Identifiers

!!!!!#4 Number Literals

!!!!!#5 String Literals

2015-09-14 10:09 by trijezdci - update to latest grammar (work in progress)e
2015-09-14 10:09 by trijezdci - update to latest grammar (work in progress)e
Changed lines 723-807 from:





























!!! Reserved Words

* 50 reserved words

@@ALIAS@@, @@AND@@, @@ARGLIST@@, @@ARRAY@@, @@BEGIN@@, @@BLUEPRINT@@,
@@BY@@,@@CASE@@, @@CONST@@, @@COPY@@, @@DEFINITION@@, @@DIV@@, @@DO@@,
@@ELSE@@, @@ELSIF@@, @@END@@, @@ENUM@@, @@EXIT@@, @@FOR@@, @@FROM@@,
@@IF@@, @@IMPLEMENTATION@@, @@IMPORT@@, @@IN@@, @@LOOP@@, @@MOD@@,
@@MODULE@@, @@NEW@@, @@NONE@@, @@NOT@@, @@OF@@, @@OPAQUE@@, @@OR@@,
@@POINTER@@, @@PROCEDURE@@, @@RECORD@@, @@REFERENTIAL@@, @@RELEASE@@,
@@REPEAT@@, @@RETAIN@@, @@RETURN@@, @@SET@@, @@THEN@@, @@TO@@, @@TYPE@@,
@@UNTIL@@, @@VAR@@, @@WHILE@@, @@YIELD@@

!!!Special Symbols
* 36 special symbols

[@.@] &nbsp; [@,@] &nbsp; [@:@] &nbsp; [@;@] &nbsp; [@|@] &nbsp; [@^@] &nbsp;
[@~@] &nbsp; [@..@] &nbsp; [@:=@] &nbsp; [@++@] &nbsp; [@--@] &nbsp; [@::@] &nbsp;
[@+@] &nbsp; [@-@] &nbsp; [@*@] &nbsp; [@*.@] &nbsp; [@/@] &nbsp; [@\@] &nbsp;
[@=@] &nbsp; [@#@] &nbsp; [@>@] &nbsp; [@>=@] &nbsp; [@<@] &nbsp; [@<=@] &nbsp;
[@==@] &nbsp; [@&@] &nbsp; [@->@] &nbsp; [@<>@] &nbsp; [@><@] &nbsp; [@+/-@] &nbsp;
[@(@] &nbsp; [@)@] &nbsp; [@[@] &nbsp; [@]@] &nbsp; [@{@] &nbsp; [@}@] &nbsp;

!!!Quoted Text Delimiters
* 4 symbols

[@'@] &nbsp; [@"@] &nbsp; [@<<@] &nbsp; [@>>@] &nbsp;

!!!Comment Delimiters
* 3 symbols

[@!@] &nbsp; [@(*@] &nbsp; [@*)@] &nbsp;

!!!Pragma Affix and Delimiters
* 3 symbols

[@?@] &nbsp; [@<*@] &nbsp; [@*>@] &nbsp;

!!!Template Language Symbols
* 7 symbols

[@##@] &nbsp; [@<#@] &nbsp; [@#>@] &nbsp; [@@@@] &nbsp; [@//@] &nbsp; [@/*@] &nbsp;  [@*/@] &nbsp;


!!! Reserved Pragmas
* 14 reserved pragmas

@@IF@@, @@ELSE@@, @@ELSIF@@, @@ENDIF@@, @@INFO@@, @@WARN@@,
@@ERROR@@, @@FATAL@@, @@ALIGN@@, @@FOREIGN@@, @@MAKE@@,
@@INLINE@@, @@NOINLINE@@, @@VOLATILE@@

!!! Non-Terminal Symbols
* 65 productions
* 15 aliases


!!!!Literals
to:
!!!!Blueprint Syntax

!!!!!#55 Blueprint
[@
blueprint :
  BLUEPRINT blueprintIdent ( '[' blueprintToRefine ']' )?
  ( FOR blueprintForTypeToExtend )? ';' ( REFERENTIAL identList ';' )?
  MODULE TYPE '=' ( typeClassification ( ';' literalCompatibility)? | NONE ) ';'
  ( constraint ';' )* ( requirement ';' )* END blueprintIdent '.'
  ;
@]

!!!!!#55.1 Blueprint Identifier
[@
blueprintIdent : Ident ;
@]

!!!!!#55.2 Blueprint To Refine, Blueprint For Type To Extend
[@
blueprintToRefine : blueprintIdent ;

blueprintForTypeToExtend : blueprintIdent ;
@]

!!!!!#56 Type Classification
[@
typeClassification :
  '{' determinedClassification ( ';' refinableClassification )? ( ';' '*' )? '}'
  | '*'
  ;
@]

!!!!!#56.1 Determined Classification
[@
determinedClassification :
  classificationIdent ( ',' classificationIdent )*
  ;
@]

!!!!!#56.2 Refinable Classification
[@
refinableClassification :
  '~' classificationIdent ( ',' '~' classificationIdent )*
  ;
@]

!!!!!#56.3 Classification Identifier
[@
classificationIdent : Ident ;
@]

!!!!!#57 Literal Compatibility
[@
literalCompatibility :
  TLITERAL '=' protoLiteral ( '|' protoLiteral )*
  ;
@]

!!!!!#57.1 Proto-Literal
[@
protoLiteral :
  protoLiteralIdent | structuredProtoLiteral
  ;
@]

!!!!!#57.2 Proto-Literal Identifier
[@
protoLiteralIdent : Ident ;
@]

!!!!!#58 Structured Proto-Literal
[@
structuredProtoLiteral :
  '{'
    ( ARGLIST reqValueCount? OF
        ( '{' builtinOrReferential ( ',' builtinOrReferential )* '}' |
          builtinOrReferential ) ) |
    builtinOrReferential '}'
  ;
@]

!!!!!#58.1 Required Value Count
[@
reqValueCount :
  greaterThan? wholeNumber
  ;
@]

!!!!!#58.2 Greater Than
[@
greaterThan : '>' ;
@]

!!!!!#58.3 Whole Number
[@
wholeNumber : NumberLiteral ;
@]

!!!!!#58.4 Built-in Type Or Referential Identifier
[@
builtinOrReferential : Ident ;
@]

!!!!!#59 Constraint
[@
constraint :
  constraintTerm ( oneWayDependency | mutualDependencyOrExclusion )
  ;
@]

!!!!!#59.1 Constraint Term
[@
constraintTerm :
  '(' classificationOrFlagIdent ')' |
  '[' bindableEntityOrProperty ']'
  ;
@]

!!!!!#59.2 Bindable Entity Or Property
[@
bindableEntityOrProperty :
  entityToBindTo | propertyToBindTo
  ;
@]

!!!!!#59.3 One-Way Dependency
[@
oneWayDependency :
  '->' termList ( '|' termList )*
  ;
@]

!!!!!#59.4 Mutual Dependency Or Exclusion
[@
mutualDependencyOrExclusion :
  ( '<>' | '><' ) termList
  ;
@]

!!!!!#59.5 Term List
[@
termList :
  constraintTerm ( ',' constraintTerm )*
  ;
@]

!!!!!#59.6 Classification Or Flag Identifier
[@
classificationOrFlagIdent : Ident ;
@]

!!!!!#60 Requirement
[@
requirement :
  condition '->' ( typeRequirement | constRequirement | procRequirement )
  ;
@]

!!!!!#60.1 Condition
[@
condition :
  NOT? boolConstIdent
  ;
@]

!!!!!#60.2 Boolean Constant Identifier
[@
boolConstIdent : Ident ;
@]

!!!!!#60.3 Type Requirement
[@
typeRequirement :
  TYPE typeDefinition
  ;
@]

!!!!!#61 Constant Requirement
[@
constRequirement :
  CONST
    ( '[' propertyToBindTo ']' ( simpleConstRequirement | '=' NONE ) |
      restrictedExport? simpleConstRequirement )
  ;
@]

!!!!!#61.1 Simple Constant Requirement
[@
simpleConstRequirement :
  Ident ( '=' constExpression | ':' builtinTypeIdent )
  ;
@]

!!!!!#61.2 Constant Expression
[@
constExpression : expression ;
@]

!!!!!#61.3 Built-in Type Identifier
[@
builtinTypeIdent : Ident ;
@]

!!!!!#61.4 Restricted Export
[@
restrictedExport : '*' ;
@]

!!!!!#62 PropertyToBindTo
[@
propertyToBindTo :
  memMgtProperty | collectionProperty | scalarProperty | TFLAGS
  ;
@]

!!!!!#62.1 Memory Management Property
[@
memMgtProperty :
  TDYN | TREFC
  ;
@]

!!!!!#62.2 Collection Property
[@
collectionProperty :
  TORDERED | TSORTED | TLIMIT
  ;
@]

!!!!!#62.3 Scalar Property
[@
scalarProperty :
  TSCALAR | TMAX | TMIN
  ;
@]

!!!!!#63 Procedure Requirement
[@
procedureRequirement :
  PROCEDURE
    ( '[' ( entityToBindTo | COROUTINE ) ']' ( procedureSignature | '=' NONE ) |
      restrictedExport? procedureSignature )
  ;
@]

!!!!!#64 Entity To Bind To
[@
entityToBindTo :
  bindableResWord | bindableOperator | bindableMacro
  ;
@]

!!!!!#64.1 Bindable Reserved Word
[@
bindableResWord :
  NEW | RETAIN | RELEASE | COPY | bindableFor
  ;
@]

!!!!!#64.2 Bindable FOR
[@
bindableFor :
  FOR forBindingDifferentiator?
  ;
@]

!!!!!#64.3 FOR Binding Differentiator
[@
forBindingDifferentiator :
  '|' ( '++' | '--' )
  ;
@]

!!!!!#64.4 Bindable Operator
[@
bindableOperator :
  '+' | '-' | '*' | '/' | '\' | '=' | '<' | '>' | '*.' | '::'
  IN | DIV | MOD | unaryMinus
  ;
@]

!!!!!#64.5 Unary Minus
[@
unaryMinus : '+/-' ;
@]

!!!!!#64.6 Bindable Macro
[@
bindableMacro :
  ABS | LENGTH | EXISTS | SEEK | SUBSET | READ | READNEW | WRITE | WRITEF |
  SXF | VAL | multiBindableMacro1 | multiBindableMacro2 | multiBindableMacro3
  ;
@]

!!!!!#64.7 Multi-Bindable Macro 1
[@
multiBindableMacro1 :
  ( COUNT | VALUE ) bindingDifferentiator1?
  ;
@]

!!!!!#64.8 Binding Differentiator 1
[@
bindingDifferentiator1 :
  '|' '#'
  ;
@]

!!!!!#64.9 Multi-Bindable Macro 2
[@
multiBindableMacro2 :
  ( STORE | INSERT | REMOVE ) bindingDifferentiator2?
  ;
@]

!!!!!#64.10 Binding Differentiator 2
[@
bindingDifferentiator2 :
  '|' ( ',' | '#' | '*' )
  ;
@]

!!!!!#64.11 Multi-Bindable Macro 3
[@
multiBindableMacro3 :
  APPEND bindingDifferentiator3?
  ;
@]

!!!!!#64.12 Binding Differentiator 3
[@
bindingDifferentiator3 :
  '|' ( ',' | '*' )
  ;
@]

!!! (2) Terminals

!!!!!#1 Reserved Words

* 50 reserved words

@@ALIAS@@, @@AND@@, @@ARGLIST@@, @@ARRAY@@, @@BEGIN@@, @@BLUEPRINT@@,
@@BY@@,@@CASE@@, @@CONST@@, @@COPY@@, @@DEFINITION@@, @@DIV@@, @@DO@@,
@@ELSE@@, @@ELSIF@@, @@END@@, @@ENUM@@, @@EXIT@@, @@FOR@@, @@FROM@@,
@@IF@@, @@IMPLEMENTATION@@, @@IMPORT@@, @@IN@@, @@LOOP@@, @@MOD@@,
@@MODULE@@, @@NEW@@, @@NONE@@, @@NOT@@, @@OF@@, @@OPAQUE@@, @@OR@@,
@@POINTER@@, @@PROCEDURE@@, @@RECORD@@, @@REFERENTIAL@@, @@RELEASE@@,
@@REPEAT@@, @@RETAIN@@, @@RETURN@@, @@SET@@, @@THEN@@, @@TO@@, @@TYPE@@,
@@UNTIL@@, @@VAR@@, @@WHILE@@, @@YIELD@@

!!!!!#2 Dual-Use Identifiers (Schrödinger's Tokens)
* 32 identifiers

@@ABS@@, @@ADDRESS@@, @@APPEND@@, @@CAST@@, @@COUNT@@, @@COROUTINE@@,
@@EXISTS@@, @@INSERT@@, @@LENGTH@@, @@OCTET@@, @@READ@@, @@READNEW@@,
@@REMOVE@@, @@SEEK@@, @@STORE@@, @@SUBSET@@, @@SXF@@, @@TDYN@@,
@@TFLAGS@@, @@TLIMIT@@, @@TLITERAL@@, @@TMAX@@, @@TMIN@@, @@TORDERED@@,
@@TREFC@@, @@TSCALAR@@, @@TSORTED@@, @@UNSAFE@@, @@VAL@@, @@VALUE@@,
@@WRITE@@, @@WRITEF@@

!!!!!#3 Special Symbols
2015-09-14 09:37 by trijezdci - update to latest grammar (work in progress)e
Changed lines 1-2 from:
!!! Non-Terminals
to:
!!! (1) Non-Terminals
Added lines 414-737:

!!!!Implementation And Program Module Syntax

!!!!!#32 Implementation Or Program Module
[@
implOrPrgmModule :
  IMPLEMENTATION? MODULE moduleIdent ';'
  ( importList ';' )* block moduleIdent '.'
  ;
@]

!!!!!#33 Block
[@
block :
  declaration* ( BEGIN statementSequence )? END
  ;
@]

!!!!!#34 Declaration
[@
declaration :
  CONST ( Ident '=' constExpression ';' )+ |
  TYPE ( Ident '=' type ';' )+ |
  VAR ( variableDeclaration ';' )+ |
  procedureHeader ';' block Ident ';'
  ;
@]

!!!!!#35 Statement Sequence
[@
statementSequence :
  statement ( ';' statement )*
  ;
@]

!!!!!#36 Statement
[@
statement :
  memMgtOperation | updateOrProcCall | ifStatement | caseStatement |
  loopStatement | whileStatement | repeatStatement | forStatement |
  ( RETURN | YIELD ) expression? | EXIT
  ;
@]

!!!!!#37 Memory Management Operation
[@
memMgtOperation :
  NEW designator ( OF initSize | := initValue )? |
  RETAIN designator |
  RELEASE designator
  ;
@]

!!!!!#37.1 Initial Size, Initial Value
[@
initSize : expression ;

initValue : expression ;
@]

!!!!!#38 Update Or Procedure Call
[@
updateOrProcCall :
  designator ( ':=' expression | incOrDecSuffix | actualParameters )? |
  COPY designator ':=' expression
  ;
@]

!!!!!#38.1 Increment Or Decrement Suffix
[@
incOrDecSuffix :
  '++' | '--'
  ;
@]

!!!!!#39 IF Statement
[@
ifStatement :
  IF boolExpression THEN statementSequence
  ( ELSIF boolExpression THEN statementSequence )?
  ( ELSE statementSequence )?
  END
  ;
@]

!!!!!#39.1 Boolean Expression
[@
boolExpression : expression ;
@]

!!!!!#40 CASE Statement
[@
caseStatement :
  CASE expression OF ( '|' case  )+ ( ELSE statementSequence )? END
  ;
@]

!!!!!#40.1 Case
[@
case :
  caseLabels ( ',' caseLabels )* ':' statementSequence
  ;
@]

!!!!!#40.2 Case Labels
[@
caseLabels :
  constExpression ( '..' constExpression )?
  ;
@]

!!!!!#41 LOOP Statement
[@
loopStatement :
  LOOP statementSequence END
  ;
@]

!!!!!#42 WHILE Statement
[@
whileStatement :
  WHILE boolExpression DO statementSequence END
  ;
@]

!!!!!#43 REPEAT Statement
[@
repeatStatement :
  REPEAT statementSequence UNTIL boolExpression
  ;
@]

!!!!!#44 FOR Statement
[@
forStatement :
  FOR forLoopVariants IN iterableEntity DO statementSequence END
  ;
@]

!!!!!#44.1 FOR Loop Variants
[@
forLoopVariants :
  accessor ascOrDesc? ( ',' value )? |
  VALUE value ascOrDesc?
  ;
@]

!!!!!#44.2 Accessor, Value
[@
accessor : Ident ;

value : Ident ;
@]

!!!!!#44.3 Iterable Entity
[@
iterableEntity :
  designator | range OF ordinalType
  ;
@]

!!!!!#44.4 Ascender Or Descender
[@
ascOrDesc : incOrDecSuffix ;
@]

!!!!!#44.5 Ordinal Type
[@
ordinalType : typeIdent ;
@]

!!!!!#45 Designator
[@
designator :
  qualident designatorTail?
  ;
@]

!!!!!#45.1 Designator Tail
[@
designatorTail :
  ( ( '[' exprListOrSlice ']' | '^' ) ( '.' Ident )* )+
  ;
@]

!!!!!#45.2 Expression List Or Slice
[@
exprListOrSlice :
  expression ( ( ',' expression )* | '..' expression? )
  ;
@]

!!!!!#46 Expression
[@
expression :
  simpleExpression ( operL1 simpleExpression )?
  ;
@]

!!!!!#46.1 Level-1 Operator
[@
operL1 :
  '=' | '#' | '<' | '<=' | '>' | '>=' | IN | concatOp | identityOp
  ;
@]

!!!!!#46.2 Concatenation Operator
[@
concatOp : '&' ;
@]

!!!!!#46.3 Identity Operator
[@
identityOp : '==' ;
@]

!!!!!#47 Simple Expression
[@
simpleExpression :
  ( '+' | '-' )? term ( operL2 term )*
  ;
@]

!!!!!#47.1 Level-2 Operator
[@
operL2 :
  '+' | '-' | OR
  ;
@]

!!!!!#48 Term
[@
term :
  factorOrNegation ( operL3 factorOrNegation )*
  ;
@]

!!!!!#48.1 Level-3 Operator
[@
operL3 :
  '*' | '/' | DIV | MOD | AND | setDiffOp | dotProductOp
  ;
@]

!!!!!#48.2 Set Difference Operator
[@
setDiffOp : '\' ;
@]

!!!!!#48.3 Dot Product Operator
[@
dotProductOp : '*.' ;
@]

!!!!!#49 Factor Or Negation
[@
factorOrNegation :
  NOT? factorOrTypeConv
  ;
@]

!!!!!#50 Factor Or Type Conversion
[@
factorOrTypeConv :
  factor ( '::' typeIdent )?
  ;
@]

!!!!!#51 Factor
[@
factor :
  NumberLiteral | StringLiteral | structuredValue |
  '(' expression ')' | designator actualParameters?
  ;
@]

!!!!!#52 Actual Parameters
[@
actualParameters :
  '(' expressionList ')'
  ;
@]

!!!!!#53 Expression List
[@
expressionList :
  expression ( ',' expression )*
  ;
@]

!!!!!#54 Structured Value
[@
structuredValue :
  '{' valueComponent ( ',' valueComponent )* '}'
  ;
@]

!!!!!#54.1 Value Component
[@
valueComponent :
  constExpression (( BY | '..' )? constExpression )? | runtimeExpression
  ;
@]

!!!!!#54.2 Runtime Expression
[@
runtimeExpression : expression ;
@]















2015-09-14 09:11 by trijezdci - update to latest grammar (work in progress)
Changed lines 104-118 from:


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

 
 (4) implementationOfModule :
      IMPLEMENTATION programModule ;

    moduleId : ident ;

    priority : constExpression ;
@]
!!!!Import Lists, Blocks, Declarations, Definitions
to:
!!!!!#6 Qualified Identifier
Changed lines 106-124 from:
 (5) importList :
      ( FROM moduleId IMPORT ( identList | '*' ) |
      IMPORT ident '+'? ( ',' ident '+'? )* ) ';' ;

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

 (7) declaration :
      CONST ( constantDeclaration ';' )* |
      TYPE ( ident '=' type ';' )* |
      VAR ( variableDeclaration ';' )* |
      procedureDeclaration ';'  ;

 (8) definition :
      CONST ( ( '[' ident ']' )? constantDeclaration ';' )* |
      TYPE ( ident '=' ( type | opaqueType ) ';' )* |
      VAR ( variableDeclaration ';' )* |
      procedureHeader ';'
;
to:
qualident :
  Ident ( '.' Ident )*
  ;
Changed lines 110-111 from:
!!!!Constant Declarations
to:

!!!!!#7 Definition
Changed lines 113-114 from:
 (9) constantDeclaration :
      ident '=' constExpression ;
to:
definition :
  CONST ( constDefinition ';' )+ |
  TYPE ( typeDefinition ';' )+ |
  VAR ( variableDeclaration ';' )+ |
  procedureHeader ';'
 
;
Changed lines 120-121 from:
!!!!Type Declarations
to:

!!!!!#8 Constant Definition
Changed lines 123-179 from:
(10) type :
      ( ALIAS OF )? namedType | anonymousType | enumerationType | setType ;

    namedType : qualident ;

(11) opaqueType :
      OPAQUE ( '(' semanticType ')' | recordType )? ;

    semanticType : string ; // "A-Type", "S-Type", "Z-Type", "R-Type", "C-Type", "V-Type"

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

(13) enumerationType :
      '(' ( ( '+' namedType ) | ident ) ( ',' ( ( '+' namedType ) | ident ) )* ')' ;

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

    arrayIndex : ordinalConstExpression ;

    ordinalConstExpression : constExpression ;

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

    baseType : ident ;

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

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

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

(19) pointerType :
      POINTER TO CONST? namedType ;

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

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

(22) attributedFormalType :
      ( CONST | VAR )? formalType ;

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

    returnedType : namedType ;
to:
constDefinition :
  ( '[' propertyToBindTo ']' | restrictedExport )?
  Ident '=' constExpression
  ;
Changed lines 128-129 from:
!!!!Variable Declarations
to:

!!!!!#8.1 Constant Expression
Changed lines 131-135 from:
(24) variableDeclaration :
       ident ( '[' machineAddress ']' | ',' identList )?
      ':' ( namedType | anonymousType ) ;

    machineAddress : constExpression
;
to:
constExpression : expression ;
Changed lines 133-134 from:
!!!!Procedure Declarations
to:

!!!!!#8.2 Constant Expression
Changed lines 136-167 from:
(25) procedureDeclaration :
      procedureHeader ';' block ident ;

(26) procedureHeader :
      PROCEDURE
      ( '[' ( boundToOperator | ident ) ']' )?
      ( '(' ident ':' receiverType ')' )?
      ident ( '(' formalParamList ')' )? ( ':' returnedType )? ;

(27) boundToOperator :
      DIV | MOD | IN | FOR | TO | FROM |
      ':=' | '::' | '.' | '!' | '+' | '-' | '*' | '/' | '=' | '<' | '>' ;

    receiverType : ident ;

(28) formalParamList :
      formalParams ( ';' formalParams )* ;

(29) formalParams :
      simpleFormalParams | variadicFormalParams ;

(30) simpleFormalParams :
      ( CONST | VAR ) identList ':' formalType ;

(31) variadicFormalParams :
      VARIADIC ( variadicCounter | '[' variadicTerminator ']' )? OF
      ( ( CONST | VAR )? formalType |
        '(' simpleFormalParams ( ';' simpleFormalParams )* ')' ) ;

    variadicCounter : ident ;

    variadicTerminator : constExpression ;
to:
restrictedExport : '*' ;
Changed lines 138-139 from:
!!!!Statements
to:

!!!!!#9 Type Definition
Changed lines 141-185 from:
(32) statement :
      ( assignmentOrProcedureCall | ifStatement | caseStatement |
        whileStatement | repeatStatement | loopStatement |
        forStatement | RETURN expression? | EXIT )? ;

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

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

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

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

(37) case :
      caseLabelList ':' statementSequence ;

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

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

(40) whileStatement :
      WHILE expression DO statementSequence END ;

(41) repeatStatement :
      REPEAT statementSequence UNTIL expression ;

(42) loopStatement :
      LOOP statementSequence END ;

(43) forStatement :
      FOR ident
      ( ':=' expression TO expression ( BY constExpression )? | IN expression )
      DO statementSequence END ;
to:
typeDefinition :
  restrictedExport? Ident '=' ( OPAQUE | type )
  ;
Changed lines 145-146 from:
!!!!Expressions
to:

!!!!!#10 Variable Declaration
Changed lines 148-199 from:
(44) constExpression :
      simpleConstExpr ( relation simpleConstExpr | '::' namedType )? ;

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

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

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

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

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

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

(51) designator :
      qualident designatorTail? ;

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

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

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

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

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

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

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

(59) actualParameters :
      '(' expressionList? ')' ;
to:
variableDeclaration :
  identList ':' ( range OF )? typeIdent
  ;
Changed lines 152-153 from:
!!!!Value Constructors
to:

!!!!!#11 Identifier List
Changed lines 155-165 from:
(60) constStructuredValue :
       '{' ( constValueComponent ( ',' constValueComponent )* )? '}' ;

(61) constValueComponent :
      constExpression ( ( BY | '..' ) constExpression  )? ;

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

(63) valueComponent :
      expression ( ( BY | '..' ) constExpression )?
;
to:
identList :
    Ident ( ',' Ident )*
    ;
Changed lines 159-160 from:
!!!!Identifiers
to:

!!!!!#12 Range
Changed lines 162-168 from:
(64) qualident :
      ident ( '.' ident )* ;

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

    ident : IDENT
;
to:
range :
  '[' greaterThan? constExpression '..' lessThan? constExpression ']'
  ;
Added lines 166-426:

!!!!!#12.1 Greater Than
[@
greaterThan : '>' ;
@]

!!!!!#12.2 Less Than
[@
lessThan : '<' ;
@]

!!!!!#13 Type
[@
type :
  typeIdent | derivedSubType | enumType | setType | arrayType |
  recordType | pointerType | coroutineType | procedureType
  ;
@]

!!!!!#13.1 Derived Sub-Type
[@
derivedSubType :
  ALIAS OF typeIdent |
  range OF ordinalOrScalarType |
  CONST dynamicTypeIdent
  ;
@]

!!!!!#13.2 Ordinal Or Scalar Type, Dynamic Type Identifier
[@
ordinalOrScalarType : typeIdent ;

dynamicTypeIdent : typeIdent ;
@]

!!!!!#14 Enumeration Type
[@
enumType :
  '(' ( '+' enumTypeToExtend )? identList ')'
  ;
@]

!!!!!#14.1 Enumeration Type To Extend
[@
enumTypeToExtend : typeIdent ;
@]

!!!!!#15 Set Type
[@
setType :
  SET OF enumTypeIdent
  ;
@]

!!!!!#16 Array Type
[@
arrayType :
  ARRAY componentCount ( ',' componentCount )* OF typeIdent
  ;
@]

!!!!!#16.1 Component Count
[@
componentCount : constExpression ;
@]

!!!!!#17 Record Type
[@
recordType :
  RECORD
    ( fieldList ( ';' fieldList )* indeterminateField? |
      '(' recTypeToExtend ')' fieldList ( ';' fieldList )* )
  ;
@]

!!!!!#17.1 Field List
[@
fieldList :
  restrictedExport? variableDeclaration
  ;
@]

!!!!!#17.2 Record Type To Extend
[@
recTypeToExtend : typeIdent ;
@]

!!!!!#17.3 Indeterminate Field
[@
indeterminateField :
  '~' Ident ':' ARRAY discriminantFieldIdent OF typeIdent
  ;
@]

!!!!!#17.4 Discriminant Field Ident
[@
discriminantFieldIdent : Ident ;
@]

!!!!!#18 Pointer Type
[@
pointerType :
  POINTER TO CONST? typeIdent
  ;
@]

!!!!!#19 Coroutine Type
[@
coroutineType :
  COROUTINE '(' assocProcType ')'
  ;
@]

!!!!!#19.1 Associated Procedure Type
[@
assocProcType : typeIdent ;
@]

!!!!!#20 Procedure Type
[@
procedureType :
  PROCEDURE ( formalType ( ',' formalType )* )? ( ':' returnedType )?
  ;
@]

!!!!!#20.1 Formal Type
[@
formalType :
  simpleFormalType | attributedFormalType | variadicFormalType
  ;
@]

!!!!!#21 Simple Formal Type
[@
simpleFormalType :
  ( ARRAY OF )? typeIdent | castingFormalType
  ;
@]

!!!!!#21.1 Casting Formal Type
[@
castingFormalType :
  CAST ( ARRAY OF OCTET | addressTypeIdent )
  ;
@]

!!!!!#21.2 Address Type Identifier
[@
addressTypeIdent :
  ( UNSAFE '.' )? ADDRESS
  ;
@]

!!!!!#22 Attributed Formal Type
[@
attributedFormalType :
  ( CONST | NEW | VAR ) ( simpleFormalType | simpleVariadicFormalType )
  ;
@]

!!!!!#23 Simple Variadic Formal Type
[@
simpleVariadicFormalType :
  ARGLIST reqNumOfArgs? OF simpleFormalType terminator?
  ;
@]

!!!!!#23.1 Required Number Of Arguments
[@
reqNumOfArgs :
  greaterThan? constExpression
  ;
@]

!!!!!#23.2 Argument List Terminator
[@
terminator :
  '|' constQualident
  ;
@]

!!!!!#23.2 Constant Qualified Identifier
[@
constQualident : qualident ;
@]

!!!!!#24 Variadic Formal Type
[@
variadicFormalType :
  ARGLIST reqNumOfArgs? OF
    ( '{' nonVariadicFormalType ( ';' nonVariadicFormalType )* '}' |
      simpleFormalType ) terminator?
  ;
@]

!!!!!#25 Non-Variadic Formal Type
[@
nonVariadicFormalType :
  ( CONST | NEW | VAR )? simpleFormalType
  ;
@]

!!!!!#26 Procedure Header
[@
procedureHeader :
  PROCEDURE ( '[' ( entityToBindTo | COROUTINE ) ']' | restrictedExport )?
  procedureSignature
  ;
@]

!!!!!#27 Procedure Signature
[@
procedureSignature :
  Ident ( '(' formalParams ( ';' formalParams )* ')' )? ( ':' returnedType )?
  ;
@]

!!!!!#28 Formal Parameters
[@
formalParams :
  identList ':' ( simpleFormalType | variadicFormalParams ) |
  attributedFormalParams
  ;
@]

!!!!!#29 Attributed Formal Parameters
[@
attributedFormalParams :
  ( CONST | NEW | VAR ) identList ':'
  ( simpleFormalType | simpleVariadicFormalType )
  ;
@]

!!!!!#30 Variadic Formal Parameters
[@
variadicFormalParams :
  ARGLIST reqNumOfArgs? OF
    ( ( '{' nonVariadicFormalParams ( ';' nonVariadicFormalParams )* '}') |
      simpleFormalType ) terminator?
  ;
@]

!!!!!#31 Non-Variadic Formal Parameters
[@
nonVariadicFormalParams :
  ( CONST | NEW | VAR )? identList ':' simpleFormalType
  ;
@]












2015-09-14 08:41 by trijezdci - update to latest grammar (work in progress)
Changed lines 1-55 from:
!!! Reserved Words
* 50 reserved words

@@ALIAS@@, @@AND@@, @@ARGLIST@@, @@ARRAY@@, @@BEGIN@@, @@BLUEPRINT@@,
@@BY@@,@@CASE@@, @@CONST@@, @@COPY@@, @@DEFINITION@@, @@DIV@@, @@DO@@,
@@ELSE@@, @@ELSIF@@, @@END@@, @@ENUM@@, @@EXIT@@, @@FOR@@, @@FROM@@,
@@IF@@, @@IMPLEMENTATION@@, @@IMPORT@@, @@IN@@, @@LOOP@@, @@MOD@@,
@@MODULE@@, @@NEW@@, @@NONE@@, @@NOT@@, @@OF@@, @@OPAQUE@@, @@OR@@,
@@POINTER@@, @@PROCEDURE@@, @@RECORD@@, @@REFERENTIAL@@, @@RELEASE@@,
@@REPEAT@@, @@RETAIN@@, @@RETURN@@, @@SET@@, @@THEN@@, @@TO@@, @@TYPE@@,
@@UNTIL@@, @@VAR@@, @@WHILE@@, @@YIELD@@

!!!Special Symbols
* 36 special symbols

[@.@] &nbsp; [@,@] &nbsp; [@:@] &nbsp; [@;@] &nbsp; [@|@] &nbsp; [@^@] &nbsp;
[@~@] &nbsp; [@..@] &nbsp; [@:=@] &nbsp; [@++@] &nbsp; [@--@] &nbsp; [@::@] &nbsp;
[@+@] &nbsp; [@-@] &nbsp; [@*@] &nbsp; [@*.@] &nbsp; [@/@] &nbsp; [@\@] &nbsp;
[@=@] &nbsp; [@#@] &nbsp; [@>@] &nbsp; [@>=@] &nbsp; [@<@] &nbsp; [@<=@] &nbsp;
[@==@] &nbsp; [@&@] &nbsp; [@->@] &nbsp; [@<>@] &nbsp; [@><@] &nbsp; [@+/-@] &nbsp;
[@(@] &nbsp; [@)@] &nbsp; [@[@] &nbsp; [@]@] &nbsp; [@{@] &nbsp; [@}@] &nbsp;

!!!Quoted Text Delimiters
* 4 symbols

[@'@] &nbsp; [@"@] &nbsp; [@<<@] &nbsp; [@>>@] &nbsp;

!!!Comment Delimiters
* 3 symbols

[@!@] &nbsp; [@(*@] &nbsp; [@*)@] &nbsp;

!!!Pragma Affix and Delimiters
* 3 symbols

[@?@] &nbsp; [@<*@] &nbsp; [@*>@] &nbsp;

!!!Template Language Symbols
* 7 symbols

[@##@] &nbsp; [@<#@] &nbsp; [@#>@] &nbsp; [@@@@] &nbsp; [@//@] &nbsp; [@/*@] &nbsp;  [@*/@] &nbsp;


!!! Reserved Pragmas
* 14 reserved pragmas

@@IF@@, @@ELSE@@, @@ELSIF@@, @@ENDIF@@, @@INFO@@, @@WARN@@,
@@ERROR@@, @@FATAL@@, @@ALIGN@@, @@FOREIGN@@, @@MAKE@@,
@@INLINE@@, @@NOINLINE@@, @@VOLATILE@@

!!! Non-Terminal Symbols
* 65 productions
* 15 aliases

!!!!Compilation Units
to:
!!! Non-Terminals

!!!!!#1 Compilation Unit
Changed lines 5-22 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:
compilationUnit :
  definitionModule | implOrPrgmModule | blueprint
 
;
Changed lines 9-12 from:
!!!!Import Lists, Blocks, Declarations, Definitions
to:

!!!!Definition Module Syntax

!!!!!#2 Definition Module
Changed lines 14-32 from:
 (5) importList :
 
     ( FROM moduleId IMPORT ( identList | '*' ) |
       IMPORT ident '+'? ( ',' ident '+'? )* ) ';' ;

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

 (7) declaration :
      CONST ( constantDeclaration ';' )* |
      TYPE ( ident '=' type ';' )* |
      VAR ( variableDeclaration ';' )* |
      procedureDeclaration ';'  ;

 (8) definition :
      CONST ( ( '[' ident ']' )? constantDeclaration ';' )* |
      TYPE ( ident '=' ( type | opaqueType ) ';' )* |
      VAR ( variableDeclaration ';' )* |
      procedureHeader ';'
;
to:
definitionModule :
  DEFINITION MODULE moduleIdent
  ( '[' blueprintToObey ']' )? ( FOR typeToExtend )? ';'
  (importList ';')* definition*
  END moduleIdent '.'
  ;
Changed lines 21-22 from:
!!!!Constant Declarations
to:

!!!!!#2.1 Module Identifier, Blueprint Identifier, Type To Extend
Changed lines 24-25 from:
 (9) constantDeclaration :
 
     ident '=' constExpression ;
to:
moduleIdent : Ident ;

blueprintIdent
: Ident ;

typeToExtend : Ident
;
Changed lines 30-31 from:
!!!!Type Declarations
to:

!!!!!#2.2 Blueprint To Obey
Changed lines 33-89 from:
(10) type :
      ( ALIAS OF )? namedType | anonymousType | enumerationType | setType ;

    namedType : qualident ;

(11) opaqueType :
      OPAQUE ( '(' semanticType ')' | recordType )? ;

    semanticType : string ; // "A-Type", "S-Type", "Z-Type", "R-Type", "C-Type", "V-Type"

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

(13) enumerationType :
      '(' ( ( '+' namedType ) | ident ) ( ',' ( ( '+' namedType ) | ident ) )* ')' ;

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

    arrayIndex : ordinalConstExpression ;

    ordinalConstExpression : constExpression ;

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

    baseType : ident ;

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

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

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

(19) pointerType :
      POINTER TO CONST? namedType ;

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

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

(22) attributedFormalType :
      ( CONST | VAR )? formalType ;

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

    returnedType : namedType ;
to:
blueprintToObey : blueprintIdent ;
Changed lines 35-36 from:
!!!!Variable Declarations
to:

!!!!!#3 Import List
Changed lines 38-42 from:
(24) variableDeclaration :
       ident ( '[' machineAddress ']' | ',' identList )?
      ':' ( namedType | anonymousType ) ;

    machineAddress : constExpression
;
to:
importList :
  libGenDirective | importDirective
  ;
Changed lines 42-43 from:
!!!!Procedure Declarations
to:

!!!!!#4 Library Generation Directive
Changed lines 45-76 from:
(25) procedureDeclaration :
      procedureHeader ';' block ident ;

(26) procedureHeader :
      PROCEDURE
      ( '[' ( boundToOperator | ident ) ']' )?
      ( '(' ident ':' receiverType ')' )?
      ident ( '(' formalParamList ')' )? ( ':' returnedType )? ;

(27) boundToOperator :
      DIV | MOD | IN | FOR | TO | FROM |
      ':=' | '::' | '.' | '!' | '+' | '-' | '*' | '/' | '=' | '<' | '>' ;

    receiverType : ident ;

(28) formalParamList :
      formalParams ( ';' formalParams )* ;

(29) formalParams :
      simpleFormalParams | variadicFormalParams ;

(30) simpleFormalParams :
      ( CONST | VAR ) identList ':' formalType ;

(31) variadicFormalParams :
      VARIADIC ( variadicCounter | '[' variadicTerminator ']' )? OF
      ( ( CONST | VAR )? formalType |
        '(' simpleFormalParams ( ';' simpleFormalParams )* ')' ) ;

    variadicCounter : ident ;

    variadicTerminator : constExpression ;
to:
libGenDirective :
  GENLIB libIdent FROM template FOR templateParamList END
  ;
Changed lines 49-50 from:
!!!!Statements
to:

!!!!!#4.1 Library Identifier, Template, Placeholder
Changed lines 52-96 from:
(32) statement :
      ( assignmentOrProcedureCall | ifStatement | caseStatement |
        whileStatement | repeatStatement | loopStatement |
        forStatement | RETURN expression? | EXIT )? ;

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

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

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

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

(37) case :
      caseLabelList ':' statementSequence ;

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

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

(40) whileStatement :
      WHILE expression DO statementSequence END ;

(41) repeatStatement :
      REPEAT statementSequence UNTIL expression ;

(42) loopStatement :
      LOOP statementSequence END ;

(43) forStatement :
      FOR ident
      ( ':=' expression TO expression ( BY constExpression )? | IN expression )
      DO statementSequence END ;
to:
libIdent : Ident ;

template : Ident ;

placeholder : Ident ;
Changed lines 58-59 from:
!!!!Expressions
to:

!!!!!#4.2 Replacement
Changed lines 61-112 from:
(44) constExpression :
      simpleConstExpr ( relation simpleConstExpr | '::' namedType )? ;

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

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

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

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

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

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

(51) designator :
      qualident designatorTail? ;

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

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

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

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

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

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

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

(59) actualParameters :
      '(' expressionList? ')' ;
to:
replacement :
  NumberLiteral | StringLiteral | ChevronText
  ;
Changed lines 65-66 from:
!!!!Value Constructors
to:

!!!!!#5 Import Directive
Changed lines 68-78 from:
(60) constStructuredValue :
       '{' ( constValueComponent ( ',' constValueComponent )* )? '}' ;

(61) constValueComponent :
       constExpression ( ( BY | '..' ) constExpression  )? ;

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

(63) valueComponent :
      expression ( ( BY | '..' ) constExpression )?
;
to:
importDirective :
  FROM ( moduleIdent | ENUM enumTypeIdent )
 
  IMPORT ( identifiersToImport | importAll ) |
  IMPORT modulesToImport
  ;
Changed lines 74-75 from:
!!!!Identifiers
to:

!!!!!#5.1 Enumeration Type Identifier
Changed lines 77-83 from:
(64) qualident :
       ident ( '.' ident )* ;

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

    ident : IDENT
;
to:
enumTypeIdent : typeIdent ;
Added lines 79-430:

!!!!!#5.2 Type Identifier
[@
typeIdent : qualident ;
@]

!!!!!#5.3 Identifiers To Import, Modules To Import
[@
identifiersToImport :
  Ident reExport? ( ',' Ident reExport? )*
  ;

modulesToImport : identifiersToImport ;
@]

!!!!!#5.4 Re-Export
[@
reExport : '+' ;
@]

!!!!!#5.5 Import All
[@
importAll : '*' ;
@]



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

 
 (4) implementationOfModule :
      IMPLEMENTATION programModule ;

    moduleId : ident ;

    priority : constExpression ;
@]
!!!!Import Lists, Blocks, Declarations, Definitions
[@
 (5) importList :
      ( FROM moduleId IMPORT ( identList | '*' ) |
      IMPORT ident '+'? ( ',' ident '+'? )* ) ';' ;

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

 (7) declaration :
      CONST ( constantDeclaration ';' )* |
      TYPE ( ident '=' type ';' )* |
      VAR ( variableDeclaration ';' )* |
      procedureDeclaration ';'  ;

 (8) definition :
      CONST ( ( '[' ident ']' )? constantDeclaration ';' )* |
      TYPE ( ident '=' ( type | opaqueType ) ';' )* |
      VAR ( variableDeclaration ';' )* |
      procedureHeader ';' ;
@]
!!!!Constant Declarations
[@
 (9) constantDeclaration :
      ident '=' constExpression ;
@]
!!!!Type Declarations
[@
(10) type :
      ( ALIAS OF )? namedType | anonymousType | enumerationType | setType ;

    namedType : qualident ;

(11) opaqueType :
      OPAQUE ( '(' semanticType ')' | recordType )? ;

    semanticType : string ; // "A-Type", "S-Type", "Z-Type", "R-Type", "C-Type", "V-Type"

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

(13) enumerationType :
      '(' ( ( '+' namedType ) | ident ) ( ',' ( ( '+' namedType ) | ident ) )* ')' ;

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

    arrayIndex : ordinalConstExpression ;

    ordinalConstExpression : constExpression ;

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

    baseType : ident ;

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

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

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

(19) pointerType :
      POINTER TO CONST? namedType ;

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

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

(22) attributedFormalType :
      ( CONST | 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
      ( '[' ( boundToOperator | ident ) ']' )?
      ( '(' ident ':' receiverType ')' )?
      ident ( '(' formalParamList ')' )? ( ':' returnedType )? ;

(27) boundToOperator :
      DIV | MOD | IN | FOR | TO | FROM |
      ':=' | '::' | '.' | '!' | '+' | '-' | '*' | '/' | '=' | '<' | '>' ;

    receiverType : ident ;

(28) formalParamList :
      formalParams ( ';' formalParams )* ;

(29) formalParams :
      simpleFormalParams | variadicFormalParams ;

(30) simpleFormalParams :
      ( CONST | VAR ) identList ':' formalType ;

(31) variadicFormalParams :
      VARIADIC ( variadicCounter | '[' variadicTerminator ']' )? OF
      ( ( CONST | VAR )? formalType |
        '(' simpleFormalParams ( ';' simpleFormalParams )* ')' ) ;

    variadicCounter : ident ;

    variadicTerminator : constExpression ;
@]
!!!!Statements
[@
(32) statement :
      ( assignmentOrProcedureCall | ifStatement | caseStatement |
        whileStatement | repeatStatement | loopStatement |
        forStatement | RETURN expression? | EXIT )? ;

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

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

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

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

(37) case :
      caseLabelList ':' statementSequence ;

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

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

(40) whileStatement :
      WHILE expression DO statementSequence END ;

(41) repeatStatement :
      REPEAT statementSequence UNTIL expression ;

(42) loopStatement :
      LOOP statementSequence END ;

(43) forStatement :
      FOR ident
      ( ':=' expression TO expression ( BY constExpression )? | IN expression )
      DO statementSequence END ;
@]
!!!!Expressions
[@
(44) constExpression :
      simpleConstExpr ( relation simpleConstExpr | '::' namedType )? ;

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

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

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

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

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

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

(51) designator :
      qualident designatorTail? ;

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

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

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

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

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

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

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

(59) actualParameters :
      '(' expressionList? ')' ;
@]
!!!!Value Constructors
[@
(60) constStructuredValue :
      '{' ( constValueComponent ( ',' constValueComponent )* )? '}' ;

(61) constValueComponent :
      constExpression ( ( BY | '..' ) constExpression  )? ;

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

(63) valueComponent :
      expression ( ( BY | '..' ) constExpression )? ;
@]
!!!!Identifiers
[@
(64) qualident :
      ident ( '.' ident )* ;

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

    ident : IDENT ;
@]

!!! Reserved Words
* 50 reserved words

@@ALIAS@@, @@AND@@, @@ARGLIST@@, @@ARRAY@@, @@BEGIN@@, @@BLUEPRINT@@,
@@BY@@,@@CASE@@, @@CONST@@, @@COPY@@, @@DEFINITION@@, @@DIV@@, @@DO@@,
@@ELSE@@, @@ELSIF@@, @@END@@, @@ENUM@@, @@EXIT@@, @@FOR@@, @@FROM@@,
@@IF@@, @@IMPLEMENTATION@@, @@IMPORT@@, @@IN@@, @@LOOP@@, @@MOD@@,
@@MODULE@@, @@NEW@@, @@NONE@@, @@NOT@@, @@OF@@, @@OPAQUE@@, @@OR@@,
@@POINTER@@, @@PROCEDURE@@, @@RECORD@@, @@REFERENTIAL@@, @@RELEASE@@,
@@REPEAT@@, @@RETAIN@@, @@RETURN@@, @@SET@@, @@THEN@@, @@TO@@, @@TYPE@@,
@@UNTIL@@, @@VAR@@, @@WHILE@@, @@YIELD@@

!!!Special Symbols
* 36 special symbols

[@.@] &nbsp; [@,@] &nbsp; [@:@] &nbsp; [@;@] &nbsp; [@|@] &nbsp; [@^@] &nbsp;
[@~@] &nbsp; [@..@] &nbsp; [@:=@] &nbsp; [@++@] &nbsp; [@--@] &nbsp; [@::@] &nbsp;
[@+@] &nbsp; [@-@] &nbsp; [@*@] &nbsp; [@*.@] &nbsp; [@/@] &nbsp; [@\@] &nbsp;
[@=@] &nbsp; [@#@] &nbsp; [@>@] &nbsp; [@>=@] &nbsp; [@<@] &nbsp; [@<=@] &nbsp;
[@==@] &nbsp; [@&@] &nbsp; [@->@] &nbsp; [@<>@] &nbsp; [@><@] &nbsp; [@+/-@] &nbsp;
[@(@] &nbsp; [@)@] &nbsp; [@[@] &nbsp; [@]@] &nbsp; [@{@] &nbsp; [@}@] &nbsp;

!!!Quoted Text Delimiters
* 4 symbols

[@'@] &nbsp; [@"@] &nbsp; [@<<@] &nbsp; [@>>@] &nbsp;

!!!Comment Delimiters
* 3 symbols

[@!@] &nbsp; [@(*@] &nbsp; [@*)@] &nbsp;

!!!Pragma Affix and Delimiters
* 3 symbols

[@?@] &nbsp; [@<*@] &nbsp; [@*>@] &nbsp;

!!!Template Language Symbols
* 7 symbols

[@##@] &nbsp; [@<#@] &nbsp; [@#>@] &nbsp; [@@@@] &nbsp; [@//@] &nbsp; [@/*@] &nbsp;  [@*/@] &nbsp;


!!! Reserved Pragmas
* 14 reserved pragmas

@@IF@@, @@ELSE@@, @@ELSIF@@, @@ENDIF@@, @@INFO@@, @@WARN@@,
@@ERROR@@, @@FATAL@@, @@ALIGN@@, @@FOREIGN@@, @@MAKE@@,
@@INLINE@@, @@NOINLINE@@, @@VOLATILE@@

!!! Non-Terminal Symbols
* 65 productions
* 15 aliases

2015-09-14 08:19 by trijezdci - update to latest grammar (in progress)
Changed lines 2-20 from:
* 41 reserved words

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

!!!Reserved Symbols
* 30 reserved symbols

[@!@] &nbsp; [@#@] &nbsp; [@&@] &nbsp; [@(@] &nbsp; [@)@] &nbsp; [@*@] &nbsp;
[@+@] &nbsp; [@++@] &nbsp; [@,@] &nbsp; [@-@] &nbsp; [@--@] &nbsp; [@.@] &nbsp;
[@..@] &nbsp; [@/@] &nbsp; [@:@] &nbsp; [@::@] &nbsp; [@:=@] &nbsp; [@;@] &nbsp;
[@<@] &nbsp; [@<=@] &nbsp; [@=@] &nbsp; [@>@] &nbsp; [@>=@] &nbsp; [@[@] &nbsp;
[@]@] &nbsp; [@^@] &nbsp; [@{@] &nbsp; [@|@] &nbsp; [@}@] &nbsp; [@~@]
to:
* 50 reserved words

@@ALIAS@@, @@AND@@, @@ARGLIST@@, @@ARRAY@@, @@BEGIN@@, @@BLUEPRINT@@,
@@BY@@,@@CASE@@, @@CONST@@, @@COPY@@, @@DEFINITION@@, @@DIV@@, @@DO@@,
@@ELSE@@, @@ELSIF@@, @@END@@, @@ENUM@@, @@EXIT@@, @@FOR@@, @@FROM@@,
@@IF@@, @@IMPLEMENTATION@@, @@IMPORT@@, @@IN@@, @@LOOP@@, @@MOD@@,
@@MODULE@@, @@NEW@@, @@NONE@@, @@NOT@@, @@OF@@, @@OPAQUE@@, @@OR@@,
@@POINTER@@, @@PROCEDURE@@, @@RECORD@@, @@REFERENTIAL@@, @@RELEASE@@,
@@REPEAT@@, @@RETAIN@@, @@RETURN@@, @@SET@@, @@THEN@@, @@TO@@, @@TYPE@@,
@@UNTIL@@, @@VAR@@, @@WHILE@@, @@YIELD@@

!!!Special Symbols
* 36 special symbols

[@.@] &nbsp; [@,@] &nbsp; [@:@] &nbsp; [@;@] &nbsp; [@|@] &nbsp; [@^@] &nbsp;
[@~@] &nbsp; [@..@] &nbsp; [@:=@] &nbsp; [@++@] &nbsp; [@--@] &nbsp; [@::@] &nbsp;
[@+@] &nbsp; [@-@] &nbsp; [@*@] &nbsp; [@*.@] &nbsp; [@/@] &nbsp; [@\@] &nbsp;
[@=@] &nbsp; [@#@] &nbsp; [@>@] &nbsp; [@>=@] &nbsp; [@<@] &nbsp; [@<=@] &nbsp;
[@==@] &nbsp; [@&@] &nbsp; [@->@] &nbsp; [@<>@] &nbsp; [@><@] &nbsp; [@+/-@] &nbsp;
[@(@] &nbsp; [@)@] &nbsp; [@[@] &nbsp; [@]@] &nbsp; [@{@] &nbsp; [@}@] &nbsp;

!!!Quoted Text Delimiters
* 4 symbols

[@'@] &nbsp; [@"@] &nbsp; [@<<@] &nbsp; [@>>@] &nbsp;

!!!Comment Delimiters
* 3 symbols

[@!@] &nbsp; [@(*@] &nbsp; [@*)@] &nbsp;

!!!Pragma Affix and Delimiters
* 3 symbols

[@?@] &nbsp; [@<*@] &nbsp; [@*>@] &nbsp;

!!!Template Language Symbols
* 7 symbols

[@##@] &nbsp; [@<#@] &nbsp; [@#>@] &nbsp; [@@@@] &nbsp; [@//@] &nbsp; [@/*@] &nbsp;  [@*/@] &nbsp;