RegressionTests__FloatTest.st
author Claus Gittinger <cg@exept.de>
Tue, 17 Jun 2003 10:19:21 +0200
changeset 194 12598a62d57a
parent 192 403ba5cd66c4
child 195 c1b18c70ebc1
permissions -rw-r--r--
*** empty log message ***

"{ Package: 'exept:regression' }"

"{ NameSpace: RegressionTests }"

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


!FloatTest methodsFor:'helpers'!

actualPrecisionOf:aFloatClass
    "get the actual number of valid bits in the mantissa.
     This does a real test (i.e. does not believe the compiled-in ifdefs)"

    |one half x count|

    one := aFloatClass unity.  "/ 1.0 in this class
    half := one coerce:0.5.
    x := one.    
    count := 0.

    [ one + x ~= one] whileTrue:[
        x := x * half.
        count := count + 1.
    ].
    ^ count

    "
     self basicNew actualPrecisionOf:ShortFloat 
     self basicNew actualPrecisionOf:Float      
     self basicNew actualPrecisionOf:LongFloat   
    "
! !

!FloatTest methodsFor:'tests'!

test00_Precision
    "computed precision vs. assumed precision."

    self assert:( Float precision == (self actualPrecisionOf:Float)).
    self assert:( ShortFloat precision == (self actualPrecisionOf:ShortFloat)).
    self assert:( LongFloat precision == (self actualPrecisionOf:LongFloat)).

    "
     self basicNew test00_Precision
    "
!

test01_Nan
    "NaN in all avaliable formats."

    |shouldBeNaN|

    shouldBeNaN := 0.0 uncheckedDivide: 0.0.
    self assert:( shouldBeNaN isMemberOf:Float ).
    self assert:( shouldBeNaN isNaN ).
    self assert:( shouldBeNaN isFinite not ).

    shouldBeNaN := 0.0 asShortFloat uncheckedDivide: 0.0 asShortFloat.
    self assert:( shouldBeNaN isMemberOf:ShortFloat ).
    self assert:( shouldBeNaN isNaN ).
    self assert:( shouldBeNaN isFinite not ).

    shouldBeNaN := 0.0 asLongFloat uncheckedDivide: 0.0 asLongFloat.
    self assert:( shouldBeNaN isMemberOf:LongFloat ).
    self assert:( shouldBeNaN isNaN ).
    self assert:( shouldBeNaN isFinite not ).

    shouldBeNaN := 0.0 uncheckedDivide: 0.0.
    self assert:( shouldBeNaN isNaN ).
    self assert:( shouldBeNaN asShortFloat isNaN ).
    self assert:( shouldBeNaN asLongFloat isNaN ).

    shouldBeNaN := 0.0 asShortFloat uncheckedDivide: 0.0.
    self assert:( shouldBeNaN isNaN ).
    self assert:( shouldBeNaN asFloat isNaN ).
    self assert:( shouldBeNaN asLongFloat isNaN ).

    shouldBeNaN := 0.0 asLongFloat uncheckedDivide: 0.0.
    self assert:( shouldBeNaN isNaN ).
    self assert:( shouldBeNaN asShortFloat isNaN ).
    self assert:( shouldBeNaN asLongFloat isNaN ).

    shouldBeNaN := 0.0 uncheckedDivide: 0.0.
    self should:[ shouldBeNaN asInteger ] raise:DomainError.

"/ mhmh - the following are not true.
"/    self should:[ shouldBeNaN + 1 ] raise:DomainError.
"/    self should:[ shouldBeNaN + 1.0 ] raise:DomainError.
"/    self should:[ shouldBeNaN + 1.0 asShortFloat ] raise:DomainError.
"/    self should:[ shouldBeNaN + 1.0 asLongFloat ] raise:DomainError.
"/
"/    self should:[ shouldBeNaN - 1 ] raise:DomainError.
"/    self should:[ shouldBeNaN - 1.0 ] raise:DomainError.
"/    self should:[ shouldBeNaN - 1.0 asShortFloat ] raise:DomainError.
"/    self should:[ shouldBeNaN - 1.0 asLongFloat ] raise:DomainError.

    "/ but these are:
    self assert:( shouldBeNaN + 1 ) isNaN.
    self assert:( shouldBeNaN + 1.0 ) isNaN.
    self assert:( shouldBeNaN + 1.0 asShortFloat ) isNaN.
    self assert:( shouldBeNaN + 1.0 asLongFloat ) isNaN.

    self assert:( shouldBeNaN - 1 ) isNaN.
    self assert:( shouldBeNaN - 1.0 ) isNaN.
    self assert:( shouldBeNaN - 1.0 asShortFloat ) isNaN.
    self assert:( shouldBeNaN - 1.0 asLongFloat ) isNaN.

    "
     self basicNew test01_Nan
    "
