RegressionTests__FloatTest.st
author Stefan Vogel <sv@exept.de>
Sat, 30 Oct 2004 16:10:24 +0200
changeset 255 f9c2f38ffcfd
parent 203 10c8e5197b62
child 257 94924ee6840b
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."

    |shouldBeFloatNaN shouldBeLongFloatNaN shouldBeShortFloatNaN|

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

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

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

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

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

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

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

"/ mhmh - the following are not true (they silently return NaNs).
"/    self should:[ shouldBeFloatNaN + 1 ] raise:DomainError.
"/    self should:[ shouldBeFloatNaN + 1.0 ] raise:DomainError.
"/    self should:[ shouldBeFloatNaN + 1.0 asShortFloat ] raise:DomainError.
"/    self should:[ shouldBeFloatNaN + 1.0 asLongFloat ] raise:DomainError.
"/
"/    self should:[ shouldBeFloatNaN - 1 ] raise:DomainError.
"/    self should:[ shouldBeFloatNaN - 1.0 ] raise:DomainError.
"/    self should:[ shouldBeFloatNaN - 1.0 asShortFloat ] raise:DomainError.
"/    self should:[ shouldBeFloatNaN - 1.0 asLongFloat ] raise:DomainError.

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

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


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

    self assert:( shouldBeShortFloatNaN + 1 ) isNaN.
    self assert:( shouldBeShortFloatNaN + 1.0 ) isNaN.
    self assert:( shouldBeShortFloatNaN + 1.0 asShortFloat ) isNaN.
    self assert:( shouldBeShortFloatNaN + 1.0 asLongFloat ) isNaN.

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

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

    self assert:( shouldBeLongFloatNaN + 1 ) isNaN.
    self assert:( shouldBeLongFloatNaN + 1.0 ) isNaN.
    self assert:( shouldBeLongFloatNaN + 1.0 asShortFloat ) isNaN.
    self assert:( shouldBeLongFloatNaN + 1.0 asLongFloat ) isNaN.

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

    "
     self basicNew test01_Nan
    "
!

test02_Inf
    "Infinity in all avaliable formats."

    |check posInf negInf|

    check := 
        [:v1 :v2 |

            posInf := v1 uncheckedDivide: v2.

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

            negInf := v1 negated uncheckedDivide: v2.

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

            self assert:( negInf + negInf = negInf).
            self assert:( posInf + posInf = posInf).
            self assert:( negInf + posInf) isNaN.
            self assert:( posInf + negInf) isNaN.

            self assert:( negInf - posInf = negInf).
            self assert:( negInf - negInf) isNaN.
            self assert:( posInf - negInf = posInf).
            self assert:( posInf - posInf) isNaN.

            self assert:( posInf + v1) = posInf.
            self assert:( posInf - v1) = posInf.
            self assert:( negInf + v1) = negInf.
            self assert:( negInf - v1) = negInf.
        ].

    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 assert: ((5/9) asFloat     - 0.555555555555) abs < 0.0000000001.
    self assert: ((5/9) asLongFloat - 0.555555555555) abs < 0.0000000001.
    self assert: ((Fraction basicNew setNumerator:500000000000 denominator:900000000000)
                        asLongFloat - 0.555555555555) abs <  0.000000000001.
    self assert: ((Fraction basicNew setNumerator:500000000001 denominator:900000000000)
                        asLongFloat - 0.555555555555) abs >= 0.000000000001.

    self assert: (8901234567890123456 asLongFloat asInteger = 8901234567890123456).    
    self assert: (-8901234567890123456 asLongFloat asInteger = -8901234567890123456).

    self assert: (89012345678901234567 asLongFloat = 89012345678901234567).    
    self assert: (-89012345678901234567 asLongFloat = -89012345678901234567).
    self assert: (89012345678901234567 negated asLongFloat = -89012345678901234567).

    self assert: ((89012345678901234567 / 123456789123456789) asLongFloat  - (89012345678901234567 asLongFloat / 123456789123456789 asLongFloat) ) abs < 0.000000000001.
    self assert: ((-89012345678901234567 / 123456789123456789) asLongFloat - (-89012345678901234567 asLongFloat / 123456789123456789 asLongFloat)) abs < 0.000000000001.

    "
     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
    |check v1 v2 v1b|

    check := [:iv1 :iv2|
        #(yourself asInteger asFloat asShortFloat asLongFloat asLargeFloat) do:[:conv1 |
            v1 := (iv1 perform:conv1).

            self assert:( v1 = nil ) not.
            self assert:( nil = v1 ) not.
            self assert:( v1 ~= nil ).
            self assert:( nil ~= v1 ).

            #(yourself asInteger asFloat asShortFloat asLongFloat asLargeFloat) do:[:conv2 |
                v1b := (iv1 perform:conv2).

                self assert:( v1 = v1b ).
                self assert:( v1 <= v1b ).
                self assert:( v1 >= v1b ).

                v2 := (iv2 perform:conv2).

                self assert:( v1 < v2 ).
                self assert:( v1 <= v2 ).
                self assert:( v2 >= v1 ).
                self assert:( v2 > v1 ).
            ]
        ].
    ].

    check value:2 value:3.
    check value:0 value:1.
    check value:-1 value:0.
    check value:-3 value:-2.
    check value:-3 value:3.

    check value:-30 value:1.
    check value:-1 value:30.

    self assert:( 200000000000000000000.0 = 200000000000000000000 ).
    self assert:( 200000000000000000000.0 asLongFloat = 200000000000000000000 ).
    self assert:( 2000000.0 asShortFloat = 2000000 ).

    self assert:( 200000000000000000000 = 200000000000000000000.0).
    self assert:( 200000000000000000000 = 200000000000000000000.0 asLongFloat ).
    self assert:( 2000000 = 2000000.0 asShortFloat ).


    self assert:( 200000000000000000000.0 < 200000100000000000000 ).
    self assert:( 200000000000000000000.0 asLongFloat < 200000000000100000000 ).
    self assert:( 200000000000000000000.0 asShortFloat < 200001000000000000000 ).

    self assert:( 200000000000000000000 < 200001000000000000000.0).
    self assert:( 200000000000000000000 < 200001000000000000000.0 asLongFloat ).
    self assert:( 200000000000000000000 < 200001000000000000000.0 asShortFloat ).


    self assert:( 200000000000000000000.0 <= 200000100000000000000 ).
    self assert:( 200000000000000000000.0 <= 200000000000000000000 ).
    self assert:( 200000000000000000000.0 asLongFloat <= 200000000000000000001 ).
    self assert:( 200000000000000000000.0 asLongFloat <= 200000000000000000000 ).
    self assert:( 2000000.0 asShortFloat <= 200000100000000000000 ).
    self assert:( 2000000.0 asShortFloat <= 2000000 ).

    self assert:( 200000000000000000000 <= 200001000000000000000.0).
    self assert:( 200000000000000000000 <= 200000000000000000000.0).
    self assert:( 200000000000000000000 <= 200001000000000000000.0 asLongFloat ).
    self assert:( 200000000000000000000 <= 200000000000000000000.0 asLongFloat ).
    self assert:( 2000000 <= 2000000.0 asShortFloat ).
    self assert:( 2000000 <= 2000000.0 asShortFloat ).

    "
     self basicNew test05_Comparing
    "
