Number.st
author Claus Gittinger <cg@exept.de>
Wed, 02 Jul 2003 11:34:42 +0200
changeset 7468 61c8a3053bf4
parent 7456 42a1cbc55b6c
child 7729 bbd20db09d1b
permissions -rw-r--r--
moved math functions to number

"
 COPYRIGHT (c) 1988 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.
"

"{ Package: 'stx:libbasic' }"

ArithmeticValue subclass:#Number
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Magnitude-Numbers'
!

!Number class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1988 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
"
    abstract superclass for all kinds of numbers

    [author:]
	Claus Gittinger

    [see also:]
	Integer LargeInteger SmallInteger
	LimitedPrecisionReal Float ShortFloat
	Fraction FixedPoint
"
! !

!Number class methodsFor:'instance creation'!

fromString:aString
    "for compatibility with other smalltalks - same as #readFrom:"

    |s num|

    s := aString readStream.
    num := self readFrom:s onError:[^ self error:'invalid number'].
    s atEnd ifFalse:[^ self error:'garbage at end of number'].
    ^ num.

    "
     Number fromString:'12345'
     Number fromString:'abc'
     Number fromString:'1abc'
     '12345' asNumber
    "

    "Modified: / 3.8.1998 / 20:05:11 / cg"
!

fromString:aString onError:exceptionBlock
    "for compatibility with other smalltalks - same as #readFrom:"

    ^ self readFrom:aString onError:exceptionBlock

    "
     Number fromString:'12345' onError:0
     Number fromString:'fooBarBaz' onError:0
    "

    "Modified: / 3.8.1998 / 20:05:34 / cg"
!

readFrom:aStringOrStream onError:exceptionBlock
    "return the next Number from the (character-)stream aStream;
     skipping all whitespace first; return the value of exceptionBlock,
     if no number can be read.
     This method is less strict than the smalltalk number reader; it
     allows for prefixed + and also allows missing fractional part after eE"

    ^ [
        |value intValue mantissaAndScale scale decimalMantissa str 
         nextChar radix negative signExp exp denom|

        str := aStringOrStream readStream.

        nextChar := str skipSeparators.
        nextChar isNil ifTrue:[^ exceptionBlock value].

        (nextChar == $-) ifTrue:[
            negative := true.
            str next.
            nextChar := str peekOrNil
        ] ifFalse:[
            negative := false.
            (nextChar == $+) ifTrue:[
                str next.
                nextChar := str peekOrNil
            ]
        ].
        (nextChar isDigit or:[nextChar == $.]) ifFalse:[
            ^ exceptionBlock value.
"/          value := super readFrom:str.
"/          negative ifTrue:[value := value negated].
"/          ^ value
        ].
        nextChar == $. ifTrue:[
            radix := 10.
            value := 0.0.
            intValue := 0.
        ] ifFalse:[
            value := Integer readFrom:str radix:10.
            nextChar := str peekOrNil.
            ((nextChar == $r) or:[ nextChar == $R]) ifTrue:[
                str next.
                radix := value.
                value := Integer readFrom:str radix:radix.
            ] ifFalse:[
                radix := 10
            ].
            intValue := value.
        ].

        (nextChar == $.) ifTrue:[
            str next.
            nextChar := str peekOrNil.
            scale := 0.
            decimalMantissa := 0.
            (nextChar notNil and:[nextChar isDigitRadix:radix]) ifTrue:[
                mantissaAndScale := Number readMantissaAndScaleFrom:str radix:radix.
                value := value asFloat + (mantissaAndScale first).
                nextChar := str peekOrNil
            ]
        ].
        ('eEdDqQ' includes:nextChar) ifTrue:[
            str next.
            nextChar := str peekOrNil.
            signExp := 1.
            (nextChar == $+) ifTrue:[
                str next.
                nextChar := str peekOrNil.
            ] ifFalse:[
                (nextChar == $-) ifTrue:[
                    str next.
                    nextChar := str peekOrNil.
                    signExp := -1
                ]
            ].
            ('qQ' includes:nextChar) ifTrue:[
                value := value asLongFloat.
            ] ifFalse:[
                value := value asFloat.
"/ future: (for now, always create Doubles for Dolphin,Squeak etc. compatibility
"/                ('eE' includes:nextChar) ifTrue:[
"/                    value := value asShortFloat
"/                ]
            ].
            (nextChar notNil and:[(nextChar isDigitRadix:radix)]) ifTrue:[
                exp := (Integer readFrom:str radix:radix) * signExp.
                value := value * ((value class unity * 10.0) raisedToInteger:exp)
            ]
        ] ifFalse:[
            ('s' includes:nextChar) ifTrue:[
                mantissaAndScale isNil ifTrue:[
                    value := intValue asFixedPoint:0.
                ] ifFalse:[
                    denom := 10 raisedTo:mantissaAndScale last.
                    value := FixedPoint 
                                numerator:(intValue * denom) + (mantissaAndScale second)
                                denominator:denom
                                scale:mantissaAndScale last.
                ].
            ] ifFalse:[
                value isLimitedPrecisionReal ifTrue:[
                    value := value asFloat.
                ]
            ].
        ].
        negative ifTrue:[
            value := value negated
        ].
        value.
    ] on:Error do:exceptionBlock

    "
     Number readFrom:(ReadStream on:'54.32e-01')      
     Number readFrom:(ReadStream on:'12345678901234567890') 
     Number readFrom:(ReadStream on:'12345678901234567890.0') 
     Number readFrom:(ReadStream on:'12345678901234567890.012345678901234567890') 
     Number readFrom:(ReadStream on:'16rAAAAFFFFAAAAFFFF') 
     Number readFrom:'16rAAAAFFFFAAAAFFFF' 
     Number readFrom:'0.000001'  
     '+00000123.45' asNumber  
     Number readFrom:'99s'      
     Number readFrom:'99.00s'      
     Number readFrom:'99.0000000s'      
     Number readFrom:'.0000000s'      
     Number readFrom:'.0000000q'      
     Number readFrom:'.0000000f'      
     Number readFrom:'.0000000e'      
     Number readFrom:'.0000000s1'      
     Number readFrom:'.0000000q1'      
     Number readFrom:'.0000000f1'      
     Number readFrom:'.0000000e1'      
    "

    "Modified: / 14.4.1998 / 19:22:50 / cg"
!

readSmalltalkSyntaxFrom:aStream
    "ST-80 compatibility (thanks to a note from alpha testers)
     read and return the next Number in smalltalk syntax from the 
     (character-) aStream.
     Returns nil if aStream contains no valid number."

    ^ Scanner scanNumberFrom:aStream
"/    ^ Compiler evaluate:aStream compile:false "/ self readFrom:aStream.

    "
     Number readSmalltalkSyntaxFrom:'99d'    
     Number readSmalltalkSyntaxFrom:'99.00d'    
     Number readSmalltalkSyntaxFrom:(ReadStream on:'54.32e-01')    
     Number readSmalltalkSyntaxFrom:(ReadStream on:'12345678901234567890')
     Number readSmalltalkSyntaxFrom:(ReadStream on:'16rAAAAFFFFAAAAFFFF')
     Number readSmalltalkSyntaxFrom:(ReadStream on:'(1/10)') 
     Number readFrom:(ReadStream on:'(1/10)') 
     Number readSmalltalkSyntaxFrom:(ReadStream on:'+00000123.45')  
     Number readFrom:(ReadStream on:'+00000123.45')  

     |s|
     s := ReadStream on:'2.'.
     Number readSmalltalkSyntaxFrom:s.
     s next    

     |s|
     s := ReadStream on:'2.0.'.
     Number readSmalltalkSyntaxFrom:s.
     s next    
    "

    "Modified: / 19.11.1999 / 18:26:47 / cg"
! !

!Number class methodsFor:'error reporting'!

raise:aSignalSymbolOrErrorClass receiver:someNumber selector:sel arg:arg errorString:text 
    "ST-80 compatible signal raising. Provided for PD numeric classes"

    <context: #return>

    ^ self
        raise:aSignalSymbolOrErrorClass 
        receiver:someNumber 
        selector:sel 
        arguments:(Array with:arg)
        errorString:text 

    "
     Number 
        raise:#domainErrorSignal
        receiver:1.0
        selector:#sin
        arg:nil
        errorString:'foo bar test'
    "

    "Modified: / 16.11.2001 / 14:12:50 / cg"
!

raise:aSignalSymbolOrErrorClass receiver:someNumber selector:sel arguments:argArray errorString:text 
    "ST-80 compatible signal raising. Provided for PD numeric classes.
     aSignalSymbolOrErrorClass is either an Error-subclass, or
     the selector which is sent to myself, to retrieve the Exception class / Signal."

    <context: #return>

    |msg signalOrException|

    msg := MessageSend
                receiver:someNumber
                selector:sel
                arguments:argArray.

    aSignalSymbolOrErrorClass isSymbol ifTrue:[
        signalOrException := self perform:aSignalSymbolOrErrorClass.
    ] ifFalse:[
        signalOrException := aSignalSymbolOrErrorClass.    "/ assume its an Error-Subclass
    ].

    ^ signalOrException
         raiseRequestWith:msg 
         errorString:text 
         in:thisContext sender

    "
     Number 
        raise:#domainErrorSignal
        receiver:1.0
        selector:#foo 
        errorString:'foo bar test'
    "

    "Modified: / 16.11.2001 / 14:12:09 / cg"
!

raise:aSignalSymbolOrErrorClass receiver:someNumber selector:sel errorString:text 
    "ST-80 compatible signal raising. Provided for PD numeric classes.
     aSignalSymbolOrErrorClass is either an Error-subclass, or
     the selector which is sent to myself, to retrieve the Exception class / Signal."

    <context: #return>

    ^ self
        raise:aSignalSymbolOrErrorClass 
        receiver:someNumber 
        selector:sel 
        arguments:#()
        errorString:text 

    "
     Number 
        raise:#domainErrorSignal
        receiver:1.0
        selector:#foo 
        errorString:'foo bar test'
    "

    "Modified: / 16.11.2001 / 14:13:16 / cg"
! !

!Number class methodsFor:'private'!

readMantissaAndScaleFrom:aStream radix:radix
    "helper for readFrom: -
     return the mantissa (post-decimal-point digits) from the (character-)stream aStream;
     In addition, the scale (number of postDecimalPoint digits) is returned 
     (to support reading fixedPoint numbers).
     No whitespace is skipped.
     Errs if no number is available on aStream."

    |nextChar value factor intMantissa scale highPrecision|

    highPrecision := false.
    value := 0.0.
    factor := 1.0 asLongFloat / radix.
    scale := 0.
    intMantissa := 0.
    nextChar := aStream peekOrNil.
    [nextChar notNil and:[nextChar isDigitRadix:radix]] whileTrue:[
        value := value + (nextChar digitValue * factor).
        intMantissa := (intMantissa * radix) + nextChar digitValue.
        factor := factor / radix.
        scale := scale + 1.
        aStream next.
        nextChar := aStream peekOrNil
    ].

    ^ (Array with:value with:intMantissa with:scale).

    "
     Number readMantissaAndScaleFrom:'234'    readStream radix:10. 
     Number readMantissaAndScaleFrom:'2'      readStream radix:10. 
     Number readMantissaAndScaleFrom:'234567' readStream radix:10. 
     Number readMantissaAndScaleFrom:'234000' readStream radix:10. 
     Number readMantissaAndScaleFrom:'234'    readStream radix:10. 

     Number readMantissaAndScaleFrom:'12345678901234567890' readStream radix:10. 
    "

    "Modified: / 14.4.1998 / 18:47:47 / cg"
!

readMantissaFrom:aStream radix:radix
    "helper for readFrom: -
     return the mantissa (post-decimal-point digits)
     from the (character-)stream aStream;
     No whitespace is skipped.
     Errs if no number available."

    ^ (self readMantissaAndScaleFrom:aStream radix:radix) first

    "
     Number readMantissaFrom:'234'    readStream radix:10.
     Number readMantissaFrom:'2'      readStream radix:10.
     Number readMantissaFrom:'234567' readStream radix:10.
    "

    "Modified: / 14.4.1998 / 18:47:47 / cg"
