RegressionTests__QuadFloatTest.st
author Claus Gittinger <cg@exept.de>
Tue, 09 Jul 2019 18:53:03 +0200
changeset 2327 bf482d49aeaf
parent 2311 fd628a61a55d
child 2411 4e2559b4b988
permissions -rw-r--r--
#QUALITY by exept class: RegressionTests::StringTests added: #test82c_expanding

"{ Encoding: utf8 }"

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

"{ NameSpace: RegressionTests }"

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

!QuadFloatTest class methodsFor:'documentation'!

documentation
"
    documentation to be added.

    class:
        <a short class summary here, describing what instances represent>

    responsibilities:    
        <describing what my main role is>

    collaborators:    
        <describing with whom and how I talk to>

    API:
        <public api and main messages>
        
    example:
        <a one-line examples on how to use - can also be in a separate example method>

    implementation:
        <implementation points>

    [author:]
        Claus Gittinger

    [instance variables:]

    [class variables:]

    [see also:]

"
! !

!QuadFloatTest class 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 x count|

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

    [one + x > one] whileTrue:[
        x := x / 2.
        count := count + 1.
    ].
    ^ count

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

!QuadFloatTest methodsFor:'helpers'!

setUp
    Error handle:[:ex |
        longFloatToQuadFloatSupported := false.
    ] do:[    
        0.0 asLongFloat asQuadFloat isZero.
        longFloatToQuadFloatSupported := true.
    ].

    "Created: / 08-06-2019 / 13:42:50 / Claus Gittinger"
! !

!QuadFloatTest methodsFor:'tests'!

test00_Precision
    "computed precision vs. assumed precision."

    |a b|

    self skipIf:(ExternalAddress pointerSize == 4) description:'only suported on 64bit machines'.
    
    self assert:( (a := QuadFloat precision) = (b := self class actualPrecisionOf:QuadFloat))
                description:('QuadFloat precision: %1 ~~ actual: %2' bindWith:a with:b).

    "
     self basicNew test00_Precision
    "

    "Modified: / 03-05-2012 / 18:47:21 / cg"
    "Modified: / 07-06-2019 / 03:22:43 / Claus Gittinger"
!

test01_Nan
    "NaN"

    |shouldBeQuadFloatNaN|

    self skipIf:(ExternalAddress pointerSize == 4) description:'only supported on 64bit machines'.

    self assert:( QuadFloat NaN isNaN ).
    self assert:( QuadFloat NaN isFinite not ).
    self assert:( QuadFloat NaN asFloat isNaN ).
    self assert:( QuadFloat NaN asShortFloat isNaN ).
    self should:[ QuadFloat NaN asInteger isNaN ] raise:Error.

    shouldBeQuadFloatNaN := 0.0 asQuadFloat uncheckedDivide: 0.0 asQuadFloat.
    self assert:( shouldBeQuadFloatNaN isMemberOf:QuadFloat ).
    self assert:( shouldBeQuadFloatNaN isNaN ).
    self assert:( shouldBeQuadFloatNaN isFinite not ).
    self assert:( shouldBeQuadFloatNaN asFloat isNaN ).
    self assert:( shouldBeQuadFloatNaN asShortFloat isNaN ).

    self assert:(QuadFloat zero isZero).
    self assert:(0.0 asQuadFloat isZero).
    
    shouldBeQuadFloatNaN := 0.0 asQuadFloat uncheckedDivide: 0.0.
    self assert:( shouldBeQuadFloatNaN isMemberOf:QuadFloat ).
    self assert:( shouldBeQuadFloatNaN isNaN ).
    self assert:( shouldBeQuadFloatNaN isFinite not ).
    self assert:( shouldBeQuadFloatNaN asFloat isNaN ).
    self assert:( shouldBeQuadFloatNaN asShortFloat isNaN ).

    self assert:( shouldBeQuadFloatNaN + 1 ) isNaN.
    self assert:( shouldBeQuadFloatNaN + 1.0 ) isNaN.
    self assert:( shouldBeQuadFloatNaN + 1.0 asShortFloat ) isNaN.

    self assert:( shouldBeQuadFloatNaN - 1 ) isNaN.
    self assert:( shouldBeQuadFloatNaN - 1.0 ) isNaN.
    self assert:( shouldBeQuadFloatNaN - 1.0 asShortFloat ) isNaN.

    "
     self basicNew test01_Nan
    "

    "Modified: / 20-06-2017 / 14:00:08 / cg"
    "Modified: / 10-06-2019 / 21:50:19 / Claus Gittinger"
!

