compiler/Dart__Parser.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Fri, 11 Jan 2013 13:40:41 +0000
changeset 3 46c322c66a29
parent 2 8fedb5e096fc
child 4 5ef74750c3bc
permissions -rw-r--r--
More work on parser.

"{ Package: 'jv:dart/compiler' }"

"{ NameSpace: Dart }"

PPCompositeParser subclass:#Parser
	instanceVariableNames:'additiveExpression additiveOperator argumentList arguments
		assignableExpression assignableSelector assignmentOperator
		bitwiseAndExpression bitwiseOperator bitwiseOrExpression
		bitwiseXorExpression block catchPart classDefinition
		classMemberDefinition compilationUnit compoundLiteral
		conditionalExpression constInitializedIdentifier
		constInitializedVariableDeclaration
		constantConstructorDeclaration constantExpression
		constructorDeclaration declaration declaredIdentifier defaultCase
		defaultFormalParameter directive equalityExpression
		equalityOperator expression expressionInParentheses
		expressionList factoryConstructorDeclaration factorySpecification
		fieldFormalParameter fieldInitializer finalVarOrType finallyPart
		forInitializerStatement forLoopParts formalParameterList
		functionBody functionBodyOrNative functionDeclaration
		functionExpression functionExpressionBody functionNative
		functionPrefix functionTypeAlias getOrSet identifier
		importReference importReferences incrementOperator
		initializedIdentifier initializedIdentifierList
		initializedVariableDeclaration initializers interfaceDefinition
		interfaceMemberDefinition interfaces isOperator
		iterationStatement label libraryBody libraryDefinition
		libraryImport librarySource libraryUnit listLiteral literal
		logicalAndExpression logicalOrExpression mapLiteral
		mapLiteralEntry methodDeclaration multiplicativeExpression
		multiplicativeOperator namedArgument namedConstructorDeclaration
		namedFormalParameters negateOperator nonLabelledStatement
		normalFormalParameter normalFormalParameterTail postfixExpression
		postfixOperator prefixOperator primary primaryFE primaryNoFE
		qualified redirection relationalExpression relationalOperator
		returnType selectionStatement selector shiftExpression
		shiftOperator simpleFormalParameter sourceUrls
		specialSignatureDefinition statement statements
		staticFinalDeclaration staticFinalDeclarationList
		superCallOrFieldInitializer superclass superinterfaces switchCase
		topLevelDefinition tryStatement type typeArguments typeList
		typeParameter typeParameters unaryExpression
		userDefinableOperator variableDeclaration'
	classVariableNames:'Debugging'
	poolDictionaries:''
	category:'Languages-Dart-Parser'
!

PPParser subclass:#TokenParser
	instanceVariableNames:'tokenType'
	classVariableNames:''
	poolDictionaries:''
	privateIn:Parser
!


!Parser methodsFor:'grammar'!

