update
authorClaus Gittinger <cg@exept.de>
Tue, 04 Mar 2014 15:33:36 +0100
changeset 182 dad0accb9b2c
parent 181 6e0a8571dd88
child 183 553dad635f6d
update
PPCompositeParser.st
--- a/PPCompositeParser.st	Tue Mar 04 15:33:27 2014 +0100
+++ b/PPCompositeParser.st	Tue Mar 04 15:33:36 2014 +0100
@@ -1,7 +1,7 @@
 "{ Package: 'stx:goodies/petitparser' }"
 
 PPDelegateParser subclass:#PPCompositeParser
-	instanceVariableNames:''
+	instanceVariableNames:'dependencies'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'PetitParser-Tools'
@@ -17,13 +17,42 @@
 !
 
 newStartingAt: aSymbol
-	"Answer a new parser starting at aSymbol."
+	"Answer a new parser starting at aSymbol. The code makes sure to resolve all dependent parsers correctly."
 
-	^ self basicNew initializeStartingAt: aSymbol
+	| parsers remaining |
+	parsers := IdentityDictionary new.
+	remaining := OrderedCollection with: self.
+	[ remaining isEmpty ] whileFalse: [
+		| dependency |
+		dependency := remaining removeLast.
+		(parsers includesKey: dependency) ifFalse: [
+			parsers at: dependency put: dependency basicNew.
+			remaining addAll: dependency dependencies ] ].
+	parsers keysAndValuesDo: [ :class :parser |
+		| dependencies |
+		dependencies := IdentityDictionary new.
+		class dependencies 
+			do: [ :dependency | dependencies at: dependency put: (parsers at: dependency) ].
+		parser 
+			initializeStartingAt: (class == self
+				ifTrue: [ aSymbol ]
+				ifFalse: [ class startSymbol ]) 
+			dependencies: dependencies ].
+	parsers keysAndValuesDo: [ :class :parser |
+		parser setParser: (parser perform: parser children first name).
+		parser productionNames keysAndValuesDo: [ :key :value |
+			(parser instVarAt: key) setParser: (parser perform: value) ] ].
+	^ parsers at: self
 ! !
 
 !PPCompositeParser class methodsFor:'accessing'!
 
+dependencies
+	"Answer a collection of PPCompositeParser classes that this parser directly dependends on. Override this method in subclasses to declare dependent parsers. The default implementation does not depend on other PPCompositeParser."
+
+	^ #()
+!
+
 ignoredNames
 	"Answer a collection of instance-variables that should not be automatically initialized with productions, but that are used internal to the composite parser."
 
@@ -88,10 +117,24 @@
 		(self respondsTo: assoc value)
 			ifFalse: [ self error: 'Unable to initialize ' , assoc value printString ]
 			ifTrue: [ (self instVarAt: assoc key) def: (self perform: assoc value) ] ]
+!
+
+initializeStartingAt: aSymbol dependencies: aDictionary
+	self initialize.
+	parser := PPDelegateParser named: aSymbol.
+	self productionNames keysAndValuesDo: [ :key :value |
+		self instVarAt: key put: (PPDelegateParser named: value) ].
+	dependencies := aDictionary
 ! !
 
 !PPCompositeParser methodsFor:'querying'!
 
+dependencyAt: aClass
+	"Answer the dependent parser aClass. Throws an error if this parser class is not declared in the method #dependencies on the class-side of the receiver."
+	
+	^ dependencies at: aClass ifAbsent: [ self error: 'Undeclared dependency in ' , self class name , ' to ' , aClass name ]
+!
+
 productionAt: aSymbol
 	"Answer the production named aSymbol."
 	
@@ -108,18 +151,32 @@
 	^ self instVarAt: (self class allInstVarNames
 		indexOf: aSymbol asString
 		ifAbsent: [ ^ aBlock value ])
+!
+
+productionNames
+	"Answer a dictionary of slot indexes and production names."
+	
+	| productionNames ignoredNames |
+	productionNames := Dictionary new.
+	ignoredNames := self class ignoredNames
+		collect: [ :each | each asSymbol ].
+	self class allInstVarNames keysAndValuesDo: [ :key :value |
+		(ignoredNames includes: value asSymbol)
+			ifFalse: [ productionNames at: key put: value asSymbol ] ].
+	^ productionNames
 ! !
 
 !PPCompositeParser class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/goodies/petitparser/PPCompositeParser.st,v 1.3 2012-05-04 22:02:49 vrany Exp $'
+    ^ '$Header: /cvs/stx/stx/goodies/petitparser/PPCompositeParser.st,v 1.4 2014-03-04 14:33:36 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/petitparser/PPCompositeParser.st,v 1.3 2012-05-04 22:02:49 vrany Exp $'
+    ^ '$Header: /cvs/stx/stx/goodies/petitparser/PPCompositeParser.st,v 1.4 2014-03-04 14:33:36 cg Exp $'
 !
 
 version_SVN
-    ^ '§Id: PPCompositeParser.st 2 2010-12-17 18:44:23Z vranyj1 §'
+    ^ '$Id: PPCompositeParser.st,v 1.4 2014-03-04 14:33:36 cg Exp $'
 ! !
+