! !

!Number methodsFor:'Compatibility-Squeak'!

asSmallAngleDegrees
    "Return the receiver normalized to lie within the range (-180, 180)"

    | pos |

    pos := self \\ 360.
    pos > 180 ifTrue: [pos := pos - 360].
    ^ pos

    "
     #(-500 -300 -150 -5 0 5 150 300 500 1200) 
        collect: [:n | n asSmallAngleDegrees]
    "
!

closeFrom:aNumber
    "are these two numbers close?"

    | fuzz |

    self isNaN == aNumber isNaN ifFalse: [^ false]. 
    self isInfinite == aNumber isInfinite ifFalse: [^ false].

    fuzz := (self abs max:aNumber abs) * 0.0001. 
    ^ (self - aNumber) abs <= fuzz

    "
     9.0 closeTo: 8.9999     
     9.9 closeTo: 9          
     (9/3) closeTo: 2.9999      
     1 closeTo: 0.9999      
     1 closeTo: 1.0001      
     1 closeTo: 1.001       
     1 closeTo: 0.999       

     0.9999 closeTo: 1      
     1.0001 closeTo: 1      
     1.001 closeTo: 1     
     0.999 closeTo: 1
     Float NaN closeTo:Float NaN
     Float infinity closeTo:Float infinity
    "
!

closeTo:num
    "are these two numbers close to each other?"

    num isNumber ifFalse:[^false].
    ^ num closeFrom:self

    "
     1 closeTo:1.0000000001
     1 closeTo:1.001
    "

    "Created: / 5.11.2001 / 18:07:26 / cg"
!

newTileMorphRepresentative
	^ TileMorph new addArrows; setLiteral: self; addSuffixIfCan
!

stringForReadout
    ^ self rounded printString
! !

!Number methodsFor:'coercing'!

