tools/JavaParserI.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Sun, 04 Aug 2013 01:46:45 +0100
branchdevelopment
changeset 2641 79395ea8b58f
parent 2501 53d731454d43
child 2672 5e4a61287345
child 2879 5abbda3a589b
permissions -rw-r--r--
Initial support for block and incremental highlighting... ...although very naive now. Block and increments are highligter only on on lexical basis, i.e., no full parsing is done. Therefore method calls, fields and classes are not recognized...

"{ Package: 'stx:libjava/tools' }"

PPCompositeParser subclass:#JavaParserI
	instanceVariableNames:'unicodeEscape rawInputCharacter unicodeMarker hexDigit
		lineTerminator unicodeInputCharacter inputElements sub
		inputElement whiteSpace comment javaToken keyword literal
		separator operator identifier traditionalComment endOfLineComment
		commentTail charactersInLine commentTailStar notStar
		notStarNotSlash inputCharacter booleanLiteral nullLiteral
		keywords floatingPointLiteral integerLiteral characterLiteral
		stringLiteral input operators separators block'
	classVariableNames:'Debugging'
	poolDictionaries:''
	category:'Languages-Java-Parser'
!

PPParser subclass:#BlockParser
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:JavaParserI
!

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

!JavaParserI class methodsFor:'documentation'!

documentation
"
    Part of petit parser for Java. Contains only lexical structure.
    Usefull only for inheriting and extending

    [author:]
        Jan Vrany <jan.vrany@fit.cvut.cz>

    [instance variables:]

    [class variables:]

    [see also:]

"
! !

!JavaParserI 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>"
! !

!JavaParserI class methodsFor:'instance creation'!

new
    "return an initialized instance"

    ^ self basicNew initializeStartingAt: #start.

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

!JavaParserI class methodsFor:'accessing'!

ignoredNames
	"Answer a collection of instance-variables that should not be automatically initialized with productions, but that are used internal to the composite parser."

	| newArray |	
	newArray := Array new: ((self namesToIgnore size) + (super ignoredNames size)).
	newArray
		replaceFrom: 1
		to: self namesToIgnore size
		with: self namesToIgnore.
	newArray
		replaceFrom: (self namesToIgnore size + 1)
		to: newArray size
		with: super ignoredNames.	
	^newArray
!

namesToIgnore

	^#('keywords' 'operators' 'separators')
! !

!JavaParserI methodsFor:'accessing'!

builder

    ^nil

    "Created: / 10-03-2012 / 12:17:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

start
	"Default start production."

	^ input end
! !

!JavaParserI methodsFor:'grammar-blocks'!

block
    "Do no parse content of the block"

    ^BlockParser new    

"/    ^ (self tokenFor: '{') , (self tokenFor: '}')

    "Created: / 11-03-2012 / 13:20:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaParserI methodsFor:'grammar-comments'!

charactersInLine   

	^ inputCharacter plus
!

comment
	"traditional -> /*
	 endOfLine -> //"
	^ traditionalComment / endOfLineComment
!

commentTail

	^ 	('*' asParser , commentTailStar ) /
		(notStar , commentTail)
!

commentTailStar 

	^ ('/' asParser ) /
	  ('*' asParser , commentTailStar ) /
	  (notStarNotSlash , commentTail )
!

endOfLineComment 

        ^ 'cxcxcx' asParser

    "Modified: / 14-03-2012 / 23:13:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

notStar

	^ lineTerminator / ('*' asParser not , inputCharacter)
!

notStarNotSlash  

	^ lineTerminator / ((PPPredicateObjectParser anyOf: '*/') not , inputCharacter )
!

traditionalComment

        ^ 'aaaaa' asParser

    "Modified: / 14-03-2012 / 23:13:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaParserI methodsFor:'grammar-identifiers'!

