compiler/PPCTrimmingTokenNode.st
changeset 421 7e08b31e0dae
parent 414 0eaf09920532
child 422 116d2b2af905
--- a/compiler/PPCTrimmingTokenNode.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCTrimmingTokenNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -27,6 +27,24 @@
 	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.
@@ -95,6 +113,14 @@
 	(block value: self) ifTrue: [ aCollection add: self. ^ aCollection ].
 	
 	^ self child firstSetSuchThat: block into: aCollection openSet: aSet.
+!
+
+firstSets: aFirstDictionary into: aSet suchThat: aBlock
+	"PRIVATE: Try to add additional elements to the first-set aSet of the receiver, use the incomplete aFirstDictionary."
+
+	(aBlock value: self) ifFalse: [ 
+		aSet addAll: (aFirstDictionary at: self child)
+	]
 ! !
 
 !PPCTrimmingTokenNode methodsFor:'as yet unclassified'!
@@ -106,6 +132,7 @@
 	compiler addVariable: 'start'.
 	compiler addVariable: 'end'.
 	
+	"self compileFirstWhitespace: compiler."
 	self compileWhitespace: compiler.
 
 	(compiler guards and: [(guard := PPCGuard on: self) makesSense]) ifTrue: [ 
@@ -120,6 +147,7 @@
 	compiler add: 'error ifTrue: [ ^ self ].'.	
 	compiler add: 'end := context position.'.
 	
+"	self compileSecondWhitespace: compiler."
 	self compileWhitespace: compiler.
 
 	compiler add: '^ ', tokenClass asString, ' on: (context collection) 
@@ -133,3 +161,14 @@
 	^ #token
 ! !
 
+!PPCTrimmingTokenNode methodsFor:'comparing'!
+
+= anotherNode
+	super = anotherNode ifFalse: [ ^ false ].
+	^ tokenClass = anotherNode tokenClass.
+!
+
+hash
+	^ super hash bitXor: tokenClass hash
+! !
+