RegressionTests__SmallIntegerTest.st
author sr
Wed, 15 Nov 2017 16:41:47 +0100
changeset 1890 9367c7639c2d
parent 1882 b4bb993596b6
child 2109 851570e26c15
permissions -rw-r--r--
removed not existing Class from project definition

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

"{ NameSpace: RegressionTests }"

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


!SmallIntegerTest class methodsFor:'others'!

version_CVS
    ^ '$Header$'
! !

!SmallIntegerTest methodsFor:'tests-arithmetic'!

testBitShift
    #(
	(1 1 2)
	(1 2 4)
	(1 3 8)
	(1 7 16r080)
	(1 8 16r100)
	(1 15 16r08000)
	(1 16 16r10000)
	(1 17 16r20000)
	(1 30 16r040000000)
	(1 31 16r080000000)
	(1 32 16r100000000)
	(1 33 16r200000000)

	(1 62 16r04000000000000000)
	(1 63 16r08000000000000000)
	(1 64 16r10000000000000000)
	(1 65 16r20000000000000000)

	(1 126 16r040000000000000000000000000000000)
	(1 127 16r080000000000000000000000000000000)
	(1 128 16r100000000000000000000000000000000)
	(1 129 16r200000000000000000000000000000000)

	(16r10 1 16r20)
	(16r10 2 16r40)
	(16r10 3 16r80)
	(16r10 7 16r0800)
	(16r10 8 16r1000)
	(16r10 15 16r080000)
	(16r10 16 16r100000)
	(16r10 17 16r200000)
	(16r10 30 16r0400000000)
	(16r10 31 16r0800000000)
	(16r10 32 16r1000000000)
	(16r10 33 16r2000000000)

	(16r10 62 16r040000000000000000)
	(16r10 63 16r080000000000000000)
	(16r10 64 16r100000000000000000)
	(16r10 65 16r200000000000000000)

	(16r10 126 16r0400000000000000000000000000000000)
	(16r10 127 16r0800000000000000000000000000000000)
	(16r10 128 16r1000000000000000000000000000000000)
	(16r10 129 16r2000000000000000000000000000000000)
    ) triplesDo:[:val :cnt :expected |
	|rslt1 rslt2|

	rslt1 := val bitShift:cnt.
	self assert:(rslt1 = expected).
	expected class == SmallInteger ifTrue:[
	    self assert:(rslt1 == expected)
	].
	rslt2 := rslt1 bitShift:cnt negated.
	self assert:(rslt2 = val).
	val class == SmallInteger ifTrue:[
	    self assert:(rslt2 == val)
	].
    ].
!

testBitShiftNegative
    #(
        (-1 1 -2)
        (-1 2 -4)
        (-1 3 -8)
        (-1 7 16r-080)
        (-1 8 16r-100)
        (-1 15 16r-08000)
        (-1 16 16r-10000)
        (-1 17 16r-20000)
        (-1 30 16r-040000000)
        (-1 31 16r-080000000)
        (-1 32 16r-100000000)
        (-1 33 16r-200000000)

        (-1 62 16r-04000000000000000)
        (-1 63 16r-08000000000000000)
        (-1 64 16r-10000000000000000)
        (-1 65 16r-20000000000000000)

        (-1 126 16r-040000000000000000000000000000000)
        (-1 127 16r-080000000000000000000000000000000)
        (-1 128 16r-100000000000000000000000000000000)
        (-1 129 16r-200000000000000000000000000000000)

        (16r-10 1 16r-20)
        (16r-10 2 16r-40)
        (16r-10 3 16r-80)
        (16r-10 7 16r-0800)
        (16r-10 8 16r-1000)
        (16r-10 15 16r-080000)
        (16r-10 16 16r-100000)
        (16r-10 17 16r-200000)
        (16r-10 30 16r-0400000000)
        (16r-10 31 16r-0800000000)
        (16r-10 32 16r-1000000000)
        (16r-10 33 16r-2000000000)

        (16r-10 62 16r-040000000000000000)
        (16r-10 63 16r-080000000000000000)
        (16r-10 64 16r-100000000000000000)
        (16r-10 65 16r-200000000000000000)

        (16r-10 126 16r-0400000000000000000000000000000000)
        (16r-10 127 16r-0800000000000000000000000000000000)
        (16r-10 128 16r-1000000000000000000000000000000000)
        (16r-10 129 16r-2000000000000000000000000000000000)
    ) triplesDo:[:val :cnt :expected |
        |rslt1 rslt2|

        rslt1 := val bitShift:cnt.
        self assert:(rslt1 = expected).
        expected class == SmallInteger ifTrue:[
            self assert:(rslt1 == expected)
        ].
        rslt2 := rslt1 bitShift:cnt negated.
        self assert:(rslt2 = val).
        val class == SmallInteger ifTrue:[
            self assert:(rslt2 == val)
        ].
    ].

    "Modified (format): / 19-09-2017 / 16:29:36 / stefan"
