RegressionTests__ScaledDecimalTest.st
author Claus Gittinger <cg@exept.de>
Tue, 09 Aug 2011 21:22:24 +0200
changeset 624 d102acf4b889
parent 623 2a27ea2f2490
child 625 9ed02c4fa1d0
permissions -rw-r--r--
added: #literal_helper1 #testLiteralInSTC changed: #testLiteral1 category of:

"{ Package: 'exept:regression' }"

"{ NameSpace: RegressionTests }"

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


!ScaledDecimalTest methodsFor:'helpers'!

literal_helper1
    ^ 1.40s2.

    "Created: / 09-08-2011 / 21:11:13 / cg"
! !

!ScaledDecimalTest methodsFor:'temporary'!

literal_helper2
    ^ 1.40s2.
! !

!ScaledDecimalTest methodsFor:'tests'!

testAsNumber
        "Ensure no loss of precision"

        | sd |
        sd := '1.40s2' asNumber.
        self assert: (ScaledDecimal ? FixedPoint) == sd class.
        self assert: sd scale == 2.

        Smalltalk isSmalltalkX ifTrue:[
            self assert: '1.40' = sd printString.
            self assert: '1.40s2' = sd storeString.
        ] ifFalse:[
            self assert: '1.40s2' = sd printString.
        ]
!

testAsNumberNegatedWithoutDecimalPoint

        | sd |
        sd := '-123s0' asNumber.
        self assert: (ScaledDecimal ? FixedPoint) == sd class.
        self assert: sd scale == 0.

        Smalltalk isSmalltalkX ifTrue:[
            self assert: '-123' = sd printString.
            self assert: '-123s0' = sd storeString.
        ] ifFalse:[
            self assert: '-123s0' = sd printString.
        ]
!

testAsNumberNegatedWithoutDecimalPoint2

        | sd |
        sd := '-123s2' asNumber.
        self assert: (ScaledDecimal ? FixedPoint) == sd class.
        self assert: sd scale == 2.

        Smalltalk isSmalltalkX ifTrue:[
            self assert: '-123.00' = sd printString.
            self assert: '-123.00s2' = sd storeString.
        ] ifFalse:[
            self assert: '-123.00s2' = sd printString.
        ]
!

testAsNumberWithExtendedScale

        | sd |
        sd := '123s2' asNumber.
        self assert: (ScaledDecimal ? FixedPoint) == sd class.
        self assert: sd scale == 2.

        Smalltalk isSmalltalkX ifTrue:[
            self assert: '123.00' = sd printString.
            self assert: '123.00s2' = sd storeString.
        ] ifFalse:[
            self assert: '123.00s2' = sd printString.
        ]
!

testAsNumberWithRadix
        | sd oldSetting |

        Smalltalk isSmalltalkX ifTrue:[
            oldSetting := ParserFlags allowFixedPointLiterals.
            ParserFlags allowFixedPointLiterals:true.
            [
                sd := Number readSmalltalkSyntaxFrom:'10r-22.2s5'.
            ] ensure:[
                ParserFlags allowFixedPointLiterals:oldSetting.
            ]
        ] ifFalse:[
            sd := '10r-22.2s5' asNumber.
        ].

        self assert: (ScaledDecimal ? FixedPoint) == sd class.
        self assert: sd scale == 5.

        Smalltalk isSmalltalkX ifTrue:[
            self assert: '-22.20000' = sd printString.
            self assert: '-22.20000s5' = sd storeString.
        ] ifFalse:[
            self assert: '-22.20000s5' = sd printString.
        ]

    "Modified: / 09-08-2011 / 20:57:54 / cg"
!

testAsNumberWithSuperfluousDecimalPoint

        | sd |
        sd := '123.s2' asNumber.
        self assert: (ScaledDecimal ? FixedPoint) == sd class.
        self assert: sd scale == 2.

        Smalltalk isSmalltalkX ifTrue:[
            self assert: '123.00' = sd printString.
            self assert: '123.00s2' = sd storeString.
        ] ifFalse:[
            self assert: '123.00s2' = sd printString.
        ]
!

testAsNumberWithoutDecimalPoint

        | sd |
        sd := '123s0' asNumber.
        self assert: (ScaledDecimal ? FixedPoint) == sd class.
        self assert: sd scale == 0.

        Smalltalk isSmalltalkX ifTrue:[
            self assert: '123' = sd printString.
            self assert: '123s0' = sd storeString.
        ] ifFalse:[
            self assert: '123s0' = sd printString.
        ]
!

testAsNumberWithoutDecimalPoint2

        | sd |
        sd := '123s2' asNumber.
        self assert: (ScaledDecimal ? FixedPoint) == sd class.
        self assert: sd scale == 2.

        Smalltalk isSmalltalkX ifTrue:[
            self assert: '123.00' = sd printString.
            self assert: '123.00s2' = sd storeString.
        ] ifFalse:[
            self assert: '123.00s2' = sd printString.
        ]
