compiler/PPCGuard.st
changeset 452 9f4558b3be66
parent 438 20598d7ce9fa
child 459 4751c407bb40
--- a/compiler/PPCGuard.st	Thu Apr 30 23:43:14 2015 +0200
+++ b/compiler/PPCGuard.st	Sun May 10 06:28:36 2015 +0100
@@ -12,104 +12,76 @@
 !PPCGuard class methodsFor:'as yet unclassified'!
 
 on: aPPCNode
-	^ self new
-		initializeFor: aPPCNode;
-		yourself
+    ^ self new
+        initializeFor: aPPCNode;
+        yourself
 ! !
 
 !PPCGuard methodsFor:'accessing'!
 
 classification
-	^ classification
+    ^ classification
 !
 
 id
-	
-	^ id
+    
+    ^ id
 !
 
 id: anObject
-	
-	id := anObject
+    
+    id := anObject
 !
 
 message
-	(message == #unknown) ifTrue: [ 
-		(self testMessage: #isLetter) ifTrue: [ ^ message := #isLetter ].
-		(self testMessage: #isAlphaNumeric) ifTrue: [ ^ message := #isAlphaNumeric ].
-		(self testMessage: #isDigit) ifTrue: [ ^ message := #isDigit ].
-		
-		^ message := nil.
-	].
-	^ message
+    (message == #unknown) ifTrue: [ 
+        (self testMessage: #isLetter) ifTrue: [ ^ message := #isLetter ].
+        (self testMessage: #isAlphaNumeric) ifTrue: [ ^ message := #isAlphaNumeric ].
+        (self testMessage: #isDigit) ifTrue: [ ^ message := #isDigit ].
+        
+        ^ message := nil.
+    ].
+    ^ message
 ! !
 
 !PPCGuard methodsFor:'as yet unclassified'!
 
 classificationOn: aBlock
-	classification := Array new: 255.
-	1 to: classification size do: [ :index |
-		classification at: index put: (aBlock
-			value: (Character value: index)) ].
+    classification := Array new: 255.
+    1 to: classification size do: [ :index |
+        classification at: index put: (aBlock
+            value: (Character value: index)) ].
 !
 
 compileAny: compiler
-	compiler add: '(context atEnd not)'.
+    compiler add: '(context atEnd not)'.
 !
 
 compileCharacter: compiler
-	self assert: (classification select: [ :e | e ]) size = 1.
-	
-	classification keysAndValuesDo: [ :index :value | value ifTrue: [  
-		(index > 32 and: [ index < 127 ]) ifTrue: [ 
-			compiler add: '(context peek = ', (Character value: index) storeString, ')'
-		] ifFalse: [ 
-			id := compiler idFor: (Character value: index) prefixed: #character.
-			compiler addConstant: (Character value: index) as: id.
-			compiler add: '(context peek = ', id, ')'.
-	 	] 
-	] ].
-
+    self assert: (classification select: [ :e | e ]) size = 1.
+    
+    classification keysAndValuesDo: [ :index :value | value ifTrue: [  
+        (index > 32 and: [ index < 127 ]) ifTrue: [ 
+            compiler add: '(context peek = ', (Character value: index) storeString, ')'
+        ] ifFalse: [ 
+            id := compiler idFor: (Character value: index) prefixed: #character.
+            compiler addConstant: (Character value: index) as: id.
+            compiler add: '(context peek = ', id, ')'.
+     	] 
+    ] ].
 !
 
 compileGuard: compiler id: symbol
-	self id: symbol.
-	^ self compileGuard: compiler
+    self id: symbol.
+    ^ self compileGuard: compiler
 !
 
 compileMessage: compiler
-	compiler add: '(context peek ', message, ')'
-!
-
-initializeFor: node
-	message := #unknown.
-	id := nil.
-	
-	"No Guards for trimming parser so far"
-	((node firstSetSuchThat: [ :e | e isKindOf: PPCTrimNode ]) isEmpty) ifFalse: [ 
-		^ self initializeForNoGuard 
-	].
-	(node acceptsEpsilon) ifTrue: [  
-		^ self initializeForEpsilon
-	].
-
-	self classificationOn: [:char | node firstSet anySatisfy: [:e | (e firstCharSetCached value: char) ]]
-
-"	self classificationOn: [ :char | node firstSet anySatisfy: [ :e |  (e firstCharParser parse: char asString) isPetitFailure not ] ]"
-!
-
-initializeForEpsilon
-	classification := nil
-	
-!
-
-initializeForNoGuard
-	classification := nil
-	
+    compiler add: '(context peek ', message, ')'
 !
 
 testAny
-	^ classification allSatisfy: [ :e | e ].
+    ^ classification allSatisfy: [ :e | e ].
 !
 
 testMessage: selector
@@ -122,33 +94,62 @@
 !
 
 testSingleCharacter
-	^ (classification select: [ :e | e ]) size = 1
+    ^ (classification select: [ :e | e ]) size = 1
 ! !
 
 !PPCGuard methodsFor:'code generation'!
 
 compileArray: compiler
-	| array |
-	self assert: id isNotNil.
+    | array |
+    self assert: id isNotNil.
 
-	array := ((classification asOrderedCollection) addLast: false; yourself) asArray.
-	compiler addConstant: array as: id.
-	compiler add: '(', id, ' at: context peek asInteger)'.
+    array := ((classification asOrderedCollection) addLast: false; yourself) asArray.
+    compiler addConstant: array as: id.
+    compiler add: '(', id, ' at: context peek asInteger)'.
 !
 
 compileGuard: compiler
-	self assert: self makesSense description: 'No Guard could be compiled'.
-	self assert: id notNil.
-	
-	
-	self message ifNotNil: [ ^ self compileMessage: compiler ].
-	self testAny ifTrue: [ ^ self compileAny: compiler ].
-	self testSingleCharacter ifTrue: [ ^ self compileCharacter: compiler ].
-	
-	^ self compileArray: compiler
+    self assert: self makesSense description: 'No Guard could be compiled'.
+    self assert: id notNil.
+    
+    
+    self message ifNotNil: [ ^ self compileMessage: compiler ].
+    self testAny ifTrue: [ ^ self compileAny: compiler ].
+    self testSingleCharacter ifTrue: [ ^ self compileCharacter: compiler ].
+    
+    ^ self compileArray: compiler
 !
 
 makesSense
-	^ classification isNil not
+    ^ classification isNil not
 ! !
 
+!PPCGuard methodsFor:'initialization'!
+
+initializeFor: node
+    message := #unknown.
+    id := nil.
+    
+    "No Guards for trimming parser so far"
+"	((node firstSetSuchThat: [ :e | e isKindOf: PPCTrimNode ]) isEmpty) ifFalse: [ 
+        ^ self initializeForNoGuard 
+    ]."
+    (node acceptsEpsilon) ifTrue: [  
+        ^ self initializeForEpsilon
+    ].
+
+    self classificationOn: [:char | node firstSet anySatisfy: [:e | (e firstCharSetCached value: char) ]]
+
+"	self classificationOn: [ :char | node firstSet anySatisfy: [ :e |  (e firstCharParser parse: char asString) isPetitFailure not ] ]"
+!
+
+initializeForEpsilon
+    classification := nil
+    
+!
+
+initializeForNoGuard
+    classification := nil
+    
+! !
+