compiler/PPCChoiceNode.st
changeset 438 20598d7ce9fa
parent 422 116d2b2af905
child 452 9f4558b3be66
--- a/compiler/PPCChoiceNode.st	Tue Apr 21 17:20:11 2015 +0100
+++ b/compiler/PPCChoiceNode.st	Thu Apr 30 23:43:14 2015 +0200
@@ -9,7 +9,13 @@
 	category:'PetitCompiler-Nodes'
 !
 
-!PPCChoiceNode methodsFor:'as yet unclassified'!
+!PPCChoiceNode methodsFor:'accessing'!
+
+prefix
+	^ #ch
+! !
+
+!PPCChoiceNode methodsFor:'analysis'!
 
 acceptsEpsilon
 	^ self acceptsEpsilonOpenSet: IdentitySet new.
@@ -18,52 +24,11 @@
 acceptsEpsilonOpenSet: set
 	set add: self.
 	^ self children anySatisfy: [:e | e acceptsEpsilonOpenSet: set ].
-!
-
-compileWith: compiler effect: effect id: id
-	| firsts guard whitespaceConsumed |
-
-	whitespaceConsumed := false.
-	firsts := (self firstSetSuchThat: [ :e | (e isKindOf: PPCTrimmingTokenNode) or: [ e isTerminal ] ]).
-	
-	compiler startMethod: id.
-	compiler addVariable: 'element'.
-
-	"If we start with trimming token, we should invoke the whitespace parser"
-	(firsts allSatisfy: [ :e | e isKindOf: PPCTrimmingTokenNode ]) ifTrue: [  
-		firsts anyOne compileWhitespace: compiler.
-		whitespaceConsumed := true.
-	].
-	
-	(1 to: children size) do: [ :idx  | |child allowGuard |
-		child := children at: idx.
-"		allowGuard := ((child isKindOf: PPCTrimmingTokenNode) and: [ whitespaceConsumed not ]) not.
-"	
-		allowGuard := whitespaceConsumed.
-				
- 		(allowGuard and: [compiler guards and: [ (guard := PPCGuard on: child) makesSense ]]) ifTrue: [ 	
-			guard id: (compiler idFor: guard prefixed: #guard).
-			guard compileGuard: compiler.
-			compiler add: ' ifTrue: [ '.
-			compiler indent.
-				compiler add: 'self clearError.'.
-				compiler add: 'element := '.
-				compiler callOnLine: (child compileWith: compiler).
-				compiler add: 'error ifFalse: [ ^ element ].'.
-			compiler dedent.
-			compiler add: ' ].'.
-		] ifFalse: [
-			compiler add: 'self clearError.'.
-			compiler add: 'element := '.
-			compiler callOnLine: (child compileWith: compiler).
-			compiler add: 'error ifFalse: [ ^ element ].'.
-		]
-	].
-	compiler add: '^ self error: ''no choice suitable'''.
- ^ compiler stopMethod.
-!
-
-prefix
-	^ #ch
 ! !
 
+!PPCChoiceNode methodsFor:'visiting'!
+
+accept: visitor
+	^ visitor visitChoiceNode: self
+! !
+