IRTransformTest.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Wed, 11 Jun 2008 14:54:42 +0000
changeset 1 0dd36941955f
child 9 04518c7fb91c
permissions -rw-r--r--
Initial revision. All tests pass.

"{ Package: 'stx:goodies/newcompiler' }"

TestCase subclass:#IRTransformTest
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'NewCompiler-IR-Tests'
!


!IRTransformTest methodsFor:'testing'!

testAdd
	
	| iRMethod aCompiledMethod |

	iRMethod := IRBuilder new
		numRargs: 1;
		addTemps: #(self);		"receiver and args declarations"
		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 compiledMethod.
	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 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].
!

testAddIntructions
	
	| iRMethod aCompiledMethod |

	iRMethod := IRBuilder new
		numRargs: 1;
		addTemps: #(self);		"receiver and args declarations"
		pushLiteral: 1;				
		returnTop;
		ir.

	(iRMethod allSequences last) last delete.
	(iRMethod allSequences last) last delete.

	(iRMethod allSequences last)
			addInstructions: {(IRInstruction pushLiteral: 2). (IRInstruction returnTop)}.

	aCompiledMethod := iRMethod compiledMethod.
	self should: [(aCompiledMethod valueWithReceiver: nil arguments: #() ) = 2].
!

testAddIntructionsBefore
	
	| iRMethod aCompiledMethod push |

	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 allSequences last)
			addInstructions: {(IRInstruction pushLiteral: 2). (IRInstruction returnTop)} before: push.

	aCompiledMethod := iRMethod compiledMethod.
	self should: [(aCompiledMethod valueWithReceiver: nil arguments: #() ) = 2].
!

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) .

	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].
!

testDelete
	
	| 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].
!

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).

	aCompiledMethod := iRMethod compiledMethod.
	self should: [(aCompiledMethod valueWithReceiver: nil arguments: #() ) = 2].
!

testReplaceInstr
	
	| iRMethod aCompiledMethod |

	iRMethod := IRBuilder new
		numRargs: 1;
		addTemps: #(self);		"receiver and args declarations"
		pushLiteral: 1;				
		returnTop;
		ir.
	
	(iRMethod allSequences last at: 1) 
			replaceWithInstructions: {(IRInstruction pushLiteral: 2)}.

	aCompiledMethod := iRMethod compiledMethod.
	self should: [(aCompiledMethod valueWithReceiver: nil arguments: #() ) = 2].
! !

!IRTransformTest class methodsFor:'documentation'!

version
    ^'$Id$'
! !