parsers/smalltalk/PPSmalltalkWhitespaceParser.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Mon, 03 Nov 2014 19:42:31 +0000
changeset 411 06b96374dd10
parent 390 17ba167b8ee1
child 417 3c0a91182e65
permissions -rw-r--r--
Removed PPTrimmingParser>>trim

"{ 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
	[ [aPPContext atEnd not and: [ separator value: aPPContext uncheckedPeek ] ]
		whileTrue: [ aPPContext next ].
		
	 aPPContext atEnd not and: [ aPPContext uncheckedPeek = $" ] ] whileTrue: [
		aPPContext next.
		aPPContext upTo: $".
	].
! !

!PPSmalltalkWhitespaceParser class methodsFor:'documentation'!

version_HG

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