Fraction.st
author Claus Gittinger <cg@exept.de>
Fri, 10 Jan 1997 19:55:31 +0100
changeset 2140 5e2def558185
parent 1893 c66af5c46272
child 2789 e3e8707d26b4
permissions -rw-r--r--
added #asFixedPoint:

"
 COPYRIGHT (c) 1989 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

Number subclass:#Fraction
	instanceVariableNames:'numerator denominator'
	classVariableNames:'FractionOne FractionZero'
	poolDictionaries:''
	category:'Magnitude-Numbers'
!

!Fraction class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1989 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    Instances of Fraction represent fractional numbers consisting of
    a numerator and denominator. Both are themselfes arbitrary precision
    integers. Fractions are usually created by dividing Integers using /
    (for exact division).

    Mixed mode arithmetic:
        fraction op fraction    -> fraction
        fraction op fix         -> fix; scale is fix's scale
        fraction op integer     -> fraction
        fraction op float       -> float

    [author:]
        Claus Gittinger

    [see also:]
        Number
        Float Integer FixedPoint 
"
! !

!Fraction class methodsFor:'initialization'!

initialize
    FractionZero isNil ifTrue:[
	FractionZero := self numerator:0 denominator:1.
	FractionOne := self numerator:1 denominator:1
    ]
! !

!Fraction class methodsFor:'instance creation'!

new
    "create and return a new fraction with value 0"

    ^ self numerator:0 denominator:1
!

numerator:num denominator:den
    "create and return a new fraction with numerator num and denominator den"

%{  /* NOCONTEXT */

    /* this check allows subclassing .. */
    if (self == Fraction) {
	if (__CanDoQuickAlignedNew(sizeof(struct __fraction))) {
	    OBJ newFraction;
	    int spc;

	    __qCheckedAlignedNew(newFraction, sizeof(struct __fraction));
	    __InstPtr(newFraction)->o_class = self;
	    __FractionInstPtr(newFraction)->f_numerator = num;
	    __FractionInstPtr(newFraction)->f_denominator = den;
	    if (! __bothSmallInteger(num, den)) {
		spc = __qSpace(newFraction);
		__STORE_SPC(newFraction, num, spc);
		__STORE_SPC(newFraction, den, spc);
	    }
	    RETURN ( newFraction );
	}
    }
%}
.
    ^ self basicNew setNumerator:num denominator:den
! !

!Fraction class methodsFor:'constants'!

pi
    "return the constant pi as Fraction"

    ^ self 
        numerator:  31415926535897932384626434
        denominator:10000000000000000000000000

    "
     Fraction pi         
     Fraction pi asFloat
     Float pi            
    "

    "Modified: 5.11.1996 / 11:11:44 / cg"
!

unity
    "return the neutral element for multiplication (1 / 1)"

    ^ FractionOne

    "Modified: 18.7.1996 / 12:26:06 / cg"
!

zero
    "return the neutral element for addition (0 / 1)"

    ^ FractionZero

    "Modified: 18.7.1996 / 12:26:12 / cg"
! !

!Fraction class methodsFor:'queries'!

isBuiltInClass
    "return true if this class is known by the run-time-system.
     Here, true is returned for myself, false for subclasses."

    ^ self == Fraction

    "Modified: 23.4.1996 / 15:59:10 / cg"
! !

!Fraction methodsFor:'accessing'!

denominator
    "return the denominator"

    ^ denominator
!

numerator
    "return the numerator"

    ^ numerator
! !

!Fraction methodsFor:'arithmetic'!

* aNumber
    "return the product of the receiver and the argument, aNumber"

    |n d|

    (aNumber isMemberOf:SmallInteger) ifTrue:[
        ^ (self class numerator:(numerator * aNumber)
                    denominator:denominator) reduced
    ].
    aNumber isFraction ifTrue:[
        aNumber isFixedPoint ifFalse:[  "/ the value was corrent, but the scale is lost
            n := numerator * aNumber numerator.
            d := denominator * aNumber denominator.
            ^ (self class numerator:n denominator:d) reduced
        ]
    ].
    (aNumber isMemberOf:Float) ifTrue:[
        ^ (numerator * aNumber) / denominator
    ].
    ^ aNumber productFromFraction:self

    "Modified: 5.11.1996 / 19:31:50 / cg"
!

+ aNumber
    "return the sum of the receiver and the argument, aNumber"

    |n d|

    (aNumber isMemberOf:SmallInteger) ifTrue:[
        ^ (self class numerator:(numerator + (denominator * aNumber))
                    denominator:denominator) reduced
    ].
    aNumber isFraction ifTrue:[
        aNumber isFixedPoint ifFalse:[  "/ the value was corrent, but the scale is lost
            n := aNumber numerator.
            d := aNumber denominator.

            "save a multiplication if possible"
            denominator == d ifTrue:[
                n := numerator + n
            ] ifFalse:[
                n := (numerator * d) + (n * denominator).
                d := denominator * d.
            ].
            ^ (self class numerator:n denominator:d) reduced
        ]
    ].
    (aNumber isMemberOf:Float) ifTrue:[
        ^ aNumber + (numerator asFloat / denominator asFloat)
    ].
    ^ aNumber sumFromFraction:self

    "Modified: 5.11.1996 / 19:31:41 / cg"
