compiler/extensions.st
changeset 452 9f4558b3be66
parent 438 20598d7ce9fa
child 459 4751c407bb40
--- a/compiler/extensions.st	Thu Apr 30 23:43:14 2015 +0200
+++ b/compiler/extensions.st	Sun May 10 06:28:36 2015 +0100
@@ -3,237 +3,255 @@
 !Character methodsFor:'*petitcompiler'!
 
 ppcPrintable
-	^ self asInteger > 31 and: [ self asInteger < 127 ]
+    ^ self asInteger > 31 and: [ self asInteger < 127 ]
 ! !
 
 !Object methodsFor:'*petitcompiler'!
 
 isInlinedMethod
-	^ false
+    ^ false
 ! !
 
 !PPActionParser methodsFor:'*petitcompiler'!
 
 asCompilerNode
-	^ PPCActionNode new
-		name: self name;
-		block: block;
-		child: parser;
-		properties: properties;
-		yourself
+    ^ PPCActionNode new
+        name: self name;
+        block: block;
+        child: parser;
+        properties: properties;
+        parser: self;
+        yourself
 ! !
 
 !PPActionParser methodsFor:'*petitcompiler'!
 
 compileWith: aPetitCompiler
-	block isSymbol ifTrue: [  
-		^ aPetitCompiler compileSymbolBlock: block for: self 
-	].
-	^ aPetitCompiler compileBlock: block for: self
+    block isSymbol ifTrue: [  
+        ^ aPetitCompiler compileSymbolBlock: block for: self 
+    ].
+    ^ aPetitCompiler compileBlock: block for: self
 ! !
 
 !PPAndParser methodsFor:'*petitcompiler'!
 
 asCompilerNode
-	^ PPCAndNode new
-		name: self name;
-		child: parser;
-		yourself
+    ^ PPCAndNode new
+        name: self name;
+        child: parser;
+        yourself
 ! !
 
 !PPCharSetPredicate methodsFor:'*petitcompiler'!
 
 = anObject
-	self == anObject ifTrue: [ ^ true ].
-	self class == anObject class ifFalse: [ ^ false ].
-	^ classification = anObject classification
+    self == anObject ifTrue: [ ^ true ].
+    self class == anObject class ifFalse: [ ^ false ].
+    ^ classification = anObject classification
 ! !
 
 !PPCharSetPredicate methodsFor:'*petitcompiler'!
 
 block
-	^ block
+    ^ block
 ! !
 
 !PPCharSetPredicate methodsFor:'*petitcompiler'!
 
 classification
-	^ classification
+    ^ classification
 ! !
 
 !PPCharSetPredicate methodsFor:'*petitcompiler'!
 
 equals: anotherPredicate
-	self == anotherPredicate ifTrue: [ ^ true ].
-	self class == anotherPredicate class ifFalse: [ ^ false ].
-	
-	^ classification  = anotherPredicate classification.
+    self == anotherPredicate ifTrue: [ ^ true ].
+    self class == anotherPredicate class ifFalse: [ ^ false ].
+    
+    ^ classification  = anotherPredicate classification.
 ! !
 
 !PPCharSetPredicate methodsFor:'*petitcompiler'!
 
 hash
-	^ classification hash
+    ^ classification hash
 ! !
 
 !PPChoiceParser methodsFor:'*petitcompiler'!
 
 asCompilerNode
-	^ PPCChoiceNode new
-		name: self name;
-		children: parsers;
-		yourself
+    ^ PPCChoiceNode new
+        name: self name;
+        children: parsers;
+        parser: self;
+        yourself
 ! !
 
 !PPChoiceParser methodsFor:'*petitcompiler'!
 
 compileWith: aPetitCompiler
-	^ aPetitCompiler compileChoice: self
+    ^ aPetitCompiler compileChoice: self
 ! !
 
 !PPContext methodsFor:'*petitcompiler'!
 
 asCompiledParserContext
-	^ PPCContext new
-		stream: stream;
-		yourself
-		
+    ^ PPCContext new
+        stream: stream;
+        yourself
+        
 ! !
 
 !PPContext methodsFor:'*petitcompiler'!
 
 atWs
-	^ false
+    ^ false
 ! !
 
 !PPContext methodsFor:'*petitcompiler'!
 
 comment