retry: aSymbol coercing: aNumber
    "Arithmetic represented by the symbol, aSymbol,
    could not be performed with the receiver and the argument,
    aNumber, because of the differences in representation.  Coerce either
    the receiver or the argument, depending on which has higher generality, and
    try again.  If the symbol is the equals sign, answer false if the argument
    is not a Number.  If the generalities are the same, create an error message."

    |myGenerality otherGenerality|

    (aSymbol == #=) ifTrue:[
        (aNumber respondsTo:#generality) ifFalse:[^ false]
    ] ifFalse:[
        (aNumber respondsTo:#generality) ifFalse:[
            self error:'retry:coercing: argument is not a number'.
            ^ self
        ]
    ].
    myGenerality := self generality.
    otherGenerality := aNumber generality.
    (myGenerality > otherGenerality) ifTrue:[
        ^ self perform:aSymbol with:(self coerce:aNumber)
    ].
    (myGenerality < otherGenerality) ifTrue:[
        ^ (aNumber coerce:self) perform:aSymbol with:aNumber
    ].
    self error:'retry:coercing: oops - same generality'
! !

!Number methodsFor:'converting'!

% aNumber 
    "Return a complex number with the receiver as the real part and 
     aNumber as the imaginary part"

    ^ Complex real:self imaginary:aNumber

    "Modified: / 9.7.1998 / 10:18:12 / cg"
!

@ aNumber
    "return a Point with the receiver as x-coordinate and the argument
     as y-coordinate"

%{  /* NOCONTEXT */

    /*
     * I cannot tell if this special code is worth anything
     */
    if (__CanDoQuickNew(sizeof(struct __Point))) {      /* OBJECT ALLOCATION */
	OBJ newPoint;
	int spc;

	__qCheckedAlignedNew(newPoint, sizeof(struct __Point));
	__InstPtr(newPoint)->o_class = @global(Point);
	__PointInstPtr(newPoint)->p_x = self;
	__PointInstPtr(newPoint)->p_y = aNumber;
	if (! __bothSmallInteger(self, aNumber)) {
	    spc = __qSpace(newPoint);
	    __STORE_SPC(newPoint, aNumber, spc);
	    __STORE_SPC(newPoint, self, spc);
	}
	RETURN ( newPoint );
    }
%}
.
    ^ Point x:self y:aNumber
!

asComplex
    "Return a complex number with the receiver as the real part and 
     zero as the imaginary part"

    ^ Complex real:self

    "Modified: / 9.7.1998 / 10:18:16 / cg"
!

asMetaNumber
    ^ SomeNumber new realNumber:self
!

asNumber

    ^ self.
!

asPoint
    "return a new Point with the receiver as all coordinates;  
     often used to supply the same value in two dimensions, as with 
     symmetrical gridding or scaling."

%{  /* NOCONTEXT */

    if (__CanDoQuickNew(sizeof(struct __Point))) {      /* OBJECT ALLOCATION */
	OBJ newPoint;

	__qCheckedAlignedNew(newPoint, sizeof(struct __Point));
	__InstPtr(newPoint)->o_class = @global(Point);
	__PointInstPtr(newPoint)->p_x = self;
	__PointInstPtr(newPoint)->p_y = self;
	__STORE(newPoint, self);
	RETURN ( newPoint );
    }
%}.
    ^ Point x:self y:self
!

decodeAsLiteralArray
    "given a literalEncoding in the receiver,
     create & return the corresponding object.
     The inverse operation to #literalArrayEncoding."

    ^ self

    "Created: 25.2.1997 / 19:17:06 / cg"
    "Modified: 25.2.1997 / 19:17:42 / cg"
!

degreesToRadians
    "interpreting the receiver as radians, return the degrees"

    ^ (self * (Float pi)) / 180.0

    "
     180 degreesToRadians
     Float pi radiansToDegrees
    "
!

literalArrayEncoding
    "encode myself as an array literal, from which a copy of the receiver
     can be reconstructed with #decodeAsLiteralArray."

    ^ self

    "Modified: 1.9.1995 / 02:25:26 / claus"
    "Modified: 22.4.1996 / 13:00:27 / cg"
!

radiansToDegrees
    "interpreting the receiver as degrees, return the radians"

    ^ (self * 180.0) / (Float pi)

    "
     180 degreesToRadians     
     Float pi radiansToDegrees
    "
!

withScale:newScale
    "return a fixedPoint number representing the same valie as the receiver, 
     with newScale number of post-decimal digits"

    ^ self asFixedPoint:newScale

    "
     1234 withScale:2 
     1234.1 withScale:2 
     1234.12 withScale:2 
     1234.123 withScale:2 
     (1/7) withScale:2
    "
! !

!Number methodsFor:'intervals'!

downTo:stop
    "return an interval from receiver down to the argument, incrementing by -1"

    ^ self to:stop by:-1

    "
     (10 downTo:1) do:[:i | Transcript showCR:i].
    "
!

to:stop
    "return an interval from receiver up to the argument, incrementing by 1"

    ^ Interval from:self to:stop
!

to:stop by:step
    "return an interval from receiver up to the argument, incrementing by step"

    ^ Interval from:self to:stop by:step
!

to:stop byFactor:factor
    "return a geometric series from receiver up to the argument;
     elements have a constant factor in between"

    ^ GeometricSeries from:self to:stop byFactor:factor

    "
     (1 to:256 byFactor:2)
     (256 to:1 byFactor:1/2)     
    "
! !

!Number methodsFor:'iteration'!

timesRepeat:aBlock
    "evaluate the argument, aBlock self times"

    |count|

    count := self.
    [count > 0] whileTrue:[
	aBlock value.
	count := count - 1
    ]
! !

!Number methodsFor:'mathematical functions'!

conjugated
    "Return the complex conjugate of this Number."

    ^ self

    "Modified: / 9.7.1998 / 10:17:31 / cg"
!

exp
    "compute e**x of the receiver"

    (self isLimitedPrecisionReal not
    or:[self generality < 1.0 generality]) ifTrue:[
        ^ self asFloat exp.
    ].
    ^ self exp_withAccuracy:(self precision)
!

floorLog:radix
    "return the logarithm truncated as an integer"

    ^ (self log:radix) floor
!

imaginary
    "Return the imaginary part of this Number."

    ^ 0

    "Modified: / 9.7.1998 / 10:17:24 / cg"
!

ln
    "compute ln of the receiver"

    (self isLimitedPrecisionReal not
    or:[self generality < 1.0 generality]) ifTrue:[
        ^ self asFloat ln.
    ].
    ^ self ln_withAccuracy:self precision
!

log
    "return log base 10 of the receiver.
     Alias for log10."

    ^ self log10
!

log10
    "return log base 10 of the receiver"

    ^ self log:10
!

log:aNumber
    "return log base aNumber of the receiver"

    ^ self ln / aNumber ln
!

raisedTo:aNumber
    "return the receiver raised to aNumber"

    aNumber = 0 ifTrue:[^ 1].
    aNumber = 1 ifTrue:[^ self].
    aNumber isInteger ifTrue:[
        ^ self raisedToInteger:aNumber
    ].
    ^ self asFloat raisedTo:aNumber

    "
     2 raisedTo: 4    
     10 raisedTo: 4    
    "
!

raisedToInteger:exp 
    "return the receiver raised to exp"

    |result e t|

    "use the addition chaining algorithm,
     which is much faster for big exp-arguments"

    result := 1.
    t := self.
    exp < 0 ifTrue:[
        e := exp negated.
    ] ifFalse:[
        e := exp.
    ].

    [e ~~ 0] whileTrue:[
        [(e bitAnd:1) == 0] whileTrue:[
            e := e bitShift:-1.
            t := t * t.
        ].
        e := e - 1.
        result := result * t.
    ].

    (exp < 0) ifTrue:[
        ^ 1 / result
    ].

    ^ result


    "
     (2 raisedToInteger:216)
     (2 raisedTo:216) 
-> 105312291668557186697918027683670432318895095400549111254310977536     

     (2 raisedToInteger:216) asFloat     
     (2 raisedTo:216) asFloat     
-> 1.05312E+65

     (2 raisedToInteger:500)
     (2 raisedTo:500) 
-> 3273390607896141870013189696827599152216642046043064789483291368096133796404674554883270092325904157150886684127560071009217256545885393053328527589376
     2 raisedToInteger:10 
-> 1024
    -2 raisedToInteger:10
-> 1024
     -2 raisedToInteger:9
-> -512
     10 raisedToInteger:-10
-> (1/10000000000)
     2 raisedToInteger:0 
-> 1
     2 raisedToInteger:-1 
-> (1/2)

     Time millisecondsToRun:[
        10000 timesRepeat:[
            (2 raisedToInteger:500)
        ]
     ]  

     Time millisecondsToRun:[
        |bigNum|
        bigNum := 2 raisedToInteger:500.
        10 timesRepeat:[
            (bigNum raisedToInteger:500)
        ]
     ]
    "

    "Created: / 27.4.1999 / 15:19:22 / stefan"
    "Modified: / 27.4.1999 / 16:16:11 / stefan"
!

real
    "Return the real part of this Number."

    ^ self

    "Modified: / 9.7.1998 / 10:17:17 / cg"
!

sqrt
    "return the square root of the receiver"

    (self isLimitedPrecisionReal not
    or:[self generality < 1.0 generality]) ifTrue:[
        ^ self asFloat sqrt.
    ].
    ^ self sqrt_withAccuracy:self precision
!

timesTwoPower:anInteger
    "Return the receiver multiplied by 2.0 raised to the power of the argument.
     For protocol completeness wrt. Squeak and ST80."

    ^ self * (2.0 raisedToInteger:anInteger)

    "
     123 timesTwoPower:0  
     123 timesTwoPower:1  
     123 timesTwoPower:2  
     123 timesTwoPower:3  
    "
! !

!Number methodsFor:'printing & storing'!

printOn:aStream paddedWith:padCharacter to:size base:radix
    |s|

    s := self printStringRadix:radix.
    s printOn: aStream leftPaddedTo:size with: padCharacter


!

storeOn:aStream
    "append a string for storing the receiver onto the argument,
     aStream - since numbers are literals,they store as they print."

    ^ self printOn:aStream
!

storeString
    "return a string for storing 
     - since numbers are literals, they store as they print."

    ^ self printString
! !

!Number methodsFor:'taylor series'!

arcSin_withAccuracy:epsilon
    "compute the arcSine of the receiver"

    "/ uses taylor series:
    "/                 1*x^3   1*3 * x^5   
    "/    arcSin = x + ----- + ---------- + ...
    "/                 2* 3    2*4 *  5    

    |x2 num numf den denf approx lastApprox d|

    x2 := self squared.
    num := (x2 * self).
    approx := self + (num / 6).
    lastApprox := self.

    numf := 3.
    denf  := 4.
    den := 2.

    [ (lastApprox - approx) abs > epsilon ] whileTrue:[
        num := (num * x2) * numf.   numf := numf + 2.
        den := den * denf.          denf := denf + 2.
        d := den * numf.

        lastApprox := approx.
        approx := approx + (num / d).
    ].
    ^ approx

    "
     0.5 arcSin                                    0.523599
     0.5 asLongFloat arcSin                        0.523598776

     0.5 asLongFloat arcSin_withAccuracy:1         0.520833333
     0.5 asLongFloat arcSin_withAccuracy:0.1       0.520833333
     0.5 asLongFloat arcSin_withAccuracy:0.01      0.523177083
     0.5 asLongFloat arcSin_withAccuracy:0.001     0.523525856

     0.5 asLongFloat arcSin_withAccuracy:1e-20     0.523598776

     0.5 asLargeFloat arcSin_withAccuracy:1e-30     


     0.1 arcSin                                    0.100167
     0.1 asLongFloat arcSin                        0.100167421

     0.1 asLongFloat arcSin_withAccuracy:1         0.100166667
     0.1 asLongFloat arcSin_withAccuracy:0.1       0.100166667
     0.1 asLongFloat arcSin_withAccuracy:0.01      0.100166667
     0.1 asLongFloat arcSin_withAccuracy:0.001     0.100166667

     0.1 asLongFloat arcSin_withAccuracy:1e-20     0.100167421

     0.1 asLargeFloat arcSin_withAccuracy:1e-30     
    "
!

arcSinh_withAccuracy:epsilon
    "compute the hyperbolic arcSine of the receiver"

    "/ uses taylor series:
    "/                 1*x^3   1*3 * x^5   
    "/    arcSinh = x - ----- + --------- - ...
    "/                 2* 3    2*4 *  5   

    |x2 num numf den denf approx lastApprox d|

    x2 := self squared.
    num := (x2 * self) negated.
    approx := self + (num / 6).
    lastApprox := self.

    numf := 3.
    denf  := 4.
    den := 2.

    [ (lastApprox - approx) abs > epsilon ] whileTrue:[
        num := (num * x2) * numf.   numf := numf + 2.
        num := num negated.
        den := den * denf.          denf := denf + 2.
        d := den * numf.

        lastApprox := approx.
        approx := approx + (num / d).
    ].
    ^ approx

    "
     0.5 arcSinh                                    0.481212
     0.5 asLongFloat arcSinh                        0.481211825

     0.5 asLongFloat arcSinh_withAccuracy:1         0.479166667
     0.5 asLongFloat arcSinh_withAccuracy:0.1       0.479166667
     0.5 asLongFloat arcSinh_withAccuracy:0.01      0.481510417
     0.5 asLongFloat arcSinh_withAccuracy:0.001     0.481161644

     0.5 asLongFloat arcSinh_withAccuracy:1e-20     0.481211825

     0.5 asLargeFloat arcSinh_withAccuracy:1e-30     


     0.1 arcSinh                                    0.0998341
     0.1 asLongFloat arcSinh                        0.0998340789

     0.1 asLongFloat arcSinh_withAccuracy:1         0.0998333333
     0.1 asLongFloat arcSinh_withAccuracy:0.1       0.0998333333
     0.1 asLongFloat arcSinh_withAccuracy:0.01      0.0998333333
     0.1 asLongFloat arcSinh_withAccuracy:0.001     0.0998333333

     0.1 asLongFloat arcSinh_withAccuracy:1e-20     0.0998340789
     0.1 asLongFloat arcSinh_withAccuracy:1e-30     0.0998340789

     0.1 asLargeFloat arcSinh_withAccuracy:1e-30     
    "
!

arcTan_withAccuracy:epsilon
    "compute the arcTangent of the receiver"

    "/ uses taylor series:
    "/                 x^3   x^5   x^7
    "/    arcTan = x - --- + --- - --- ...
    "/                  3     5    7

    |x2 num den approx lastApprox|

    x2 := self squared.

    num := (x2 * self) negated.
    den := 3.
    approx := self + (num / den).
    lastApprox := self.

    [ (lastApprox - approx) abs > epsilon ] whileTrue:[
        den := den + 2.
        num := (num * x2) negated.

        lastApprox := approx.
        approx := approx + (num / den).
"/Transcript show:num; show:' '.
"/Transcript show:den; show:' '.
"/Transcript showCR:(num / den).
"/Transcript showCR:approx.
"/Transcript cr.

Transcript showCR:(lastApprox - approx) abs.
    ].
    ^ approx

    "
     1.0 arcTan                                    0.785398
     1.0 asLongFloat arcTan                        0.785398163

     1.0 asLongFloat arcTan_withAccuracy:1         0.666666667
     1.0 asLongFloat arcTan_withAccuracy:0.1       0.744011544
     1.0 asLongFloat arcTan_withAccuracy:0.01      0.790299653
     1.0 asLongFloat arcTan_withAccuracy:0.001     0.785897165

     1.0 asLongFloat arcTan_withAccuracy:1e-20     


     0.5 arcTan                                    0.463648
     0.5 asLongFloat arcTan                        0.463647609

     0.5 asLongFloat arcTan_withAccuracy:1         0.458333333
     0.5 asLongFloat arcTan_withAccuracy:0.1       0.458333333
     0.5 asLongFloat arcTan_withAccuracy:0.01      0.464583333
     0.5 asLongFloat arcTan_withAccuracy:0.001     0.463684276

     0.5 asLongFloat arcTan_withAccuracy:1e-20     0.463647609
     0.5 asLargeFloat arcTan_withAccuracy:1e-30     
    "
!

arcTanh_withAccuracy:epsilon
    "compute the hyperbolic arcTangent of the receiver"

    "/ uses taylor series:
    "/                 x^3   x^5   x^7
    "/    arcTanh = x + --- + --- + --- ...
    "/                  3     5    7

    |x2 num den approx lastApprox|

    x2 := self squared.

    num := (x2 * self).
    den := 3.
    approx := self + (num / den).
    lastApprox := self.

    [ (lastApprox - approx) abs > epsilon ] whileTrue:[
        den := den + 2.
        num := (num * x2).

        lastApprox := approx.
        approx := approx + (num / den).
    ].
    ^ approx

    "
     0.5 arcTanh                                    0.549306
     0.5 asLongFloat arcTanh                        0.549306144

     0.5 asLongFloat arcTanh_withAccuracy:1         0.541666667
     0.5 asLongFloat arcTanh_withAccuracy:0.1       0.541666667
     0.5 asLongFloat arcTanh_withAccuracy:0.01      0.547916667
     0.5 asLongFloat arcTanh_withAccuracy:0.001     0.549249752

     0.5 asLongFloat arcTanh_withAccuracy:1e-20     0.549306144

     0.5 asLargeFloat arcTanh_withAccuracy:1e-30     
    "
!

cos_withAccuracy:epsilon
    "compute the cosine of the receiver"

    "/ uses taylor series:
    "/               x^2   x^4   x^6
    "/    cos = 1 - --- + --- - --- ...
    "/                2!!    4!!    6!!

    |x2 facN num den approx lastApprox|

    x2 := self squared.

    num := x2 negated.
    den := 2.
    facN := 2.
    approx := 1 + (num / den).
    lastApprox := 1.

    [ (lastApprox - approx) abs > epsilon ] whileTrue:[
        facN := facN + 2.
        den := den * (facN - 1) * facN.
        num := (num * x2) negated.
        lastApprox := approx.
        approx := approx + (num / den).
    ].
    ^ approx

    "
     1.0 cos                                    0.540302
     1.0 asLongFloat cos_withAccuracy:1         0.5
     1.0 asLongFloat cos_withAccuracy:0.1       0.541666667 
     1.0 asLongFloat cos_withAccuracy:0.01      0.540277778
     1.0 asLongFloat cos_withAccuracy:0.001     0.540302579

     1.0 asLongFloat cos_withAccuracy:1e-40     0.540302306    
    "
!

cosh_withAccuracy:epsilon
    "compute the hyperbolic cosine of the receiver"

    "/ uses taylor series:
    "/               x^2   x^4   x^6
    "/    cosh = x + --- + --- + --- ...
    "/                2!!    4!!    6!!

    |x2 facN num den approx lastApprox|

    x2 := self squared.

    num := x2.
    den := 2.
    facN := 2.
    approx := self + (num / den).
    lastApprox := self.

    [ (lastApprox - approx) abs > epsilon ] whileTrue:[
        facN := facN + 2.
        den := den * (facN - 1) * facN.
        num := num * x2.

        lastApprox := approx.
        approx := approx + (num / den).
    ].
    ^ approx

    "
     1.0 cosh                                    1.54308
     1.0 asLongFloat cosh_withAccuracy:1         1.5 
     1.0 asLongFloat cosh_withAccuracy:0.1       1.54308 
     1.0 asLongFloat cosh_withAccuracy:0.01      1.54308 
     1.0 asLongFloat cosh_withAccuracy:0.001     1.54308 

     1.0 asLongFloat cosh_withAccuracy:1e-40   -> 1.543080    
    "
!

exp_withAccuracy:epsilon
    "compute e**x of the receiver"

    "/ uses taylor series:
    "/             x    x^2   x^3
    "/    e = 1 + --- + --- + --- ...
    "/             1!!    2!!    3!!

    |x2 facN num den approx lastApprox|

    x2 := self squared.

    num := x2.
    den := 2.
    facN := 2.
    approx := self + self + (num / den).
    lastApprox := self.

    [ (lastApprox - approx) abs > epsilon ] whileTrue:[
        facN := facN + 1.
        den := den * facN.
        num := num * self.

        lastApprox := approx.
        approx := approx + (num / den).
    ].
    ^ approx

    "
     1.0 exp                                    2.71828
     1.0 asLongFloat exp                        2.71828183

     1.0 asLongFloat exp_withAccuracy:1         2.66666667
     1.0 asLongFloat exp_withAccuracy:0.1       2.70833333
     1.0 asLongFloat exp_withAccuracy:0.01      2.71666667
     1.0 asLongFloat exp_withAccuracy:0.001     2.71825397

     1.0 asLongFloat exp_withAccuracy:1e-40     2.71828183 
    "
!

ln_withAccuracy:epsilon
    "compute ln of the receiver"

    "/ uses taylor series:
    "/             x^2   x^3
    "/    ln = u - --- + --- ...
    "/              2    3

    |u u2 num den approx lastApprox|

    u := self - 1.
    u2 := u squared.

    num := u2 negated.
    den := 2.

    approx := u + (num / den).
    lastApprox := self.

    [ (lastApprox - approx) abs > epsilon ] whileTrue:[
        den := den + 1.
        num := (num * u) negated.

        lastApprox := approx.
        approx := approx + (num / den).
    ].
    ^ approx

    "
     2.0 ln                                    0.693147
     2.0 asLongFloat ln                        0.693147181

     2.0 asLongFloat ln_withAccuracy:1         0.833333333
     2.0 asLongFloat ln_withAccuracy:0.1       0.645634921
     2.0 asLongFloat ln_withAccuracy:0.01      0.688172179
     2.0 asLongFloat ln_withAccuracy:0.001     0.692647431

     2.0 asLongFloat ln_withAccuracy:1e-10     
     2.0 asLongFloat ln_withAccuracy:1e-20     
     2.0 asLongFloat ln_withAccuracy:1e-40     2.71828183 
    "
!

sin_withAccuracy:epsilon
    "compute the sine of the receiver"

    "/ uses taylor series:
    "/               x^3   x^5   x^7
    "/    sin = x - --- + --- - --- ...
    "/                3!!    5!!    7!!

    |x2 facN num den approx lastApprox|

    x2 := self squared.

    num := (x2 * self) negated.
    den := 2*3.
    facN := 3.
    approx := self + (num / den).
    lastApprox := self.

    [ (lastApprox - approx) abs > epsilon ] whileTrue:[
        facN := facN + 2.
        den := den * (facN - 1) * facN.
        num := (num * x2) negated.

        lastApprox := approx.
        approx := approx + (num / den).
    ].
    ^ approx

    "
     1.0 sin                                    0.841471
     1.0 asLongFloat sin                        0.841470985

     1.0 asLongFloat sin_withAccuracy:1         0.833333333
     1.0 asLongFloat sin_withAccuracy:0.1       0.841666667 
     1.0 asLongFloat sin_withAccuracy:0.01      0.841666667
     1.0 asLongFloat sin_withAccuracy:0.001     0.841468254

     1.0 asLongFloat sin_withAccuracy:1e-40     0.841470985
    "
!

sinh_withAccuracy:epsilon
    "compute the hyperbolic sine of the receiver"

    "/ uses taylor series:
    "/               x^3   x^5   x^7
    "/    sinh = x + --- + --- + --- ...
    "/                3!!    5!!    7!!

    |x2 facN num den approx lastApprox|

    x2 := self squared.

    num := x2 * self.
    den := 2*3.
    facN := 3.
    approx := self + (num / den).
    lastApprox := self.

    [ (lastApprox - approx) abs > epsilon ] whileTrue:[
        facN := facN + 2.
        den := den * (facN - 1) * facN.
        num := num * x2.

        lastApprox := approx.
        approx := approx + (num / den).
    ].
    ^ approx

    "
     1.0 sinh                                    1.1752
     1.0 asLongFloat sinh                        1.17520119

     1.0 asLongFloat sinh_withAccuracy:1         1.16666667
     1.0 asLongFloat sinh_withAccuracy:0.1       1.175 
     1.0 asLongFloat sinh_withAccuracy:0.01      1.175
     1.0 asLongFloat sinh_withAccuracy:0.001     1.17519841

     1.0 asLongFloat sinh_withAccuracy:1e-40     1.17520119 
    "
!

tan_withAccuracy:epsilon
    "compute the tangens of the receiver"

    "/ uses taylor series:
    "/                x^3     x^5      x^7      x^9     2^2n * ( 2^2n - 1) * B2n * x^(2n-1)
    "/    tan = x + 1*--- + 2*--- + 17*--- + 62*----... ----------------------------------...
    "/                 3       15      315      2835                 (2n)!!
    "/ where Bi is the ith bernoulli number.

    |factors idx x2 num t approx lastApprox|

    "/    (1 to:20) collect:[:n| |num den|
    "/        num := (2 raisedTo:(2*n)) * ((2 raisedTo:(2*n))-1) * ((n*2) bernoulli).
    "/        den := (2*n) factorial.
    "/        num / den
    "/    ]   
   factors := #(
        (1 3) 
        (2 15) 
        (17 315) 
        (62 2835)
        (1382 155925) 
        (21844 6081075) 
        (929569 638512875)
        (6404582 10854718875) 
        (443861162 1856156927625) 
        (18888466084 194896477400625) 
        (113927491862 2900518163668125) 
        (58870668456604 3698160658676859375) 
        (8374643517010684 1298054391195577640625) 
        (689005380505609448 263505041412702261046875) 
        (129848163681107301953 122529844256906551386796875) 
        (1736640792209901647222 4043484860477916195764296875) 
        (418781231495293038913922 2405873491984360136479756640625) 
        (56518638202982204522669764 801155872830791925447758961328125) 
        (32207686319158956594455462 1126482925555250126673224649609375)).

    x2 := self squared.

    num := x2 * self.  "/ x^3
    approx := self + (num * 1 / 3).
    lastApprox := self.
    idx := 1.

    [ (lastApprox - approx) abs > epsilon ] whileTrue:[
        idx := idx + 1.
        t := factors at:idx.
        num := num * x2.

        lastApprox := approx.
        approx := approx + (num * t first / t second).
    ].
    ^ approx

    "
     0.5 tan                                    0.546302
     0.5 asLongFloat tan                        0.54630249

     0.5 asLongFloat tan_withAccuracy:1         0.541666667
     0.5 asLongFloat tan_withAccuracy:0.1       0.541666667
     0.5 asLongFloat tan_withAccuracy:0.01      0.545833333
     0.5 asLongFloat tan_withAccuracy:0.001     0.54625496
     0.5 asLongFloat tan_withAccuracy:1e-15     0.54630249

     0.5 asLongFloat tan_withAccuracy:1e-40     
    "
