PPListParser.st
author Stefan Vogel <sv@exept.de>
Thu, 07 Mar 2019 17:13:54 +0100
changeset 635 cc19416f97b1
parent 169 cba3a51b9704
child 421 7e08b31e0dae
child 638 e41b42b3928f
permissions -rw-r--r--
#BUGFIX by stefan class: stx_goodies_petitparser class changed: #extensionMethodNames #value: moved to libbasic

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

PPParser subclass:#PPListParser
	instanceVariableNames:'parsers'
	classVariableNames:''
	poolDictionaries:''
	category:'PetitParser-Parsers'
!


!PPListParser class methodsFor:'instance creation'!

with: aParser
	^ self withAll: (Array with: aParser)
!

with: aFirstParser with: aSecondParser
	^ self withAll: (Array with: aFirstParser with: aSecondParser)
!

withAll: aCollection
	^ self basicNew setParsers: aCollection
! !

!PPListParser methodsFor:'*petitanalyzer-matching'!

copyInContext: aDictionary seen: aSeenDictionary
	| copy copies |
	aSeenDictionary at: self ifPresent: [ :value | ^ value ].
	copy := aSeenDictionary at: self put: self copy.
	copies := OrderedCollection new.
	parsers do: [ :each |
		| result |
		result := each 
			copyInContext: aDictionary
			seen: aSeenDictionary.
		result isCollection
			ifTrue: [ copies addAll: result ]
			ifFalse: [ copies add: result ] ].
	^ copy
		setParsers: copies;
		yourself
! !

!PPListParser methodsFor:'*petitanalyzer-transforming'!

replace: aParser with: anotherParser
	super replace: aParser with: anotherParser.
	parsers keysAndValuesDo: [ :index :parser |
		parser == aParser
			ifTrue: [ parsers at: index put: anotherParser ] ]
! !

!PPListParser methodsFor:'accessing'!

children
	^ parsers
! !

!PPListParser methodsFor:'copying'!

copyWith: aParser
	^ self species withAll: (parsers copyWith: aParser)
!

postCopy
	super postCopy.
	parsers := parsers copy
! !

!PPListParser methodsFor:'initialization'!

initialize
	super initialize.
	self setParsers: #()
!

setParsers: aCollection
	parsers := aCollection asArray
! !

!PPListParser class methodsFor:'documentation'!

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

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

version_SVN
    ^ '$Id: PPListParser.st,v 1.4 2014-03-04 14:32:58 cg Exp $'
! !