FixedPoint.st
author Claus Gittinger <cg@exept.de>
Tue, 05 Nov 1996 19:36:39 +0100
changeset 1892 d3564145c15c
parent 1891 58073a4e3859
child 1893 c66af5c46272
permissions -rw-r--r--
*** empty log message ***

"
     this comes from:

     Jan Steinman, Bytesmiths
     2002 Parkside Court, West Linn, OR 97068-2767 USA, +1 503 657 7703
     Friedlistrasse 19, CH-3006, Bern, Switzerland, +41 31 999 3946

     this code was published in comp.lang.smalltalk; 
     added here as an example ...
"

Fraction subclass:#FixedPoint
	instanceVariableNames:'scale'
	classVariableNames:''
	poolDictionaries:''
	category:'Magnitude-Numbers'
!

FixedPoint comment:'
Description: This class implements infinite precision fixed-point numbers. 
It doesn''t really do anything too interesting except creating instances, converting, and printing, 
since its superclass Fraction does all the work.

Test: "''123456789012345678901234567890.123456789'' asFixed * 1000000000 = 123456789012345678901234567890123456789"

Notes: 1) The current implementation does not convert arbitrarily-based String representations, 
	  which shouldn''t be too much a problem for financial types.'!

!FixedPoint class methodsFor:'documentation'!

copyright
"
     this comes from:

     Jan Steinman, Bytesmiths
     2002 Parkside Court, West Linn, OR 97068-2767 USA, +1 503 657 7703
     Friedlistrasse 19, CH-3006, Bern, Switzerland, +41 31 999 3946

     this code was published in comp.lang.smalltalk; 
     added here as an example ...
"
!

documentation
"
    Description: This class implements infinite precision fixed-point numbers,
    which internally hold exact (fractional) results, but print themself with
    a limited number of digits after the decimal point. 
    These can be used in computation, where rounding errors should not accumulate,
    but only a limited precision is required for the final result.

    It doesn't really do anything too interesting except creating instances, 
    converting, and printing, since its superclass Fraction does all the work.

    Test: 
        '123456789012345678901234567890.123456789' asFixed * 1000000000
        -> 123456789012345678901234567890123456789'

    Notes: 1) The current implementation does not convert arbitrarily-based 
              String representations, which shouldn't be too much a problem 
              for financial types.

           2) the implementation is a hack - it has not been optimized for speed
              in particular.

    Mixed mode arithmetic:
        fix op fix       -> fix, scale is max. of operands
        fix op fraction  -> fix; scale is fix's scale
        fix op integer   -> fix; scale is fix's scale
        fix op float     -> float

    [author:]
        Jan Steinman, Bytesmiths
        modified & enhanced by Claus Gittinger

    [see also:]
        Integer Float Number
"
!

examples
"
                                                                [exBegin]
     |a b r|

     a := (FixedPoint fromString:'123.456').
     b := (FixedPoint fromString:'1.10').
     r := a + b.
     Transcript showCR:r.
     Transcript showCR:(r withScale:2).
     Transcript showCR:(r withScale:1).
     Transcript showCR:(r rounded).
                                                                [exEnd]

                                                                [exBegin]
     |a b r|

     a := (FixedPoint fromString:'0.9999999').
     b := (FixedPoint fromString:'0.0000001').
     r := a + b.
     Transcript showCR:r.
     Transcript showCR:(r withScale:2).
     Transcript showCR:(r withScale:1).
     Transcript showCR:(r rounded).
                                                                [exEnd]

                                                                [exBegin]
     |a b r|

     a := (FixedPoint fromString:'0.9999998').
     b := (FixedPoint fromString:'0.0000001').
     r := a + b.
     Transcript showCR:r.
     Transcript showCR:(r withScale:2).
     Transcript showCR:(r withScale:1).
     Transcript showCR:(r rounded).
                                                                [exEnd]

                                                                [exBegin]
     |a b r|

     a := (FixedPoint fromString:'1.0').
     b := (FixedPoint fromString:'0.0000001').
     r := a + b.
     Transcript showCR:r.
     Transcript showCR:(r withScale:2).
     Transcript showCR:(r withScale:1).
     Transcript showCR:(r rounded).
                                                                [exEnd]

                                                                [exBegin]
     |a b r|

     a := (FixedPoint fromString:'0.99').
     b := (FixedPoint fromString:'0.0000001').
     r := a + b.
     Transcript showCR:r.
     Transcript showCR:(r withScale:2).
     Transcript showCR:(r withScale:1).
     Transcript showCR:(r rounded).
                                                                [exEnd]