!

testDivide
        |zero us1 us2 us3 us4 usm2 usm4|

        "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 assert: 4 / -2 = -2.
        self assert: -4 / 2 = -2.
        self assert: -4 / -2 = 2.
        self should: [ 1 / zero ] raise: ZeroDivide.

        us1 := 1.
        us2 := 2.
        us3 := 3.
        us4 := 4.
        usm2 := -2.
        usm4 := -4.

        self assert: us2 / us1 = us2.
        self assert: (us3 / us2) isFraction.
        self assert: us4 / us2 = 2.
        self assert: us4 / usm2 = -2.
        self assert: usm4 / us2 = -2.
        self assert: usm4 / usm2 = 2.
!

testMultiply
    |i ii|

    #(
	16r3fff
	16r7fff
	16rffff
	16r3fffffff
	16r7fffffff
	16rffffffff
	16r20000000
	16r40000000
	16r80000000
	16r100000000
	16r20000001
	16r40000001
	16r80000001
	16r100000001

	"/ for 64 bit machines:
	16r3fffffffffffffff
	16r7fffffffffffffff
	16rffffffffffffffff
	16r2000000000000000
	16r4000000000000000
	16r8000000000000000
	16r10000000000000000
	16r2000000000000001
	16r4000000000000001
	16r8000000000000001
	16r10000000000000001
    ) 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 iNNN|

    #(
        16r1fffffff
        16r3fffffff
        16r7fffffff
        16rffffffff
        16r20000000
        16r40000000
        16r80000000
        16r100000000
        16r20000001
        16r40000001
        16r80000001
        16r100000001

        "/ for 64bit machines:
        16r3fffffffffffffff
        16r7fffffffffffffff
        16rffffffffffffffff
        16r2000000000000000
        16r4000000000000000
        16r8000000000000000
        16r10000000000000000
        16r2000000000000001
        16r4000000000000001
        16r8000000000000001
        16r10000000000000001
    ) do:[:x |
        i := x.
        iN := i negated.
        iNN := iN negated.
        iNNN := iNN negated.
        self assert:(i = iNN).
        i class == SmallInteger ifTrue:[
            self assert:(i == iNN).
        ].
        self assert:(iN = iNNN).
        iN class == SmallInteger ifTrue:[
            self assert:(iN == iNNN).
        ].
    ].
    self assert:(SmallInteger maxVal negated class == SmallInteger).
    self assert:(SmallInteger maxVal negated negated == SmallInteger maxVal).

    self assert:(SmallInteger maxVal negated -1 == SmallInteger minVal).
    self assert:(SmallInteger minVal negated negated class == SmallInteger).

    "Modified: / 28-02-2017 / 16:42:04 / cg"
! !

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

testMaxValPointerSizeConsistency
    SmallInteger maxBytes == 4 ifTrue:[
	self assert: ((SmallInteger maxBits == 31) or:[SmallInteger maxBits == 32]).
	self assert: (ExternalAddress pointerSize == 4).
    ] ifFalse:[
	self assert: ((SmallInteger maxBits == 63) or:[SmallInteger maxBits == 64]).
	self assert: (ExternalAddress pointerSize == 8).
    ]
!

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

    Smalltalk isSmalltalkX ifTrue:[
        SmallInteger maxBytes == 4 ifTrue:[
            self should: [SmallInteger minVal = 16r-40000000].
            self should: [SmallInteger minVal == 16r-40000000].
        ] ifFalse:[
            self should: [SmallInteger minVal = 16r-4000000000000000].
            self should: [SmallInteger minVal == 16r-4000000000000000].
        ].
    ] ifFalse:[
        self should: [SmallInteger minVal = 16r-40000000].
    ]

    "Modified (format): / 19-09-2017 / 16:29:45 / stefan"
!

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

!SmallIntegerTest class methodsFor:'documentation'!

version
    ^ '$Header$'
! !