RegressionTests__BlockTest.st
author Claus Gittinger <cg@exept.de>
Thu, 31 Aug 2000 13:12:02 +0200
changeset 70 c677f96c4a0b
parent 69 ffbf7492f5e5
child 95 362e58ff28ba
permissions -rw-r--r--
*** empty log message ***

"{ Package: 'exept:regression' }"

"{ NameSpace: RegressionTests }"

Object subclass:#BlockTest
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Tests-Regression'
!


!BlockTest class methodsFor:'varArgBlocks'!

getVarArgBlock1
     |b|

     b := [:argList | Transcript 
			show:'invoked with args:'; 
			showCR:argList
	  ] asVarArgBlock.
     ^ b


!

getVarArgBlock2
     |b|

     b := [:argList | Transcript 
			show:'invoked with args:'; 
			showCR:argList.
		      argList
	  ] asVarArgBlock.
     ^ b


!

getVarArgBlock3
     |b|

     b := [:argList | Transcript 
			show:'invoked with args:'; 
			showCR:argList.
		      argList size
	  ] asVarArgBlock.
     ^ b


!

testAll
    self testVarArgBlocks.

    "
     self testAll
    "
!

testVarArgBlock1
    |b|

    b := self getVarArgBlock1.

    b value.
    b code notNil ifTrue:[
	Transcript showCR:'blocks code is jitted'
    ] ifFalse:[
	Transcript showCR:'*** blocks code is NOT jitted'
    ].

    b value.
    b value:'arg1'.
    b value:'arg1' value:'arg2' value:'arg3' value:'arg4'

    "
     self testVarArgBlock1
    "
!

testVarArgBlock2
    |b|

    b := self getVarArgBlock2.

    b value.
    b code notNil ifTrue:[
	Transcript showCR:'blocks code is jitted'
    ] ifFalse:[
	Transcript showCR:'*** blocks code is NOT jitted'
    ].

    b value     = #()  ifFalse:[ self halt ].
    (b value:1) = #(1) ifFalse:[ self halt ].
    (b value:1 value:2) = #(1 2) ifFalse:[ self halt ].
    (b value:1 value:2 value:3) = #(1 2 3) ifFalse:[ self halt ].
    (b value:1 value:2 value:3 value:4) = #(1 2 3 4) ifFalse:[ self halt ].
    (b valueWithArguments:#(1 2 3 4)) = #(1 2 3 4) ifFalse:[ self halt ].

    (b perform:#value)     = #()  ifFalse:[ self halt ].
    (b perform:#'value:' with:1) = #(1) ifFalse:[ self halt ].
    (b perform:#'value:value:' with:1 with:2) = #(1 2) ifFalse:[ self halt ].
    (b perform:#'value:value:value:' with:1 with:2 with:3) = #(1 2 3) ifFalse:[ self halt ].
    (b perform:#'value:value:value:value:' with:1 with:2 with:3 with:4) = #(1 2 3 4) ifFalse:[ self halt ].
    (b perform:#'valueWithArguments:' with:#(1 2 3 4)) = #(1 2 3 4) ifFalse:[ self halt ].

    "
     self testVarArgBlock2
    "
!

testVarArgBlock3
    |b|

    b := self getVarArgBlock3.

    b value.
    b code notNil ifTrue:[
	Transcript showCR:'blocks code is jitted'
    ] ifFalse:[
	Transcript showCR:'*** blocks code is NOT jitted'
    ].

    b value     = 0  ifFalse:[ self halt ].
    (b value:1) = 1 ifFalse:[ self halt ].
    (b value:1 value:2) = 2 ifFalse:[ self halt ].
    (b value:1 value:2 value:3) = 3 ifFalse:[ self halt ].
    (b value:1 value:2 value:3 value:4) = 4 ifFalse:[ self halt ].
    (b valueWithArguments:#(1 2 3 4)) = 4 ifFalse:[ self halt ].

    (b perform:#value)     = 0  ifFalse:[ self halt ].
    (b perform:#'value:' with:1) = 1 ifFalse:[ self halt ].
    (b perform:#'value:value:' with:1 with:2) = 2 ifFalse:[ self halt ].
    (b perform:#'value:value:value:' with:1 with:2 with:3) = 3 ifFalse:[ self halt ].
    (b perform:#'value:value:value:value:' with:1 with:2 with:3 with:4) = 4 ifFalse:[ self halt ].
    (b perform:#'valueWithArguments:' with:#(1 2 3 4)) = 4 ifFalse:[ self halt ].

    "
     self testVarArgBlock3
    "
!

testVarArgBlocks
    self testVarArgBlock1.
    self testVarArgBlock2.
    self testVarArgBlock3.

! !

!BlockTest class methodsFor:'documentation'!

version
    ^ '$Header$'
! !