"
! !

!FixedPoint class methodsFor:'instance creation'!

fromString: fixedPointString
    "Answer a new instance of the receiver which is an interpretation of the digits found in <fixedPointString>."

    ^self readFrom: (ReadStream on: fixedPointString)

    "
     Fixed fromString:'123.456'
    "
!

numerator:n denominator:d scale:s
    ^ self basicNew
        setNumerator:n
        denominator:d
        scale:s
!

readFrom:aStream 
    "return an instance of me as described on the stream, aStream."

    | sign integerPart fractionStream char fractionPart scale |

    aStream peek == $- ifTrue:[
        sign := -1.
        aStream next.
    ] ifFalse:[
        sign := 1
    ].

    (aStream atEnd or:[aStream peek isLetter]) ifTrue: [^0].

    integerPart := (aStream upTo:$.) asNumber.
    (aStream atEnd or: [aStream peek isLetter]) ifTrue: [^integerPart].

    fractionStream := ReadWriteStream on:(String new: 10).
    [
        char := aStream next.
        char ~~ nil and:[char isDigit]
    ] whileTrue:[
        fractionStream nextPut:char
    ].

    scale := fractionStream contents size.
    fractionPart := Number readFromString:(fractionStream contents).

    ^ self basicNew 
        setNumerator:(integerPart * (10 raisedTo:scale) + fractionPart) * sign
        scale:scale

    "
     Fixed readFrom:('123.456' readStream) 
     Fixed readFrom:('-123.456' readStream) 
    "
! !

!FixedPoint methodsFor:'accessing'!

scale
    "Return the number of places of significance that is carried by the receiver."

    ^ scale
!

withScale:newScale
    "Return a copy of the receiver, with newScale number of post-decimal
     digits"

    ^ self class
        numerator:numerator
        denominator:denominator
        scale:newScale

    "
     (Fixed fromString:'12345.12345') withScale:2 

     ((Fixed fromString:'0.33333333')
      + 
      (Fixed fromString:'0.33333333')
     ) withScale:2   
    "
! !

!FixedPoint methodsFor:'arithmetic'!

* aNumber
    "return the product of the receiver and the argument, aNumber.
     Redefined to care for the scale if the argument is another fixPoint number.
     The results scale is the maximum of the receivers scale and the arguments
     scale."

    |n d sMax|

    (aNumber isMemberOf:SmallInteger) ifTrue:[
        ^ self class 
                numerator:(numerator * aNumber)
                denominator:denominator
                scale:scale
    ].
    (aNumber isMemberOf:self class) ifTrue:[
        n := numerator * aNumber numerator.
        d := denominator * aNumber denominator.
        sMax := scale max:aNumber scale.

        ^ self class 
            numerator:n 
            denominator:d
            scale:sMax
    ].
    ^ aNumber productFromFixedPoint:self

    "                       
     |a r|

     a := (FixedPoint fromString:'123.456').
     r := a * 5.    
     Transcript showCR:r.    
     Transcript showCR:(r withScale:2).
    "

    "                       
     |a b r|

     a := (FixedPoint fromString:'123.456').
     b := (FixedPoint fromString:'1.10').
     r := a * b.    
     Transcript showCR:r.    
     Transcript showCR:(r withScale:2).
    "

    "                       
     |a b r|

     a := (FixedPoint fromString:'123.456').
     b := (FixedPoint fromString:'-1.10').
     r := a * b.    
     Transcript showCR:r.    
     Transcript showCR:(r withScale:2).
    "

    "
     |a b r|

     a := (FixedPoint fromString:'0.9999999').
     b := (FixedPoint fromString:'0.9999999').
     r := a * b.    
     Transcript show:'fixed (exact)  : '; showCR:r.    
     Transcript show:'fixed (scale2) : '; showCR:(r withScale:2).

     Transcript show:'float (inexact): '; showCR:(0.9999999 * 0.9999999).
    "

    "
     |a b r|

     a := 1.
     b := (FixedPoint fromString:'0.9999999').
     r := a * b.    
     Transcript show:'fixed (exact)  : '; showCR:r.    
     Transcript show:'fixed (scale2) : '; showCR:(r withScale:2).

     Transcript show:'float (inexact): '; showCR:(0.9999999 * 0.9999999).
    "