!

test06_MiscMath
    #(
        sqrt       0.5
        exp        0.5
        ln         0.5
        log10      0.5
        sin        0.5
        cos        0.5
        tan        0.5
        arcSin     0.5
        arcCos     0.5
        arcTan     0.5
        sinh       0.5 
        cosh       0.5
        tanh       0.5
        arcSinh    0.5
        arcCosh    1.5
        arcTanh    0.5

        sin        0.0
        cos        0.0
        tan        0.0
        sinh       0.0 
        cosh       0.0
        tanh       0.0

        sin        1.0
        cos        1.0
        tan        1.0
        sinh       1.0 
        cosh       1.0
        tanh       1.0

    ) pairWiseDo:[:op :arg |
        self assert:( arg perform:op ) class == Float.
        self assert:( arg asShortFloat perform:op ) class == Float.
"/        self assert:( arg asLongFloat perform:op ) class == LongFloat.
        ( arg asLongFloat perform:op ) class == LongFloat ifFalse:[
            Transcript showCR:'warning: missing LongFloat function: ' , op.
        ].

        self assert:( (arg perform:op) - (arg asShortFloat perform:op) ) < 0.000001.
        self assert:( (arg perform:op) - (arg asLongFloat perform:op) ) < 0.000001.
"/        self assert:( (arg perform:op) - (arg asLargeFloat perform:op) ) < 0.000001.
        self assert:( (arg perform:op) - (arg perform:op) asShortFloat ) < 0.000001.
        self assert:( (arg perform:op) - (arg perform:op) asLongFloat ) < 0.000001.
        self assert:( (arg perform:op) - (arg perform:op) asLargeFloat ) < 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
    "
!

test08_Representation
    self assert:( 0.0 exponent = 0 ).
    self assert:( 1.0 exponent = 1 ).
    self assert:( 2.0 exponent = 2 ).
    self assert:( 3.0 exponent = 2 ).
    self assert:( 4.0 exponent = 3 ).
    self assert:( 0.5 exponent = 0 ).
    self assert:( 0.4 exponent = -1 ).
    self assert:( 0.25 exponent = -1 ).
    self assert:( 0.125 exponent = -2 ).
    self assert:( 0.00000011111 exponent = -23 ).

    self assert:( 0.0 asShortFloat exponent = 0 ).      
    self assert:( 1.0 asShortFloat exponent = 1 ).
    self assert:( 2.0 asShortFloat exponent = 2 ).
    self assert:( 3.0 asShortFloat exponent = 2 ).
    self assert:( 4.0 asShortFloat exponent = 3 ).
    self assert:( 0.5 asShortFloat exponent = 0 ).
    self assert:( 0.4 asShortFloat exponent = -1 ).
    self assert:( 0.25 asShortFloat exponent = -1 ).
    self assert:( 0.125 asShortFloat exponent = -2 ).
    self assert:( 0.00000011111 asShortFloat exponent = -23 ).

    self assert:( 0.0 asLongFloat exponent = 0 ).      
    self assert:( 1.0 asLongFloat exponent = 1 ).
    self assert:( 2.0 asLongFloat exponent = 2 ).
    self assert:( 3.0 asLongFloat exponent = 2 ).
    self assert:( 4.0 asLongFloat exponent = 3 ).
    self assert:( 0.5 asLongFloat exponent = 0 ).
    self assert:( 0.4 asLongFloat exponent = -1 ).
    self assert:( 0.25 asLongFloat exponent = -1 ).
    self assert:( 0.125 asLongFloat exponent = -2 ).
    self assert:( 0.00000011111 asLongFloat exponent = -23 ).

    "
     self basicNew test08_Representation
    "
! !

!FloatTest class methodsFor:'documentation'!

version
    ^ '$Header$'
! !