test01b_Nan
    "NaN against longFloat"

    |shouldBeQuadFloatNaN|

    self skipIf:(ExternalAddress pointerSize == 4) description:'only supported on 64bit machines'.
    self skipIf:(longFloatToQuadFloatSupported not) description:'longFloat to quadFloat not yet supported'.
    
    self assert:( QuadFloat NaN isNaN ).

    shouldBeQuadFloatNaN := 0.0 asQuadFloat uncheckedDivide: 0.0 asQuadFloat.
    self assert:( shouldBeQuadFloatNaN isNaN ).

    self assert:( shouldBeQuadFloatNaN asLongFloat isNaN ).
    self assert:( shouldBeQuadFloatNaN + 1.0 asLongFloat ) isNaN.
    self assert:( shouldBeQuadFloatNaN - 1.0 asLongFloat ) isNaN.

    "
     self basicNew test01b_Nan
    "

    "Created: / 08-06-2019 / 13:38:12 / Claus Gittinger"
!

test02_Inf
    "Infinity"

    |check posInf negInf|

    self skipIf:(ExternalAddress pointerSize == 4) description:'only supported on 64bit machines'.

    self assert:(QuadFloat NaN isNaN).
    self assert:(QuadFloat NaN isFinite not).  
    self assert:(QuadFloat NaN isInfinite not).  

    self assert:(QuadFloat infinity isNaN not). 
    self assert:(QuadFloat infinity isFinite not). 
    self assert:(QuadFloat infinity isInfinite). 

    self assert:(QuadFloat negativeInfinity isNaN not). 
    self assert:(QuadFloat negativeInfinity isFinite not). 
    self assert:(QuadFloat negativeInfinity isInfinite). 
    
    self assert:(QuadFloat infinity negated = QuadFloat negativeInfinity). 
    self assert:(QuadFloat negativeInfinity negated = QuadFloat infinity). 

    { QuadFloat }
    do:[:cls |
        posInf := cls infinity.
        self assert:( posInf isInfinite ).
        self assert:( posInf isFinite not ).
        self assert:( posInf > 0 ).
        self assert:( posInf >= 0 ).
        self assert:( posInf < 0 ) not.
        self assert:( posInf <= 0 ) not.
        self assert:( posInf positive ).
        self assert:( posInf negative not ).

        negInf := cls negativeInfinity.
        self assert:( negInf isInfinite ).
        self assert:( negInf isFinite not ).
        self assert:( negInf < 0 ).
        self assert:( negInf <= 0 ).
        self assert:( negInf > 0 ) not.
        self assert:( negInf >= 0 ) not.
        self assert:( negInf positive not ).
        self assert:( negInf negative ).

        self assert:( posInf negated = negInf ).
        self assert:( negInf negated = posInf ).
    ].
    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 asQuadFloat value: 0.0 asQuadFloat.

    "
     self basicNew test02_Inf
    "

    "Modified: / 20-06-2017 / 14:03:08 / cg"
    "Modified: / 10-06-2019 / 23:42:43 / Claus Gittinger"
!

test03_Conversion
    self skipIf:(ExternalAddress pointerSize == 4) description:'only supported on 64bit machines'.

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

    self assert: ((5/9) asQuadFloat - 0.555555555555) abs < 0.0000000001.
    self assert: ((Fraction basicNew setNumerator:500000000000 denominator:900000000000)
                        asQuadFloat - 0.555555555555) abs <  0.000000000001.
    self assert: ((Fraction basicNew setNumerator:500000000001 denominator:900000000000)
                        asQuadFloat - 0.555555555555) abs >= 0.000000000001.

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

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

    "
     self basicNew test03_Conversion
    "

    "Modified: / 09-08-2011 / 21:01:57 / cg"
    "Modified: / 08-06-2019 / 13:53:32 / Claus Gittinger"
!