additiveExpression

        ^ (multiplicativeExpression , ((additiveOperator , multiplicativeExpression) star))
        / ((TokenParser for: #super) , ((additiveOperator , multiplicativeExpression) plus))

    "Modified: / 11-01-2013 / 09:59:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

additiveOperator

	^ ('+' asParser)
	/ ('-' asParser)
	
!

argumentList

	^ (namedArgument , (((',' asParser) , namedArgument) star))
	/ (expressionList , (((',' asParser) , namedArgument) star))
	
!

arguments

	^('(' asParser) , (argumentList optional) , (')' asParser)
!

assignableExpression

        ^ (primary , (((arguments star) , assignableSelector) plus))
        / ((TokenParser for: #super) , assignableSelector)
        / identifier

    "Modified: / 11-01-2013 / 10:00:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

assignableSelector

	^ (('[' asParser) , constantExpression , (']' asParser))
	/ (('.' asParser) , identifier)
	
!

assignmentOperator

	^ ('=' asParser)
	/ ('*=' asParser)
	/ ('/=' asParser)
	/ ('~/=' asParser)
	/ ('%=' asParser)
	/ ('+=' asParser)
	/ ('-=' asParser)
	/ ('<<=' asParser)
	/ (('>' asParser) , ('>' asParser) , ('>' asParser) , ('=' asParser))
	/ (('>' asParser) , ('>' asParser) , ('=' asParser))
	/ ('&=' asParser)
	/ ('^=' asParser)
	/ ('|=' asParser)
	
!

bitwiseAndExpression

        ^ (equalityExpression , ((('&' asParser) , equalityExpression) star))
        / ((TokenParser for: #super) , ((('&' asParser) , equalityExpression) plus))

    "Modified: / 11-01-2013 / 10:00:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

bitwiseOperator

	^ ('&' asParser)
	/ ('^' asParser)
	/ ('|' asParser)
	
!

bitwiseOrExpression

	^ (bitwiseXorExpression , ((('|' asParser) , bitwiseXorExpression) star))
	/ ((TokenParser for:#super) , ((('|' asParser) , bitwiseXorExpression) plus))
	
!

bitwiseXorExpression

	^ (bitwiseAndExpression , ((('^' asParser) , bitwiseAndExpression) star))
	/ ((TokenParser for:#super) , ((('^' asParser) , bitwiseAndExpression) plus))
	
!

block

	^('{' asParser) , statements , ('}' asParser)
!

catchPart

	^(TokenParser for:#catch) , ('(' asParser) , declaredIdentifier , (((',' asParser) , declaredIdentifier) optional) , (')' asParser) , block
!

classDefinition

	^ ((TokenParser for:#class) , identifier , (typeParameters optional) , (superclass optional) , (interfaces optional) , ('{' asParser) , (classMemberDefinition star) , ('}' asParser))
	/ ((TokenParser for:#class) , identifier , (typeParameters optional) , (interfaces optional) , (TokenParser for:#native) , (TokenParser for:#string) , ('{' asParser) , (classMemberDefinition star) , ('}' asParser))
	
!

classMemberDefinition

	^ (declaration , (';' asParser))
	/ (constructorDeclaration , (';' asParser))
	/ (methodDeclaration , functionBodyOrNative)
	/ ((TokenParser for:#const) , factoryConstructorDeclaration , functionNative)
	
!

compilationUnit

        ^( ((TokenParser for: #'#!!') optional) , (directive star) , (topLevelDefinition star) ) end

    "Modified: / 11-01-2013 / 10:02:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

compoundLiteral

	^ listLiteral
	/ mapLiteral
	
!

conditionalExpression

	^logicalOrExpression , ((('?' asParser) , constantExpression , (':' asParser) , constantExpression) optional)
!

constInitializedIdentifier

	^identifier , ((('=' asParser) , constantExpression) optional)
!

constInitializedVariableDeclaration

	^declaredIdentifier , ((('=' asParser) , constantExpression) optional) , (((',' asParser) , constInitializedIdentifier) star)
!

constantConstructorDeclaration

	^(TokenParser for:#const) , qualified , formalParameterList
!

constantExpression

	^ (assignableExpression , assignmentOperator , constantExpression)
	/ conditionalExpression
	
!

constructorDeclaration

	^ (identifier , formalParameterList , ((redirection / initializers ) optional))
	/ (namedConstructorDeclaration , ((redirection / initializers ) optional))
	
!

declaration

	^ (constantConstructorDeclaration , ((redirection / initializers ) optional))
	/ (functionDeclaration , redirection)
	/ (namedConstructorDeclaration , redirection)
	/ ((TokenParser for:#abstract) , specialSignatureDefinition)
	/ ((TokenParser for:#abstract) , functionDeclaration)
	/ ((TokenParser for:#static) , (TokenParser for:#final) , (type optional) , staticFinalDeclarationList)
	/ (((TokenParser for:#static) optional) , constInitializedVariableDeclaration)
	
!

declaredIdentifier

	^ ((TokenParser for:#final) , (type optional) , identifier)
	/ ((TokenParser for:#var) , identifier)
	/ (type , identifier)
	
!

defaultCase

	^(label optional) , (((TokenParser for:#case) , constantExpression , (':' asParser)) star) , (TokenParser for:#default) , (':' asParser) , statements
!

defaultFormalParameter

	^normalFormalParameter , ((('=' asParser) , constantExpression) optional)
!

directive

	^('#' asParser) , identifier , arguments , (';' asParser)
!

equalityExpression

	^ (relationalExpression , ((equalityOperator , relationalExpression) optional))
	/ ((TokenParser for:#super) , equalityOperator , relationalExpression)
	
!

equalityOperator

	^ ('==' asParser)
	/ ('!!=' asParser)
	/ ('===' asParser)
	/ ('!!==' asParser)
	
!

expressionInParentheses

	^('(' asParser) , constantExpression , (')' asParser)
!

expressionList

	^constantExpression , (((',' asParser) , constantExpression) star)
!

factoryConstructorDeclaration

	^(TokenParser for:#factory) , qualified , (typeParameters optional) , ((('.' asParser) , identifier) optional) , formalParameterList
!

factorySpecification

	^(TokenParser for:#factory) , type
!

fieldFormalParameter

	^(finalVarOrType optional) , (TokenParser for:#this) , ('.' asParser) , identifier
!

fieldInitializer

	^(((TokenParser for:#this) , ('.' asParser)) optional) , identifier , ('=' asParser) , conditionalExpression
!

finalVarOrType

	^ ((TokenParser for:#final) , (type optional))
	/ (TokenParser for:#var)
	/ type
	
!

finallyPart

	^(TokenParser for:#finally) , block
!

forInitializerStatement

	^ (initializedVariableDeclaration , (';' asParser))
	/ ((constantExpression optional) , (';' asParser))
	
!

forLoopParts

	^ (forInitializerStatement , (constantExpression optional) , (';' asParser) , (expressionList optional))
	/ (declaredIdentifier , (TokenParser for:#in) , constantExpression)
	/ (identifier , (TokenParser for:#in) , constantExpression)
	
!

formalParameterList

	^ (('(' asParser) , (namedFormalParameters optional) , (')' asParser))
	/ (('(' asParser) , normalFormalParameter , (normalFormalParameterTail optional) , (')' asParser))
	
!

functionBody

	^ (('=>' asParser) , constantExpression , (';' asParser))
	/ block
	
!

functionBodyOrNative

	^ ((TokenParser for:#native) , functionBody)
	/ functionNative
	/ functionBody
	
!

functionDeclaration

	^(returnType optional) , identifier , formalParameterList
!

functionExpression

	^(((returnType optional) , identifier) optional) , formalParameterList , functionExpressionBody
!

functionExpressionBody

	^ (('=>' asParser) , constantExpression)
	/ block
	
!

functionNative

	^(TokenParser for:#native) , ((TokenParser for:#string) optional) , (';' asParser)
!

functionPrefix

	^(returnType optional) , identifier
!

functionTypeAlias

	^(TokenParser for:#typedef) , functionPrefix , (typeParameters optional) , formalParameterList , (';' asParser)
!

getOrSet

	^ (TokenParser for:#get)
	/ (TokenParser for:#set)
	
!

identifier

	^ IDENTIFIER_NO_DOLLAR
	/ (TokenParser for:#identifier)
	/ (TokenParser for:#abstract)
	/ ASSERT
	/ (TokenParser for:#class)
	/ EXTENDS
	/ (TokenParser for:#factory)
	/ (TokenParser for:#get)
	/ (TokenParser for:#implements)
	/ (TokenParser for:#import)
	/ (TokenParser for:#interface)
	/ (TokenParser for:#is)
	/ (TokenParser for:#library)
	/ (TokenParser for:#native)
	/ NEGATE
	/ OPERATOR
	/ (TokenParser for:#set)
	/ (TokenParser for:#source)
	/ (TokenParser for:#static)
	/ (TokenParser for:#typedef)
	
!

importReference

	^(((TokenParser for:#identifier) , (':' asParser)) optional) , (TokenParser for:#string)
!

importReferences

	^importReference , (((',' asParser) , importReference) star) , ((',' asParser) optional)
!

initializedIdentifier

	^identifier , ((('=' asParser) , constantExpression) optional)
!

initializedIdentifierList

	^initializedIdentifier , (((',' asParser) , initializedIdentifier) star)
!

initializedVariableDeclaration

	^declaredIdentifier , ((('=' asParser) , constantExpression) optional) , (((',' asParser) , initializedIdentifier) star)
!

initializers

	^(':' asParser) , superCallOrFieldInitializer , (((',' asParser) , superCallOrFieldInitializer) star)
!

interfaceDefinition

	^(TokenParser for:#interface) , identifier , (typeParameters optional) , (superinterfaces optional) , (factorySpecification optional) , ('{' asParser) , (interfaceMemberDefinition star) , ('}' asParser)
!

interfaceMemberDefinition

	^ ((TokenParser for:#static) , (TokenParser for:#final) , (type optional) , initializedIdentifierList , (';' asParser))
	/ (functionDeclaration , (';' asParser))
	/ (constantConstructorDeclaration , (';' asParser))
	/ (namedConstructorDeclaration , (';' asParser))
	/ (specialSignatureDefinition , (';' asParser))
	/ (variableDeclaration , (';' asParser))
	
!

interfaces

	^(TokenParser for:#implements) , typeList
!

isOperator

	^(TokenParser for:#is) , (('!!' asParser) optional)
!

iterationStatement

	^ ((TokenParser for:#while) , ('(' asParser) , constantExpression , (')' asParser) , statement)
	/ ((TokenParser for:#do) , statement , (TokenParser for:#while) , ('(' asParser) , constantExpression , (')' asParser) , (';' asParser))
	/ ((TokenParser for:#for) , ('(' asParser) , forLoopParts , (')' asParser) , statement)
	
!

label

	^identifier , (':' asParser)
!

libraryBody

	^(libraryImport optional) , (librarySource optional)
!

libraryDefinition

	^(TokenParser for:#library) , ('{' asParser) , libraryBody , ('}' asParser)
!

libraryImport

	^(TokenParser for:#import) , ('=' asParser) , ('[' asParser) , (importReferences optional) , (']' asParser)
!

librarySource

	^(TokenParser for:#source) , ('=' asParser) , ('[' asParser) , (sourceUrls optional) , (']' asParser)
!

libraryUnit

        ^libraryDefinition end

    "Modified: / 11-01-2013 / 10:07:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

listLiteral

	^('[' asParser) , ((expressionList , ((',' asParser) optional)) optional) , (']' asParser)
!

literal

        ^ (TokenParser for: #null)
        / (TokenParser for: #true)
        / (TokenParser for: #false)
        / (TokenParser for: #number)
        / (TokenParser for:#string)

    "Modified: / 11-01-2013 / 10:08:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

logicalAndExpression

	^bitwiseOrExpression , ((('&&' asParser) , bitwiseOrExpression) star)
!

logicalOrExpression

	^logicalAndExpression , ((('||' asParser) , logicalAndExpression) star)
!

mapLiteral

	^('{' asParser) , ((mapLiteralEntry , (((',' asParser) , mapLiteralEntry) star) , ((',' asParser) optional)) optional) , ('}' asParser)
!

mapLiteralEntry

	^(TokenParser for:#string) , (':' asParser) , constantExpression
!

methodDeclaration

	^ factoryConstructorDeclaration
	/ ((TokenParser for:#static) , functionDeclaration)
	/ specialSignatureDefinition
	/ (functionDeclaration , (initializers optional))
	/ (namedConstructorDeclaration , (initializers optional))
	
!

multiplicativeExpression

	^ (unaryExpression , ((multiplicativeOperator , unaryExpression) star))
	/ ((TokenParser for:#super) , ((multiplicativeOperator , unaryExpression) plus))
	
!

multiplicativeOperator

	^ ('*' asParser)
	/ ('/' asParser)
	/ ('%' asParser)
	/ ('~/' asParser)
	
!

namedArgument

	^label , constantExpression
!

namedConstructorDeclaration

	^identifier , ('.' asParser) , identifier , formalParameterList
!

namedFormalParameters

	^('[' asParser) , defaultFormalParameter , (((',' asParser) , defaultFormalParameter) star) , (']' asParser)
!

negateOperator

	^ ('!!' asParser)
	/ ('~' asParser)
	
!

nonLabelledStatement

        ^ block
        / (initializedVariableDeclaration , (';' asParser))
        / iterationStatement
        / selectionStatement
        / tryStatement
        / ((TokenParser for: #break) , (identifier optional) , (';' asParser))
        / ((TokenParser for: #continue) , (identifier optional) , (';' asParser))
        / ((TokenParser for: #return) , (constantExpression optional) , (';' asParser))
        / ((TokenParser for: #throw) , (constantExpression optional) , (';' asParser))
        / ((constantExpression optional) , (';' asParser))
        / ((TokenParser for: #assert) , ('(' asParser) , conditionalExpression , (')' asParser) , (';' asParser))
        / (functionDeclaration , functionBody)

    "Modified: / 11-01-2013 / 10:09:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

normalFormalParameter

	^ functionDeclaration
	/ fieldFormalParameter
	/ simpleFormalParameter
	
!

normalFormalParameterTail

	^ ((',' asParser) , namedFormalParameters)
	/ ((',' asParser) , normalFormalParameter , (normalFormalParameterTail optional))
	
!

postfixExpression

	^ (assignableExpression , postfixOperator)
	/ (primary , (selector star))
	
!

postfixOperator

	^ ('++' asParser)
	/ ('--' asParser)
	
!

prefixOperator

	^ additiveOperator
	/ negateOperator
	
!

primary

	^ primaryNoFE
	/ primaryFE
	
!

primaryFE

	^ functionExpression
	/ primaryNoFE
	
!

primaryNoFE

        ^ (TokenParser for:#this)
        / ((TokenParser for:#super) , assignableSelector)
        / literal
        / identifier
        / (((TokenParser for:#const) optional) , (typeArguments optional) , compoundLiteral)
        / (((TokenParser for: #new) / (TokenParser for:#const) ) , type , ((('.' asParser) , identifier) optional) , arguments)
        / expressionInParentheses

    "Modified: / 11-01-2013 / 10:09:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

qualified

	^identifier , ((('.' asParser) , identifier) optional)
!

redirection

	^(':' asParser) , (TokenParser for:#this) , ((('.' asParser) , identifier) optional) , arguments
!

relationalExpression

	^ (shiftExpression , (((isOperator , type) / (relationalOperator , shiftExpression) ) optional))
	/ ((TokenParser for:#super) , relationalOperator , shiftExpression)
	
!

relationalOperator

	^ (('>' asParser) , ('=' asParser))
	/ ('>' asParser)
	/ ('<=' asParser)
	/ ('<' asParser)
	
!

returnType

        ^ (TokenParser for: #void)
        / type

    "Modified: / 11-01-2013 / 10:09:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

selectionStatement

        ^ ((TokenParser for: #if) , ('(' asParser) , constantExpression , (')' asParser) , statement , (((TokenParser for: #else) , statement) optional))
        / ((TokenParser for: #switch) , ('(' asParser) , constantExpression , (')' asParser) , ('{' asParser) , (switchCase star) , (defaultCase optional) , ('}' asParser))

    "Modified: / 11-01-2013 / 10:10:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

selector

	^ assignableSelector
	/ arguments
	
!

shiftExpression

	^ (additiveExpression , ((shiftOperator , additiveExpression) star))
	/ ((TokenParser for:#super) , ((shiftOperator , additiveExpression) plus))
	
!

shiftOperator

	^ ('<<' asParser)
	/ (('>' asParser) , ('>' asParser) , ('>' asParser))
	/ (('>' asParser) , ('>' asParser))
	
!

simpleFormalParameter

	^ declaredIdentifier
	/ identifier
	
!

sourceUrls

	^(TokenParser for:#string) , (((',' asParser) , (TokenParser for:#string)) star) , ((',' asParser) optional)
!

specialSignatureDefinition

        ^ (((TokenParser for:#static) optional) , (returnType optional) , getOrSet , identifier , formalParameterList)
        / ((returnType optional) , (TokenParser for: #operator) , userDefinableOperator , formalParameterList)

    "Modified: / 11-01-2013 / 10:10:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

statement

	^(label star) , nonLabelledStatement
!

statements

	^statement star
!

staticFinalDeclaration

	^identifier , ('=' asParser) , constantExpression
!

staticFinalDeclarationList

	^staticFinalDeclaration , (((',' asParser) , staticFinalDeclaration) star)
!

superCallOrFieldInitializer

	^ ((TokenParser for:#super) , arguments)
	/ ((TokenParser for:#super) , ('.' asParser) , identifier , arguments)
	/ fieldInitializer
	
!

superclass

        ^(TokenParser for: #extends) , type

    "Modified: / 11-01-2013 / 10:10:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

superinterfaces

        ^(TokenParser for: #extends) , typeList

    "Modified: / 11-01-2013 / 10:10:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

switchCase

	^(label optional) , (((TokenParser for:#case) , constantExpression , (':' asParser)) plus) , statements
!

topLevelDefinition

	^ classDefinition
	/ interfaceDefinition
	/ functionTypeAlias
	/ (functionDeclaration , functionBodyOrNative)
	/ ((returnType optional) , getOrSet , identifier , formalParameterList , functionBodyOrNative)
	/ ((TokenParser for:#final) , (type optional) , staticFinalDeclarationList , (';' asParser))
	/ (constInitializedVariableDeclaration , (';' asParser))
	
!

tryStatement

        ^(TokenParser for: #try) , block , (((catchPart plus) , (finallyPart optional)) / finallyPart )

    "Modified: / 11-01-2013 / 10:10:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

type

	^qualified , (typeArguments optional)
!

typeArguments

	^('<' asParser) , typeList , ('>' asParser)
!

typeList

	^type , (((',' asParser) , type) star)
!

typeParameter

        ^identifier , (((TokenParser for: #extends) , type) optional)

    "Modified: / 11-01-2013 / 10:11:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

typeParameters

	^('<' asParser) , typeParameter , (((',' asParser) , typeParameter) star) , ('>' asParser)
!

unaryExpression

	^ postfixExpression
	/ (prefixOperator , unaryExpression)
	/ (negateOperator , (TokenParser for:#super))
	/ (('-' asParser) , (TokenParser for:#super))
	/ (postfixOperator , assignableExpression)
	
!

userDefinableOperator

        ^ multiplicativeOperator
        / additiveOperator
        / shiftOperator
        / relationalOperator
        / bitwiseOperator
        / ('==' asParser)
        / ('~' asParser)
        / (TokenParser for: #negate)
        / (('[' asParser) , (']' asParser))
        / (('[' asParser) , (']' asParser) , ('=' asParser))

    "Modified: / 11-01-2013 / 10:11:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

variableDeclaration

	^declaredIdentifier , (((',' asParser) , identifier) star)
! !

!Parser class methodsFor:'initialization'!

debugging: aBoolean
    Debugging := aBoolean

    "
        JavaParser debugging: true.
        JavaParser debugging: false.
    "

    "Created: / 11-01-2013 / 11:32:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

initialize
    "Invoked at system start or when the class is dynamically loaded."

    "/ please change as required (and remove this comment)

    Debugging := false.

    "Modified: / 11-01-2013 / 11:32:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!Parser methodsFor:'accessing'!

start
    ^compilationUnit , (TokenParser for: #EOF).

    "Created: / 11-01-2013 / 13:19:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!Parser methodsFor:'grammar'!

additiveExpression

        ^ (multiplicativeExpression , ((additiveOperator , multiplicativeExpression) star))
        / ((TokenParser for: #super) , ((additiveOperator , multiplicativeExpression) plus))

    "Modified: / 11-01-2013 / 09:59:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

additiveOperator

	^ ('+' asParser)
	/ ('-' asParser)
	
!

argumentList

	^ (namedArgument , (((',' asParser) , namedArgument) star))
	/ (expressionList , (((',' asParser) , namedArgument) star))
	
!

arguments

	^('(' asParser) , (argumentList optional) , (')' asParser)
!

assignableExpression

        ^ (primary , (((arguments star) , assignableSelector) plus))
        / ((TokenParser for: #super) , assignableSelector)
        / identifier

    "Modified: / 11-01-2013 / 10:00:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

assignableSelector

	^ (('[' asParser) , constantExpression , (']' asParser))
	/ (('.' asParser) , identifier)
	
!

assignmentOperator

	^ ('=' asParser)
	/ ('*=' asParser)
	/ ('/=' asParser)
	/ ('~/=' asParser)
	/ ('%=' asParser)
	/ ('+=' asParser)
	/ ('-=' asParser)
	/ ('<<=' asParser)
	/ (('>' asParser) , ('>' asParser) , ('>' asParser) , ('=' asParser))
	/ (('>' asParser) , ('>' asParser) , ('=' asParser))
	/ ('&=' asParser)
	/ ('^=' asParser)
	/ ('|=' asParser)
	
!

bitwiseAndExpression

        ^ (equalityExpression , ((('&' asParser) , equalityExpression) star))
        / ((TokenParser for: #super) , ((('&' asParser) , equalityExpression) plus))

    "Modified: / 11-01-2013 / 10:00:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

bitwiseOperator

	^ ('&' asParser)
	/ ('^' asParser)
	/ ('|' asParser)
	
!

bitwiseOrExpression

	^ (bitwiseXorExpression , ((('|' asParser) , bitwiseXorExpression) star))
	/ ((TokenParser for:#super) , ((('|' asParser) , bitwiseXorExpression) plus))
	
!

bitwiseXorExpression

	^ (bitwiseAndExpression , ((('^' asParser) , bitwiseAndExpression) star))
	/ ((TokenParser for:#super) , ((('^' asParser) , bitwiseAndExpression) plus))
	
!

block

	^('{' asParser) , statements , ('}' asParser)
!

catchPart

	^(TokenParser for:#catch) , ('(' asParser) , declaredIdentifier , (((',' asParser) , declaredIdentifier) optional) , (')' asParser) , block
!

classDefinition

	^ ((TokenParser for:#class) , identifier , (typeParameters optional) , (superclass optional) , (interfaces optional) , ('{' asParser) , (classMemberDefinition star) , ('}' asParser))
	/ ((TokenParser for:#class) , identifier , (typeParameters optional) , (interfaces optional) , (TokenParser for:#native) , (TokenParser for:#string) , ('{' asParser) , (classMemberDefinition star) , ('}' asParser))
	
!

classMemberDefinition

	^ (declaration , (';' asParser))
	/ (constructorDeclaration , (';' asParser))
	/ (methodDeclaration , functionBodyOrNative)
	/ ((TokenParser for:#const) , factoryConstructorDeclaration , functionNative)
	
!

compilationUnit

        ^( ((TokenParser for: #'#!!') optional) , (directive star) , (topLevelDefinition star) )

    "Modified: / 11-01-2013 / 13:18:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

compoundLiteral

	^ listLiteral
	/ mapLiteral
	
!

conditionalExpression

	^logicalOrExpression , ((('?' asParser) , constantExpression , (':' asParser) , constantExpression) optional)
!

constInitializedIdentifier

	^identifier , ((('=' asParser) , constantExpression) optional)
!

constInitializedVariableDeclaration

	^declaredIdentifier , ((('=' asParser) , constantExpression) optional) , (((',' asParser) , constInitializedIdentifier) star)
!

constantConstructorDeclaration

	^(TokenParser for:#const) , qualified , formalParameterList
!

constantExpression

	^ (assignableExpression , assignmentOperator , constantExpression)
	/ conditionalExpression
	
!

constructorDeclaration

	^ (identifier , formalParameterList , ((redirection / initializers ) optional))
	/ (namedConstructorDeclaration , ((redirection / initializers ) optional))
	
!

declaration

	^ (constantConstructorDeclaration , ((redirection / initializers ) optional))
	/ (functionDeclaration , redirection)
	/ (namedConstructorDeclaration , redirection)
	/ ((TokenParser for:#abstract) , specialSignatureDefinition)
	/ ((TokenParser for:#abstract) , functionDeclaration)
	/ ((TokenParser for:#static) , (TokenParser for:#final) , (type optional) , staticFinalDeclarationList)
	/ (((TokenParser for:#static) optional) , constInitializedVariableDeclaration)
	
!

declaredIdentifier

	^ ((TokenParser for:#final) , (type optional) , identifier)
	/ ((TokenParser for:#var) , identifier)
	/ (type , identifier)
	
!

defaultCase

	^(label optional) , (((TokenParser for:#case) , constantExpression , (':' asParser)) star) , (TokenParser for:#default) , (':' asParser) , statements
!

defaultFormalParameter

	^normalFormalParameter , ((('=' asParser) , constantExpression) optional)
!

directive

	^('#' asParser) , identifier , arguments , (';' asParser)
!

equalityExpression

	^ (relationalExpression , ((equalityOperator , relationalExpression) optional))
	/ ((TokenParser for:#super) , equalityOperator , relationalExpression)
	
!

equalityOperator

	^ ('==' asParser)
	/ ('!!=' asParser)
	/ ('===' asParser)
	/ ('!!==' asParser)
	
!

expression

        ^ (assignableExpression , assignmentOperator , expression)
        / conditionalExpression

    "Created: / 11-01-2013 / 13:22:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

expressionInParentheses

	^('(' asParser) , constantExpression , (')' asParser)
!

expressionList

	^constantExpression , (((',' asParser) , constantExpression) star)
!

factoryConstructorDeclaration

	^(TokenParser for:#factory) , qualified , (typeParameters optional) , ((('.' asParser) , identifier) optional) , formalParameterList
!

factorySpecification

	^(TokenParser for:#factory) , type
!

fieldFormalParameter

	^(finalVarOrType optional) , (TokenParser for:#this) , ('.' asParser) , identifier
!

fieldInitializer

	^(((TokenParser for:#this) , ('.' asParser)) optional) , identifier , ('=' asParser) , conditionalExpression
!

finalVarOrType

	^ ((TokenParser for:#final) , (type optional))
	/ (TokenParser for:#var)
	/ type
	
!

finallyPart

	^(TokenParser for:#finally) , block
!

forInitializerStatement

	^ (initializedVariableDeclaration , (';' asParser))
	/ ((constantExpression optional) , (';' asParser))
	
!

forLoopParts

	^ (forInitializerStatement , (constantExpression optional) , (';' asParser) , (expressionList optional))
	/ (declaredIdentifier , (TokenParser for:#in) , constantExpression)
	/ (identifier , (TokenParser for:#in) , constantExpression)
	
!

formalParameterList

	^ (('(' asParser) , (namedFormalParameters optional) , (')' asParser))
	/ (('(' asParser) , normalFormalParameter , (normalFormalParameterTail optional) , (')' asParser))
	
!

functionBody

	^ (('=>' asParser) , constantExpression , (';' asParser))
	/ block
	
!

functionBodyOrNative

	^ ((TokenParser for:#native) , functionBody)
	/ functionNative
	/ functionBody
	
!

functionDeclaration

	^(returnType optional) , identifier , formalParameterList
!

functionExpression

	^(((returnType optional) , identifier) optional) , formalParameterList , functionExpressionBody
!

functionExpressionBody

	^ (('=>' asParser) , constantExpression)
	/ block
	
!

functionNative

	^(TokenParser for:#native) , ((TokenParser for:#string) optional) , (';' asParser)
!

functionPrefix

	^(returnType optional) , identifier
!

functionTypeAlias

	^(TokenParser for:#typedef) , functionPrefix , (typeParameters optional) , formalParameterList , (';' asParser)
!

getOrSet

	^ (TokenParser for:#get)
	/ (TokenParser for:#set)
	
!

identifier

        ^ (TokenParser for:#identifier_no_dollar)
        / (TokenParser for:#identifier)
        / (TokenParser for:#abstract)
        / (TokenParser for:#assert)
        / (TokenParser for:#class)
        / (TokenParser for:#extends)
        / (TokenParser for:#factory)
        / (TokenParser for:#get)
        / (TokenParser for:#implements)
        / (TokenParser for:#import)
        / (TokenParser for:#interface)
        / (TokenParser for:#is)
        / (TokenParser for:#library)
        / (TokenParser for:#native)
        / (TokenParser for:#negate)
        / (TokenParser for:#operator)
        / (TokenParser for:#set)
        / (TokenParser for:#source)
        / (TokenParser for:#static)
        / (TokenParser for:#typedef)

    "Modified: / 11-01-2013 / 13:25:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

importReference

	^(((TokenParser for:#identifier) , (':' asParser)) optional) , (TokenParser for:#string)
!

importReferences

	^importReference , (((',' asParser) , importReference) star) , ((',' asParser) optional)
!

incrementOperator

        ^ ('++' asParser)
        / ('--' asParser)

    "Created: / 11-01-2013 / 13:27:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

initializedIdentifier

	^identifier , ((('=' asParser) , constantExpression) optional)
!

initializedIdentifierList

	^initializedIdentifier , (((',' asParser) , initializedIdentifier) star)
!

initializedVariableDeclaration

	^declaredIdentifier , ((('=' asParser) , constantExpression) optional) , (((',' asParser) , initializedIdentifier) star)
!

initializers

	^(':' asParser) , superCallOrFieldInitializer , (((',' asParser) , superCallOrFieldInitializer) star)
!

interfaceDefinition

	^(TokenParser for:#interface) , identifier , (typeParameters optional) , (superinterfaces optional) , (factorySpecification optional) , ('{' asParser) , (interfaceMemberDefinition star) , ('}' asParser)
!

interfaceMemberDefinition

	^ ((TokenParser for:#static) , (TokenParser for:#final) , (type optional) , initializedIdentifierList , (';' asParser))
	/ (functionDeclaration , (';' asParser))
	/ (constantConstructorDeclaration , (';' asParser))
	/ (namedConstructorDeclaration , (';' asParser))
	/ (specialSignatureDefinition , (';' asParser))
	/ (variableDeclaration , (';' asParser))
	
!

interfaces

	^(TokenParser for:#implements) , typeList
!

isOperator

	^(TokenParser for:#is) , (('!!' asParser) optional)
!

iterationStatement

	^ ((TokenParser for:#while) , ('(' asParser) , constantExpression , (')' asParser) , statement)
	/ ((TokenParser for:#do) , statement , (TokenParser for:#while) , ('(' asParser) , constantExpression , (')' asParser) , (';' asParser))
	/ ((TokenParser for:#for) , ('(' asParser) , forLoopParts , (')' asParser) , statement)
	
!

label

	^identifier , (':' asParser)
!

libraryBody

	^(libraryImport optional) , (librarySource optional)
!

libraryDefinition

	^(TokenParser for:#library) , ('{' asParser) , libraryBody , ('}' asParser)
!

libraryImport

	^(TokenParser for:#import) , ('=' asParser) , ('[' asParser) , (importReferences optional) , (']' asParser)
!

librarySource

	^(TokenParser for:#source) , ('=' asParser) , ('[' asParser) , (sourceUrls optional) , (']' asParser)
!

libraryUnit

        ^libraryDefinition end

    "Modified: / 11-01-2013 / 10:07:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

listLiteral

	^('[' asParser) , ((expressionList , ((',' asParser) optional)) optional) , (']' asParser)
!

literal

        ^ (TokenParser for: #null)
        / (TokenParser for: #true)
        / (TokenParser for: #false)
        / (TokenParser for: #number)
        / (TokenParser for:#string)

    "Modified: / 11-01-2013 / 10:08:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

logicalAndExpression

	^bitwiseOrExpression , ((('&&' asParser) , bitwiseOrExpression) star)
!

logicalOrExpression

	^logicalAndExpression , ((('||' asParser) , logicalAndExpression) star)
!

mapLiteral

	^('{' asParser) , ((mapLiteralEntry , (((',' asParser) , mapLiteralEntry) star) , ((',' asParser) optional)) optional) , ('}' asParser)
!

mapLiteralEntry

	^(TokenParser for:#string) , (':' asParser) , constantExpression
!

methodDeclaration

	^ factoryConstructorDeclaration
	/ ((TokenParser for:#static) , functionDeclaration)
	/ specialSignatureDefinition
	/ (functionDeclaration , (initializers optional))
	/ (namedConstructorDeclaration , (initializers optional))
	
!

multiplicativeExpression

	^ (unaryExpression , ((multiplicativeOperator , unaryExpression) star))
	/ ((TokenParser for:#super) , ((multiplicativeOperator , unaryExpression) plus))
	
!

multiplicativeOperator

	^ ('*' asParser)
	/ ('/' asParser)
	/ ('%' asParser)
	/ ('~/' asParser)
	
!

namedArgument

	^label , constantExpression
!

namedConstructorDeclaration

	^identifier , ('.' asParser) , identifier , formalParameterList
!

namedFormalParameters

	^('[' asParser) , defaultFormalParameter , (((',' asParser) , defaultFormalParameter) star) , (']' asParser)
!

negateOperator

	^ ('!!' asParser)
	/ ('~' asParser)
	
!

nonLabelledStatement

        ^ block
        / (initializedVariableDeclaration , (';' asParser))
        / iterationStatement
        / selectionStatement
        / tryStatement
        / ((TokenParser for: #break) , (identifier optional) , (';' asParser))
        / ((TokenParser for: #continue) , (identifier optional) , (';' asParser))
        / ((TokenParser for: #return) , (constantExpression optional) , (';' asParser))
        / ((TokenParser for: #throw) , (constantExpression optional) , (';' asParser))
        / ((constantExpression optional) , (';' asParser))
        / ((TokenParser for: #assert) , ('(' asParser) , conditionalExpression , (')' asParser) , (';' asParser))
        / (functionDeclaration , functionBody)

    "Modified: / 11-01-2013 / 10:09:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

normalFormalParameter

	^ functionDeclaration
	/ fieldFormalParameter
	/ simpleFormalParameter
	
!

normalFormalParameterTail

	^ ((',' asParser) , namedFormalParameters)
	/ ((',' asParser) , normalFormalParameter , (normalFormalParameterTail optional))
	
!

postfixExpression

	^ (assignableExpression , postfixOperator)
	/ (primary , (selector star))
	
!

postfixOperator

	^ ('++' asParser)
	/ ('--' asParser)
	
!

prefixOperator

	^ additiveOperator
	/ negateOperator
	
!

primary

	^ primaryNoFE
	/ primaryFE
	
!

primaryFE

	^ functionExpression
	/ primaryNoFE
	
!

primaryNoFE

        ^ (TokenParser for:#this)
        / ((TokenParser for:#super) , assignableSelector)
        / literal
        / identifier
        / (((TokenParser for:#const) optional) , (typeArguments optional) , compoundLiteral)
        / (((TokenParser for: #new) / (TokenParser for:#const) ) , type , ((('.' asParser) , identifier) optional) , arguments)
        / expressionInParentheses

    "Modified: / 11-01-2013 / 10:09:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

qualified

	^identifier , ((('.' asParser) , identifier) optional)
!

redirection

	^(':' asParser) , (TokenParser for:#this) , ((('.' asParser) , identifier) optional) , arguments
!

relationalExpression

	^ (shiftExpression , (((isOperator , type) / (relationalOperator , shiftExpression) ) optional))
	/ ((TokenParser for:#super) , relationalOperator , shiftExpression)
	
!

relationalOperator

	^ (('>' asParser) , ('=' asParser))
	/ ('>' asParser)
	/ ('<=' asParser)
	/ ('<' asParser)
	
!

returnType

        ^ (TokenParser for: #void)
        / type

    "Modified: / 11-01-2013 / 10:09:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

selectionStatement

        ^ ((TokenParser for: #if) , ('(' asParser) , constantExpression , (')' asParser) , statement , (((TokenParser for: #else) , statement) optional))
        / ((TokenParser for: #switch) , ('(' asParser) , constantExpression , (')' asParser) , ('{' asParser) , (switchCase star) , (defaultCase optional) , ('}' asParser))

    "Modified: / 11-01-2013 / 10:10:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

selector

	^ assignableSelector
	/ arguments
	
!

shiftExpression

	^ (additiveExpression , ((shiftOperator , additiveExpression) star))
	/ ((TokenParser for:#super) , ((shiftOperator , additiveExpression) plus))
	
!

shiftOperator

	^ ('<<' asParser)
	/ (('>' asParser) , ('>' asParser) , ('>' asParser))
	/ (('>' asParser) , ('>' asParser))
	
!

simpleFormalParameter

	^ declaredIdentifier
	/ identifier
	
!

sourceUrls

	^(TokenParser for:#string) , (((',' asParser) , (TokenParser for:#string)) star) , ((',' asParser) optional)
!

specialSignatureDefinition

        ^ (((TokenParser for:#static) optional) , (returnType optional) , getOrSet , identifier , formalParameterList)
        / ((returnType optional) , (TokenParser for: #operator) , userDefinableOperator , formalParameterList)

    "Modified: / 11-01-2013 / 10:10:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

statement

	^(label star) , nonLabelledStatement
!

statements

	^statement star
!

staticFinalDeclaration

	^identifier , ('=' asParser) , constantExpression
!

staticFinalDeclarationList

	^staticFinalDeclaration , (((',' asParser) , staticFinalDeclaration) star)
!

superCallOrFieldInitializer

	^ ((TokenParser for:#super) , arguments)
	/ ((TokenParser for:#super) , ('.' asParser) , identifier , arguments)
	/ fieldInitializer
	
!

superclass

        ^(TokenParser for: #extends) , type

    "Modified: / 11-01-2013 / 10:10:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

superinterfaces

        ^(TokenParser for: #extends) , typeList

    "Modified: / 11-01-2013 / 10:10:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

switchCase

	^(label optional) , (((TokenParser for:#case) , constantExpression , (':' asParser)) plus) , statements
!

topLevelDefinition

	^ classDefinition
	/ interfaceDefinition
	/ functionTypeAlias
	/ (functionDeclaration , functionBodyOrNative)
	/ ((returnType optional) , getOrSet , identifier , formalParameterList , functionBodyOrNative)
	/ ((TokenParser for:#final) , (type optional) , staticFinalDeclarationList , (';' asParser))
	/ (constInitializedVariableDeclaration , (';' asParser))
	
!

tryStatement

        ^(TokenParser for: #try) , block , (((catchPart plus) , (finallyPart optional)) / finallyPart )

    "Modified: / 11-01-2013 / 10:10:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

type

	^qualified , (typeArguments optional)
!

typeArguments

	^('<' asParser) , typeList , ('>' asParser)
!

typeList

	^type , (((',' asParser) , type) star)
!

typeParameter

        ^identifier , (((TokenParser for: #extends) , type) optional)

    "Modified: / 11-01-2013 / 10:11:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

typeParameters

	^('<' asParser) , typeParameter , (((',' asParser) , typeParameter) star) , ('>' asParser)
!

unaryExpression

	^ postfixExpression
	/ (prefixOperator , unaryExpression)
	/ (negateOperator , (TokenParser for:#super))
	/ (('-' asParser) , (TokenParser for:#super))
	/ (postfixOperator , assignableExpression)
	
!

userDefinableOperator

        ^ multiplicativeOperator
        / additiveOperator
        / shiftOperator
        / relationalOperator
        / bitwiseOperator
        / ('==' asParser)
        / ('~' asParser)
        / (TokenParser for: #negate)
        / (('[' asParser) , (']' asParser))
        / (('[' asParser) , (']' asParser) , ('=' asParser))

    "Modified: / 11-01-2013 / 10:11:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

variableDeclaration

	^declaredIdentifier , (((',' asParser) , identifier) star)
! !

!Parser methodsFor:'initialization'!

initializeStartingAt: aSymbol
        | allVariableNames ignoredVariableNames productionIndexesAndNames debugger |
        self initialize.        

        Debugging ifTrue:[
            PPDebugger notNil ifTrue:[
                self assert: (Smalltalk loadPackage: 'stx:goodies/petitparser/devtools').
                debugger := PPDebugger new
            ].
        ].
        "find all the productions that need to be initialized"
        allVariableNames := self class allInstVarNames
                collect: [ :each | each asSymbol ].
        ignoredVariableNames := self class ignoredNames
                collect: [ :each | each asSymbol ].
        productionIndexesAndNames := ((1 to: self class instSize)
                collect: [ :index | index -> (allVariableNames at: index) ])
                reject: [ :assoc | ignoredVariableNames includes: assoc value ].

        "initialize productions with an undefined parser to be replaced later"
        parser := PPUnresolvedParser named: aSymbol.
        productionIndexesAndNames do: [ :assoc |
                self instVarAt: assoc key put: (PPUnresolvedParser named: assoc value) ].
        parser def: (self perform: aSymbol).

        "resolve unresolved parsers with their actual implementation"
        productionIndexesAndNames do: [ :assoc |
                (self respondsTo: assoc value)
                        ifFalse: [ self error: 'Unable to initialize ' , assoc value printString ]
                        ifTrue: [ 
                            | production |
                            production := ((self perform: assoc value)  name: assoc value; yourself).
                            Debugging ifTrue:[
                                production := PPDebuggingParser parser: production  debugger: debugger
                            ].

                            (self instVarAt: assoc key) def: production.

                                ] ]

    "Created: / 12-03-2012 / 16:51:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 11-01-2013 / 11:35:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!Parser::TokenParser class methodsFor:'instance creation'!

for: tokenType

    ^self new tokenType: tokenType

    "Created: / 14-03-2012 / 23:10:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!Parser::TokenParser methodsFor:'accessing'!

tokenType
    ^ tokenType
!

tokenType:aSymbol
    tokenType := aSymbol.
! !

!Parser::TokenParser methodsFor:'parsing'!

parseOn:aJavaScanner
    "Parse aStream with the receiving parser and answer the parse-result or an instance of PPFailure. 
    Override this method in subclasses to specify custom parse behavior. Do not call this method from outside, 
    instead use #parse:."

    | pos |

    pos := aJavaScanner position.

    ^(aJavaScanner nextToken = tokenType) ifTrue:[
        aJavaScanner token
    ] ifFalse:[
        aJavaScanner position: pos.
        PPFailure message: (tokenType printString , ' token expected (got ', aJavaScanner tokenType , ' {',(aJavaScanner tokenValue ? '<nil>') printString,'})') at: aJavaScanner position
    ]

    "Modified: / 17-03-2012 / 13:34:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!Parser class methodsFor:'documentation'!

version_HG

    ^ '$Changeset: <not expanded> $'
! !

Parser initialize!