!

- aNumber
    "return the difference of the receiver and the argument, aNumber"

    |n d|

    (aNumber isMemberOf:SmallInteger) ifTrue:[
        ^ (self class numerator:(numerator - (denominator * aNumber))
                    denominator:denominator) reduced
    ].
    aNumber isFraction ifTrue:[
        aNumber isFixedPoint ifFalse:[  "/ the value was corrent, but the scale is lost
            n := aNumber numerator.
            d := aNumber denominator.

            "save a multiplication if possible"
            denominator == d ifTrue:[
                n := numerator - n
            ] ifFalse:[
                n := (numerator * d) - (n * denominator).
                d := denominator * d
            ].
            ^ (self class numerator:n denominator:d) reduced
        ]
    ].
    (aNumber isMemberOf:Float) ifTrue:[
        ^ (numerator asFloat / denominator asFloat) - aNumber
    ].
    ^ aNumber differenceFromFraction:self

    "
     (1/3) - (1/9)      
     (1/9) - (1/3)      
     (999/1000) - (1/1000)      
     (999/1000) - (1/1000000)      
     (999000/1000000) - (1/1000000)      
    "

    "Modified: 5.11.1996 / 19:31:32 / cg"
!

/ aNumber
    "return the quotient of the receiver and the argument, aNumber"

    |n d|

    (aNumber isMemberOf:SmallInteger) ifTrue:[
        ^ (self class numerator:numerator
                    denominator:(denominator * aNumber)) reduced
    ].
    aNumber isFraction ifTrue:[
        aNumber isFixedPoint ifFalse:[  "/ the value was corrent, but the scale is lost
            n := numerator * aNumber denominator.
            d := denominator * aNumber numerator.
            ^ (self class numerator:n denominator:d) reduced
        ]
    ].
    (aNumber isMemberOf:Float) ifTrue:[
        ^ numerator / (denominator * aNumber)
    ].
    ^ aNumber quotientFromFraction:self

    "Modified: 5.11.1996 / 19:31:23 / cg"
!