!

+ aNumber
    "return the sum of the receiver and the argument, aNumber.
     Redefined to care for the scale if the argument is another fixPoint number.
     The resulting scale will be the maximum of the receivers and the
     arguments scale."

    |n d sMax|

    (aNumber isMemberOf:self class) ifTrue:[
        n := aNumber numerator.
        d := aNumber denominator.
        sMax := scale max:aNumber scale.

        "save a multiplication if possible"
        denominator == d ifTrue:[
            ^ self class 
                numerator:(numerator + n) 
                denominator:d
                scale:sMax
        ].

        ^ self class 
                numerator:((numerator * d) + (n * denominator))
                denominator:(denominator * d)
                scale:sMax
    ].
    ^ aNumber sumFromFixedPoint:self

    "
     |a b|

     a := (FixedPoint fromString:'123.456').
     b := (FixedPoint fromString:'1.10').
     a + b
    "

    "
     |a b|

     a := (FixedPoint fromString:'0.9999999').
     b := (FixedPoint fromString:'0.0000001').
     a + b                   
    "

    "
     |a b|

     a := (FixedPoint fromString:'0.99').
     b := (FixedPoint fromString:'0.0000001').
     a + b                             
    "

    "
     |a b|

     a := (FixedPoint fromString:'0.99').
     b := (FixedPoint fromString:'0.0000001').
     (a + b) withScale:2  
    "

    "
     |a b|

     a := (FixedPoint fromString:'0.99').
     b := (FixedPoint fromString:'0.0000001').
     (a + b) withScale:1  
    "

    "
     |a b|

     a := 1.
     b := (FixedPoint fromString:'0.0000001').
     Transcript showCR:((a + b) withScale:1).
     Transcript showCR:(a + b)
    "


!

- aNumber
    "return the difference of the receiver and the argument, aNumber.
     Redefined to care for the scale if the argument is another fixPoint number.
     The results scale is the maximum of the receivers scale and the arguments
     scale."

    |n d sMax|

    (aNumber isMemberOf:self class) ifTrue:[
        n := aNumber numerator.
        d := aNumber denominator.
        sMax := scale max:aNumber scale.

        "save a multiplication if possible"
        denominator == d ifTrue:[
            ^ self class 
                numerator:(numerator - n) 
                denominator:d
                scale:sMax
        ].

        ^ self class 
                numerator:((numerator * d) - (n * denominator))
                denominator:(denominator * d)
                scale:sMax
    ].
    ^ aNumber differenceFromFixedPoint:self

    "
     |a b|

     a := (FixedPoint fromString:'123.456').
     b := (FixedPoint fromString:'1.10').
     a - b    
    "

    "
     |a b|

     a := (FixedPoint fromString:'0.9999999').
     b := (FixedPoint fromString:'0.0000009').
     a - b                   
    "

    "
     |a b|

     a := (FixedPoint fromString:'0.99').
     b := (FixedPoint fromString:'0.0000001').
     a - b                          
    "

    "
     |a b|

     a := (FixedPoint fromString:'0.99').
     b := (FixedPoint fromString:'0.0000001').
     (a - b) withScale:2  
    "

    "
     |a b|

     a := (FixedPoint fromString:'0.99').
     b := (FixedPoint fromString:'0.0000001').
     (a - b) withScale:1  
    "

    "
     |a b|

     a := (FixedPoint fromString:'0.0000001').
     b := (FixedPoint fromString:'0.99').
     (a - b) withScale:2   
    "

    "
     |a b|

     a := 1.
     b := (FixedPoint fromString:'0.0000001').
     Transcript showCR:((a - b) withScale:1).
     Transcript showCR:(a - b)
    "

!