! !

!Number methodsFor:'testing'!

isDivisibleBy:aNumber
    "return true, if the receiver can be divided by the argument, aNumber without a remainder.
     Notice, that the result is only worth trusting, if the receiver is an integer."

    aNumber = 0 ifTrue: [^ false].
    aNumber isInteger ifFalse: [^ false].
    ^ (self \\ aNumber) = 0

    "
     3 isDivisibleBy:2     
     4 isDivisibleBy:2
     4.0 isDivisibleBy:2   
     4.5 isDivisibleBy:4.5 
     4.5 isDivisibleBy:1.0 
    "
!

isFinite
	^true
!

isInfinite
	^false
!

isNaN
    "return true, if the receiver is an invalid float (NaN - not a number)."

    ^ false

    "Created: / 5.11.2001 / 18:07:26 / cg"
!

isNumber
    "return true, if the receiver is a kind of number"

    ^ true
!

isReal
    "return true, if the receiver is some kind of real number (as opposed to a complex);
     true is returned here - the method is redefined from Object."

    ^ true
!

isZero
    "return true, if the receiver is zero"

    ^ self = 0

    "Modified: 18.7.1996 / 12:40:49 / cg"
! !

!Number methodsFor:'tracing'!

traceInto:aRequestor level:level from:referrer
    "double dispatch into tracer, passing my type implicitely in the selector"

    ^ aRequestor traceNumber:self level:level from:referrer


