PPPredicateSequenceParser.st
author Claus Gittinger <cg@exept.de>
Mon, 12 Sep 2011 19:47:59 +0200
changeset 2 acb3822c73db
parent 0 739fe9b7253e
child 4 90de244a7fa2
permissions -rw-r--r--
initial checkin

"{ Package: 'squeak:petitparser' }"

PPPredicateParser subclass:#PPPredicateSequenceParser
	instanceVariableNames:'size'
	classVariableNames:''
	poolDictionaries:''
	category:'PetitParser-Parsers'
!

PPPredicateSequenceParser comment:'A parser that accepts if a given predicate on an arbitrary number of elements of the input sequence holds.
Instance Variables:
	size	<Integer>	The number of elements to consume.'
!


!PPPredicateSequenceParser class methodsFor:'instance creation'!

on: aBlock message: aString negated: aNegatedBlock message: aNegatedString size: anInteger 
	^ self new initializeOn: aBlock message: aString negated: aNegatedBlock message: aNegatedString size: anInteger
!

on: aBlock message: aString size: anInteger
	^ self on: aBlock message: aString negated: [ :each | (aBlock value: each) not ] message: 'no ' , aString size: anInteger 
! !

!PPPredicateSequenceParser methodsFor:'accessing'!

size
	"Answer the sequence size of the receiver."

	^ size
! !

!PPPredicateSequenceParser methodsFor:'initialization'!

initializeOn: aBlock message: aString negated: aNegatedBlock message: aNegatedString size: anInteger
	predicate := aBlock.
	predicateMessage := aString.
	negated := aNegatedBlock.
	negatedMessage := aNegatedString.
	size := anInteger 
! !

!PPPredicateSequenceParser methodsFor:'operators'!

negate
	"Answer a parser that is the negation of the receiving predicate parser."
	
	^ self class 
		on: negated message: negatedMessage
		negated: predicate message: predicateMessage
		size: size
! !

!PPPredicateSequenceParser methodsFor:'parsing'!

parseOn: aStream
	| position result |
	position := aStream position.
	result := aStream next: size.
	(result size = size and: [ predicate value: result ])
		ifTrue: [ ^ result ].
	aStream position: position.
	^ PPFailure message: predicateMessage at: aStream position
! !

!PPPredicateSequenceParser class methodsFor:'documentation'!

version_SVN
    ^ '$Id: PPPredicateSequenceParser.st,v 1.1 2011-08-18 18:56:17 cg Exp $'
! !