parsers/smalltalk/PPSmalltalkTokenParser.st
changeset 385 44a36ed4e484
child 417 3c0a91182e65
equal deleted inserted replaced
384:a613ecf5d2a1 385:44a36ed4e484
       
     1 "{ Package: 'stx:goodies/petitparser/parsers/smalltalk' }"
       
     2 
       
     3 PPTokenParser subclass:#PPSmalltalkTokenParser
       
     4 	instanceVariableNames:''
       
     5 	classVariableNames:'SeparatorPredicate'
       
     6 	poolDictionaries:''
       
     7 	category:'PetitSmalltalk-Core'
       
     8 !
       
     9 
       
    10 PPSmalltalkTokenParser comment:'A parser that knows how to skip comments and whitespace in Smalltalk and how to instantiate tokens.'
       
    11 !
       
    12 
       
    13 
       
    14 !PPSmalltalkTokenParser class methodsFor:'initialization'!
       
    15 
       
    16 initialize
       
    17 	SeparatorPredicate := PPCharSetPredicate on: [ :char | char isSeparator ]
       
    18 ! !
       
    19 
       
    20 !PPSmalltalkTokenParser methodsFor:'parsing'!
       
    21 
       
    22 parseComments: anArray on: aPPContext
       
    23 	| start comments |
       
    24 	comments := anArray.
       
    25 	[ [ aPPContext atEnd not and: [ SeparatorPredicate value: aPPContext uncheckedPeek ] ]
       
    26 		whileTrue: [ aPPContext next ].
       
    27 	 aPPContext atEnd not and: [ aPPContext uncheckedPeek = $" ] ] whileTrue: [
       
    28 		aPPContext next.
       
    29 		start := aPPContext position.
       
    30 		aPPContext upTo: $".
       
    31 		comments := comments copyWith: (start to: aPPContext position) ].
       
    32 	^ comments
       
    33 !
       
    34 
       
    35 parseOn: aPPContext
       
    36 	| memento comments token |
       
    37 	memento := aPPContext remember.
       
    38 	comments := self
       
    39 		parseComments: #()
       
    40 		on: aPPContext.
       
    41 	token := super parseOn: aPPContext.
       
    42 	token isPetitFailure ifTrue: [
       
    43 		aPPContext restore: memento.
       
    44 		^ token ].
       
    45 	comments := self
       
    46 		parseComments: comments
       
    47 		on: aPPContext.
       
    48 	^ token comments: comments
       
    49 ! !
       
    50 
       
    51 !PPSmalltalkTokenParser methodsFor:'private'!
       
    52 
       
    53 defaultTokenClass
       
    54 	^ PPSmalltalkToken
       
    55 ! !
       
    56 
       
    57 !PPSmalltalkTokenParser class methodsFor:'documentation'!
       
    58 
       
    59 version_HG
       
    60 
       
    61     ^ '$Changeset: <not expanded> $'
       
    62 ! !
       
    63 
       
    64 
       
    65 PPSmalltalkTokenParser initialize!