! !

!Number methodsFor:'trigonometric'!

arcCos
    "return the arccosine of the receiver (in radians)"

    (self isLimitedPrecisionReal not
    or:[self generality < 1.0 generality]) ifTrue:[
        ^ self asFloat arcCos.
    ].
    ^ self arcCos_withAccuracy:self precision
!

arcCosh
    "return the hyperbolic arccosine of the receiver."

    (self isLimitedPrecisionReal not
    or:[self generality < 1.0 generality]) ifTrue:[
        ^ self asFloat arcCosh.
    ].
    ^ self arcCosh_withAccuracy:self precision
!

arcSin
    "return the arcsine of the receiver (in radians)"

    (self isLimitedPrecisionReal not
    or:[self generality < 1.0 generality]) ifTrue:[
        ^ self asFloat arcSin.
    ].
    ^ self arcSin_withAccuracy:self precision
!

arcSinh
    "return the hyperbolic arcsine of the receiver."

    (self isLimitedPrecisionReal not
    or:[self generality < 1.0 generality]) ifTrue:[
        ^ self asFloat arcSinh.
    ].
    ^ self arcSinh_withAccuracy:self precision
!

arcTan
    "return the arctangent of the receiver (as radians)"

    (self isLimitedPrecisionReal not
    or:[self generality < 1.0 generality]) ifTrue:[
        ^ self asFloat arcTan.
    ].
    ^ self arcTan_withAccuracy:self precision