/ aNumber
    "return the quotien of the receiver and the argument, aNumber.
     Redefined to care for the scale if the argument is another fixPoint number.
     The results scale is the maximum of the receivers scale and the arguments
     scale."

    |n d sMax|

    (aNumber isMemberOf:SmallInteger) ifTrue:[
        ^ (self class 
                numerator:numerator
                denominator:(denominator * aNumber)
                scale:scale) reduced
    ].

    (aNumber isMemberOf:self class) ifTrue:[
        n := numerator * aNumber denominator.
        d := denominator * aNumber numerator.
        sMax := scale max:aNumber scale.

        ^ (self class 
            numerator:n 
            denominator:d
            scale:sMax) reduced
    ].
    ^ aNumber quotientFromFixedPoint:self

    "                       
     |a r|                     

     a := (FixedPoint fromString:'123.456').
     r := a / 5.    
     Transcript showCR:r.    
     Transcript showCR:(r withScale:2).
     Transcript showCR:(r withScale:9).
    "

    "                       
     |a b r|

     a := (FixedPoint fromString:'123.456').
     b := (FixedPoint fromString:'1.10').
     r := a / b.    
     Transcript showCR:r.    
     Transcript showCR:(r withScale:2).
    "

    "                       
     |a b r|

     a := (FixedPoint fromString:'-123.456').
     b := (FixedPoint fromString:'-1.10').
     r := a / b.    
     Transcript showCR:r.    
     Transcript showCR:(r withScale:2).
    "

    "                       
     |a b r|

     a := (FixedPoint fromString:'123.456').
     b := (FixedPoint fromString:'-1.10').
     r := a / b.    
     Transcript showCR:r.    
     Transcript showCR:(r withScale:2).
    "

    "
     |a b r|

     a := 1.
     b := (FixedPoint fromString:'0.9999999').
     r := a / b.    
     Transcript show:'fixed (exact)  : '; showCR:r.    
     Transcript show:'fixed (scale2) : '; showCR:(r withScale:2).

     Transcript show:'float (inexact): '; showCR:(1 / 0.9999999).
    "
! !

!FixedPoint methodsFor:'coercing & converting'!

asFixedPoint
    "return the receiver as a fixedPoint number"

    ^ self

!

asFraction
    "return the receiver as a fraction"

    ^ (Fraction
        numerator:numerator
        denominator:denominator) reduced

    "
     (FixedPoint fromString:'0.2')           
     (FixedPoint fromString:'0.2') asFraction
     (FixedPoint fromString:'0.2') asFloat
     (FixedPoint fromString:'0.2') asShortFloat
     (FixedPoint fromString:'0.2') asInteger
    "
!

coerce:aNumber
    "return aNumber converted into receivers type"

    ^ aNumber asFixedPoint

!

generality
    "return the generality value - see ArithmeticValue>>retry:coercing:"

    ^ 65

    "
     (FixedPoint fromString:'1.001') + 1      
     (FixedPoint fromString:'1.001') + 1.0    
     (FixedPoint fromString:'1.001') + (1/2)   
     (FixedPoint fromString:'1.001') + 1.0 asShortFloat 
     (FixedPoint fromString:'1.001') + 1 asLargeInteger 

     1 + (FixedPoint fromString:'1.001') 
     1.0 + (FixedPoint fromString:'1.001')      
     (1/2) + (FixedPoint fromString:'1.001')    
     1.0 asShortFloat + (FixedPoint fromString:'1.001')
     1 asLargeInteger + (FixedPoint fromString:'1.001')
    "
! !

!FixedPoint methodsFor:'double dispatching'!

differenceFromInteger:anInteger
    "sent when an integer does not know how to subtract the receiver.
     Redefined here to preserve the scale."

    ^ (self class 
        numerator:((anInteger * denominator) - numerator)
        denominator:denominator
        scale:scale) reduced

!

productFromInteger:anInteger
    "sent when an integer does not know how to multiply the receiver.
     Redefined here to preserve the scale."

    ^ (self class 
        numerator:(anInteger * numerator)
        denominator:denominator
        scale:scale) reduced

    "Modified: 5.11.1996 / 10:32:28 / cg"


!

quotientFromInteger:anInteger
    "sent when an integer does not know how to divide by the receiver.
     Redefined here to preserve the scale."

    ^ (self class 
        numerator:(anInteger * denominator)
        denominator:numerator
        scale:scale) reduced

    "Modified: 5.11.1996 / 10:32:35 / cg"


!

sumFromInteger:anInteger
    "sent when an integer does not know how to add the receiver.
     Redefined here to preserve the scale."

    ^ (self class 
        numerator:(numerator + (anInteger * denominator))
        denominator:denominator
        scale:scale) reduced

    "Modified: 5.11.1996 / 10:32:43 / cg"


! !

!FixedPoint methodsFor:'printing'!

