extensions.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Sun, 05 Oct 2014 00:05:20 +0100
changeset 380 8fe3cb4e607f
parent 379 451b5ae38b72
child 383 e9919f8e47de
permissions -rw-r--r--
Remove Pharoisms to make code more portable and running on Smalltalk/X * Use ANSI `(Character codePoint: 13)` (`10`) instead of `Character cr` (`lf`), This is more portable and does not depend on dialects interpretation of `#cr` - Smalltalk/X convert it according to platform line end convention (UNIX/Windows/Mac) * Do not assume exact value of a printstring in tests, i.e., instead of `msg includesSubstring: '$a' code `msg includesSubstring: $a printString. This way, the test is independent on the printString value, which may differ among dialects. Q: Is printString value of String and/or Character defined in ANSI? * In assestions, instead of `#equals:` use plain old `#=`, which is more portable. * Removed Character>>- used to create range parser. Use portable `(Interval from: $a to: $z) asParser` instead of just `$a - $z`. Do not use ($a to: $z) asParser as in Pharo, Character>>to: does not create an Interval but an Array (sigh).

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

!Block methodsFor:'*petitparser-core-converting'!

asParser
	"Answer a parser implemented in the receiving one-argument block."

	^ PPPluggableParser on: self
! !

!BlockContext methodsFor:'*petitparser-core-converting'!

asParser
	^ PPPluggableParser on: self
! !

!Character methodsFor:'*petitparser-core-converting'!

asParser
	"Answer a parser that accepts the receiving character."
	
	^ PPLiteralObjectParser on: self
! !

!Character methodsFor:'arithmetic'!

ppMinus: aCharacter
    "Create a range of characters between the receiver and the argument."

    ^ PPPredicateObjectParser between: self and: aCharacter

    "Created: / 19-12-2010 / 18:13:19 / Jan Kurs <kurs.jan@post.cz>"
! !

!Collection methodsFor:'*petitparser-core-converting'!

asChoiceParser
	^ PPChoiceParser withAll: (self collect: [ :each | each asParser ])
! !

!Collection methodsFor:'*petitparser-core-converting'!

asSequenceParser
	^ PPSequenceParser withAll: (self collect: [ :each | each asParser ])
! !

!Interval methodsFor:'*petitparser-converting'!

asParser
    "Create a range of characters between start and stop."

    self assert:start isCharacter.
    self assert:stop isCharacter.
    self assert:step == 1.
    ^ PPPredicateObjectParser between: start and: stop

    "
     ($a to:$f) asParser parse:'a'
     ($a to:$f) asParser parse:'g'
    "
! !

!Object methodsFor:'*petitparser-core-converting'!

asParser
	"Answer a parser accepting the receiving object."

	^ PPPredicateObjectParser expect: self
! !

!Object methodsFor:'*petitparser-core-testing'!

isPetitFailure
	^ false
! !

!Object methodsFor:'*petitparser-core-testing'!

isPetitParser
	^ false
! !

!PositionableStream methodsFor:'*petitparser-core-converting'!

asPetitStream
	"Some of my subclasses do not use the instance-variables collection, position and readLimit but instead have a completely different internal representation. In these cases just use the super implementation that is inefficient but should work in all cases."

	"DUNNO WHY, but on: collection from: position to: last set the start to position -1"
	self breakPoint: #petitparser.

	^ (collection isNil or: [ position  isNil or: [ readLimit isNil ] ])
		ifFalse: [ PPStream on: collection from: (position +1) to: readLimit ]
		ifTrue: [ super asPetitStream ]


"/        ^ (collection isNil or: [ position isNil or: [ readLimit isNil ] ])
"/                ifFalse: [ PPStream on: collection from: position to: readLimit ]
"/                ifTrue: [ super asPetitStream ]

    "Modified: / 18-12-2010 / 17:38:01 / Jan Kurs <kurs.jan@post.cz>"
! !

!PositionableStream methodsFor:'*petitparser-core'!

peekTwice
	"Answer what would be returned if the message next were sent to the 
	receiver. If the receiver is at the end, answer nil."

	| array |
	self atEnd 
		ifTrue: [^Array with: nil with: nil].
	array := Array with: (self next) with: (self peek).
	position := position - 1.
	^array
! !

!SequenceableCollection methodsFor:'*petitparser-core-converting'!

asParser
	^ PPSequenceParser withAll: (self collect: [ :each | each asParser ])
! !

!SequenceableCollection methodsFor:'*petitparser-core-converting'!

asPetitStream
	^ PPStream on: self
! !

!Set methodsFor:'*petitparser-core-converting'!

asParser
	^ PPChoiceParser withAll: (self collect: [ :each | each asParser ])
! !

!Stream methodsFor:'*petitparser-core-converting'!

asPetitStream
	^ self contents asPetitStream
! !

!String methodsFor:'*petitparser-core-converting'!

asParser
	"Answer a parser that accepts the receiving string."

	^ PPLiteralSequenceParser on: self
! !

!Symbol methodsFor:'*petitparser-core-converting'!

asParser
	"Answer a predicate parser named after the receiving symbol. Possible symbols are the method selectors on the class-side of PPPredicateObjectParser."

	^ PPPredicateObjectParser perform: self
! !

!Symbol methodsFor:'Compatibility-Squeak'!

value:anObject
    ^ anObject perform: self.

    "Created: / 18-12-2010 / 16:47:22 / Jan Kurs <kurs.jan@post.cz>"
! !

!Text methodsFor:'*petitparser-core'!

asPetitStream
	^ string asPetitStream
! !

!UndefinedObject methodsFor:'*petitparser-converting'!

asParser
	"Answer a parser that succeeds and does not consume anything."
	
	^ PPEpsilonParser new
! !

!stx_goodies_petitparser class methodsFor:'documentation'!

extensionsVersion_HG

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