test04_Arithmetic
    self skipIf:(ExternalAddress pointerSize == 4) description:'only supported on 64bit machines'.

    self assert:( 1.0 asQuadFloat negated = -1.0 asQuadFloat).

    self assert:( 1.0 + 1.0 asQuadFloat) class == QuadFloat.

    self assert:( 1.0 asQuadFloat + 1.0 ) class == QuadFloat.
    self assert:( 1.0 asQuadFloat + 1.0 asShortFloat ) class == QuadFloat.
    self assert:( 1.0 asQuadFloat + 1.0 asFloat ) class == QuadFloat.
    self assert:( 1.0 asQuadFloat + 1 ) class == QuadFloat.

    self assert:( 1.0 + 1.0 asQuadFloat) class == QuadFloat.
    self assert:( 1.0 asShortFloat + 1.0 asQuadFloat) class == QuadFloat.
    self assert:( 1.0 asLongFloat + 1.0 asQuadFloat) class == QuadFloat.
    self assert:( 1 + 1.0 asQuadFloat) class == QuadFloat.

    self assert:( 1.0 asQuadFloat + 1.0 ) = 2.0 asQuadFloat.
    self assert:( 1.0 asQuadFloat + 1.0 asShortFloat ) = 2.0 asQuadFloat.
    self assert:( 1.0 asQuadFloat + 1.0 asFloat ) = 2.0 asQuadFloat.
    "/ self assert:( 1.0 asQuadFloat + 1 ) = 2.0 asQuadFloat.

    self assert:( 1.0 + 1.0 asQuadFloat) = 2.0 asQuadFloat.
    self assert:( 1.0 asShortFloat + 1.0 asQuadFloat) = 2.0 asQuadFloat.
    "/ self assert:( 1.0 asLongFloat + 1.0 asQuadFloat) = 2.0 asQuadFloat.
    "/ self assert:( 1 + 1.0 asQuadFloat) = 2.0 asQuadFloat.

    self assert:( 1.0 - 1.0 asQuadFloat) class == QuadFloat.

    self assert:( 1.0 asQuadFloat - 1.0 ) class == QuadFloat.
    self assert:( 1.0 asQuadFloat - 1.0 asShortFloat ) class == QuadFloat.
    self assert:( 1.0 asQuadFloat - 1.0 asFloat ) class == QuadFloat.
    self assert:( 1.0 asQuadFloat - 1 ) class == QuadFloat.


    self assert:( 1.0 * 1.0 asQuadFloat) class == QuadFloat.

    self assert:( 1.0 asQuadFloat * 1.0 ) class == QuadFloat.
    self assert:( 1.0 asQuadFloat * 1.0 asShortFloat ) class == QuadFloat.
    self assert:( 1.0 asQuadFloat * 1.0 asFloat ) class == QuadFloat.
    self assert:( 1.0 asQuadFloat * 1 ) class == QuadFloat.

    self assert:(1.0 asQuadFloat = 1.0 asQuadFloat).
    self assert:(1.0 asQuadFloat = 1.0 ).
    self assert:(1.0 asQuadFloat = 1.0 asShortFloat).
    "/ self assert:(1.0 asQuadFloat = 1.0 asLongFloat).
    "/ self assert:(1.0 asQuadFloat = 1).
    "/ self assert:(1.0 asQuadFloat = 1 asQuadFloat).
    
    self assert:( 1.0 / 1.0 asQuadFloat) class == QuadFloat.

    self assert:( 1.0 asQuadFloat / 1.0 ) class == QuadFloat.
    self assert:( 1.0 asQuadFloat / 1.0 asShortFloat ) class == QuadFloat.
    self assert:( 1.0 asQuadFloat / 1.0 asFloat ) class == QuadFloat.
    self assert:( 1.0 asQuadFloat / 1 ) class == QuadFloat.

    self assert:( 1.0 / 2.0 asQuadFloat) class == QuadFloat.

    self assert:( 1.0 asQuadFloat / 2.0 ) class == QuadFloat.
    self assert:( 1.0 asQuadFloat / 2.0 asShortFloat ) class == QuadFloat.
    self assert:( 1.0 asQuadFloat / 2.0 asFloat ) class == QuadFloat.
    self assert:( 1.0 asQuadFloat / 2 ) class == QuadFloat.

    self assert:( 5.0 rem: 2.0 asQuadFloat) class == QuadFloat.
    self assert:( 5.0 asShortFloat rem: 2.0 asQuadFloat) class == QuadFloat.

    self assert:( 5.0 asQuadFloat rem: 2.0 ) class == QuadFloat.
    self assert:( 5.0 asQuadFloat rem: 2.0 asShortFloat ) class == QuadFloat.
    self assert:( 5.0 asQuadFloat rem: 2.0 asFloat ) class == QuadFloat.
    self assert:( 5.0 asQuadFloat rem: 2 ) class == QuadFloat.

    "
     self basicNew test04_Arithmetic
    "

    "Modified: / 10-06-2019 / 23:27:18 / Claus Gittinger"
!