printOn: aStream 
    "Append to the argument, aStream, a printed representation of the receiver.
     For printout, only scale post-decimal digits are printed
     (and the printout is rounded to that many digits)"

    |e decimals integerPart fractionPart negative num|

    numerator < 0 ifTrue:[
        negative := true.
        num := numerator negated.
    ] ifFalse:[
        negative := false.
        num := numerator.
    ].
    integerPart := (num // denominator).
    e := 10 raisedTo:scale.
    fractionPart := (num \\ denominator).

    "/ the most common case is a denominator fitting the scale
    "/ (fixedPoint numbers are created this way)

    e == denominator ifFalse:[
        fractionPart := fractionPart * (e * 10) // denominator.
        fractionPart := (fractionPart roundTo:10) // 10.

        fractionPart >= e ifTrue:[
            integerPart := integerPart + 1.
            fractionPart := 0.
        ]
    ].

    "/
    "/ add a 1000..., so we can (mis-)use integer-printString ...
    "/ the highest-1 will be cutoff after padding.
    "/
    fractionPart := e + fractionPart.

    negative ifTrue:[
        aStream nextPut:$-
    ].
    integerPart printOn:aStream.
    aStream nextPut: $..
    ((fractionPart printStringPaddedTo:scale with:$0) copyFrom:2) printOn:aStream

    "
     (FixedPoint fromString:'0.66666666')               
     (FixedPoint fromString:'0.66666666') withScale:2   
     (FixedPoint fromString:'0.99999999')               
     (FixedPoint fromString:'0.99999999') withScale:2   
     (FixedPoint fromString:'1.00000001')               
     (FixedPoint fromString:'1.00000001') withScale:2   
     (FixedPoint fromString:'1.005')                    
     (FixedPoint fromString:'1.005') withScale:2        
     (FixedPoint fromString:'1.005') withScale:1        

     (FixedPoint fromString:'-0.66666666')              
     (FixedPoint fromString:'-0.66666666') withScale:2   
     (FixedPoint fromString:'-0.99999999')              
     (FixedPoint fromString:'-0.99999999') withScale:2   
     (FixedPoint fromString:'-1.00000001')              
     (FixedPoint fromString:'-1.00000001') withScale:2   
     (FixedPoint fromString:'-1.005')                   
     (FixedPoint fromString:'-1.005') withScale:2       
     (FixedPoint fromString:'-1.005') withScale:1       
     (FixedPoint fromString:'-1.05')                    
     (FixedPoint fromString:'-1.05') withScale:2      
     (FixedPoint fromString:'-1.05') withScale:1      
     (FixedPoint fromString:'-1.04')                  
     (FixedPoint fromString:'-1.04') withScale:2      
     (FixedPoint fromString:'-1.04') withScale:1      
    "

    "
     |a b r|

     a := (FixedPoint fromString:'0.66666666') withScale:2.
     b := (FixedPoint fromString:'0.33333333').
     r := (a + b) withScale:4.
     Transcript show:'printout with scale of 4 :'; showCR:r.
     Transcript show:'more precise value       :'; showCR:(r withScale:8)
    "
! !

!FixedPoint methodsFor:'private'!

reduced
    |gc|

    scale isNil ifTrue:[
        "/ to catch inherited Fraction reduce calls
        self error:'should not happen'.
        scale := 3
    ].

    denominator == 1 ifTrue:[^ numerator].
    numerator == 1 ifTrue:[^ self].
    numerator == 0 ifTrue:[^ 0].

    gc := numerator gcd:denominator.
    gc := gc gcd:(10 raisedTo:scale).

    (gc == 1) ifFalse:[
        numerator := numerator // gc.
        denominator := denominator // gc
    ].

    (numerator < 0) ifTrue:[
        (denominator < 0) ifTrue:[
            numerator := numerator negated.
            denominator := denominator negated
        ]
    ].
    (denominator == 1) ifTrue:[^ numerator].
    ^ self

!

setNumerator:nInteger denominator:d scale:s 
    "Initialize the instance variables."

    scale := s.
    super
        setNumerator:nInteger 
        denominator:d
!

setNumerator:nInteger scale:s 
    "Initialize the instance variables."

    scale := s.
    super
        setNumerator:nInteger 
        denominator:(10 raisedTo:s)
!

setScale:newScale 
    "Initialize the scale instance variables."

    scale := newScale.
! !

!FixedPoint methodsFor:'queries'!

isFixedPoint
    "return true, if the receiver is some kind of fixedPoint number;
     true is returned here - the method is redefined from Object."

    ^ true


! !

!FixedPoint class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/FixedPoint.st,v 1.3 1996-11-05 18:36:01 cg Exp $'
! !