// aNumber
    "return the integer quotient of dividing the receiver by aNumber with
     truncation towards negative infinity."

    self negative ifTrue:[
         ^ ((numerator * aNumber denominator) // (denominator * aNumber numerator)) - 1
    ].
    ^ (numerator * aNumber denominator) // (denominator * aNumber numerator)

    "
     0.5 // 1
     -0.5 // 1
     (1/2) // 1
     (1/2) negated // 1
    "

    "Modified: 5.11.1996 / 11:47:14 / cg"
!

negated
    "optional - could use inherited method ..."

    ^ self class 
        numerator:(numerator negated)
        denominator:denominator

    "Modified: 5.11.1996 / 10:29:11 / cg"
!

reciprocal
    "optional - could use inherited method ..."

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

    "Modified: 5.11.1996 / 10:29:22 / cg"
! !

!Fraction methodsFor:'coercing & converting'!

asFixedPoint
    "return the receiver as fixedPoint number.
     Q: what should the scale be here ?"

    ^ FixedPoint numerator:numerator denominator:denominator scale:2

    "
     (1/2) asFixedPoint
    "

    "Created: 5.11.1996 / 15:15:54 / cg"
!

asFixedPoint:scale
    "return the receiver as fixedPoint number, with the given number
     of post-decimal-point digits."

    ^ FixedPoint numerator:numerator denominator:denominator scale:scale

    "
     (1/2) asFixedPoint:2 
     (1/3) asFixedPoint:2 
     (1/3) asFixedPoint:5 
     (2/3) asFixedPoint:2 
     (2/3) asFixedPoint:5 
    "

    "Created: 5.11.1996 / 15:15:54 / cg"
    "Modified: 10.1.1997 / 19:54:50 / cg"
!

asFloat
    "return a float with (approximately) my value"

    ^ (numerator asFloat) / (denominator asFloat)
!

asFraction
    "return the receiver as fraction - thats itself"

    ^ self
!

asInteger
    "return an integer with my value - will usually truncate"

    ^ numerator // denominator
!

asLargeInteger
    "return an integer with my value - will usually truncate"

    ^ self asInteger asLargeInteger
!

asShortFloat
    "return a shortFloat with (approximately) my value"

    ^ (numerator asShortFloat) / (denominator asShortFloat)

    "Created: 17.4.1996 / 12:21:08 / cg"
!

coerce:aNumber
    "return aNumber converted into receivers type"

    ^ aNumber asFraction
!

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

    ^ 60
! !

!Fraction methodsFor:'comparing'!

< aNumber
    "return true if the receiver is less
     than aNumber, false otherwise."

    |d n|

    (aNumber isMemberOf:SmallInteger) ifTrue:[
        ^ numerator < (denominator * aNumber)
    ].
    aNumber isFraction ifTrue:[
        d := aNumber denominator.
        n := aNumber numerator.

        "/ save a multiplication if possible
        d == denominator ifTrue:[
            ^ numerator < n
        ].
        ^ (numerator * d) < (denominator * n)
    ].
    ^ aNumber lessFromFraction:self

    "Modified: 5.11.1996 / 10:30:52 / cg"
!

= aNumber
    "return true, if the argument represents the same numeric value
     as the receiver, false otherwise"

    (aNumber isMemberOf:SmallInteger) ifTrue:[
	(denominator = 1) ifFalse:[^ false].
	^ numerator = aNumber
    ].
    aNumber isFraction ifTrue:[
	(numerator = aNumber numerator) ifFalse:[^ false].
	^ denominator = aNumber denominator
    ].
    ^ self retry:#= coercing:aNumber
!

> aNumber
    "return true if the receiver is greater
     than aNumber, false otherwise."
    "optional - could use inherited method ..."

    |d n|

    (aNumber isMemberOf:SmallInteger) ifTrue:[
        ^ numerator > (denominator * aNumber)
    ].
    aNumber isFraction ifTrue:[
        d := aNumber denominator.
        n := aNumber numerator.

        "/ save a multiplication if possible
        d == denominator ifTrue:[
            ^ numerator > n
        ].
        ^ (numerator * d) > (denominator * n)
    ].
    ^ self retry:#> coercing:aNumber

    "Modified: 5.11.1996 / 10:31:28 / cg"
! !

!Fraction methodsFor:'double dispatching'!

differenceFromFloat:aFloat
    "sent when a float does not know how to subtract the receiver, a fraction"

    ^ (aFloat * denominator - numerator) / denominator
!

differenceFromInteger:anInteger
    "sent when an integer does not know how to subtract the receiver, a fraction"

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

    "Modified: 5.11.1996 / 10:32:14 / cg"
!

lessFromInteger:anInteger
    "sent when an integer does not know how to compare to the receiver, a fraction"

    ^ (denominator * anInteger) < numerator
!

productFromFloat:aFloat
    "sent when a float does not know how to multiply the receiver, a fraction"

    ^ aFloat * numerator / denominator
!

productFromInteger:anInteger
    "sent when an integer does not know how to multiply the receiver, a fraction"

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

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

quotientFromFloat:aFloat
    "sent when a float does not know how to divide by the receiver, a fraction"

    ^ (aFloat * denominator) / numerator
!

quotientFromInteger:anInteger
    "sent when an integer does not know how to divide by the receiver, a fraction"

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

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

sumFromFloat:aFloat
    "sent when a float does not know how to add the receiver, a fraction"

    ^ (aFloat * denominator + numerator) / denominator
!

sumFromInteger:anInteger
    "sent when an integer does not know how to add the receiver, a fraction"

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

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

!Fraction methodsFor:'printing & storing'!

printOn:aStream
    "append a printed representation of the receiver to the
     argument, aStream"

    aStream nextPut:$(.
    numerator printOn:aStream.
    aStream nextPut:$/.
    denominator printOn:aStream.
    aStream nextPut:$)
! !

!Fraction methodsFor:'private'!

reduced
    "reduce the receiver"

    |gc|

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

    gc := numerator gcd:denominator.
    (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:num denominator:den
    "set both numerator and denominator"

    numerator := num.
    denominator := den
! !

!Fraction methodsFor:'queries'!

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

    ^ true
! !

!Fraction methodsFor:'testing'!

negative
    "return true if the receiver is negative"

    (numerator < 0) ifTrue:[
	^ (denominator < 0) not
    ].
    ^ (denominator < 0)
! !

!Fraction methodsFor:'truncation and rounding'!

rounded
    "return the receiver rounded to the nearest integer as integer"

    "/ mhmh - what about -(1/2)

    |t|

    self negative ifTrue:[
        t := self - (1/2)
    ] ifFalse:[
        t := self + (1/2)
    ].
    ^ t truncated.

    "
     (1/3) rounded           
     (1/3) negated rounded     
     (1/2) rounded           
     (1/2) negated rounded   
     0.5 rounded  
     -0.5 rounded 
     (2/3) rounded             
     (2/3) negated rounded     
    "

    "Modified: 5.11.1996 / 11:32:32 / cg"
!

truncated
    "return the receiver truncated towards zero as Integer"

    ^ numerator quo: denominator

    "
     (3/2) truncated     
     (3/2) negated truncated  
    "

    "Modified: 5.11.1996 / 12:18:46 / cg"
! !

!Fraction class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Fraction.st,v 1.36 1997-01-10 18:55:08 cg Exp $'
! !
Fraction initialize!