!

test02_Inf
    "Infinity in all avaliable formats."

    |check shouldBeInf|

    check := 
        [:v1 :v2 |

            shouldBeInf := v1 uncheckedDivide: v2.

            self assert:( shouldBeInf isMemberOf:v1 class ).
            self assert:( shouldBeInf isNaN not ).
            self assert:( shouldBeInf isFinite not ).
            self assert:( shouldBeInf isInfinite ).
            self assert:( shouldBeInf positive ).
            self assert:( shouldBeInf negative not ).
            self assert:( shouldBeInf isNegativeInfinity not).
            self assert:( shouldBeInf isPositiveInfinity ).

            shouldBeInf := v1 negated uncheckedDivide: v2.

            self assert:( shouldBeInf isMemberOf:v1 class ).
            self assert:( shouldBeInf isNaN not ).
            self assert:( shouldBeInf isFinite not ).
            self assert:( shouldBeInf isInfinite ).
            self assert:( shouldBeInf positive not).
            self assert:( shouldBeInf negative ).
            self assert:( shouldBeInf isNegativeInfinity ).
            self assert:( shouldBeInf isPositiveInfinity not ).
        ].

    check value: 1.0 value: 0.0.
    check value: 1.0 asShortFloat value: 0.0 asShortFloat.
    check value: 1.0 asLongFloat value: 0.0 asLongFloat.

"/ these are not guaranteed to work with uncheckedDivide...
"/    check value: 1.0 value: 0.0 asShortFloat.
"/    check value: 1.0 value: 0.0 asLongFloat.
"/
"/    check value: 1.0 asShortFloat value: 0.0.
"/    check value: 1.0 asShortFloat value: 0.0 asLongFloat.
"/
"/    check value: 1.0 asLongFloat value: 0.0 asShortFloat.
"/    check value: 1.0 asLongFloat value: 0.0.

    "
     self basicNew test02_Inf
    "
!

test03_Conversion
    self assert:( 1.0 asTrueFraction == 1 ).
    self assert:( 2.0 asTrueFraction == 2 ).
    self assert:( 4.0 asTrueFraction == 4 ).
    self assert:( 8.0 asTrueFraction == 8 ).
    self assert:( 16.0 asTrueFraction == 16 ).
    self assert:( 1048576.0 asTrueFraction == 1048576 ).
    self assert:( 0.5 asTrueFraction = (1/2) ).
    self assert:( 0.25 asTrueFraction = (1/4) ).
    self assert:( 0.125 asTrueFraction = (1/8) ).

    self assert:( 1.0 asShortFloat asTrueFraction == 1 ).
    self assert:( 2.0 asShortFloat asTrueFraction == 2 ).
    self assert:( 4.0 asShortFloat asTrueFraction == 4 ).
    self assert:( 8.0 asShortFloat asTrueFraction == 8 ).
    self assert:( 16.0 asShortFloat asTrueFraction == 16 ).
    self assert:( 1048576.0 asShortFloat asTrueFraction == 1048576 ).
    self assert:( 0.5 asShortFloat asTrueFraction = (1/2) ).
    self assert:( 0.25 asShortFloat asTrueFraction = (1/4) ).
    self assert:( 0.125 asShortFloat asTrueFraction = (1/8) ).

    self assert:( 1.0 asLongFloat asTrueFraction == 1 ).
    self assert:( 2.0 asLongFloat asTrueFraction == 2 ).
    self assert:( 4.0 asLongFloat asTrueFraction == 4 ).
    self assert:( 8.0 asLongFloat asTrueFraction == 8 ).
    self assert:( 16.0 asLongFloat asTrueFraction == 16 ).
    self assert:( 1048576.0 asLongFloat asTrueFraction == 1048576 ).
    self assert:( 0.5 asLongFloat asTrueFraction = (1/2) ).
    self assert:( 0.25 asLongFloat asTrueFraction = (1/4) ).
    self assert:( 0.125 asLongFloat asTrueFraction = (1/8) ).

    "
     self basicNew test03_Conversion
    "
!