test05_Comparing
    |convArray check v1 v2 v1b|

    self skipIf:(ExternalAddress pointerSize == 4) description:'only supported on 64bit machines'.

    self assert:(QuadFloat zero = QuadFloat zero).
    self assert:(QuadFloat zero = 0.0 asQuadFloat).
    self assert:((0.0 asQuadFloat) = QuadFloat zero).

    self assert:(QuadFloat unity = QuadFloat unity).
    self assert:(QuadFloat unity = 1.0 asQuadFloat).
    self assert:((1.0 asQuadFloat) = QuadFloat unity).
    
    self assert:(QuadFloat zero ~= QuadFloat unity).
    self assert:(QuadFloat zero < QuadFloat unity).
    self assert:(QuadFloat zero <= QuadFloat unity).
    self assert:(QuadFloat unity > QuadFloat zero).
    self assert:(QuadFloat unity >= QuadFloat zero).
    
    convArray := OrderedCollection new.
    convArray addAll:#(yourself asInteger asFloat asShortFloat asLongFloat).
false ifTrue:[
    (Smalltalk at:#LargeFloat) notNil ifTrue:[
        convArray add:#asLongFloat.
    ].
    (Smalltalk at:#QuadFloat) notNil ifTrue:[
        convArray add:#asQuadFloat.
    ].
].
    check := [:iv1 :iv2|
        convArray do:[:conv1 |
            v1 := (iv1 perform:conv1).

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

            convArray 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.

    "/ showing that float precision is limited...
    
    "/ test fails when stc code, jit code works
    false "(Helper 
        isStcCompiledMethod:#'test05_Comparing'
        in:self)" ifTrue:[ 
            "/ stc-compiled code handles not slightly differently
            "/ listed compares will fail
            'FloatTest >> test05_Comparing: test with 200000000000000000000 or similiar are skipped due would fail when stc code' infoPrintCR.
        ] ifFalse:[    
            self assert:( 200000000000000000000.0 = 200000000000000000001.0 ).

            self assert:( 200000000000000000000.0 = 200000000000000000001 ).
            self assert:( 200000000000000000000.0 = 200000000000000000000 ).
            self assert:( 200000000000000000000.0 asLongFloat = 200000000000000000000 ).

            self assert:( 200000000000000000000 = 200000000000000000000.0).
            self assert:( 200000000000000000000 = 200000000000000000000.0 asLongFloat ).

            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:( 200000000000000000000 <= 200001000000000000000.0).
            self assert:( 200000000000000000000 <= 200000000000000000000.0).
            self assert:( 200000000000000000000 <= 200001000000000000000.0 asLongFloat ).
            self assert:( 200000000000000000000 <= 200000000000000000000.0 asLongFloat ).
        ].

    self assert:( 2000000.0 asShortFloat = 2000000 ).
    self assert:( 2000000 = 2000000.0 asShortFloat ).

    self assert:( 2000000.0 asShortFloat <= 200000100000000000000 ).
    self assert:( 2000000.0 asShortFloat <= 2000000 ).

    self assert:( 2000000 <= 2000000.0 asShortFloat ).
    self assert:( 2000000 <= 2000000.0 asShortFloat ).

    "
     self basicNew test05_Comparing
    "

    "Modified: / 08-06-2019 / 13:53:38 / Claus Gittinger"
!