-	^ self globalAt: #comment ifAbsent: [ nil ].
+    ^ self globalAt: #comment ifAbsent: [ nil ].
 ! !
 
 !PPContext methodsFor:'*petitcompiler'!
 
 comment: value
-	^ self globalAt: #comment put: value
+    ^ self globalAt: #comment put: value
 ! !
 
 !PPContext methodsFor:'*petitcompiler'!
 
 compiledParser
-	^ self globalAt: #compiledParser
+    ^ self globalAt: #compiledParser
 ! !
 
 !PPContext methodsFor:'*petitcompiler'!
 
 compiledParser: aPPParser
-	^ self globalAt: #compiledParser put: aPPParser
+    ^ self globalAt: #compiledParser put: aPPParser
 ! !
 
 !PPContext methodsFor:'*petitcompiler'!
 
 lwRemember
-	^ self position
+    ^ self position
 ! !
 
 !PPContext methodsFor:'*petitcompiler'!
 
 lwRestore: position
-	^ self position: position
+    ^ self position: position
 ! !
 
 !PPContext methodsFor:'*petitcompiler'!
 
 methodInvoked: whatever
-	"nothing to do"
+    "nothing to do"
 ! !
 
 !PPContext methodsFor:'*petitcompiler'!
 
 peek: anInteger
-	^ stream peek: anInteger
+    ^ stream peek: anInteger
 ! !
 
 !PPContext methodsFor:'*petitcompiler'!
 
 setWs
-	"nothing to do"
+    "nothing to do"
+! !
+
+!PPContext methodsFor:'*petitcompiler'!
+
+skipSeparators
+    ^ stream skipSeparators
 ! !
 
 !PPContext methodsFor:'*petitcompiler'!
 
 whitespace
-	^ self globalAt: #whitespace ifAbsent: [ nil ].
+    ^ self globalAt: #whitespace ifAbsent: [ nil ].
 ! !
 
 !PPContext methodsFor:'*petitcompiler'!
 
 whitespace: value
-	^ self globalAt: #whitespace put: value
+    ^ self globalAt: #whitespace put: value
 ! !
 
 !PPDelegateParser methodsFor:'*petitcompiler'!
 
 asCompilerNode
-	self class == PPDelegateParser ifTrue: [ 
-		^ PPCForwardNode new
-			name: self name;
-			child: parser;
-			yourself
-	].
-	^ super asCompilerNode 
+    self class == PPDelegateParser ifTrue: [ 
+        ^ PPCForwardNode new
+            name: self name;
+            child: parser;
+            yourself
+    ].
+    ^ super asCompilerNode 
 ! !
 
 !PPDelegateParser methodsFor:'*petitcompiler'!
 
 compileWith: aPetitCompiler
-	(self class == PPDelegateParser) ifTrue: [ 
-		(self name notNil and: [ parser name isNil ]) ifTrue: [ 
-			parser name: self name.
-			^ parser compileWith: aPetitCompiler.
-		].
+    (self class == PPDelegateParser) ifTrue: [ 
+        (self name notNil and: [ parser name isNil ]) ifTrue: [ 
+            parser name: self name.
+            ^ parser compileWith: aPetitCompiler.
+        ].
 
-		(self name notNil and: [ parser name notNil ]) ifTrue: [ 
-			^ aPetitCompiler compileDelegate: self.
-		]
-	].
-	^ super compileWith: aPetitCompiler.
+        (self name notNil and: [ parser name notNil ]) ifTrue: [ 
+            ^ aPetitCompiler compileDelegate: self.
+        ]
+    ].
+    ^ super compileWith: aPetitCompiler.
+! !
+
+!PPEndOfInputParser methodsFor:'*petitcompiler'!
+
+asCompilerNode
+    
+    ^ PPCEndOfInputNode new
+        name: self name;
+        child: parser;
+        yourself	
 ! !
 
 !PPEpsilonParser methodsFor:'*petitcompiler'!
 
 asCompilerNode
-	^ PPCNilNode new
+    ^ PPCNilNode new
 ! !
 
 !PPEpsilonParser methodsFor:'*petitcompiler'!
 
 compileWith: aPetitCompiler
