Fraction.st
author Claus Gittinger <cg@exept.de>
Fri, 05 Jan 1996 13:33:18 +0100
changeset 835 8bd6f4aa8130
parent 701 a309e3ef7faf
child 1133 961f2b095c22
permissions -rw-r--r--
*** empty log message ***

"
 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)."
! !

!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 = Fraction;
	    _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'!

unity
    "return the neutral element for multiplication"

    ^ FractionOne
!

zero
    "return the neutral element for addition"

    ^ FractionZero
! !

!Fraction class methodsFor:'queries'!

isBuiltInClass
    "this class is known by the run-time-system"

    ^ self == Fraction
! !

!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:[
	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
!

+ 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:[
	n := aNumber numerator.
	d := aNumber denominator.

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

	^ (self class numerator:((numerator * d) + (n * denominator))
		    denominator:(denominator * d)) reduced
    ].
    (aNumber isMemberOf:Float) ifTrue:[
	^ aNumber + (numerator asFloat / denominator asFloat)
    ].
    ^ aNumber sumFromFraction:self
!

- 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:[
	n := aNumber numerator.
	d := aNumber denominator.

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

	^ (self class numerator:((numerator * d) - (n * denominator)) 
		    denominator:(denominator * d)) reduced
    ].
    (aNumber isMemberOf:Float) ifTrue:[
	^ (numerator asFloat / denominator asFloat) - aNumber
    ].
    ^ aNumber differenceFromFraction:self
!

/ 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:[
	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
!

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

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

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

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

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

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

!Fraction methodsFor:'coercing & converting'!

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
!

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

    (aNumber isMemberOf:SmallInteger) ifTrue:[
	^ numerator < (denominator * aNumber)
    ].
    aNumber isFraction ifTrue:[
	^ (numerator * aNumber denominator) < (denominator * aNumber numerator)
    ].
    ^ aNumber lessFromFraction:self
!

= 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 ..."

    (aNumber isMemberOf:SmallInteger) ifTrue:[
	^ numerator > (denominator * aNumber)
    ].
    aNumber isFraction ifTrue:[
	^ (numerator * aNumber denominator) > (denominator * aNumber numerator)
    ].
    ^ self retry:#> coercing:aNumber
! !

!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
!

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
!

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
!

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
! !

!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"

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

truncated
    "return the receiver truncated towards zero as Integer"

    ^ numerator // denominator
! !

!Fraction class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Fraction.st,v 1.26 1996-01-05 12:33:10 cg Exp $'
! !
Fraction initialize!