!

testConvertFromFloat

        | aFloat sd f2 diff |
        aFloat := 11/13 asFloat.
        sd := aFloat asScaledDecimal: 2.
        self assert: 2 == sd scale.
        Smalltalk isSmalltalkX ifTrue:[
            self assert: '0.85' = sd printString.
        ] ifFalse:[
            self assert: '0.84s2' = sd printString.
        ].
        f2 := sd asFloat.
        diff := f2 - aFloat.
        self assert: diff < 1.0e-9. "actually, f = f2, but this is not a requirement"
!

testConvertFromFraction

        | sd |
        sd := (13 / 11) asScaledDecimal: 6.
        self assert: (ScaledDecimal ? FixedPoint) == sd class.
        Smalltalk isSmalltalkX ifTrue:[
            self assert: ('1.181818' = sd printString).
        ] ifFalse:[
            self assert: ('1.181818s6' = sd printString).
        ].
        self assert: 6 == sd scale
!

testConvertFromInteger
        "Converting an Integer to a ScaledDecimal yields a ScaledDecimal with
        scale 0, regardless of the scale specified in the #asScaledDecimal: message."

        | sd |

        Smalltalk isSmalltalkX ifTrue:[
            "/ I think this behavior is wrong.
            ^ self.
        ].

        sd := 13 asScaledDecimal: 6.
        self assert: 0 = sd scale.
        self assert: ('13s0' = sd printString).
        sd := -13 asScaledDecimal: 6.
        self assert: 0 = sd scale.
        self assert: ('-13s0' = sd printString).
        sd := 130000000013 asScaledDecimal: 6.
        self assert: 0 = sd scale.
        self assert: ('130000000013s0' = sd printString).
        sd := -130000000013 asScaledDecimal: 6.
        self assert: 0 = sd scale.
        self assert: ('-130000000013s0' = sd printString)
!

testLiteral1
    "s2 is not a message to be sent to a float"

    self 
        shouldnt:[ self literal_helper1 ] 
        raise:MessageNotUnderstood

    "Created: / 09-08-2011 / 21:05:47 / cg"
!

testLiteral2
        | sd |

        sd := 1.40s2.
        self assert: (ScaledDecimal ? FixedPoint) == sd class.
        self assert: sd scale == 2.
        Smalltalk isSmalltalkX ifTrue:[
            self assert: '1.40' = sd printString.
            self assert: '1.40s2' = sd storeString.
        ] ifFalse:[
            self assert: '1.40s2' = sd printString.
        ].

    "Created: / 09-08-2011 / 21:06:11 / cg"
!

testLiteralInSTC
    |value|

    Class withoutUpdatingChangesDo:[
        self class
            compile:
'literal_helper2
    ^ 1.40s2.
'
            classified:'temporary'.

        Compiler stcCompileMethod:(self class compiledMethodAt:#literal_helper2).
    ].

    self 
        shouldnt:[ self literal_helper2 ] 
        raise:MessageNotUnderstood.

    value := self literal_helper2.
    self assert:( value isFixedPoint ).
    self assert:( (value * 10) = 14 ).
    self assert:( value asFloat = 1.4 ).

    "Created: / 09-08-2011 / 21:10:22 / cg"
!

testPrintString
        "The printed representation of a ScaledDecimal is truncated, not rounded.
        Not sure if this is right, so this test describes the current Squeak implementation.
        If someone knows a reason that rounding would be preferable, then update
        this test."

        | sd |

        sd := (13 / 11) asScaledDecimal: 6.
        Smalltalk isSmalltalkX ifTrue:[
            self assert: ('1.181818' = sd printString).
        ] ifFalse:[
            self assert: ('1.181818s6' = sd printString).
        ].

        sd := (13 / 11) asScaledDecimal: 5.
        Smalltalk isSmalltalkX ifTrue:[
            self assert: ('1.18182' = sd printString).
        ] ifFalse:[
            self deny: ('1.18182s5' = sd printString).
        ].

        sd := (13 / 11) asScaledDecimal: 5.
        Smalltalk isSmalltalkX ifTrue:[
            self deny: ('1.18181' = sd printString).
        ] ifFalse:[
            self assert: ('1.18181s5' = sd printString).
        ].
!

testStoreAndRead
    |check|

    check := [:originalNum |
        |s readNum|

        s := originalNum storeString.
        readNum := Number readFrom:s.
        self assert:readNum = originalNum.
    ].

    check value:((FixedPoint fromString:'0.66666666')                   ).
    check value:((FixedPoint fromString:'0.66666666') withScale:2       ).

    check value:((FixedPoint fromString:'1.5')                          ).
    check value:((FixedPoint fromString:'1.5') withScale:2              ).
    check value:((FixedPoint fromString:'1.5') withScale:1              ).
    check value:((FixedPoint fromString:'1.5') withScale:0              ).
! !

!ScaledDecimalTest class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !