[an error occurred while processing this directive] Objective Modula-2 · Grammar [an error occurred while processing this directive]

Objective Modula-2

Latest Update: July 24, 2010

Overview

Frequently Asked Questions

Other Objective-C Inspired Hybrid Languages

The Modula-2 Webring

Visitor Map

Visitor Map - Click to view visits

Objective Modula-2 Grammar


Formal Syntax Definition for Objective Modula-2 in EBNF notation

last revised May 24, 2010

Compilation Units

compilationUnit

programModule | definitionOfBindings | definitionOfModule | implementationOfModule | protocolModule

programModule

MODULE moduleId ( '['priority']' )? ';'
importList* block moduleId

definitionOfBindings

BINDINGS FOR semanticType ';'
bindingsHeader bindings*
END semanticType '.'

definitionOfModule

DEFINITION MODULE moduleId ( '[' semanticType ']' )? ';'
importList* definition*
END moduleId '.'

implementationOfModule

IMPLEMENTATION programModule

protocolModule

PROTOCOL protocolId ( '(' adoptedProtocols ')' )? ';'
importList* ( OPTIONAL? methodHeader )*
END protocolId '.'

moduleId

ident

priority

constExpression

semanticType

ident

protocolId

ident

adoptedProtocols

identList

Bindings, Import Lists, Blocks, Declarations, Definitions

bindingsHeader

TYPE '=' ( RECORD | OPAQUE RECORD? ( ':=' ( literalType | '{' '}' ) )? ) ';'

bindings

( CONST '[' bindableIdent ']' |
PROCEDURE '[' ( bindableOperator | bindableIdent ) ']' ) ';'

bindableOperator

DIV | MOD | IN | FOR | TO | FROM |
':=' | '::' | '.' | '!' | '+' | '-' | '*' | '/' | '=' | '<' | '>'

bindableIdent

ident

literalType

ident

importList

( FROM moduleId IMPORT ( identList | '*' ) |
IMPORT ident '+'? ( ',' ident '+'? )* ) ';'

block

declaration* ( BEGIN statementSequence )?
END

declaration

CONST ( constantDeclaration ';' )* |
TYPE ( ident '=' type ';' )* |
VAR ( variableDeclaration ';' )* |
procedureDeclaration ';' |
methodDeclaration ';'

definition

CONST ( ( '[' bindableIdent ']' )? constantDeclaration ';' )* |
TYPE ( ident '=' ( type | OPAQUE recordType ) ';' )* |
VAR ( variableDeclaration ';' )* |
procedureHeader ';' |
methodHeader ';'

Constant Declarations

constDeclaration

ident '=' constExpression

Type Declarations

type

( ALIAS OF | '[' constExpression '..' constExpression ']' OF )? namedType | anonymousType | enumerationType | recordType | setType | classType

namedType

qualident

anonymousType

arrayType | pointerType | procedureType

enumerationType

'(' ( ( '+' namedType ) | ident ) ( ',' ( ( '+' namedType ) | ident ) )* ')'

arrayType

( ARRAY arrayIndex ( ',' arrayIndex )* | ASSOCIATIVE ARRAY )
OF ( namedType | pointerType | procedureType )

arrayIndex

ordinalConstExpression

ordinalConstExpression

constExpression

recordType

RECORD ( ( '(' baseType ')' )? fieldListSequence? END

baseType

qualident

fieldListSequence

fieldList ( ';' fieldList )*

fieldList

identList ':' ( namedType | arrayType | pointerType | procedureType )

classType

<*QUALIFIED*>? CLASS '(' superClass ( ',' adoptedProtocols )? ')'
( ( PUBLIC | MODULE | PROTECTED | PRIVATE )? fieldListSequence )*
END

superClass

qualident

setType

SET OF ( namedEnumType | '(' identList ')' )

namedEnumType

namedType

pointerType

POINTER TO CONST? namedType

procedureType

PROCEDURE ( '(' formalTypeList ')' )? ( ':' returnedType )?

formalTypeList

attributedFormalType ( ',' attributedFormalType )*

attributedFormalType

( CONST | VAR )? formalType

formalType

( ARRAY OF )? namedType

returnedType

namedType

Variable Declarations

variableDeclaration

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

machineAddress

ordinalConstExpression

Procedure Declarations

procedureDeclaration

procedureHeader ';' block ident

procedureHeader

PROCEDURE
( '[' ( bindableOperator | bindableIdent ) ']' )?
( '(' ident ':' receiverType ')' )?
ident ( '(' formalParamList ')' )? ( ':' returnedType )?

receiverType

ident

formalParamList

formalParams ( ';' formalParams )*

formalParams

simpleFormalParams | variadicFormalParams

simpleFormalParams

( CONST | VAR )? identList ':' formalType

variadicFormalParams

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

variadicCounter

ident

variadicTerminator

constExpression

Method Declarations

methodDeclaration

methodHeader ';' block ident

methodHeader

CLASS? METHOD '(' ident ':' ( receiverClass | '*' ) ')'
( ident | methodArg ) methodArg* ( ':' returnedType )?

receiverClass

qualident

methodArg

colonIdent '(' ( CONST | VAR )? ident ':' formalType ')'

Statements

statement

( assignmentOrProcedureCall | methodInvocation | ifStatement | caseStatement | whileStatement | repeatStatement | loopStatement | forStatement | tryStatement | criticalStatement | RETURN expression? | EXIT )?

statementSequence

statement ( ';' statement )*

methodInvocation

'[' receiver message ']'

receiver

ident | methodInvocation

message

ident ( colonIdent expression )* | ( colonIdent expression )+

assignmentOrProcedureCall

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

ifStatement

IF expression THEN statementSequence
( ELSIF expression THEN statementSequence )*
( ELSE statementSequence )?
END

caseStatement

CASE expression OF case ( '|' case )*
( ELSE statementSequence )?
END

case

caseLabelList ':' statementSequence

caseLabelList

caseLabels ( ',' caseLabels )*

caseLabels

constExpression ( '..' constExpression )?

whileStatement

WHILE expression DO statementSequence END

repeatStatement

REPEAT statementSequence UNTIL expression

loopStatement

LOOP statementSequence END

forStatement

FOR ident
( IN expression |
  ':' namedType ':=' expression TO expression ( BY constExpression )? )
DO statementSequence END

tryStatement

TRY statementSequence
ON ident DO statementSequence
CONTINUE statementSequence
END

criticalStatement

CRITICAL '(' classInstance ')'
statementSequence
END

classInstance

qualident

Expressions

constExpression

simpleConstExpr ( relation simpleConstExpr )?

relation

'=' | '#' | '<' | '<=' | '>' | '>=' | IN

simpleConstExpr

( '+' | '-' )? constTerm ( addOperator constTerm )*

addOperator

'+' | '-' | OR

constTerm

constFactor ( mulOperator constFactor )*

mulOperator

'*' | '/' | DIV | MOD | AND | '&'

constFactor

( number | string | constQualident | constStructuredValue |
  '(' constExpression ')' ) ( '::' namedType )? |
( NOT | '~' ) constFactor

designator

qualident ( designatorTail )?

designatorTail

( ( '[' ( expressionList ']' | '^' ) ( '.' ident )* )+

expressionList

expression ( ',' expression )*

expression

simpleExpression ( relation simpleExpression )?

simpleExpression

( '+' | '-' )? term ( addOperator term )*

term

factor ( mulOperator factor )*

factor

( number | string | structuredValue | designatorOrProcedureCall |
  '(' expression ')' ) ( '::' namedType )? |
( NOT | '~' ) factor | methodInvocation

designatorOrProcedureCall

qualident designatorTail? actualParameters?

actualParameters

'(' expressionList? ')'

Value Constructors

constStructuredValue

'{' ( constValueComponent ( ',' constValueComponent )* )? '}'

constValueComponent

constExpression ( ( BY | '..' ) constExpression )?

structuredValue

'{' ( valueComponent ( ',' valueComponent )* )? '}'

valueComponent

expression ( ( BY | '..' ) constExpression )?

Identifiers

qualident

ident ( '.' ident )*

identList

ident ( ',' ident )*

ident

IDENT

constQualident

qualident

colonIdent

COLON_IDENT

Literals

number

NUMBER

string

STRING

Pragmas

pragma

'<*' ( conditionalPragma | compileTimeMessagePragma |
          codeGenerationPragma | implementationDefinedPragma ) '*>'

conditionalPragma

( IF | ELSEIF ) constExpression | ELSE | ENDIF

compileTimeMessagePragma

( INFO | WARN | ERROR | FATAL ) compileTimeMessage

codeGenerationPragma

ALIGN '=' constExpression |
FOREIGN ( '=' string )? |
MAKE '=' string |
INLINE | NOINLINE | VOLATILE |
FRAMEWORK | IBACTION | IBOUTLET | QUALIFIED

implementationDefinedPragma

pragmaName ( '+' | '-' | '=' ( ident | string ) )?

compileTimeMessage

string

pragmaName

ident

Terminal Symbols

IDENT

( '_' | '$' | LETTER ) ( '_' | '$' | LETTER | DIGIT )*

COLON_IDENT

IDENT ':'

NUMBER

DIGIT+ |
BINARY_DIGIT+ 'B' |
DIGIT SEDECIMAL_DIGIT* ( 'C' | 'H' ) |
DIGIT+ '.' DIGIT+ ( 'E' ( '+' | '-' )? DIGIT+ )?

STRING

"'" ( CHARACTER | '"' )* "'" |
'"' ( CHARACTER | "'" )* '"'

LETTER

'A' .. 'Z' | 'a' .. 'z'

DIGIT

BINARY_DIGIT | '2' | '3' | '4' | '5' | '6' | '7' | '8' | '9'

BINARY_DIGIT

'0' | '1'

SEDECIMAL_DIGIT

DIGIT | 'A' | 'B' | 'C' | 'D' | 'E' | 'F'

CHARACTER

DIGIT | LETTER |
' ' | '!' | '#' | '$' | '%' | '&' | '(' | ')' | '*' | '+' | ',' | '-' | '.' | '/' | ':' | ';' | '<' | '=' | '>' | '?' | '@' | '[' | ']' | '^' | '_' | '`' | '{' | '|' | '}' | '~' |
ESCAPE_SEQUENCE

ESCAPE_SEQUENCE

'\' ( '0' | 'n' | 'r' | 't' | '\' | "'" | '"' )

Whitespace and Comments

WHITESPACE

' ' | ASCII(8)

NESTABLE_COMMENT

'(*' ( ANY_CHAR | END_OF_LINE )* NESTABLE_COMMENT* '*)'

NON_NESTABLE_COMMENT

'/*' ( ANY_CHAR | END_OF_LINE )* '*/'

SINGLE_LINE_COMMENT

'//' ANY_CHAR* END_OF_LINE

ANY_CHAR

\u0000 .. \uffff

END_OF_LINE

ASCII(10) ASCII(13)? | ASCII(13) ASCII(10)?

Tokens

Reserved Words

ALIAS AND ARRAY ASSOCIATIVE BEGIN BINDINGS BY BYCOPY BYREF CASE CLASS CONST CONTINUE CRITICAL DEFINITION DIV DO ELSE ELSIF END EXIT FOR FROM IF IMPLEMENTATION IMPORT IN INOUT LOOP METHOD MOD MODULE NOT OF ON OPAQUE OPTIONAL OR OUT POINTER PRIVATE PROCEDURE PROTECTED PROTOCOL PUBLIC RECORD REPEAT RETURN SET SUPER THEN TO TRY TYPE UNTIL VAR VARIADIC WHILE

Reserved Symbols

:= + - * / ++ -- & ~ = # < <= > >= ' " ( ) [ ] { } ^ | . , : ; .. :: !
<* *> // (* *) /* */

Built-in Identifiers

Pervasive Identifiers

NIL TRUE FALSE YES NO BOOLEAN BITSET LONGBITSET CHAR UNICHAR OCTET CARDINAL INTEGER REAL LONGCARD LONGINT LONGREAL OBJECT NEW DISPOSE READ WRITE WRITEF ABS NEG ODD ORD CHR PRED SUCC COUNT LENGTH HIGH NEXTV SIZE TMIN TMAX TSIZE MIN MAX VAL

Pragma Identifiers

IF ELSIF ELSE ENDIF INFO WARN ERROR FATAL ALIGN FOREIGN MAKE INLINE NOINLINE VOLATILE FRAMEWORK IBACTION IBOUTLET QUALIFIED

The Modula-2 Webring


Web sites and web pages related to the Modula-2 programming language.

List all sites | Previous site | Next site | Random site | Join this webring