test04_Arithmetic
    self assert:( 1.0 + 1.0 ) class == Float.
    self assert:( 1.0 + 1.0 asShortFloat) class == Float.
    self assert:( 1.0 + 1.0 asLongFloat) class == LongFloat.
    self assert:( 1.0 + 1) class == Float.

    self assert:( 1.0 asShortFloat + 1.0 ) class == Float.
    self assert:( 1.0 asShortFloat + 1.0 asShortFloat) class == ShortFloat.
    self assert:( 1.0 asShortFloat + 1.0 asLongFloat) class == LongFloat.
    self assert:( 1.0 asShortFloat + 1) class == ShortFloat.

    self assert:( 1.0 asLongFloat + 1.0 ) class == LongFloat.
    self assert:( 1.0 asLongFloat + 1.0 asShortFloat ) class == LongFloat.
    self assert:( 1.0 asLongFloat + 1.0 asFloat ) class == LongFloat.
    self assert:( 1.0 asLongFloat + 1 ) class == LongFloat.


    self assert:( 1.0 - 1.0 ) class == Float.
    self assert:( 1.0 - 1.0 asShortFloat) class == Float.
    self assert:( 1.0 - 1.0 asLongFloat) class == LongFloat.
    self assert:( 1.0 - 1) class == Float.

    self assert:( 1.0 asShortFloat - 1.0 ) class == Float.
    self assert:( 1.0 asShortFloat - 1.0 asShortFloat) class == ShortFloat.
    self assert:( 1.0 asShortFloat - 1.0 asLongFloat) class == LongFloat.
    self assert:( 1.0 asShortFloat - 1) class == ShortFloat.

    self assert:( 1.0 asLongFloat - 1.0 ) class == LongFloat.
    self assert:( 1.0 asLongFloat - 1.0 asShortFloat ) class == LongFloat.
    self assert:( 1.0 asLongFloat - 1.0 asFloat ) class == LongFloat.
    self assert:( 1.0 asLongFloat - 1 ) class == LongFloat.


    self assert:( 1.0 * 1.0 ) class == Float.
    self assert:( 1.0 * 1.0 asShortFloat) class == Float.
    self assert:( 1.0 * 1.0 asLongFloat) class == LongFloat.
    self assert:( 1.0 * 1) class == Float.

    self assert:( 1.0 asShortFloat * 1.0 ) class == Float.
    self assert:( 1.0 asShortFloat * 1.0 asShortFloat) class == ShortFloat.
    self assert:( 1.0 asShortFloat * 1.0 asLongFloat) class == LongFloat.
    self assert:( 1.0 asShortFloat * 1) class == ShortFloat.

    self assert:( 1.0 asLongFloat * 1.0 ) class == LongFloat.
    self assert:( 1.0 asLongFloat * 1.0 asShortFloat ) class == LongFloat.
    self assert:( 1.0 asLongFloat * 1.0 asFloat ) class == LongFloat.
    self assert:( 1.0 asLongFloat * 1 ) class == LongFloat.


    self assert:( 1.0 / 1.0 ) class == Float.
    self assert:( 1.0 / 1.0 asShortFloat) class == Float.
    self assert:( 1.0 / 1.0 asLongFloat) class == LongFloat.
    self assert:( 1.0 / 1) class == Float.

    self assert:( 1.0 asShortFloat / 1.0 ) class == Float.
    self assert:( 1.0 asShortFloat / 1.0 asShortFloat) class == ShortFloat.
    self assert:( 1.0 asShortFloat / 1.0 asLongFloat) class == LongFloat.
    self assert:( 1.0 asShortFloat / 1) class == ShortFloat.

    self assert:( 1.0 asLongFloat / 1.0 ) class == LongFloat.
    self assert:( 1.0 asLongFloat / 1.0 asShortFloat ) class == LongFloat.
    self assert:( 1.0 asLongFloat / 1.0 asFloat ) class == LongFloat.
    self assert:( 1.0 asLongFloat / 1 ) class == LongFloat.

    "
     self basicNew test04_Arithmetic
    "
!

test05_Comparing
    self assert:( 2.0 = 2 ).
    self assert:( 2.0 = 2.0 asShortFloat ).
    self assert:( 2.0 = 2.0 asLongFloat ).

    self assert:( 2.0 asShortFloat = 2 ).
    self assert:( 2.0 asShortFloat = 2.0 asShortFloat ).
    self assert:( 2.0 asShortFloat = 2.0 asLongFloat ).

    self assert:( 2.0 asLongFloat = 2 ).
    self assert:( 2.0 asLongFloat = 2.0 asShortFloat ).
    self assert:( 2.0 asLongFloat = 2.0 asLongFloat ).

    self assert:( 2 asLongFloat = 2 ).
    self assert:( 2 asLongFloat = 2.0 asShortFloat ).
    self assert:( 2 asLongFloat = 2.0 asLongFloat ).

    "
     self basicNew test05_Comparing
    "
!