-	^ aPetitCompiler compileNil
+    ^ aPetitCompiler compileNil
 ! !
 
 !PPFailure methodsFor:'*petitcompiler'!
 
 context: aPPContext
-	context := aPPContext
+    context := aPPContext
 ! !
 
 !PPFailure methodsFor:'*petitcompiler'!
 
 message: text
-	message := text
+    message := text
 ! !
 
 !PPFailure methodsFor:'*petitcompiler'!
 
 position: anInteger
-	position := anInteger
+    position := anInteger
 ! !
 
 !PPJavaWhitespaceParser methodsFor:'*petitcompiler'!
 
 = anotherParser
-	anotherParser == self ifTrue: [ ^ true ].
+    anotherParser == self ifTrue: [ ^ true ].
    anotherParser class = self class ifFalse: [ ^ false ].
  ^ anotherParser name = self name
 ! !
@@ -241,67 +259,67 @@
 !PPJavaWhitespaceParser methodsFor:'*petitcompiler'!
 
 hash
-	^ self name hash
+    ^ self name hash
 ! !
 
 !PPLiteralObjectParser methodsFor:'*petitcompiler'!
 
 asCompilerNode
-	^ PPCCharacterNode new
-		character: literal;
-		name: self name;
-		yourself
+    ^ PPCCharacterNode new
+        character: literal;
+        name: self name;
+        yourself
 ! !
 
 !PPLiteralObjectParser methodsFor:'*petitcompiler'!
 
 compileWith: aPetitCompiler
-	^ aPetitCompiler compileCharacter: literal.
+    ^ aPetitCompiler compileCharacter: literal.
 ! !
 
 !PPLiteralParser methodsFor:'*petitcompiler'!
 
 id
-	^ literal printString
+    ^ literal printString
 ! !
 
 !PPLiteralSequenceParser methodsFor:'*petitcompiler'!
 
 asCompilerNode
-	^ PPCLiteralNode new
-		literal: literal;
-		name: self name;
-		yourself
+    ^ PPCLiteralNode new
+        literal: literal;
+        name: self name;
+        yourself
 ! !
 
 !PPLiteralSequenceParser methodsFor:'*petitcompiler'!
 
 compileWith: aPetitCompiler
-	^ aPetitCompiler compileLiteral: literal.
+    ^ aPetitCompiler compileLiteral: literal.
 ! !
 
 !PPNotParser methodsFor:'*petitcompiler'!
 
 asCompilerNode
-	^ PPCNotNode new 
-		child: parser;
-		name: self name;
-		yourself
+    ^ PPCNotNode new 
+        child: parser;
+        name: self name;
+        yourself
 ! !
 
 !PPNotParser methodsFor:'*petitcompiler'!
 
 compileWith: aPetitCompiler
-	^ aPetitCompiler compileNot: self
+    ^ aPetitCompiler compileNot: self
 ! !
 
 !PPOptionalParser methodsFor:'*petitcompiler'!
 
 asCompilerNode
-	^ PPCOptionalNode new
-		name: self name;
-		child: parser;
-		yourself
+    ^ PPCOptionalNode new
+        name: self name;
+        child: parser;
+        yourself
 
 "	^ super asCompilerNode "
 ! !
@@ -309,264 +327,281 @@
 !PPOptionalParser methodsFor:'*petitcompiler'!
 
 compileWith: aPetitCompiler
-	^ aPetitCompiler compileOptional: self
+    ^ aPetitCompiler compileOptional: self
+! !
+
+!PPParser methodsFor:'*petitcompiler'!
+
+allNodesDo: aBlock seen: aSet
+    "Iterate over all the parse nodes of the receiver, do not visit and follow the ones contained in aSet."
+
+    (aSet includes: self) ifTrue: [ ^ self ].
+    aSet add: self.
+    aBlock value: self.
+    
+    self children do: [ :each | 
+        each allNodesDo: aBlock seen: aSet 
+    ]
 ! !
 
 !PPParser methodsFor:'*petitcompiler'!
 
 asCompilerNode
-	^ PPCUnknownNode new
-		parser: self;
-		name: self name;
-		yourself
+    ^ PPCUnknownNode new
+        parser: self;
+        name: self name;
+        yourself
 ! !
 
 !PPParser methodsFor:'*petitcompiler'!
 
 asCompilerTree
