compiler/PPCTrimmingTokenNode.st
changeset 438 20598d7ce9fa
parent 422 116d2b2af905
child 452 9f4558b3be66
--- a/compiler/PPCTrimmingTokenNode.st	Tue Apr 21 17:20:11 2015 +0100
+++ b/compiler/PPCTrimmingTokenNode.st	Thu Apr 30 23:43:14 2015 +0200
@@ -21,47 +21,8 @@
 	children at: 2 put: anObject
 !
 
-compileFirstWhitespace: compiler
-	compiler call: (self whitespace compileWith: compiler).
-!
-
-compileSecondWhitespace: compiler
-	| root follow |
-	root := compiler rootNode.
-	
-	follow := self followSetWithTokens.
-	
-	(follow allSatisfy: [ :e | e isKindOf: PPCTrimmingTokenNode ]) ifTrue: [  
-		compiler add: '"second water skipped because there are only trimming tokens in the follow"'
-	] ifFalse: [  
-		compiler add: '"second water compiled because some of the follow parsers are not trimming toknes"'.
-		compiler call: (self whitespace compileWith: compiler).
-	]
-!
-
-compileWhitespace: compiler
-	compiler add: 'context atWs ifFalse: ['.
-	compiler indent.
-		compiler call: (self whitespace compileWith: compiler).
-		compiler add: 'context setWs.'.
-	compiler dedent.
-	compiler add: '].'.
-!
-
-initialize
-	super initialize.
-	children := Array new: 2
-!
-
-rewrite: changeStatus
-	|  |
-	super rewrite: changeStatus.
-	
-	(self allNodes anySatisfy: [ :node | node asFast ~= node ]) ifTrue: [  
-		changeStatus change.
-		self replace: self whitespace with: (self whitespace transform: [ :node | node asFast ]).
-		self replace: self child with: (self child transform: [:node | node asFast]).
-	]
+prefix
+	^ #token
 !
 
 tokenClass
@@ -117,44 +78,6 @@
 	]
 ! !
 
-!PPCTrimmingTokenNode methodsFor:'as yet unclassified'!
-
-compileWith: compiler effect: effect id: id
-	|  guard |
-
-	compiler startMethod: id.
-	compiler addVariable: 'start'.
-	compiler addVariable: 'end'.
-	
-	"self compileFirstWhitespace: compiler."
-	self compileWhitespace: compiler.
-
-	(compiler guards and: [(guard := PPCGuard on: self) makesSense]) ifTrue: [ 
-		compiler add: 'context atEnd ifTrue: [ ^ self error ].'.
-		guard id: id, '_guard'.
-		guard compileGuard: compiler.
-		compiler addOnLine: 'ifFalse: [ ^ self error ].'
-	].
-
-	compiler add: 'start := context position + 1.'.
-	compiler call: (self child compileWith: compiler).
-	compiler add: 'error ifTrue: [ ^ self ].'.	
-	compiler add: 'end := context position.'.
-	
-"	self compileSecondWhitespace: compiler."
-	self compileWhitespace: compiler.
-
-	compiler add: '^ ', tokenClass asString, ' on: (context collection) 
-																start: start  
-																stop: end
-																value: nil'.
- ^ compiler stopMethod.	
-!
-
-prefix
-	^ #token
-! !
-
 !PPCTrimmingTokenNode methodsFor:'comparing'!
 
 = anotherNode
@@ -166,3 +89,16 @@
 	^ super hash bitXor: tokenClass hash
 ! !
 
+!PPCTrimmingTokenNode methodsFor:'initialization'!
+
+initialize
+	super initialize.
+	children := Array new: 2
+! !
+
+!PPCTrimmingTokenNode methodsFor:'visiting'!
+
+accept: visitor
+	^ visitor visitTrimmingTokenNode: self
+! !
+