PPPredicateSequenceParser.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Mon, 23 Nov 2015 11:14:30 +0100
changeset 551 00ebb1b85f53
parent 377 6112a403a52d
permissions -rw-r--r--
Fixed CI scripts on Windows For an unknown reason, unzip on Windows reports status code 50 (presumably "the disk is (or was) full during extraction.") even if there's plenty of space. To workaround this, simply ignore status code 50 on Windows. Sigh.

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

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


!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: aPPContext
	| memento result |
	memento := aPPContext remember.
	result := aPPContext stream next: size.
	(result size = size and: [ predicate value: result ])
		ifTrue: [ ^ result ].
	aPPContext restore: memento.
	^ PPFailure message: predicateMessage context: aPPContext
! !

!PPPredicateSequenceParser class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/goodies/petitparser/PPPredicateSequenceParser.st,v 1.4 2014-03-04 14:33:22 cg Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/goodies/petitparser/PPPredicateSequenceParser.st,v 1.4 2014-03-04 14:33:22 cg Exp $'
!

version_SVN
    ^ '$Id: PPPredicateSequenceParser.st,v 1.4 2014-03-04 14:33:22 cg Exp $'
! !