-	^ self transform: [ :p | p asCompilerNode  ]
+    ^ self transform: [ :p | p asCompilerNode  ]
 ! !
 
 !PPParser methodsFor:'*petitcompiler'!
 
 bridge
-	^ self
+    ^ self
 ! !
 
 !PPParser methodsFor:'*petitcompiler'!
 
 compile
-	^ self compile: PPCArguments default
+    ^ self compile: PPCArguments default
 ! !
 
 !PPParser methodsFor:'*petitcompiler'!
 
 compile: arguments
-	self assert: (arguments isKindOf: PPCArguments).
-	
-	^ PPCConfiguration default
-		arguments: arguments;
-		compile: self
+    self assert: (arguments isKindOf: PPCArguments).
+    
+    ^ PPCConfiguration default
+        arguments: arguments;
+        compile: self
 ! !
 
 !PPParser methodsFor:'*petitcompiler'!
 
 compile: arguments andParse: input
-	^ (self compile: arguments) parse: input
+    ^ (self compile: arguments) parse: input
 ! !
 
 !PPParser methodsFor:'*petitcompiler'!
 
 compileAs: name
-	| arguments |
-	arguments := PPCArguments default.
-	arguments name: name.
-	
-	^ self compile: arguments
+    | arguments |
+    arguments := PPCArguments default.
+    arguments name: name.
+    
+    ^ self compile: arguments
 ! !
 
 !PPParser methodsFor:'*petitcompiler'!
 
 compileWithConfiguration: configuration
-	^ configuration compile: self
+    ^ configuration compile: self
 ! !
 
 !PPParser methodsFor:'*petitcompiler'!
 
 firstSetSuchThat: block
-	^ self firstSetSuchThat: block into: (OrderedCollection new) openSet: IdentitySet new.
+    self halt: 'deprecated?'.
+    ^ self firstSetSuchThat: block into: (OrderedCollection new) openSet: IdentitySet new.
 ! !
 
 !PPParser methodsFor:'*petitcompiler'!
 
 firstSetSuchThat: block into: aCollection openSet: aSet
-	(aSet includes: self) ifTrue: [ ^ aCollection ].
-	aSet add: self.
-	
-	(block value: self) ifTrue: [aCollection add: self. ^ aCollection ].
-	self children do: [ :child | 
-		child firstSetSuchThat: block into: aCollection openSet: aSet 
-	].
-	^ aCollection
+    (aSet includes: self) ifTrue: [ ^ aCollection ].
+    aSet add: self.
+    
+    (block value: self) ifTrue: [aCollection add: self. ^ aCollection ].
+    self children do: [ :child | 
+        child firstSetSuchThat: block into: aCollection openSet: aSet 
+    ].
+    ^ aCollection
 ! !
 
 !PPParser methodsFor:'*petitcompiler'!
 
 id
-	self name ifNotNil: [ ^ self name ].
-	^ self hash asString
+    self name ifNotNil: [ ^ self name ].
+    ^ self hash asString
 ! !
 
 !PPParser methodsFor:'*petitcompiler'!
 
 isCompiled
-	^ false
+    ^ false
 ! !
 
 !PPParser methodsFor:'*petitcompiler'!
 
 isContextFree
-	^ self propertyAt: #isContextFree ifAbsentPut: 
-		[ self allParsers allSatisfy: [ :p | p isContextFreePrim ] ].
-	
+    ^ self propertyAt: #isContextFree ifAbsentPut: 
+        [ self allParsers allSatisfy: [ :p | p isContextFreePrim ] ].
+    
 ! !
 
 !PPParser methodsFor:'*petitcompiler'!
 
 isContextFreePrim
-	^ true
+    ^ true
 ! !
 
 !PPParser methodsFor:'*petitcompiler'!
 
 isToken
-	^ false
+    ^ false
 ! !
 
 !PPParser methodsFor:'*petitcompiler'!
 
 isTokenParser
-	^ false
+    ^ false
 ! !
 
 !PPParser methodsFor:'*petitcompiler'!
 
 javaToken
