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

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

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


!IRBuilderTest class methodsFor:'as yet unclassified'!

testToPush
	^TestToPush
!

testToPush: anObject

	TestToPush := anObject
! !

!IRBuilderTest methodsFor:'testing'!

halt
        "Redefinition for testing the #send:toSuperOf:"

    "Created: / 11-06-2008 / 16:08:52 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

isThisEverCalled
	"Redefinition for testing the #send:toSuperOf:"
!

testDup

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

	aCompiledMethod := iRMethod compiledMethod.

	self assert: (aCompiledMethod isKindOf: CompiledMethod).
     self assert: ((aCompiledMethod valueWithReceiver: nil arguments: #() ) = true).
	
!

testInstVar

        | aCompiledMethod irBuilder |
        irBuilder := IRBuilder new
                numRargs: 1;
                addTemps: #(self);              "receiver and args declarations"

                pushInstVar: 1;
                pushInstVar: 2;
                send: #+;
                
                returnTop;
                ir.

        aCompiledMethod := irBuilder compiledMethod.

        self assert: (aCompiledMethod isKindOf: CompiledMethod).
     self assert: ((aCompiledMethod valueWithReceiver: (3@4) arguments: #() ) = 7).

    "Modified: / 11-06-2008 / 13:16:41 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

testJumpAheadTo

	| iRMethod aCompiledMethod |
	iRMethod := IRBuilder new
		numRargs: 1;
		addTemps: #(self);		"receiver and args declarations"
		pushTemp: #self	;
			
		jumpAheadTo: #end;
		pushLiteral: 3;
		jumpAheadTarget: #end;	
		
		returnTop;
		ir.

	aCompiledMethod := iRMethod compiledMethod.

	self assert: (aCompiledMethod isKindOf: CompiledMethod).
     self assert: ((aCompiledMethod valueWithReceiver: nil arguments: #() ) = nil).
	
!

testJumpAheadToIf

	| iRMethod aCompiledMethod |
	iRMethod := IRBuilder new
		numRargs: 1;
		addTemps: #(self);		"receiver and args declarations"
		pushTemp: #self	;
		pushLiteral: true;
		
		"jumpAhaedTo pop the first element of thz stack"
		jumpAheadTo: #end if: true;
		pushLiteral: 3;
		jumpAheadTarget: #end;	
		
		returnTop;
		ir.

	aCompiledMethod := iRMethod compiledMethod.

	self assert: (aCompiledMethod isKindOf: CompiledMethod).
     self assert: ((aCompiledMethod valueWithReceiver: nil arguments: #() ) = nil).
	
!

testJumpBackTo

	| iRMethod aCompiledMethod |
	iRMethod := IRBuilder new
		numRargs: 1;
		addTemps: #(self);		"receiver and args declarations"
		pushTemp: #self	;
		pushLiteral: false;
		jumpBackTarget: #begin;
		
		"jumpAhaedTo pop the first element of the stack"
		jumpAheadTo: #end if: true;
		pushLiteral: true;
		jumpBackTo: #begin;
		jumpAheadTarget: #end;	
		
		returnTop;
		ir.

	aCompiledMethod := iRMethod compiledMethod.

	self assert: (aCompiledMethod isKindOf: CompiledMethod).
     self assert: ((aCompiledMethod valueWithReceiver: nil arguments: #() ) = nil).
	
!

testLiteralArray

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

	aCompiledMethod := iRMethod compiledMethod.

	self assert: (aCompiledMethod isKindOf: CompiledMethod).
     self assert: ((aCompiledMethod valueWithReceiver: nil arguments: #() ) = #(test 4 you)).

	
!

testLiteralBoolean

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

	aCompiledMethod := iRMethod compiledMethod.

	self assert: (aCompiledMethod isKindOf: CompiledMethod).
     self assert: ((aCompiledMethod valueWithReceiver: nil arguments: #() ) = true).

	
!

testLiteralCharacter

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

	aCompiledMethod := iRMethod compiledMethod.

	self assert: (aCompiledMethod isKindOf: CompiledMethod).
     self assert: ((aCompiledMethod valueWithReceiver: nil arguments: #() ) = $e).

	
!

testLiteralFloat

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

	aCompiledMethod := iRMethod compiledMethod.

	self assert: (aCompiledMethod isKindOf: CompiledMethod).
     self assert: ((aCompiledMethod valueWithReceiver: nil arguments: #() ) = 2.0).

	
!

testLiteralInteger

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

	aCompiledMethod := iRMethod compiledMethod.

	self assert: (aCompiledMethod isKindOf: CompiledMethod).
     self assert: ((aCompiledMethod valueWithReceiver: nil arguments: #() ) = 2).

	
!

testLiteralNil

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

	aCompiledMethod := iRMethod compiledMethod.

	self assert: (aCompiledMethod isKindOf: CompiledMethod).
     self assert: ((aCompiledMethod valueWithReceiver: 4 arguments: #() ) = nil).

	
!

testLiteralString

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

	aCompiledMethod := iRMethod compiledMethod.

	self assert: (aCompiledMethod isKindOf: CompiledMethod).
     self assert: ((aCompiledMethod valueWithReceiver: nil arguments: #() ) = 'hello').

	
!

testLiteralSymbole

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

	aCompiledMethod := iRMethod compiledMethod.

	self assert: (aCompiledMethod isKindOf: CompiledMethod).
     self assert: ((aCompiledMethod valueWithReceiver: nil arguments: #() ) = #you).

	
!

testLiteralVariableClass

	| iRMethod aCompiledMethod |
	iRMethod := IRBuilder new
		numRargs: 1;
		addTemps: #(self);		"receiver and args declarations"
			
		pushLiteralVariable: Object binding;	
		returnTop;
		ir.

	aCompiledMethod := iRMethod compiledMethod.

	self assert: (aCompiledMethod isKindOf: CompiledMethod).
     self assert: ((aCompiledMethod valueWithReceiver: nil arguments: #() ) = Object).

	
!

testLiteralVariableClassVariable

        | iRMethod aCompiledMethod |
        iRMethod := IRBuilder new
                numRargs: 1;
                addTemps: #(self);              "receiver and args declarations"
                        
                pushLiteralVariable: (ArithmeticValue bindingOf: #ArithmeticSignal);   
                returnTop;
                ir.

        aCompiledMethod := iRMethod compiledMethod.

        self assert: (aCompiledMethod isKindOf: CompiledMethod).
     self assert: ((aCompiledMethod valueWithReceiver: nil arguments: #() ) = ArithmeticValue arithmeticSignal).

    "Modified: / 11-06-2008 / 11:31:32 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

testLiteralVariableGlobale

        | iRMethod aCompiledMethod |
        iRMethod := IRBuilder new
                numRargs: 1;
                addTemps: #(self);              "receiver and args declarations"
                        
                pushLiteralVariable: Smalltalk binding;     
                returnTop;
                ir.

        aCompiledMethod := iRMethod compiledMethod.

        self assert: (aCompiledMethod isKindOf: CompiledMethod).
     self assert: ((aCompiledMethod valueWithReceiver: nil arguments: #() ) = Smalltalk).

    "Modified: / 11-06-2008 / 11:32:07 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

testPopTop

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

        aCompiledMethod := iRMethod compiledMethod.

        self assert: (aCompiledMethod isKindOf: CompiledMethod).
     self assert: ((aCompiledMethod valueWithReceiver: nil arguments: #() ) = true).

    "Modified: / 11-06-2008 / 13:22:11 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

testPushReceiver

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

	aCompiledMethod := iRMethod compiledMethod.
	
	receiver :=  (5@8).

	self assert: (aCompiledMethod isKindOf: CompiledMethod).
     self assert: ((aCompiledMethod valueWithReceiver: receiver arguments: #() ) == receiver).
!

testPushTempArgument

	| iRMethod aCompiledMethod  |
	iRMethod := IRBuilder new
		numRargs: 3;
		addTemps: #(self a b);		"receiver and args declarations"
		pushTemp: #a;
		pushTemp: #b;
		send: #+;
		returnTop;
		ir.

	aCompiledMethod := iRMethod compiledMethod.


	self assert: (aCompiledMethod isKindOf: CompiledMethod).
     self assert: ((aCompiledMethod valueWithReceiver: nil arguments: #(2 8) ) = 10).
	
!

testPushTempSelf

	| iRMethod aCompiledMethod |
	iRMethod := IRBuilder new
		numRargs: 1;
		addTemps: #(self);		"receiver and args declarations"
		pushTemp: #self;
		send: #class;
		returnTop;
		ir.

	aCompiledMethod := iRMethod compiledMethod.


	self assert: (aCompiledMethod isKindOf: CompiledMethod).
     self assert: ((aCompiledMethod valueWithReceiver: nil arguments: #() ) == UndefinedObject).
	
!

testPushTempTemp

	| iRMethod aCompiledMethod  |
	iRMethod := IRBuilder new
		numRargs: 1;
		addTemps: #(self a);		"receiver and args declarations"
	
		pushTemp: #a;

		returnTop;
		ir.

	aCompiledMethod := iRMethod compiledMethod.


	self assert: (aCompiledMethod isKindOf: CompiledMethod).
     self assert: ((aCompiledMethod valueWithReceiver: 5 arguments: #() ) = nil).
	
!

testPushThisContext

	| iRMethod aCompiledMethod  |
	iRMethod := IRBuilder new
		numRargs: 1;
		addTemps: #(self a);		"receiver and args declarations"
	
		pushThisContext;
		send: #receiver;

		returnTop;
		ir.

	aCompiledMethod := iRMethod compiledMethod.


	self assert: (aCompiledMethod isKindOf: CompiledMethod).
     self assert: ((aCompiledMethod valueWithReceiver: 5 arguments: #() ) = 5).
	
!

testPushThisEnv

        | iRMethod aCompiledMethod receiver |

        ^self.


        iRMethod := IRBuilder new
                numRargs: 1;
                addTemps: #(self);              "receiver and args declarations"
                pushThisContext;
                pushLiteral: 5;
                pushLiteral: ClosureEnvironment;
                pushLiteral: 1;
                send: #new:;
                send: #privSetInstVar:put:;
                pushThisEnv;
                returnTop;
                ir.

        aCompiledMethod := iRMethod compiledMethod.

        receiver := Object new.
        
        self assert: (aCompiledMethod isKindOf: CompiledMethod).
     self assert: ((aCompiledMethod valueWithReceiver: receiver arguments: #()) isKindOf: ClosureEnvironment)

    "Modified: / 11-06-2008 / 14:47:36 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

testSendSuper

        | iRMethod aCompiledMethod  |
        iRMethod := IRBuilder new
                numRargs: 1;
                addTemps: #(self);              "receiver and args declarations"
        
                pushReceiver;
                send: #halt toSuperOf: IRBuilderTest;

                returnTop;
                ir.

        aCompiledMethod := iRMethod compiledMethod.


        self assert: (aCompiledMethod isKindOf: CompiledMethod).
     self should: [(aCompiledMethod valueWithReceiver: (IRBuilderTest new) arguments: #())] raise: Error.

    "Modified: / 11-06-2008 / 16:09:12 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

testStorIntoVariable

	| iRMethod aCompiledMethod  |
	iRMethod := IRBuilder new
		numRargs: 1;
		addTemps: #(self);		"receiver and args declarations"
	
		pushLiteral: 4;
		storeIntoLiteralVariable: (IRBuilderTest bindingOf: #TestToPush);

		returnTop;
		ir.

	aCompiledMethod := iRMethod compiledMethod.


	self assert: (aCompiledMethod isKindOf: CompiledMethod).
     aCompiledMethod valueWithReceiver: nil arguments: #().
	self assert: (IRBuilderTest testToPush = 4).
	IRBuilderTest testToPush: nil.

	
!

testStoreTemp

        | iRMethod aCompiledMethod  |
        iRMethod := IRBuilder new
                numRargs: 1;
                addTemps: #(self a);            "receiver and args declarations"
        
                pushLiteral: 34;
                storeTemp: #a;
                pushTemp: #a;

                returnTop;
                ir.

        aCompiledMethod := iRMethod compiledMethod.

        self assert: (aCompiledMethod isKindOf: CompiledMethod).
     self assert: ((aCompiledMethod valueWithReceiver: nil arguments: #() ) = 34).

    "Modified: / 11-06-2008 / 16:24:43 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

testStoreThisEnv

        | iRMethod aCompiledMethod  |

        ^self.

        iRMethod := IRBuilder new
                numRargs: 1;
                addTemps: #(self a);            "receiver and args declarations"
                pushLiteral: ClosureEnvironment;
                pushLiteral: 1;
                send: #new:;
                storeThisEnv;
                pushThisContext;
                pushLiteral: 5;
                send: #privGetInstVar:;
                returnTop;
                ir.

        aCompiledMethod := iRMethod compiledMethod.

        self assert: (aCompiledMethod isKindOf: CompiledMethod).
     self assert: ((aCompiledMethod valueWithReceiver: nil arguments: #() ) isKindOf: ClosureEnvironment).

    "Modified: / 11-06-2008 / 14:47:51 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!IRBuilderTest class methodsFor:'documentation'!

version
    ^'$Id$'
! !