parsers/smalltalk/PPSmalltalkWhitespaceParser.st
changeset 421 7e08b31e0dae
parent 417 3c0a91182e65
equal deleted inserted replaced
420:b2f2f15cef26 421:7e08b31e0dae
     1 "{ Package: 'stx:goodies/petitparser/parsers/smalltalk' }"
     1 "{ Package: 'stx:goodies/petitparser/parsers/smalltalk' }"
     2 
     2 
     3 PPParser subclass:#PPSmalltalkWhitespaceParser
     3 PPParser subclass:#PPSmalltalkWhitespaceParser
     4 	instanceVariableNames:'separator'
     4 	instanceVariableNames:''
     5 	classVariableNames:''
     5 	classVariableNames:''
     6 	poolDictionaries:''
     6 	poolDictionaries:''
     7 	category:'PetitSmalltalk-Core'
     7 	category:'PetitSmalltalk-Core'
     8 !
     8 !
     9 
     9 
    17 
    17 
    18 !PPSmalltalkWhitespaceParser methodsFor:'initialization'!
    18 !PPSmalltalkWhitespaceParser methodsFor:'initialization'!
    19 
    19 
    20 initialize
    20 initialize
    21 	super initialize.
    21 	super initialize.
    22 	separator := PPCharSetPredicate on: [ :char | char isSeparator ].
       
    23 ! !
    22 ! !
    24 
    23 
    25 !PPSmalltalkWhitespaceParser methodsFor:'parsing'!
    24 !PPSmalltalkWhitespaceParser methodsFor:'parsing'!
    26 
    25 
       
    26 name
       
    27 	^ 'smalltalk_ws'
       
    28 !
       
    29 
    27 parseOn: aPPContext
    30 parseOn: aPPContext
    28         "Skip any leading whitespace"
    31         "Skip any leading whitespace"
    29         [ [aPPContext atEnd not and: [ separator value: aPPContext uncheckedPeek ] ]
    32         [ [aPPContext atEnd not and: [  aPPContext uncheckedPeek isSeparator ] ]
    30                 whileTrue: [ aPPContext next ].
    33                 whileTrue: [ aPPContext next ].
    31 
    34 
    32         "Check for comment"
    35         "Check for comment"
    33          aPPContext atEnd not and: [ aPPContext uncheckedPeek = $" ] ] whileTrue: [
    36          aPPContext atEnd not and: [ aPPContext uncheckedPeek = $" ] ] whileTrue: [
    34                 aPPContext next.
    37                 aPPContext next.
    47                 ] ifFalse:[ 
    50                 ] ifFalse:[ 
    48                     aPPContext upTo: $".
    51                     aPPContext upTo: $".
    49                 ]
    52                 ]
    50         ].
    53         ].
    51 
    54 
    52     "Modified: / 07-11-2014 / 01:18:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    55     "Modified: / 21-11-2014 / 10:10:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    53 ! !
    56 ! !
    54 
    57 
    55 !PPSmalltalkWhitespaceParser class methodsFor:'documentation'!
    58 !PPSmalltalkWhitespaceParser class methodsFor:'documentation'!
    56 
    59 
    57 version_HG
    60 version_HG