PPCompositeParser.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Thu, 10 Jan 2013 14:25:17 +0100
changeset 113 ed5e4d654ce8
parent 28 1194e560eda4
child 182 dad0accb9b2c
permissions -rw-r--r--
Added PPCompositeParserGenerator & PPParserVisitor

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

PPDelegateParser subclass:#PPCompositeParser
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'PetitParser-Tools'
!


!PPCompositeParser class methodsFor:'instance creation'!

new
	"Answer a new parser starting at the default start symbol."

	^ self newStartingAt: self startSymbol
!

newStartingAt: aSymbol
	"Answer a new parser starting at aSymbol."

	^ self basicNew initializeStartingAt: aSymbol
! !

!PPCompositeParser class methodsFor:'accessing'!

ignoredNames
	"Answer a collection of instance-variables that should not be automatically initialized with productions, but that are used internal to the composite parser."

	^ PPCompositeParser allInstVarNames
!

startSymbol
	"Answer the method that represents the default start symbol."

	^ #start
! !

!PPCompositeParser class methodsFor:'parsing'!

parse: anObject
	^ self parse: anObject startingAt: self startSymbol
!

parse: anObject onError: aBlock
	^ self parse: anObject startingAt: self startSymbol onError: aBlock
!

parse: anObject startingAt: aSymbol
	^ (self newStartingAt: aSymbol) parse: anObject
!

parse: anObject startingAt: aSymbol onError: aBlock
	^ (self newStartingAt: aSymbol) parse: anObject onError: aBlock
! !

!PPCompositeParser methodsFor:'accessing'!

start
	"Answer the production to start this parser with."
	
	self subclassResponsibility
! !

!PPCompositeParser methodsFor:'initialization'!

initializeStartingAt: aSymbol
	| allVariableNames ignoredVariableNames productionIndexesAndNames |
	self initialize.	

	"find all the productions that need to be initialized"
	allVariableNames := self class allInstVarNames
		collect: [ :each | each asSymbol ].
	ignoredVariableNames := self class ignoredNames
		collect: [ :each | each asSymbol ].
	productionIndexesAndNames := ((1 to: self class instSize)
		collect: [ :index | index -> (allVariableNames at: index) ])
		reject: [ :assoc | ignoredVariableNames includes: assoc value ].
	
	"initialize productions with an undefined parser to be replaced later"
	parser := PPUnresolvedParser named: aSymbol.
	productionIndexesAndNames do: [ :assoc |
		self instVarAt: assoc key put: (PPUnresolvedParser named: assoc value) ].
	parser def: (self perform: aSymbol).
	
	"resolve unresolved parsers with their actual implementation"
	productionIndexesAndNames do: [ :assoc |
		(self respondsTo: assoc value)
			ifFalse: [ self error: 'Unable to initialize ' , assoc value printString ]
			ifTrue: [ (self instVarAt: assoc key) def: (self perform: assoc value) ] ]
! !

!PPCompositeParser methodsFor:'querying'!

productionAt: aSymbol
	"Answer the production named aSymbol."
	
	^ self productionAt: aSymbol ifAbsent: [ nil ]
!

productionAt: aSymbol ifAbsent: aBlock
	"Answer the production named aSymbol, if there is no such production answer the result of evaluating aBlock."
	
	(self class ignoredNames includes: aSymbol asString)
		ifTrue: [ ^ aBlock value ].
	(self class startSymbol = aSymbol)
		ifTrue: [ ^ parser ].
	^ self instVarAt: (self class allInstVarNames
		indexOf: aSymbol asString
		ifAbsent: [ ^ aBlock value ])
! !

!PPCompositeParser class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/goodies/petitparser/PPCompositeParser.st,v 1.3 2012-05-04 22:02:49 vrany Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/goodies/petitparser/PPCompositeParser.st,v 1.3 2012-05-04 22:02:49 vrany Exp $'
!

version_SVN
    ^ '§Id: PPCompositeParser.st 2 2010-12-17 18:44:23Z vranyj1 §'
! !