!

arcTanh
    "return the hyperbolic arctangent of the receiver."

    (self isLimitedPrecisionReal not
    or:[self generality < 1.0 generality]) ifTrue:[
        ^ self asFloat arcTanh.
    ].
    ^ self arcTanh_withAccuracy:self precision
!

cos
    "return the cosine of the receiver (interpreted as radians)"

    (self isLimitedPrecisionReal not
    or:[self generality < 1.0 generality]) ifTrue:[
        ^ self asFloat cos.
    ].
    ^ self cos_withAccuracy:self precision
!

cosh
    "return the hyperbolic cosine of the receiver"

    (self isLimitedPrecisionReal not
    or:[self generality < 1.0 generality]) ifTrue:[
        ^ self asFloat cosh.
    ].
    ^ self cosh_withAccuracy:self precision
!

sin
    "return the sine of the receiver (interpreted as radians)"

    (self isLimitedPrecisionReal not
    or:[self generality < 1.0 generality]) ifTrue:[
        ^ self asFloat sin.
    ].
    ^ self sin_withAccuracy:self precision
!

sinh
    "return the hyperbolic sine of the receiver"

    (self isLimitedPrecisionReal not
    or:[self generality < 1.0 generality]) ifTrue:[
        ^ self asFloat sinh.
    ].
    ^ self sinh_withAccuracy:self precision
