compiler/benchmarks/PPCSmalltalkNoopParser.st
changeset 503 ff58cd9f1f3c
parent 477 b18b6cc7aabc
parent 502 1e45d3c96ec5
child 504 0fb1f0799fc1
--- a/compiler/benchmarks/PPCSmalltalkNoopParser.st	Fri Jun 19 08:13:39 2015 +0100
+++ b/compiler/benchmarks/PPCSmalltalkNoopParser.st	Fri Jul 24 15:37:23 2015 +0100
@@ -12,21 +12,21 @@
 !PPCSmalltalkNoopParser methodsFor:'accessing'!
 
 startExpression
-	"Make the sequence node has a method node as its parent and that the source is set."
+    "Make the sequence node has a method node as its parent and that the source is set."
 
-	^ ([ :stream | stream collection ] asParser and , super startExpression) map: [ :source :node | 
-		(RBMethodNode selector: #doIt body: node)
-			source: source.
-		(node statements size = 1 and: [ node temporaries isEmpty ])
-			ifTrue: [ node statements first ]
-			ifFalse: [ node ] ]
+    ^ ([ :stream | stream collection ] asParser and , super startExpression) map: [ :source :node | 
+        (RBMethodNode selector: #doIt body: node)
+            source: source.
+        (node statements size = 1 and: [ node temporaries isEmpty ])
+            ifTrue: [ node statements first ]
+            ifFalse: [ node ] ]
 !
 
 startMethod
-	"Make sure the method node has the source code properly set."
-	
-	^ ([ :stream | stream collection ] asParser and , super startMethod)
-		map: [ :source :node | node source: source ]
+    "Make sure the method node has the source code properly set."
+    
+    ^ ([ :stream | stream collection ] asParser and , super startMethod)
+        map: [ :source :node | node source: source ]
 ! !
 
 !PPCSmalltalkNoopParser methodsFor:'grammar'!
@@ -100,7 +100,7 @@
 !
 
 blockArgument
-	^ super blockArgument ==> #second
+    ^ super blockArgument ==> #second
 !
 
 blockBody
@@ -213,107 +213,107 @@
 !PPCSmalltalkNoopParser methodsFor:'private'!
 
 addStatements: aCollection into: aNode
-	aCollection isNil 
-		ifTrue: [ ^ aNode ].
-	aCollection do: [ :each |
-		each class == PPSmalltalkToken
-			ifFalse: [ aNode addNode:  each ]
-			ifTrue: [
-				aNode statements isEmpty
-					ifTrue: [ aNode addComments: each comments ]
-					ifFalse: [ aNode statements last addComments: each comments ].
-				aNode periods: (aNode periods asOrderedCollection
-					addLast: each start;
-					yourself) ] ].
-	^ aNode
+    aCollection isNil 
+        ifTrue: [ ^ aNode ].
+    aCollection do: [ :each |
+        each class == PPSmalltalkToken
+            ifFalse: [ aNode addNode:  each ]
+            ifTrue: [
+                aNode statements isEmpty
+                    ifTrue: [ aNode addComments: each comments ]
+                    ifFalse: [ aNode statements last addComments: each comments ].
+                aNode periods: (aNode periods asOrderedCollection
+                    addLast: each start;
+                    yourself) ] ].
+    ^ aNode
 !
 
 build: aNode assignment: anArray
-	^ anArray isEmpty
-		ifTrue: [ aNode ]
-		ifFalse: [
-			anArray reverse 
-				inject: aNode
-				into: [ :result :each |
-					RBAssignmentNode 
-						variable: each first
-						value: result
-						position: each second start ] ]
+    ^ anArray isEmpty
+        ifTrue: [ aNode ]
+        ifFalse: [
+            anArray reverse 
+                inject: aNode
+                into: [ :result :each |
+                    RBAssignmentNode 
+                        variable: each first
+                        value: result
+                        position: each second start ] ]
 !
 
 build: aNode cascade: anArray 
-	| messages semicolons |
-	^ (anArray isNil or: [ anArray isEmpty ]) 
-		ifTrue: [ aNode ]
-		ifFalse: [
-			messages := OrderedCollection new: anArray size + 1.
-			messages addLast: aNode.
-			semicolons := OrderedCollection new.
-			anArray do: [ :each | 
-				messages addLast: (self 
-					build: aNode receiver
-					messages: (Array with: each second)).
-				semicolons addLast: each first start ].
-			RBCascadeNode messages: messages semicolons: semicolons ]
+    | messages semicolons |
+    ^ (anArray isNil or: [ anArray isEmpty ]) 
+        ifTrue: [ aNode ]
+        ifFalse: [
+            messages := OrderedCollection new: anArray size + 1.
+            messages addLast: aNode.
+            semicolons := OrderedCollection new.
+            anArray do: [ :each | 
+                messages addLast: (self 
+                    build: aNode receiver
+                    messages: (Array with: each second)).
+                semicolons addLast: each first start ].
+            RBCascadeNode messages: messages semicolons: semicolons ]
 !
 
 build: aNode messages: anArray 
-	^ (anArray isNil or: [ anArray isEmpty ]) 
-		ifTrue: [ aNode ]
-		ifFalse: [
-			anArray 
-				inject: aNode
-				into: [ :rec :msg | 
-					msg isNil 
-						ifTrue: [ rec ]
-						ifFalse: [
-							RBMessageNode 
-								receiver: rec
-								selectorParts: msg first
-								arguments: msg second ] ] ]
+    ^ (anArray isNil or: [ anArray isEmpty ]) 
+        ifTrue: [ aNode ]
+        ifFalse: [
+            anArray 
+                inject: aNode
+                into: [ :rec :msg | 
+                    msg isNil 
+                        ifTrue: [ rec ]
+                        ifFalse: [
+                            RBMessageNode 
+                                receiver: rec
+                                selectorParts: msg first
+                                arguments: msg second ] ] ]
 !
 
 build: aTempCollection sequence: aStatementCollection
-	| result |
-	result := self
-		addStatements: aStatementCollection
-		into: RBSequenceNode new.
-	aTempCollection isEmpty ifFalse: [
-		result
-			leftBar: aTempCollection first start
-			temporaries: aTempCollection second
-			rightBar: aTempCollection last start ].
-	^ result
+    | result |
+    result := self
+        addStatements: aStatementCollection
+        into: RBSequenceNode new.
+    aTempCollection isEmpty ifFalse: [
+        result
+            leftBar: aTempCollection first start
+            temporaries: aTempCollection second
+            rightBar: aTempCollection last start ].
+    ^ result
 !
 
 buildArray: aStatementCollection
-	^ self addStatements: aStatementCollection into: RBArrayNode new
+    ^ self addStatements: aStatementCollection into: RBArrayNode new
 !
 
 buildMethod: aMethodNode
-	aMethodNode selectorParts 
-		do: [ :each | aMethodNode addComments: each comments ].
-	aMethodNode arguments
-		do: [ :each | aMethodNode addComments: each token comments ].
-	aMethodNode pragmas do: [ :pragma |
-		aMethodNode addComments: pragma comments.
-		pragma selectorParts 
-			do: [ :each | aMethodNode addComments: each comments ].
-		pragma arguments do: [ :each | 
-			each isLiteralArray
-				ifFalse: [ aMethodNode addComments: each token comments ] ].
-		pragma comments: nil ].
-	^ aMethodNode
+    aMethodNode selectorParts 
+        do: [ :each | aMethodNode addComments: each comments ].
+    aMethodNode arguments
+        do: [ :each | aMethodNode addComments: each token comments ].
+    aMethodNode pragmas do: [ :pragma |
+        aMethodNode addComments: pragma comments.
+        pragma selectorParts 
+            do: [ :each | aMethodNode addComments: each comments ].
+        pragma arguments do: [ :each | 
+            each isLiteralArray
+                ifFalse: [ aMethodNode addComments: each token comments ] ].
+        pragma comments: nil ].
+    ^ aMethodNode
 !
 
 buildString: aString 
-	(aString isEmpty or: [ aString first ~= $' or: [ aString last ~= $' ] ])
-		ifTrue: [ ^ aString ].
-	^ (aString 
-		copyFrom: 2
-		to: aString size - 1) 
-		copyReplaceAll: ''''''
-		with: ''''
+    (aString isEmpty or: [ aString first ~= $' or: [ aString last ~= $' ] ])
+        ifTrue: [ ^ aString ].
+    ^ (aString 
+        copyFrom: 2
+        to: aString size - 1) 
+        copyReplaceAll: ''''''
+        with: ''''
 ! !
 
 !PPCSmalltalkNoopParser methodsFor:'token'!