identifier

    ^ (self tokenParserFor:#Identifier) ==> [:token|token value]


"/    ^  self asToken: (((keyword not) , (booleanLiteral not) , (nullLiteral not) , identifierChars ))

    "Modified: / 15-12-2012 / 22:32:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaParserI methodsFor:'grammar-input'!

input

	^ (inputElements optional) , (sub optional)
!

inputElement

	^ whiteSpace / comment / javaToken
!

inputElements

	^ inputElement plus
!

javaToken
        "/self flag: 'TODO: check order'.

        ^ keyword / literal / separator / operator / identifier

    "Modified: / 23-08-2011 / 00:17:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

sub

	^ (Character value: 26) asParser 
! !

!JavaParserI methodsFor:'grammar-keywords'!

abstractKW
    ^ self tokenParserFor:'abstract'
!

assertKW
    ^ self tokenParserFor:'assert'
!

booleanKW
    ^ self tokenParserFor:'boolean'
!

breakKW
    ^ self tokenParserFor:'break'
!

byteKW
    ^ self tokenParserFor:'byte'
!

caseKW
    ^ self tokenParserFor:'case'
!

catchKW
    ^ self tokenParserFor:'catch'
!

charKW
    ^ self tokenParserFor:'char'
!

classKW
    ^ self tokenParserFor:'class'
!

constKW
    ^ self tokenParserFor:'const'
!

continueKW
    ^ self tokenParserFor:'continue'
!

defaultKW
    ^ self tokenParserFor:'default'
!

doKW
    ^ self tokenParserFor:'do'
!

doubleKW
    ^ self tokenParserFor:'double'
!

elseKW
    ^ self tokenParserFor:'else'
!

enumKW
    ^ self tokenParserFor:'enum'
!

extendsKW
    ^ self tokenParserFor:'extends'
!

finalKW
    ^ self tokenParserFor:'final'
!

finallyKW
    ^ self tokenParserFor:'finally'
!

floatKW
    ^ self tokenParserFor:'float'
!

forKW
    ^ self tokenParserFor:'for'
!

gotoKW
    ^ self tokenParserFor:'goto'
!

ifKW
    ^ self tokenParserFor:'if'
!

implementsKW
    ^ self tokenParserFor:'implements'
!

importKW
    ^ self tokenParserFor:'import'
!

instanceofKW
    ^ self tokenParserFor:'instanceof'
!

intKW
    ^ self tokenParserFor:'int'
!

interfaceKW
    ^ self tokenParserFor:'interface'
!

keyword

        | keywordParsers keywordParser |
        
        keywordParsers := keywords keys asSortedCollection "/SortedSafely 
                                                                collect: [:eachKey | keywords at: eachKey ].
        keywordParser := nil.
        keywordParsers do:[:each|
            keywordParser notNil ifTrue:[
                keywordParser := keywordParser / each
            ] ifFalse:[
                keywordParser := each
            ]
        ].

        ^ "self asToken: "keywordParser

    "Modified: / 09-03-2012 / 20:48:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

longKW
    ^ self tokenParserFor:'long'
!

nativeKW
    ^ self tokenParserFor:'native'
!

newKW
    ^ self tokenParserFor:'new'
!

operator

        | operatorParsers operatorParser |
        
        operatorParsers := operators keys asSortedCollection "/SortedSafely 
                                                                collect: [:eachKey | operators at: eachKey ].
        operatorParser := nil.
        operatorParsers do:[:each|
            operatorParser notNil ifTrue:[
                operatorParser := operatorParser / each
            ] ifFalse:[
                operatorParser := each
            ]
        ].

        ^ "self asToken: "operatorParser

    "Modified: / 09-03-2012 / 20:50:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

packageKW
    ^ self tokenParserFor:'package'
!

privateKW
    ^ self tokenParserFor:'private'
!

protectedKW
    ^ self tokenParserFor:'protected'
!

publicKW
    ^ self tokenParserFor:'public'
!

returnKW
    ^ self tokenParserFor:'return'
!

shortKW
    ^ self tokenParserFor:'short'
!

staticKW
    ^ self tokenParserFor:'static'
!

strictfpKW
    ^ self tokenParserFor:'strictfp'
!

superKW
    ^ self tokenParserFor:'super'
!

switchKW
    ^ self tokenParserFor:'switch'
!

synchronizedKW
    ^ self tokenParserFor:'synchronized'
!

thisKW
    ^ self tokenParserFor:'this'
!

throwKW
    ^ self tokenParserFor:'throw'
!

throwsKW
    ^ self tokenParserFor:'throws'
!

transientKW
    ^ self tokenParserFor:'transient'
!

tryKW
    ^ self tokenParserFor:'try'
!

voidKW
    ^ self tokenParserFor:'void'
!

volatileKW
    ^ self tokenParserFor:'volatile'
!

whileKW
    ^ self tokenParserFor:'while'
! !

!JavaParserI methodsFor:'grammar-lineTerminators'!

inputCharacter 

	^(lineTerminator not) , unicodeInputCharacter ==> #second
!

lineTerminator

	^ (Character lf asParser) / (Character cr asParser , (Character lf asParser ) optional )
! !

!JavaParserI methodsFor:'grammar-literals'!

literal
        "a literal must be a single token. Whitespaces are not allowed inside the literal"
        
        ^" self asToken: "(nullLiteral / booleanLiteral / floatingPointLiteral / integerLiteral / characterLiteral / stringLiteral)

    "Modified: / 09-03-2012 / 20:49:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaParserI methodsFor:'grammar-literals-boolean'!

booleanLiteral 

    ^ self tokenParserFor:#boolean
 "Modified: / 14-03-2012 / 23:36:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"

    "Modified: / 14-03-2012 / 23:36:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaParserI methodsFor:'grammar-literals-character'!

characterLiteral 
    ^ self tokenParserFor:#Character
 "Modified: / 15-03-2012 / 00:11:19 / Jan Vrany <jan.vrany@fit.cvut.cz>" "Modified (format): / 15-03-2012 / 08:35:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"

    "Modified: / 15-03-2012 / 00:11:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 15-03-2012 / 08:35:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaParserI methodsFor:'grammar-literals-floating'!

floatingPointLiteral
    ^ (self tokenParserFor:#Float) /
            (self tokenParserFor:#Double)
 "Modified: / 15-03-2012 / 00:03:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"

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

!JavaParserI methodsFor:'grammar-literals-integer'!

integerLiteral
    ^ (self tokenParserFor:#Integer) /
            (self tokenParserFor:#LongInteger)
 "Modified: / 15-03-2012 / 00:00:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"

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

!JavaParserI methodsFor:'grammar-literals-null'!

nullLiteral 

    ^ self tokenParserFor:#null

    "Modified: / 14-03-2012 / 23:22:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaParserI methodsFor:'grammar-literals-string'!

stringLiteral 

    ^ self tokenParserFor:#String

    "Modified: / 14-03-2012 / 23:42:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaParserI methodsFor:'grammar-separators'!

separator

        "should it be:
        
        | separatorParsers |
        separatorParsers := separators keysSortedSafely 
                                                                collect: [:eachKey | separators at: eachKey ].
        ^ (separatorParsers reduce: [ :a :b | a / b ]) token trimBlanks
        
        for consistency to keywords and operators ?"
        
        ^"self asToken: "(PPPredicateObjectParser anyOf: '(){}[];,.' )

    "Modified: / 09-03-2012 / 20:49:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaParserI methodsFor:'grammar-unicode-escapes'!

hexDigit 

	^#hex asParser
!

rawInputCharacter

	^#any asParser
!

unicodeEscape

	^ $\ asParser , unicodeMarker , hexDigit , hexDigit , hexDigit , hexDigit
!

unicodeInputCharacter

	 ^ unicodeEscape / rawInputCharacter
!

unicodeMarker

	^$u asParser plus
! !

!JavaParserI methodsFor:'grammar-whiteSpace'!

whiteSpace

	^ (Character space asParser ) /
	  (Character tab asParser ) /
	  ((Character value: 12) asParser ) /
		lineTerminator 
! !

!JavaParserI methodsFor:'initialization'!

initialize

        super initialize.
        "/self initializeStartingAt: #start.
        
        self initializeKeywords.
        self initializeOperators.
        self initializeSeparators.

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

initializeKeywords

        | values |
        keywords := Dictionary new.
        values := #('abstract' 'assert' 'boolean' 'break' 'byte' 'case'  'catch' 'char' 'class' 'const'
           'continue' 'default' 'do' 'double' 'else' 'enum' 'extends' 'final'  'finally' 'float'
           'for' 'if' 'goto' 'implements' 'import' 'instanceof' 'int' 'interface' 'long' 'native'
           'new' 'package' 'private' 'protected' 'public' 'return' 'short' 'static' 'strictfp' 'super'
           'switch' 'synchronized' 'this' 'throw' 'throws' 'transient' 'try' 'void' 'volatile' 'while').
        
        values do: [:eachKeyword |
                keywords at: eachKeyword 
                        put: (PPUnresolvedParser named: ('keyword', eachKeyword first asUppercase asString , eachKeyword allButFirst))          
                ].
        
        keywords keysAndValuesDo:  [:key :value |
                (keywords at: key) def: key asParser trim
        ]

    "Modified: / 10-03-2012 / 13:16:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

initializeOperators

        | values |
        operators := Dictionary new.
        values := #(    '>>>=' '>>>' '>>=' '>>' '>=' '>'        '<<=' '<<' '<=' '<'     '++' '+=' '+'   '--' '-=' '-'   '&&' '&=' '&'
                                        '||' '|=' '|'   '*=' '*'        '%=' '%'        '/=' '/'        '^=' '^'        '!!=' '!!'        '==' '='        '~'     '?'     ':'     '@' ).
        
        values do: [:eachOperator |
                operators at: eachOperator 
                        put: (PPUnresolvedParser named: ('operator', eachOperator asString))            
                ].
        
        operators  keysAndValuesDo:  [:key :value |
                (operators at: key) def: (key asParser trim)]

    "Modified: / 10-03-2012 / 13:16:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

initializeSeparators

        | values |
        separators := Dictionary new.
        values := #( '(' ')' '{' '}' '[' ']' ';' ',' '.' ).
        
        values do: [:eachSeparator |
                separators at: eachSeparator 
                        put: (PPUnresolvedParser named: ('separator', eachSeparator asString))          
                ].
        
        separators  keysAndValuesDo:  [:key :value |
                (separators at: key) def: (key asParser trim)]

    "Modified: / 10-03-2012 / 13:16:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

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>"
! !

!JavaParserI methodsFor:'parsing'!

parse: anObject
    "Parse anObject with the receiving parser and answer the parse-result or an instance of PPFailure."

    | scanner |

    (anObject isKindOf: JavaScanner) ifFalse:[
        scanner := JavaScanner for: anObject readStream.
    ] ifTrue:[
        scanner := anObject
    ].

    ^super parse: scanner

    "Created: / 15-03-2012 / 11:10:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaParserI methodsFor:'private'!

tokenParserFor: aSymbol
    ^TokenParser for:aSymbol

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

!JavaParserI methodsFor:'querying'!

productionAt: aSymbol ifAbsent: aBlock
    "Answer the production named aSymbol, if there is no such production answer the result of evaluating aBlock."

    parser isNil ifTrue:[
        self initializeStartingAt: aSymbol.
    ].
    ^super productionAt: aSymbol ifAbsent: aBlock

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

!JavaParserI methodsFor:'utility'!

asToken:aParser
    ^aParser

    "Created: / 11-03-2012 / 08:43:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

emptySquaredParenthesis

        ^ (self tokenFor:$[) , (self tokenFor:$])

    "Created: / 11-03-2012 / 00:02:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

tokenFor: aString

    ^aString size == 1 ifTrue:[
        self tokenParserFor:aString first
    ] ifFalse:[
        self tokenParserFor:aString
    ]


"/    | p |
"/
"/    p := keywords at: aString ifAbsent:[nil].
"/    p notNil ifTrue:[ ^ self asToken: p ].
"/
"/    p := operators at: aString ifAbsent:[nil].
"/    p notNil ifTrue:[ ^ self asToken: p ].
"/
"/    p := separators at: aString ifAbsent:[nil].
"/    p notNil ifTrue:[ ^ self asToken: p ].
"/
"/    self error: 'Should not be reached'

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

!JavaParserI::BlockParser class methodsFor:'documentation'!

version_HG

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

version_SVN
    ^ '§Id§'
! !

!JavaParserI::BlockParser methodsFor:'parsing'!

old_parseOn: aStream

    | openCount peekC start stop |

    aStream skipSeparators.
    peekC := aStream peek.
    peekC == #/ ifTrue:[
        aStream next.
        aStream skipComment
    ].

    peekC ~~ ${ ifTrue:[
        ^ PPFailure message: ('unexpected char (got ', (peekC ? 'nil'), ' expecting { )') at: aStream position
    ].
    openCount := 1.
    aStream next.
    start := aStream position.
    [ openCount ~~ 0 ] whileTrue:[
        aStream atEnd ifTrue:[
            ^ PPFailure message: ('unexpected end of input') at: aStream position
        ].
        peekC := aStream peek.
        peekC == ${ ifTrue:[
            aStream next.    
            openCount := openCount + 1
        ] ifFalse:[peekC == $} ifTrue:[
            aStream next.
            openCount := openCount - 1
        ] ifFalse:[peekC == $/ ifTrue:[
            aStream next.
            aStream peek == $*  ifTrue:[
                aStream next.
                aStream rememberTokenStartPosition:2.
                aStream skipComment
            ] ifFalse:[
                aStream peek == $/ ifTrue:[
                    aStream next.
                    aStream rememberTokenStartPosition:0.
                    aStream skipEOLComment
                ]
            ]
        ] ifFalse:[peekC == $" ifTrue:[
            aStream rememberTokenStartPosition.
            aStream nextString: $" character: false.
        ] ifFalse:[peekC == $' ifTrue:[
            aStream rememberTokenStartPosition.
            aStream  nextString: $' character: true.
        ] ifFalse:[
            aStream next
        ]]]]]
    ].
    stop := aStream position.
    ^JavaScanner::Token new
        type: #__Block__;
        value: nil;
        startPosition: start;
        endPosition: stop;
        yourself.



    "
        ( JavaBlockParser new trim , ';' asParser trim) parse: '{ } ;'

    "

    "Created: / 03-08-2013 / 19:37:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parseOn: aStream

    | start stop scanner stack t |


    scanner := aStream. "/give it better name so the code is readable...
    stack := Stack new:10.
    t := scanner nextToken.
    t ~~ ${ ifTrue:[
        ^ PPFailure message: ('unexpected token (got ', (scanner tokenValue ? nil) printString , ' expecting { )') at: aStream position
    ].
    stack push: t.
    [ t ~~ #EOF and:[ stack notEmpty ] ] whileTrue:[
        "/Skip all non-paren like tokens...    
        t := scanner nextToken.
        [ ('{}[]()' includes: t) or: [ t == #EOF ] ] whileFalse:[
            t := scanner nextToken.    
        ].
        ('{[(' includes: t) ifTrue:[
            stack push: t.
        ] ifFalse:[
            | opening |

            opening := '{[(' at: ('}])' indexOf: t).
            stack top == opening ifTrue:[
                stack pop
            ] ifFalse:[
                ^ PPFailure message: ('mispatched (got ''', t , ''' expecting ''', ('}])' at: ('{[(' indexOf: stack top)) , ''' )') at: aStream position
            ]
        ]
    ].

    stop := aStream position.
    ^JavaScanner::Token new
        type: #__Block__;
        value: nil;
        startPosition: start;
        endPosition: stop;
        yourself.



    "
        ( JavaBlockParser new trim , ';' asParser trim) parse: '{ } ;'

    "

    "Modified: / 04-08-2013 / 01:42:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaParserI::TokenParser class methodsFor:'documentation'!

version_HG

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

version_SVN
    ^ '§Id§'
! !

!JavaParserI::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>"
! !

!JavaParserI::TokenParser methodsFor:'accessing'!

tokenType
    ^ tokenType
!

tokenType:something
    tokenType := something.
! !

!JavaParserI::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>"
! !

!JavaParserI class methodsFor:'documentation'!

version_CVS
    ^ '$Header: /cvs/stx/stx/libjava/tools/JavaParserI.st,v 1.2 2013-02-25 11:15:35 vrany Exp $'
!

version_HG

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

version_SVN
    ^ '§Id§'
! !


JavaParserI initialize!