-	| ws |
-	ws := PPJavaWhitespaceParser new.
-	^ ((ws, ((PPTokenParser on: self) tokenClass: PPJavaToken; yourself), ws) ==> #second)
-		propertyAt: #'trimmingToken' put: true;
-		yourself
+    | ws |
+    ws := PPJavaWhitespaceParser new.
+    ^ ((ws, ((PPTokenParser on: self) tokenClass: PPJavaToken; yourself), ws) ==> #second)
+        propertyAt: #'trimmingToken' put: true;
+        yourself
 ! !
 
 !PPParser methodsFor:'*petitcompiler'!
 
 optimize
-	^ self copy
+    ^ self copy
 ! !
 
 !PPParser methodsFor:'*petitcompiler'!
 
 optimized
-	^ self copy
+    ^ self copy
 ! !
 
 !PPParser methodsFor:'*petitcompiler'!
 
 trimmingToken
-	| ws |
-	ws := #space asParser star.
-	^ ((ws, (PPTokenParser on: self), ws) ==> #second)
-		propertyAt: #trimmingToken put: true;
-		yourself
+    | ws |
+    ws := #space asParser star.
+    ^ ((ws, (PPTokenParser on: self), ws) ==> #second)
+        propertyAt: #trimmingToken put: true;
+        yourself
 ! !
 
 !PPPluggableParser methodsFor:'*petitcompiler'!
 
 acceptsEpsilon
-	^ true
+    ^ true
 ! !
 
 !PPPluggableParser methodsFor:'*petitcompiler'!
 
 asCompilerNode
-	^ PPCPluggableNode new
-		block: block;
-		name: self name;
-		yourself
+    ^ PPCPluggableNode new
+        block: block;
+        name: self name;
+        yourself
 ! !
 
 !PPPossessiveRepeatingParser methodsFor:'*petitcompiler'!
 
 asCompilerNode
-	((self min = 0) and: [ self max = SmallInteger maxVal ]) ifTrue: [
-		^ PPCStarNode new
-			name: self name;
-			child: parser;
-			yourself
-	].
+    ((self min = 0) and: [ self max = SmallInteger maxVal ]) ifTrue: [
+        ^ PPCStarNode new
+            name: self name;
+            child: parser;
+            parser: self;
+            yourself
+    ].
 
-	((self min = 1) and: [ self max = SmallInteger maxVal ]) ifTrue: [
-		^ PPCPlusNode new
-			name: self name;
-			child: parser;
-			yourself
-	].
-	^ super asCompilerNode
+    ((self min = 1) and: [ self max = SmallInteger maxVal ]) ifTrue: [
+        ^ PPCPlusNode new
+            name: self name;
+            child: parser;
+            parser: self;
+            yourself
+    ].
+    ^ super asCompilerNode
 ! !
 
 !PPPossessiveRepeatingParser methodsFor:'*petitcompiler'!
 
 compileWith: aPetitCompiler
-	((self min = 1) and: [ self max = SmallInteger maxVal ]) ifTrue: [
-		^ aPetitCompiler compilePlus: self.
-	].	
-	((self min = 0) and: [ self max = SmallInteger maxVal ]) ifTrue: [
-		^ aPetitCompiler compileStar: self.
-	].
+    ((self min = 1) and: [ self max = SmallInteger maxVal ]) ifTrue: [
+        ^ aPetitCompiler compilePlus: self.
+    ].	
+    ((self min = 0) and: [ self max = SmallInteger maxVal ]) ifTrue: [
+        ^ aPetitCompiler compileStar: self.
+    ].
 
-	^ super compileWith: aPetitCompiler.
+    ^ super compileWith: aPetitCompiler.
 ! !
 
 !PPPredicateObjectParser methodsFor:'*petitcompiler'!
 
 asCompilerNode
-	^ PPCPredicateNode new
-		name: self name;
-		predicate: predicate;
-		yourself
+    ^ PPCPredicateNode new
+        name: self name;
+        predicate: predicate;
+        yourself
 ! !
 
 !PPPredicateObjectParser methodsFor:'*petitcompiler'!
 
 compileWith: aPetitCompiler
-	(predicateMessage  = 'input expected') ifTrue: [  
-		^ aPetitCompiler compileAny.
-	].
-	^ aPetitCompiler compilePredicate: predicate.
+    (predicateMessage  = 'input expected') ifTrue: [  
+        ^ aPetitCompiler compileAny.
+    ].
+    ^ aPetitCompiler compilePredicate: predicate.
 ! !
 
 !PPPredicateObjectParser methodsFor:'*petitcompiler'!
 
 firstCharSet
-	^ predicate
+    ^ predicate
 ! !
 
 !PPPredicateObjectParser methodsFor:'*petitcompiler'!
 
 firstCharSetCached
-	^ predicate
+    ^ predicate
 ! !
 
 !PPSequenceParser methodsFor:'*petitcompiler'!
 
 asCompilerNode
-	^ PPCSequenceNode new
-		children: parsers;
-		name: self name;
-		properties: properties;
-		yourself
+    ^ PPCSequenceNode new
+        children: parsers;
+        name: self name;
+        properties: properties;
+        yourself
 ! !
 
 !PPSequenceParser methodsFor:'*petitcompiler'!
 
 compileWith: aPetitCompiler
-	^ aPetitCompiler compileSequence: self.
+    ^ aPetitCompiler compileSequence: self.
 ! !
 
 !PPSequenceParser methodsFor:'*petitcompiler'!
 
 firstSetSuchThat: block into: aCollection openSet: aSet
-	(aSet includes: self) ifTrue: [ ^ aCollection ].
-	aSet add: self.
-	
-	(block value: self) ifTrue: [ aCollection add: self. ^ aCollection ].
-	
-	self children do: [ :child | 
-		child firstSetSuchThat: block into: aCollection openSet: aSet.
-		child acceptsEpsilon ifFalse: [ ^ aCollection ]
-	].
-	^ aCollection
+    (aSet includes: self) ifTrue: [ ^ aCollection ].
+    aSet add: self.
+    
+    (block value: self) ifTrue: [ aCollection add: self. ^ aCollection ].
+    
+    self children do: [ :child | 
+        child firstSetSuchThat: block into: aCollection openSet: aSet.
+        child acceptsEpsilon ifFalse: [ ^ aCollection ]
+    ].
+    ^ aCollection
 ! !
 
 !PPSmalltalkGrammar methodsFor:'*petitcompiler'!
@@ -578,182 +613,189 @@
 !PPSmalltalkGrammar methodsFor:'*petitcompiler'!
 
 whitespace
-	^ #space asParser plus
+    ^ #space asParser plus
 ! !
 
 !PPSmalltalkTokenParser methodsFor:'*petitcompiler'!
 
 compileWith: aPetitCompiler
 
-	^ aPetitCompiler compileSmalltalkToken: self.
+    ^ aPetitCompiler compileSmalltalkToken: self.
 ! !
 
 !PPSmalltalkTokenParser methodsFor:'*petitcompiler'!
 
 parseOnX: aPPContext
-	| memento comments token |
+    | memento comments token |
 
-	memento := aPPContext remember.
-	comments := self
-		parseComments: #()
-		on: aPPContext.
-	token := super parseOn: aPPContext.
-	token isPetitFailure ifTrue: [
-		aPPContext restore: memento.
-		^ token ].
-	comments := self
-		parseComments: comments
-		on: aPPContext.
-	^ token comments: comments
+    memento := aPPContext remember.
+    comments := self
+        parseComments: #()
+        on: aPPContext.
+    token := super parseOn: aPPContext.
+    token isPetitFailure ifTrue: [
+        aPPContext restore: memento.
+        ^ token ].
+    comments := self
+        parseComments: comments
+        on: aPPContext.
+    ^ token comments: comments
 ! !
 
 !PPSmalltalkTokenParser methodsFor:'*petitcompiler'!
 
 whitespace
-	^ PPSmalltalkWhitespaceParser new
+    ^ PPSmalltalkWhitespaceParser new
 ! !
 
 !PPSmalltalkWhitespaceParser methodsFor:'*petitcompiler'!
 
 = anotherParser
-	anotherParser == self ifTrue: [ ^ true ].
-	anotherParser class = self class ifFalse: [ ^ false ].
+    anotherParser == self ifTrue: [ ^ true ].
+    anotherParser class = self class ifFalse: [ ^ false ].
  ^ anotherParser name = self name
 ! !
 
 !PPSmalltalkWhitespaceParser methodsFor:'*petitcompiler'!
 
 acceptsEpsilon
-	^ true
+    ^ true
 ! !
 
 !PPSmalltalkWhitespaceParser methodsFor:'*petitcompiler'!
 
 acceptsEpsilonOpenSet: set
-	^ true
+    ^ true
 ! !
 
 !PPSmalltalkWhitespaceParser methodsFor:'*petitcompiler'!
 
 firstCharSet
-	^ PPCharSetPredicate on: [:e | false ] 
+    ^ PPCharSetPredicate on: [:e | false ] 
+! !
+
+!PPSmalltalkWhitespaceParser methodsFor:'*petitcompiler'!
+
+hash
+    ^ self name hash
 ! !
 
 !PPStream methodsFor:'*petitcompiler'!
 
 peek: anInteger
-	| endPosition |
-	endPosition := position + anInteger  min:  readLimit.
-	^ collection copyFrom: position+1 to: endPosition.
+    | endPosition |
+    endPosition := position + anInteger  min:  readLimit.
+    ^ collection copyFrom: position+1 to: endPosition.
 ! !
 
 !PPToken methodsFor:'*petitcompiler'!
 
 = anObject
-	^ self class = anObject class and: [ self inputValue = anObject inputValue ]
+    ^ self class = anObject class and: [ self inputValue = anObject inputValue ]
 ! !
 
 !PPToken methodsFor:'*petitcompiler'!
 
 hash
-	^ self inputValue hash
+    ^ self inputValue hash
 ! !
 
 !PPToken methodsFor:'*petitcompiler'!
 
 isToken
-	^ true
+    ^ true
 ! !
 
 !PPTokenParser methodsFor:'*petitcompiler'!
 
 asCompilerNode
-	^ PPCTokenNode new
-		name: self name;
-		tokenClass: self tokenClass;
-		child: parser;
-		yourself
+    ^ PPCTokenNode new
+        name: self name;
+        tokenClass: self tokenClass;
+        child: parser;
+        yourself
 ! !
 
 !PPTokenParser methodsFor:'*petitcompiler'!
 
 displayName
-	^ 'TOKEN[', parser displayName, ']'
+    ^ 'TOKEN[', parser displayName, ']'
 ! !
 
 !PPTokenParser methodsFor:'*petitcompiler'!
 
 isFirstSetTerminal
-	^ false
+    ^ false
 ! !
 
 !PPTokenParser methodsFor:'*petitcompiler'!
 
 isTokenParser
-	^ true
+    ^ true
 ! !
 
 !PPTokenParser methodsFor:'*petitcompiler'!
 
 optimize
-	^ self transform: [ :each | each optimized ]
+    ^ self transform: [ :each | each optimized ]
 ! !
 
 !PPTokenParser methodsFor:'*petitcompiler'!
 
 parser
-	^ parser
+    ^ parser
 ! !
 
 !PPTokenParser methodsFor:'*petitcompiler'!
 
 startsWith: aCharacter
-	^ self first anySatisfy: [ :first | first startsWith: aCharacter ]
+    ^ self first anySatisfy: [ :first | first startsWith: aCharacter ]
 ! !
 
 !PPTokenParser methodsFor:'*petitcompiler'!
 
 whitespace
-	^ self class whitespace 
+    ^ self class whitespace 
 ! !
 
 !PPTrimmingParser methodsFor:'*petitcompiler'!
 
 asCompilerNode
-	^ PPCTrimNode new
-		child: parser;
-		name: self name;
-		yourself
+    ^ PPCTrimNode new
+        child: parser;
+        name: self name;
+        parser: self;
+        yourself
 ! !
 
 !UndefinedObject methodsFor:'*petitcompiler'!
 
 asInteger
-	^ 256
+    ^ 256
 ! !
 
 !UndefinedObject methodsFor:'*petitcompiler'!
 
 isAlphaNumeric
-	^ false
+    ^ false
 ! !
 
 !UndefinedObject methodsFor:'*petitcompiler'!
 
 isDigit
-	^ false
+    ^ false
 ! !
 
 !UndefinedObject methodsFor:'*petitcompiler'!
 
 isLetter
-	^ false
+    ^ false
 ! !
 
 !UndefinedObject methodsFor:'*petitcompiler'!
 
 isSeparator
-	^ false
+    ^ false
 ! !
 
 !stx_goodies_petitparser_compiler class methodsFor:'documentation'!