PPCompositeParser.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Fri, 04 May 2012 23:59:14 +0200
changeset 12 ace2bacc5f6a
parent 4 90de244a7fa2
child 28 1194e560eda4
permissions -rw-r--r--
Checkin from browser

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

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

PPCompositeParser comment:'A PPCompositeParser is composed parser built from various primitive parsers.
Every production in the receiver is specified as a method that returns its parser. Note that every production requires an instance variable of the same name, otherwise the production is not cached and cannot be used in recursive grammars. Productions should refer to each other by reading the respective inst-var. Note: these inst-vars are typically not written, as the assignment happens in the initialize method using reflection.
The start production is defined in the method start. It is aliased to the inst-var parser defined in the superclass of PPCompositeParser.'
!


!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_SVN
    ^ '$Id: PPCompositeParser.st,v 1.2 2012-01-13 11:22:50 cg Exp $'
! !