test06_MiscMath
    |epsilon|

    self skipIf:(ExternalAddress pointerSize == 4) description:'only supported on 64bit machines'.

    epsilon := 0.000001.

    #(
        sqrt       0.5       0.707107
        sqrt       4         2.0
        exp        0.5       1.64872
        ln         0.5       -0.693147
        log10      0.5       -0.30103

        sin        0.5      0.479426
        cos        0.5      0.877583
        tan        0.5      0.546302
        arcSin     0.5      0.523599
        arcCos     0.5      1.0472
        arcTan     0.5      0.463648
        sinh       0.5      0.521095
        cosh       0.5      1.12763
        tanh       0.5      0.462117
        arcSinh    0.5      0.481212
        arcCosh    1.5      1.24983
        arcTanh    0.5      0.549306

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

        sin        1.0      0.841471
        cos        1.0      0.540302
        tan        1.0      1.55741
        sinh       1.0      1.1752
        cosh       1.0      1.54308
        tanh       1.0      0.761594

        sin        3.14159  0.0
        cos        3.14159  -1.0
        tan        3.14159  0.0
        sinh       3.14159  11.5487
        cosh       3.14159  11.5919
        tanh       3.14159  0.996272


        tan        0.785398 1.0         "pi/4  -> should be 1"
        arcCos     -1.0     3.14159     "should be pi"
        arcSin     1.0      1.5708      "should be pi/2 (1.5708)"
        arcTan     1.0      0.785398    "should be pi/4 (.785398)"
    ) inGroupsOf:3 do:[:op :x :expected|
        |rslt rsltQuadFloat|

        rslt := x perform:op.
        rsltQuadFloat := x asQuadFloat perform:op.

        self assert:(rslt class == Float).
        self assert:(rsltQuadFloat class == QuadFloat).

        self assert:( rslt - rsltQuadFloat ) < epsilon.
        self assert:( rslt - rslt asShortFloat ) < epsilon.
        self assert:( rslt - rslt asLongFloat ) < epsilon.
        self assert:( rslt - rslt asQuadFloat ) < epsilon.
    ].

    self should:[ -2 arcSin ] raise:DomainError.
    self should:[ -2 arcCos ] raise:DomainError.
    self should:[ -1 arcTanh ] raise:DomainError.

    #(
        0.0
        0.5
        1.0
        2.0
        1.57079
     ) do:[:x |
        self assert:( x sin arcSin - x < epsilon).
        self assert:( x cos arcCos - x < epsilon).
        self assert:( x tan arcTan - x < epsilon).
    ].

    #(
        -1.0
        -0.5
        0.0
        0.5
        1.0
     ) do:[:x |
        self assert:( x arcSin sin - x < epsilon).
        self assert:( x arcCos cos - x < epsilon).
        self assert:( x arcTan tan - x < epsilon).
    ].

    #(
        0.0
        0.5
        1.0
        2.0
        10
     ) do:[:x |
        self assert:( x cosh arcCosh - x < epsilon).
    ].
    #(
        -10
        -2
        -1
        -0.5
        0.0
        0.5
        1.0
        2.0
        10
     ) do:[:x |
        self assert:( x sinh arcSinh - x < epsilon).
        self assert:( x tanh arcTanh - x < epsilon).
    ].


    #(
        -0.99
        -0.5
        0.0
        0.5
        0.99
     ) do:[:x |
        self assert:( x arcTanh - (( ( (1+x)/(1-x) ) ln ) / 2 ) ) < epsilon.
    ].

    #(
        -10
        -5
        -2.0
        -1.0
        0.0
        1.0
        2.0
        10
     ) do:[:x |
        self assert:( x arcSinh sinh - x < epsilon).
    ].

    #(
        1.0
        2.0
        10.0
     ) do:[:x |
        self assert:( x arcCosh cosh - x < epsilon).
    ].

    self assert:(2.0 raisedTo:2) = 4.0.
    self assert:(2 raisedTo:2.0) = 4.0.
    self assert:(2.0 raisedTo:2.0) = 4.0.
    
    "
     self basicNew test06_MiscMath
    "

    "Modified: / 02-07-2017 / 00:51:05 / cg"
    "Modified: / 08-06-2019 / 13:53:42 / Claus Gittinger"
!

test07_Truncation
    |check|

    self skipIf:(ExternalAddress pointerSize == 4) description:'only supported on 64bit machines'.

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

    check value:1.6 asQuadFloat.
    check value:-1.6 asQuadFloat.


    self assert:( 1.6 asQuadFloat ceiling ) = 2.

    self assert:( 1.6 asQuadFloat ceilingAsFloat ) = 2.0 asQuadFloat.
    self assert:( 1.6 asQuadFloat ceilingAsFloat ) class == QuadFloat.


    self assert:( 1.6 asQuadFloat floor ) = 1.

    self assert:( 1.6 asQuadFloat floorAsFloat ) = 1.0 asQuadFloat.
    self assert:( 1.6 asQuadFloat floorAsFloat ) class == QuadFloat.

    self assert:( -1.6 asQuadFloat floor ) = -2.

    self assert:( -1.6 asQuadFloat floorAsFloat ) = -2.0 asQuadFloat.
    self assert:( -1.6 asQuadFloat floorAsFloat ) class == QuadFloat.


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

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

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

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

    "
     self basicNew test07_Truncation
    "

    "Modified: / 08-06-2019 / 13:53:46 / Claus Gittinger"
!

test08_Representation
    self skipIf:(ExternalAddress pointerSize == 4) description:'only supported on 64bit machines'.


    self assert: (QuadFloat unity class == QuadFloat).

    self assert: (QuadFloat unity = 1.0).

    self assert: (QuadFloat zero class == QuadFloat).

    self assert: (QuadFloat zero = 0.0).

    self assert:( QuadFloat unity = 1 asLongFloat ).

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

    "
     self basicNew test08_Representation
    "

    "Modified: / 02-08-2011 / 18:34:39 / cg"
    "Modified: / 08-06-2019 / 13:53:48 / Claus Gittinger"
! !

!QuadFloatTest class methodsFor:'documentation'!

version_CVS
    ^ '$Header$'
! !