!

tan
    "return the tangens of the receiver (interpreted as radians)"

    ^ self sin / self cos
!

tanh
    "return the hyperbolic tangens of the receiver"

    (self isLimitedPrecisionReal not
    or:[self generality < 1.0 generality]) ifTrue:[
        ^ self asFloat tanh.
    ].
    ^ self tanh_withAccuracy:self precision

"/ If a fast exp is available, the following might be better...
"/
"/    |exp nexp|
"/
"/    "/ tanh is:
"/    "/      sinh(x)
"/    "/      -------
"/    "/      cosh(x)
"/    "/
"/    "/ which is:
"/    "/      (exp(x) - exp(-x)) / 2
"/    "/      ----------------------
"/    "/      (exp(x) + exp(-x)) / 2
"/    
"/    exp := self exp.
"/    nexp := self negated exp.
"/
"/    ^ (exp - nexp) / (exp + nexp)
! !

!Number methodsFor:'truncation & rounding'!

detentBy: detent atMultiplesOf: grid snap: snap
    "Map all values that are within detent/2 of any multiple of grid 
     to that multiple.  
     Otherwise, if snap is true, return self, meaning that the values 
     in the dead zone will never be returned.  
     If snap is false, then expand the range between dead zones
     so that it covers the range between multiples of the grid, 
     and scale the value by that factor."

    | r1 r2 |

    r1 := self roundTo: grid.                    "Nearest multiple of grid"
    (self roundTo: detent) = r1 ifTrue: [^ r1].  "Snap to that multiple..."
    snap ifTrue: [^ self].                       "...or return self"

    r2 := self < r1                               "Nearest end of dead zone"
	    ifTrue: [r1 - (detent asFloat/2)]
	    ifFalse: [r1 + (detent asFloat/2)].

    "Scale values between dead zones to fill range between multiples"
    ^ r1 + ((self - r2) * grid asFloat / (grid - detent))

    "
     (170 to: 190 by: 2) collect: [:a | a detentBy: 10 atMultiplesOf: 90 snap: true]         
     (170 to: 190 by: 2) collect: [:a | a detentBy: 10 atMultiplesOf: 90 snap: false]
     (3.9 to: 4.1 by: 0.02) collect: [:a | a detentBy: 0.1 atMultiplesOf: 1.0 snap: true]    
     (-3.9 to: -4.1 by: -0.02) collect: [:a | a detentBy: 0.1 atMultiplesOf: 1.0 snap: false]
    "
!

fractionPart
    "return a float with value from digits after the decimal point.
     i.e. the receiver minus its truncated value,
     such that (self truncated + self fractionPart) = self"

    ^ self - self truncated

    "
     1234.56789 fractionPart
     1.2345e6 fractionPart  

     1.6 asLongFloat fractionPart + 1.6 asLongFloat truncated    
     -1.6 asLongFloat fractionPart + -1.6 asLongFloat truncated    
    "

    "Modified: / 4.11.1996 / 20:26:54 / cg"
    "Created: / 28.10.1998 / 17:14:40 / cg"
!

integerPart
    "return a float with value from digits before the decimal point
     (i.e. the truncated value)"

    ^ self truncated asFloat

    "
     1234.56789 integerPart 
     1.2345e6 integerPart   
     12.5 integerPart 
     -12.5 integerPart 
     (5/3) integerPart  
     (-5/3) integerPart 
     (5/3) truncated  
     (-5/3) truncated  
    "

    "Created: / 28.10.1998 / 17:14:56 / cg"
    "Modified: / 5.11.2001 / 17:54:22 / cg"
! !

!Number class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Number.st,v 1.87 2003-07-02 09:34:42 cg Exp $'
! !