RegressionTests__SmallIntegerTest.st
author Claus Gittinger <cg@exept.de>
Sat, 01 Mar 2014 14:58:32 +0100
changeset 1074 905aea054cf4
parent 619 f918fa22ad81
child 1223 708a62eac280
permissions -rw-r--r--
category

"{ Package: 'exept:regression' }"

"{ NameSpace: RegressionTests }"

TestCase subclass:#SmallIntegerTest
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'tests-Regression-Numbers'
!


!SmallIntegerTest class methodsFor:'others'!

version_CVS
    ^ '$Header$'
! !

!SmallIntegerTest methodsFor:'tests-arithmetic'!

testDivide
        |zero|

        "circumvent compiler error about division by zero"
        zero := 0.

        self assert: 2 / 1 = 2.
        self assert: (3 / 2) isFraction.
        self assert: 4 / 2 = 2.
        self should: [ 1 / zero ] raise: ZeroDivide.
!

testMultiply
    |i ii|

    #( 
        16r3fff
        16r7fff 
        16rffff 
        16r3fffffff
        16r7fffffff
        16rffffffff
        16r20000000
        16r40000000
        16r80000000
        16r100000000
        16r20000001
        16r40000001
        16r80000001
        16r100000001
    ) do:[:x |
        i := x.
        ii := i * i.
        self assert:((ii / i) = i).
        i class == SmallInteger ifTrue:[
            self assert:((ii / i) == i).
        ].

        i := x negated.
        ii := i * i.
        self assert:((ii / i) = i).
        i class == SmallInteger ifTrue:[
            self assert:((ii / i) == i).
        ].
    ].
!

testNegation
    |i iN iNN|

    #( 
        16r3fffffff
        16r7fffffff
        16rffffffff
        16r20000000
        16r40000000
        16r80000000
        16r100000000
        16r20000001
        16r40000001
        16r80000001
        16r100000001
    ) do:[:x |
        i := x.
        iN := i negated.
        iNN := iN negated.
        self assert:(i = iNN).
        i class == SmallInteger ifTrue:[
            self assert:(i == iNN).
        ].
    ].
! !

!SmallIntegerTest methodsFor:'tests-class protocol'!

testBasicNew
    self should: [SmallInteger basicNew] raise: TestResult error. 
!

testMaxVal
    "/ the original code did not check for pointer-size;

    Smalltalk isSmalltalkX ifTrue:[
        SmallInteger maxBytes == 4 ifTrue:[
            self should: [SmallInteger maxVal = 16r3FFFFFFF].
            self should: [SmallInteger maxVal == 16r3FFFFFFF].
        ] ifFalse:[
            self should: [SmallInteger maxVal = 16r3FFFFFFFFFFFFFFF].
            self should: [SmallInteger maxVal == 16r3FFFFFFFFFFFFFFF].
        ].
    ] ifFalse:[
        self should: [SmallInteger maxVal = 16r3FFFFFFF].
    ]
!

testMinVal
    "/ the original code did not check for pointer-size;

    Smalltalk isSmalltalkX ifTrue:[
        SmallInteger maxBytes == 4 ifTrue:[
            self should: [SmallInteger minVal = -16r40000000].
            self should: [SmallInteger minVal == -16r40000000].
        ] ifFalse:[
            self should: [SmallInteger minVal = -16r4000000000000000].
            self should: [SmallInteger minVal == -16r4000000000000000].
        ].
    ] ifFalse:[
        self should: [SmallInteger minVal = -16r40000000].
    ]
!

testNew
    self should: [SmallInteger new] raise: TestResult error. 
! !

!SmallIntegerTest class methodsFor:'documentation'!

version
    ^ '$Header$'
! !