test06_MiscMath
    #(
        sqrt
        exp
        ln
        sin
        cos
        tan
        arcSin
        arcCos
        arcTan
    ) do:[:op |
        self assert:( 0.5 perform:op ) class == Float.
        self assert:( 0.5 asShortFloat perform:op ) class == Float.
        self assert:( 0.5 asLongFloat perform:op ) class == LongFloat.
        self assert:( (0.5 perform:op) - (0.5 asShortFloat perform:op) ) < 0.000001.
        self assert:( (0.5 perform:op) - (0.5 asLongFloat perform:op) ) < 0.000001.
        self assert:( (0.5 perform:op) - (0.5 perform:op) asShortFloat ) < 0.000001.
        self assert:( (0.5 perform:op) - (0.5 perform:op) asLongFloat ) < 0.000001.
    ]

    "
     self basicNew test06_MiscMath
    "
!

test07_Truncation
    |check|

    check := [:num |
        self assert:( num fractionPart + num truncated ) = num.
        self assert:( num fractionPart + num truncated ) class == num class.
    ].

    check value:1.6.
    check value:-1.6.

    check value:1.6 asShortFloat.
    check value:-1.6 asShortFloat.

    check value:1.6 asLongFloat.
    check value:-1.6 asLongFloat.


    self assert:( 1.6 ceiling ) = 2.
    self assert:( 1.6 asShortFloat ceiling ) = 2.
    self assert:( 1.6 asLongFloat ceiling ) = 2.

    self assert:( 1.6 ceilingAsFloat ) = 2.0.
    self assert:( 1.6 ceilingAsFloat ) class == Float.
    self assert:( 1.6 asShortFloat ceilingAsFloat ) = 2.0 asShortFloat.
    self assert:( 1.6 asShortFloat ceilingAsFloat ) class == ShortFloat.
    self assert:( 1.6 asLongFloat ceilingAsFloat ) = 2.0 asLongFloat.
    self assert:( 1.6 asLongFloat ceilingAsFloat ) class == LongFloat.


    self assert:( 1.6 floor ) = 1.
    self assert:( 1.6 asShortFloat floor ) = 1.
    self assert:( 1.6 asLongFloat floor ) = 1.

    self assert:( 1.6 floorAsFloat ) = 1.0.
    self assert:( 1.6 floorAsFloat ) class == Float.
    self assert:( 1.6 asShortFloat floorAsFloat ) = 1.0 asShortFloat.
    self assert:( 1.6 asShortFloat floorAsFloat ) class == ShortFloat.
    self assert:( 1.6 asLongFloat floorAsFloat ) = 1.0 asLongFloat.
    self assert:( 1.6 asLongFloat floorAsFloat ) class == LongFloat.


    self assert:( 0.4 rounded ) class == SmallInteger.    
    self assert:( 0.4 rounded = 0 ).    
    self assert:( 0.5 rounded = 1 ).     
    self assert:( 0.6 rounded = 1 ).     
    self assert:( -0.4 rounded = 0 ).    
    self assert:( -0.5 rounded = -1 ).    
    self assert:( -0.6 rounded = -1 ).    

    self assert:( 0.4 roundedAsFloat ) class == Float.    
    self assert:( 0.4 roundedAsFloat  = 0.0 ).    
    self assert:( 0.5 roundedAsFloat  = 1.0 ).    
    self assert:( 0.6 roundedAsFloat  = 1.0 ).    
    self assert:( -0.4 roundedAsFloat = 0 ).    
    self assert:( -0.5 roundedAsFloat = -1.0 ).    
    self assert:( -0.6 roundedAsFloat = -1.0 ).    

    self assert:( 0.4 asShortFloat rounded ) class == SmallInteger.    
    self assert:( 0.4 asShortFloat rounded = 0 ).    
    self assert:( 0.5 asShortFloat rounded = 1 ).     
    self assert:( 0.6 asShortFloat rounded = 1 ).     
    self assert:( -0.4 asShortFloat rounded = 0 ).    
    self assert:( -0.5 asShortFloat rounded = -1 ).    
    self assert:( -0.6 asShortFloat rounded = -1 ).    

    self assert:( 0.4 asShortFloat roundedAsFloat ) class == ShortFloat.    
    self assert:( 0.4 asShortFloat roundedAsFloat  = 0.0 ).    
    self assert:( 0.5 asShortFloat roundedAsFloat  = 1.0 ).    
    self assert:( 0.6 asShortFloat roundedAsFloat  = 1.0 ).    
    self assert:( -0.4 asShortFloat roundedAsFloat = 0 ).    
    self assert:( -0.5 asShortFloat roundedAsFloat = -1.0 ).    
    self assert:( -0.6 asShortFloat roundedAsFloat = -1.0 ).    

    self assert:( 0.4 asLongFloat rounded ) class == SmallInteger.    
    self assert:( 0.4 asLongFloat rounded = 0 ).    
    self assert:( 0.5 asLongFloat rounded = 1 ).     
    self assert:( 0.6 asLongFloat rounded = 1 ).     
    self assert:( -0.4 asLongFloat rounded = 0 ).    
    self assert:( -0.5 asLongFloat rounded = -1 ).    
    self assert:( -0.6 asLongFloat rounded = -1 ).    

    self assert:( 0.4 asLongFloat roundedAsFloat ) class == LongFloat.    
    self assert:( 0.4 asLongFloat roundedAsFloat  = 0.0 ).    
    self assert:( 0.5 asLongFloat roundedAsFloat  = 1.0 ).    
    self assert:( 0.6 asLongFloat roundedAsFloat  = 1.0 ).    
    self assert:( -0.4 asLongFloat roundedAsFloat = 0 ).    
    self assert:( -0.5 asLongFloat roundedAsFloat = -1.0 ).    
    self assert:( -0.6 asLongFloat roundedAsFloat = -1.0 ).    

    self assert:( 0.4 truncated ) class == SmallInteger.    
    self assert:( 0.4 truncated = 0 ).    
    self assert:( 0.5 truncated = 0 ).     
    self assert:( 0.6 truncated = 0 ).     
    self assert:( -0.4 truncated = 0 ).    
    self assert:( -0.5 truncated = 0 ).    
    self assert:( -0.6 truncated = 0 ).    

    self assert:( 0.4 truncatedAsFloat ) class == Float.    
    self assert:( 0.4 truncatedAsFloat  = 0.0 ).    
    self assert:( 0.5 truncatedAsFloat  = 0.0 ).    
    self assert:( 0.6 truncatedAsFloat  = 0.0 ).    
    self assert:( -0.4 truncatedAsFloat = 0 ).    
    self assert:( -0.5 truncatedAsFloat = 0.0 ).    
    self assert:( -0.6 truncatedAsFloat = 0.0 ).    

    self assert:( 0.4 asShortFloat truncated ) class == SmallInteger.    
    self assert:( 0.4 asShortFloat truncated = 0 ).    
    self assert:( 0.5 asShortFloat truncated = 0 ).     
    self assert:( 0.6 asShortFloat truncated = 0 ).     
    self assert:( -0.4 asShortFloat truncated = 0 ).    
    self assert:( -0.5 asShortFloat truncated = 0 ).    
    self assert:( -0.6 asShortFloat truncated = 0 ).    

    self assert:( 0.4 asShortFloat truncatedAsFloat ) class == ShortFloat.    
    self assert:( 0.4 asShortFloat truncatedAsFloat  = 0.0 ).    
    self assert:( 0.5 asShortFloat truncatedAsFloat  = 0.0 ).    
    self assert:( 0.6 asShortFloat truncatedAsFloat  = 0.0 ).    
    self assert:( -0.4 asShortFloat truncatedAsFloat = 0 ).    
    self assert:( -0.5 asShortFloat truncatedAsFloat = 0.0 ).    
    self assert:( -0.6 asShortFloat truncatedAsFloat = 0.0 ).    

    self assert:( 0.4 asLongFloat truncated ) class == SmallInteger.    
    self assert:( 0.4 asLongFloat truncated = 0 ).    
    self assert:( 0.5 asLongFloat truncated = 0 ).     
    self assert:( 0.6 asLongFloat truncated = 0 ).     
    self assert:( -0.4 asLongFloat truncated = 0 ).    
    self assert:( -0.5 asLongFloat truncated = 0 ).    
    self assert:( -0.6 asLongFloat truncated = 0 ).    

    self assert:( 0.4 asLongFloat truncatedAsFloat ) class == LongFloat.    
    self assert:( 0.4 asLongFloat truncatedAsFloat  = 0.0 ).    
    self assert:( 0.5 asLongFloat truncatedAsFloat  = 0.0 ).    
    self assert:( 0.6 asLongFloat truncatedAsFloat  = 0.0 ).    
    self assert:( -0.4 asLongFloat truncatedAsFloat = 0 ).    
    self assert:( -0.5 asLongFloat truncatedAsFloat = 0.0 ).    
    self assert:( -0.6 asLongFloat truncatedAsFloat = 0.0 ).    

    "
     self basicNew test07_Truncation
    "
! !

!FloatTest class methodsFor:'documentation'!

version
    ^ '$Header$'
! !