IRTransformTest.st
changeset 9 04518c7fb91c
parent 1 0dd36941955f
child 10 0fd549e0c784
--- a/IRTransformTest.st	Wed Feb 25 16:49:21 2009 +0000
+++ b/IRTransformTest.st	Mon Mar 30 14:47:18 2009 +0000
@@ -11,53 +11,38 @@
 !IRTransformTest methodsFor:'testing'!
 
 testAdd
-	
-	| iRMethod aCompiledMethod |
-
-	iRMethod := IRBuilder new
-		numRargs: 1;
-		addTemps: #(self);		"receiver and args declarations"
-		pushLiteral: 1;				
-		returnTop;
-		ir.
+    |iRMethod aCompiledMethod|
 
-	(iRMethod allSequences last) last delete.
-	(iRMethod allSequences last) last delete.
-
-	(iRMethod allSequences last)
-			add: (IRInstruction pushLiteral: 2).
-
-	(iRMethod allSequences last)
-			add: (IRInstruction returnTop).
-
-	aCompiledMethod := iRMethod compiledMethod.
-	self should: [(aCompiledMethod valueWithReceiver: nil arguments: #() ) = 2].
+    iRMethod := (IRBuilder new)
+                numRargs:1;
+                addTemps:#( #self );
+                pushLiteral:1;
+                returnTop;
+                ir.
+    (iRMethod allSequences last) last delete.
+    (iRMethod allSequences last) last delete.
+    (iRMethod allSequences last) add:(IRInstruction pushLiteral:2).
+    (iRMethod allSequences last) add:(IRInstruction returnTop).
+    aCompiledMethod := iRMethod compiledCode.
+    self should:[ (aCompiledMethod valueWithReceiver:nil arguments:#()) = 2 ].
 !
 
 testAddBefore
-	
-	| iRMethod aCompiledMethod ret |
-
-	iRMethod := IRBuilder new
-		numRargs: 1;
-		addTemps: #(self);		"receiver and args declarations"
-		pushLiteral: 1;				
-		returnTop;
-		ir.
+    |iRMethod aCompiledMethod ret|
 
-	(iRMethod allSequences last) last delete.
-	(iRMethod allSequences last) last delete.
-
-	ret :=  (IRInstruction returnTop).
-
-	(iRMethod allSequences last)
-			add: ret.
-
-	(iRMethod allSequences last)
-			add: (IRInstruction pushLiteral: 2) before: ret.
-
-	aCompiledMethod := iRMethod compiledMethod.
-	self should: [(aCompiledMethod valueWithReceiver: nil arguments: #() ) = 2].
+    iRMethod := (IRBuilder new)
+                numRargs:1;
+                addTemps:#( #self );
+                pushLiteral:1;
+                returnTop;
+                ir.
+    (iRMethod allSequences last) last delete.
+    (iRMethod allSequences last) last delete.
+    ret := (IRInstruction returnTop).
+    (iRMethod allSequences last) add:ret.
+    (iRMethod allSequences last) add:(IRInstruction pushLiteral:2) before:ret.
+    aCompiledMethod := iRMethod compiledCode.
+    self should:[ (aCompiledMethod valueWithReceiver:nil arguments:#()) = 2 ].
 !
 
 testAddIntructions
@@ -102,66 +87,53 @@
 !
 
 testAddIntructionsBeforeFromLList
-	
-	| iRMethod aCompiledMethod push llist col |
-
-	iRMethod := IRBuilder new
-		numRargs: 1;
-		addTemps: #(self);		"receiver and args declarations"
-		pushLiteral: 1;				
-		returnTop;
-		ir.
-
-	push := (iRMethod allSequences last) at: (iRMethod allSequences size - 1) .
+    |iRMethod aCompiledMethod push llist col|
 
-	llist := LinkedList new.
-	llist add: (IRInstruction pushLiteral: 2).
-	llist add: (IRInstruction returnTop).
-
-	col := llist asOrderedCollection.
-
-	(iRMethod allSequences last)
-			addInstructions:  col before: push.
-
-	aCompiledMethod := iRMethod compiledMethod.
-	self should: [(aCompiledMethod valueWithReceiver: nil arguments: #() ) = 2].
+    iRMethod := (IRBuilder new)
+                numRargs:1;
+                addTemps:#( #self );
+                pushLiteral:1;
+                returnTop;
+                ir.
+    push := (iRMethod allSequences last) at:(iRMethod allSequences size - 1).
+    llist := LinkedList new.
+    llist add:(IRInstruction pushLiteral:2).
+    llist add:(IRInstruction returnTop).
+    col := llist asOrderedCollection.
+    (iRMethod allSequences last) addInstructions:col before:push.
+    aCompiledMethod := iRMethod compiledCode.
+    self should:[ (aCompiledMethod valueWithReceiver:nil arguments:#()) = 2 ].
 !
 
 testDelete
-	
-	| iRMethod aCompiledMethod |
+    |iRMethod aCompiledMethod|
 
-	iRMethod := IRBuilder new
-		numRargs: 1;
-		addTemps: #(self);		"receiver and args declarations"
-		pushLiteral: 1;				
-		pushLiteral: 2;	
-		returnTop;
-		ir.
-
-	((iRMethod allSequences last) 
-		detect: [:each | each isConstant: [:c | c == 2]]) delete.
-			
-
-	aCompiledMethod := iRMethod compiledMethod.
-	self should: [(aCompiledMethod valueWithReceiver: nil arguments: #() ) = 1].
+    iRMethod := (IRBuilder new)
+                numRargs:1;
+                addTemps:#( #self );
+                pushLiteral:1;
+                pushLiteral:2;
+                returnTop;
+                ir.
+    ((iRMethod allSequences last) 
+        detect:[:each | each isConstant:[:c | c == 2 ] ]) delete.
+    aCompiledMethod := iRMethod compiledCode.
+    self should:[ (aCompiledMethod valueWithReceiver:nil arguments:#()) = 1 ].
 !
 
 testReplace
-	| iRMethod aCompiledMethod |
-	
-	iRMethod := IRBuilder new
-		numRargs: 1;
-		addTemps: #(self);		"receiver and args declarations"
-		pushLiteral: 1;				
-		returnTop;
-		ir.
-	
-	(iRMethod allSequences last at: 1) 
-			replaceWith: (IRInstruction pushLiteral: 2).
+    |iRMethod aCompiledMethod|
 
-	aCompiledMethod := iRMethod compiledMethod.
-	self should: [(aCompiledMethod valueWithReceiver: nil arguments: #() ) = 2].
+    iRMethod := (IRBuilder new)
+                numRargs:1;
+                addTemps:#( #self );
+                pushLiteral:1;
+                returnTop;
+                ir.
+    (iRMethod allSequences last at:1) 
+        replaceWith:(IRInstruction pushLiteral:2).
+    aCompiledMethod := iRMethod compiledCode.
+    self should:[ (aCompiledMethod valueWithReceiver:nil arguments:#()) = 2 ].
 !
 
 testReplaceInstr