Number.st
author Claus Gittinger <cg@exept.de>
Sun, 10 Oct 1999 14:46:54 +0200
changeset 4895 cc546b082506
parent 4682 4158042a9c8c
child 4988 ac426684e852
permissions -rw-r--r--
checkin from browser

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

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

    ^ self readFrom:aString

    "
     Number fromString:'12345'
     '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."

    |value|

    ErrorSignal handle:[:ex |
        ^ exceptionBlock value
    ] do:[
        |str nextChar radix negative signExp|

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

        (nextChar == $.) ifTrue:[
            str next.
            nextChar := str peekOrNil.
            (nextChar notNil and:[nextChar isDigitRadix:radix]) ifTrue:[
                value := value asFloat 
                         + (Number readMantissaFrom:str radix:radix).
                nextChar := str peekOrNil
            ]
        ].
        ((nextChar == $e) or:[nextChar == $E]) 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
                ]
            ].
            (nextChar notNil and:[(nextChar isDigitRadix:radix)]) ifTrue:[
                value := value asFloat 
                         * (10.0 raisedToInteger:
                                    ((Integer readFrom:str radix:radix) * signExp))
            ]
        ].
        negative ifTrue:[
            value := value negated
        ].
    ].
    ^ value.

    "
     Number readFrom:(ReadStream on:'54.32e-01')      
     Number readFrom:(ReadStream on:'12345678901234567890') 
     Number readFrom:(ReadStream on:'16rAAAAFFFFAAAAFFFF') 
     Number readFrom:'16rAAAAFFFFAAAAFFFF' 
     Number readFrom:'0.000001'  
     '+00000123.45' asNumber  
    "

    "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-)stream aStream."

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

    "
     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')  
    "

    "Modified: / 18.6.1998 / 23:02:57 / cg"
! !

!Number class methodsFor:'error reporting'!

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

    <context: #return>

    |msg|

    msg := MessageSend
                receiver:someNumber
                selector:sel
                arguments:(Array with:arg).

    ^ (self perform:aSignalSymbol)
         raiseRequestWith:msg 
         errorString:text 
         in:thisContext sender

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

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

    <context: #return>

    |msg|

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

    ^ (self perform:aSignalSymbol)
         raiseRequestWith:msg 
         errorString:text 
         in:thisContext sender

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

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

    <context: #return>

    |msg|

    msg := MessageSend
                receiver:someNumber
                selector:sel
                arguments:#().

    ^ (self perform:aSignalSymbol)
         raiseRequestWith:msg 
         errorString:text 
         in:thisContext sender

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

!Number class methodsFor:'private'!

readMantissaFrom:aStream radix:radix
    "helper for readFrom: -
     return the mantissa from the (character-)stream aStream;
     no whitespace-skipping; error if no number available"

    |nextChar value factor|

    value := 0.0.
    factor := 1.0 / radix.
    nextChar := aStream peekOrNil.
    [nextChar notNil and:[nextChar isDigitRadix:radix]] whileTrue:[
        value := value + (nextChar digitValue * factor).
        factor := factor / radix.
        aStream next.
        nextChar := aStream peekOrNil
    ].
    ^ value

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

!Number methodsFor:'coercing'!

coerce:aNumber
    "return aNumber converted into receivers type"

    ^ self subclassResponsibility
!

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

    ^ 40
! !

!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 fromReal:self

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

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
!

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

!Number methodsFor:'intervals'!

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

!Number methodsFor:'iteration'!

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

    |count|

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

to:stop by:incr do:aBlock
    "For each element of the interval from the receiver up to the argument stop, incrementing
     by step, evaluate aBlock passing the element as argument."

    |tmp|

    tmp := self.
    (incr > 0) ifTrue:[
        [tmp <= stop] whileTrue:[
            aBlock value:tmp.
            tmp := tmp+incr
        ]
    ] ifFalse:[
        [tmp >= stop] whileTrue:[
            aBlock value:tmp.
            tmp := tmp+incr
        ]
    ]
!

to:stop by:incr doWithBreak:aBlock
    "For each element of the interval from the receiver up to the argument stop, incrementing
     by step, evaluate aBlock passing the element as argument.
     Pass a break argument, to allow for premature exit of the loop."

    |tmp break|

    break := [^ self].
    tmp := self.
    (incr > 0) ifTrue:[
        [tmp <= stop] whileTrue:[
            aBlock value:tmp value:break.
            tmp := tmp+incr
        ]
    ] ifFalse:[
        [tmp >= stop] whileTrue:[
            aBlock value:tmp value:break.
            tmp := tmp+incr
        ]
    ]

    "
     1 to:100 by:5 doWithBreak:[:index :break |
        Transcript showCR:index printString.
        index > 50 ifTrue:[
            break value
        ].
     ]
    "
!

to:stop do:aBlock
    "For each element of the interval from the receiver up to the argument stop,
     evaluate aBlock, passing the number as argument."

    |tmp|

    tmp := self.
    [tmp <= stop] whileTrue:[
        aBlock value:tmp.
        tmp := tmp+1
    ]
!

to:stop doWithBreak:aBlock
    "For each element of the interval from the receiver up to the argument stop,
     evaluate aBlock, passing the number as argument.
     Pass a break argument, to allow for premature exit of the loop."

    |tmp break|

    break := [^ self].
    tmp := self.
    [tmp <= stop] whileTrue:[
        aBlock value:tmp value:break.
        tmp := tmp+1
    ]

    "
     1 to:10 doWithBreak:[:index :break |
        Transcript showCR:index printString.
        index > 5 ifTrue:[
            break value
        ].
     ]
    "
! !

!Number methodsFor:'mathematical functions'!

conjugated
    "Return the complex conjugate of this Number."

    ^ self

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

imaginary
    "Return the imaginary part of this Number."

    ^ 0

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

real
    "Return the real part of this Number."

    ^ self

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

!Number methodsFor:'printing & storing'!

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:'testing'!

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

    ^ 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:'truncation and 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)"

    ^ self - self truncated asFloat

    "
     1234.56789 fractionPart
     1.2345e6 fractionPart  
    "

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

    "Modified: / 4.11.1996 / 20:26:21 / cg"
    "Created: / 28.10.1998 / 17:14:56 / cg"
! !

!Number class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Number.st,v 1.54 1999-10-10 12:46:54 cg Exp $'
! !