parsers/smalltalk/PPSmalltalkWhitespaceParser.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Fri, 07 Nov 2014 02:14:26 +0000
changeset 417 3c0a91182e65
parent 390 17ba167b8ee1
child 421 7e08b31e0dae
permissions -rw-r--r--
Smalltalk grammar updated to allow for Smalltalk/X EOL comments

"{ Package: 'stx:goodies/petitparser/parsers/smalltalk' }"

PPParser subclass:#PPSmalltalkWhitespaceParser
	instanceVariableNames:'separator'
	classVariableNames:''
	poolDictionaries:''
	category:'PetitSmalltalk-Core'
!



!PPSmalltalkWhitespaceParser methodsFor:'analysis'!

isNullable
	^ true
! !

!PPSmalltalkWhitespaceParser methodsFor:'initialization'!

initialize
	super initialize.
	separator := PPCharSetPredicate on: [ :char | char isSeparator ].
! !

!PPSmalltalkWhitespaceParser methodsFor:'parsing'!

parseOn: aPPContext
        "Skip any leading whitespace"
        [ [aPPContext atEnd not and: [ separator value: aPPContext uncheckedPeek ] ]
                whileTrue: [ aPPContext next ].

        "Check for comment"
         aPPContext atEnd not and: [ aPPContext uncheckedPeek = $" ] ] whileTrue: [
                aPPContext next.
                "Check for Smalltalk/X EOL comment"
                aPPContext uncheckedPeek == $/ ifTrue:[
                    | c |
                    aPPContext next.
                    [ aPPContext atEnd not 
                        and:[ (c := aPPContext uncheckedPeek) ~~ (Character codePoint: 15r0A) 
                        and: [ c ~~ (Character codePoint: 15r0D) ] ] ] whileTrue:[ 
                            aPPContext next.
                        ].
                    (c == (Character codePoint: 15r0D) and:[ aPPContext atEnd not and:[ aPPContext uncheckedPeek == (Character codePoint: 15r0A) ] ] ) ifTrue:[ 
                        aPPContext next
                    ].
                ] ifFalse:[ 
                    aPPContext upTo: $".
                ]
        ].

    "Modified: / 07-11-2014 / 01:18:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!PPSmalltalkWhitespaceParser class methodsFor:'documentation'!

version_HG

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