Integer.st
author Claus Gittinger <cg@exept.de>
Fri, 15 Nov 2002 13:16:19 +0100
changeset 6858 13919a7544b6
parent 6682 9a97f4deb836
child 6875 d064224376bf
permissions -rw-r--r--
raisedToInteger pushed up

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

Number subclass:#Integer
	instanceVariableNames:''
	classVariableNames:'DefaultDisplayRadix BCDConversionErrorSignal'
	poolDictionaries:''
	category:'Magnitude-Numbers'
!

Object subclass:#ModuloNumber
	instanceVariableNames:'modulus reciprocal shift'
	classVariableNames:''
	poolDictionaries:''
	privateIn:Integer
!

!Integer 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 integer numbers.
    See details in concrete subclasses LargeInteger and SmallInteger.

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

    [Class variables:]

	DefaultDisplayRadix     the radix in which integers present their 
				displayString (which is used in inspectors)
				If you are to look at many hex numbers, bitmasks
				etc. you may set this to 2 or 16.
				(avoids typing printStringRadix:.. all the time
				 - I know - I am lazy ;-). Default is 10.


    [author:]
	Claus Gittinger

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

!Integer class methodsFor:'initialization'!

initialize
    BCDConversionErrorSignal isNil ifTrue:[
        BCDConversionErrorSignal := ConversionErrorSignal newSignal.
        BCDConversionErrorSignal nameClass:self message:#bcdConversionErrorSignal.
        BCDConversionErrorSignal notifierString:'bcd conversion error'.
    ].

    "Modified: / 15.11.1999 / 20:36:04 / cg"
! !

!Integer class methodsFor:'instance creation'!

byte1:b1 byte2:b2 byte3:b3 byte4:b4
    "Squeak compatibility:
     Return an Integer given four value bytes.
     The returned integer is either a Small- or a LargeInteger"

    |t|

    t := b4.
    t := (t bitShift:8) + b3.
    t := (t bitShift:8) + b2.
    ^ (t bitShift:8) + b1.

    "
     (Integer byte1:16r10 byte2:16r32 byte3:16r54 byte4:16r76) hexPrintString
     (Integer byte1:16r00 byte2:16r11 byte3:16r22 byte4:16r33) hexPrintString
    "

    "Created: 19.10.1997 / 18:08:52 / cg"
    "Modified: 19.10.1997 / 18:09:04 / cg"
!

fastFromString:aString at:startIndex
    "return the next unsigned Integer from the string 
     as a decimal number, starting at startIndex.
     The number must be in the native machines int range
     (i.e. 63bit on alpha / 31 on all others);
     However, for portability, only use it for 31bit numbers.
     No spaces are skipped.

     This is a specially tuned entry (using a low-level C-call), which
     returns garbage if the argument string is not a small integer number.
     It has been added to allow higher speed string decomposition into
     numbers."
%{
     if (__isString(aString) && __isSmallInteger(startIndex)) {
        char *cp = (char *)(__stringVal(aString));
        int idx = __intVal(startIndex) - 1;
        unsigned INT val;

        if ((unsigned)idx < __stringSize(aString)) {
            val = atoi(cp + idx);
            if (val <= _MAX_INT) {
                RETURN(__MKSMALLINT(val));
            }
            RETURN (__MKUINT(val));
        }
     }
%}.
     self primitiveFailed.

    "
     Integer fastFromString:'12345' at:1  
     Integer fastFromString:'12345' at:2  
     Integer fastFromString:'12345' at:3  
     Integer fastFromString:'12345' at:4  
     Integer fastFromString:'12345' at:5  
     Integer fastFromString:'1234512345' at:1  
     Integer fastFromString:'2147483647' at:1  

     Integer fastFromString:'4294967295' at:1 
     Integer fastFromString:'12345' at:6  
     Integer fastFromString:'12345' at:0  

     Time millisecondsToRun:[
        100000 timesRepeat:[
            Integer readFrom:'12345'
        ]
     ]  
    "

    "
     Time millisecondsToRun:[
        100000 timesRepeat:[
            Integer fastFromString:'12345' at:1  
        ]
     ]   
    "
!

fromBCDBytes:aByteArray
    "given a byteArray in BCD format, return an appropriate integer.
     The byteArray must contain the BCD encoded decimal string,
     starting with the most significant digits.
     This conversion is useful for some communication protocols,
     or control systems, which represent big numbers this way...
    "

    |val|

    val := 0.
    aByteArray do:[:twoDigits |
        |hi lo|

        hi := (twoDigits bitShift:-4) bitAnd:16r0F.
        lo := twoDigits bitAnd:16r0F.
        val := (val * 100) + (hi * 10) + lo
    ].
    ^ val

    "
     Integer fromBCDBytes:#[16r12 16r34 16r56]    
     Integer fromBCDBytes:#[16r12 16r34 16r56 16r78]   
     Integer fromBCDBytes:#[16r12 16r34 16r56 16r78 16r90] 
     Integer fromBCDBytes:#[16r98 16r76 16r54] 
     Integer fromBCDBytes:#[16r98 16r76 16r54 16r32] 
     Integer fromBCDBytes:#[16r98 16r76 16r54 16r32 16r10] 
     Integer fromBCDBytes:#[16r12 16r34 16r56 16r78 16r90 16r12 16r34 16r56 16r78 16r90]
    "
!

fromSwappedBCDBytes:aByteArray
    "given a byteArray in BCD format, return an appropriate integer.
     The byteArray must contain the BCD encoded decimal string,
     starting with the LEAST significant digits.
     This conversion is useful for some communication protocols,
     or control systems (e.g. SMC), which represent big numbers this way...
    "

    |val|

    val := 0.
    aByteArray do:[:twoDigits |
        |hi lo|

        lo := (twoDigits bitShift:-4) bitAnd:16r0F.
        hi := twoDigits bitAnd:16r0F.
        lo <= 9 ifTrue:[
            val := (val * 100) + (hi * 10) + lo
        ] ifFalse:[
            "16rF is used to encode an odd number of digits"
            val := (val * 10) + hi.
        ].
    ].
    ^ val

    "
     Integer fromSwappedBCDBytes:#[16r12 16r34 16r56]    
     Integer fromSwappedBCDBytes:#[16r12 16r34 16rF6]    
     Integer fromSwappedBCDBytes:#[16r12 16r34 16r56 16r78]   
     Integer fromSwappedBCDBytes:#[16r12 16r34 16r56 16r78 16r90] 
     Integer fromSwappedBCDBytes:#[16r98 16r76 16r54] 
     Integer fromSwappedBCDBytes:#[16r98 16r76 16r54 16r32] 
     Integer fromSwappedBCDBytes:#[16r98 16r76 16r54 16r32 16r10] 
     Integer fromSwappedBCDBytes:#[16r12 16r34 16r56 16r78 16r90 16r12 16r34 16r56 16r78 16r90]
    "
!

new:numberOfBytes neg:negative
    "for ST-80 compatibility:
     Return an empty Integer (uninitialized value) with space for
     numberOfBytes bytes (= digitLength). The additional argument
     negative specifies if the result should be a negative number.
     The digits can be stored byte-wise into the result, using digitAt:put:"

    ^ (LargeInteger basicNew numberOfDigits:numberOfBytes) 
		sign:(negative ifTrue:[-1] ifFalse:[1])
!

readFrom:aStringOrStream 
    "return the next unsigned Integer from the (character-)stream aStream 
     as decimal number. 

     NOTICE:   
       This behaves different from the default readFrom:, in returning
       0 (instead of raising an error) in case no number can be read.
       It is unclear, if this is the correct behavior (ST-80 does this)
       - depending on the upcoming ANSI standard, this may change."

    ^ self readFrom:aStringOrStream onError:0

    "
     Integer readFrom:(ReadStream on:'foobar')     
     Integer readFrom:(ReadStream on:'foobar') onError:nil  
    "
!

readFrom:aStringOrStream onError:exceptionBlock
    "return the next Integer from the (character-)stream aStream,
     handling initial XXr for arbitrary radix numbers and initial sign.
     Also, all initial whitespace is skipped.
     If the string does not represent a valid integer number,
     return the value of exceptionBlock."

    |value|

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

        str := aStringOrStream readStream.

        nextChar := str skipSeparators.
        (nextChar == $-) ifTrue:[
            negative := true.
            str next.
            nextChar := str peekOrNil
        ] ifFalse:[
            negative := false
        ].
        (nextChar isNil or:[nextChar isDigit not]) ifTrue:[ 
            "
             the string does not represent an integer
            "
            ^ exceptionBlock value
        ].
        value := self readFrom:str radix:10.
        nextChar := str peekOrNil.
        ((nextChar == $r) or:[ nextChar == $R]) ifTrue:[
            "-xxr<number> is invalid; should be xxr-<val>"

            negative ifTrue:[
                'Integer [warning]: invalid (negative) radix ignored' errorPrintCR.
                negative := false
            ].
            str next.
            value := self readFrom:str radix:value
        ].
        negative ifTrue:[
            value := value negated
        ].
    ].
    ^ value

    "
     Integer readFrom:'12345'      onError:['wrong']    
     Integer readFrom:'-12345'     onError:['wrong']    
     Integer readFrom:'+12345'     onError:['wrong']    
     Integer readFrom:'16rFFFF'    onError:['wrong']    
     Integer readFrom:'12345.1234' onError:['wrong'] 
     Integer readFrom:'foo'        onError:['wrong']
     Integer readFrom:'foo'                          
    "

    "Created: / 16.11.1995 / 22:48:59 / cg"
    "Modified: / 14.4.1998 / 19:17:28 / cg"
!

readFrom:aStringOrStream radix:radix
    "return the next unsigned Integer from the (character-)stream aStream 
     in radix; (assumes that the initial XXr has already been read).
     No whitespace-skipping is done.
     Returns 0 if no number available.

     NOTICE:   
       This behaves different from the default readFrom:, in returning
       0 (instead of raising an error) in case no number can be read.
       It is unclear, if this is the correct behavior (ST-80 does this)
       - depending on the upcoming ANSI standard, this may change."

    ^ self readFrom:aStringOrStream radix:radix onError:0
!

readFrom:aStringOrStream radix:radix onError:exceptionBlock
    "return the next unsigned Integer from the (character-)stream aStream 
     in radix; (assumes that the initial XXr has already been read).
     No whitespace-skipping is done.
     Returns the value of exceptionBlock, if no number is available."

    |str nextChar nextChar2 value 
     r     "{ Class: SmallInteger }"
     r2    "{ Class: SmallInteger }"|

    str := aStringOrStream readStream.

    nextChar := str peekOrNil.
    (nextChar notNil and:[nextChar isDigitRadix:radix]) ifFalse:[
        ^ exceptionBlock value
    ].

    value := nextChar digitValue.
    str next.
    nextChar := str peekOrNil.

"/ OLD code
"/    [nextChar notNil and:[nextChar isDigitRadix:radix]] whileTrue:[
"/        str next.
"/        value := value * radix + nextChar digitValue.
"/        nextChar := str peekOrNil.
"/    ].
"/    ^ value.

    "/ the code below does the same, but is much faster, if the
    "/ converted number is large
    "/ (requires only half as many LargeInt multiplications and additions)
    "/ It should not be slower for smallIntegers.

    r := radix.
    r2 := r * r.

    [nextChar notNil and:[nextChar isDigitRadix:r]] whileTrue:[
        str next.
        nextChar2 := str peekOrNil.
        (nextChar2 notNil and:[nextChar2 isDigitRadix:r]) ifTrue:[
            str next.
            value := (value * r2) + ((nextChar digitValue * r) + nextChar2 digitValue).
            nextChar := str peekOrNil.
        ] ifFalse:[
            ^ (value * r) + nextChar digitValue.
        ]
    ].
    ^ value

    "
     Integer readFrom:(ReadStream on:'12345') radix:10  
     Integer readFrom:(ReadStream on:'FFFF') radix:16  
     Integer readFrom:(ReadStream on:'1010') radix:2   
     Integer readFrom:(ReadStream on:'foobar') radix:10   
     Integer readFrom:(ReadStream on:'foobar') radix:10 onError:nil  
     Integer readFrom:'gg' radix:10 onError:0                      
    "

    "Modified: / 14.4.1998 / 19:16:46 / cg"
!

readFromRomanString:aStringOrStream
    "convert a string or stream containing a roman representation into an integer.
     Raises an exception, if the inputs format is completely wrong.
     Raises BadRomanNumberFormatError if its wrong, but could be parsed.
     Notifies via NaiveRomanNumberFormatNotification, if its a bit wrong (naive format).
     Will read both real and naive roman numbers (see printRomanOn: vs. printRomanOn:naive:),
     however, a notification is raised for for naive numbers (catch it if you are interested in it)."

    |romanValues s c val digitVal prevDigitVal countSame delta 
     stopOnSeparator finish|

    romanValues := Dictionary 
                    withKeys:#($M $D $C $L $X $V $I) 
                    andValues:#(1000 500 100 50 10 5 1).

    (stopOnSeparator := aStringOrStream isStream) ifFalse:[
        s := aStringOrStream readStream.
    ].
    s atEnd ifTrue:[ 
        ^ RomanNumberFormatError raiseErrorString:'empty string'
    ].
    val := 0.
    prevDigitVal := 99999.
    countSame := 1.
    finish := false.

    [s atEnd or:[finish]] whileFalse:[
        c := s next asUppercase.
        c isSeparator ifTrue:[
            stopOnSeparator ifFalse:[
                ^ RomanNumberFormatError raiseErrorString:'garbage at the end'
            ].
            finish := true.
        ] ifFalse:[
            digitVal := romanValues at:c ifAbsent:nil.
            digitVal isNil ifTrue:[
                ^ RomanNumberFormatError raiseErrorString:'invalid character'
            ].

            digitVal = prevDigitVal ifTrue:[
                ( #( 1 10 100 1000) includes:digitVal) ifFalse:[
                    ^ RomanNumberFormatError raiseErrorString:'character may not be repeated'
                ].
                val := val + digitVal.
                countSame := countSame + 1.
                countSame >= 4 ifTrue:[
                    digitVal ~= 1000 ifTrue:[
                        countSame > 4 ifTrue:[
                            "/ this is a bad roman number (such as MCCCCCCCCXXXXXXII);
                            "/ Its not correct, but sometimes encountered on buildings.
                            "/ If you do not want to be too picky,
                            "/ provide a proceeding handler in order to proceed the conversion.
                            BadRomanNumberFormatError raiseRequestErrorString:'more than 4 occurrences of same character'
                        ] ifFalse:[
                            "/ this is a naive roman number (such as VIIII);
                            "/ Its not correct, but very often encountered (especially as page numbers).
                            "/ The notification below normally goes unnoticed, unless some input validator
                            "/ wants to be very picky, and treat this as an error.
                            "/ To do so, provide a handler for NaiveRomanNumberFormatNotification.
                            NaiveRomanNumberFormatNotification raiseRequestErrorString:'more than 3 occurrences of same character'.
                        ]
                    ]
                ].
            ] ifFalse:[
                digitVal < prevDigitVal ifTrue:[
                    val := val + digitVal.
                ] ifFalse:[
                    countSame == 1 ifFalse:[
                        ^ RomanNumberFormatError raiseErrorString:'invalid character combination'
                    ].
                    delta := digitVal - prevDigitVal.
                    ( #( 4 9 40 90 400 900) includes:delta) ifFalse:[
                        ^ RomanNumberFormatError raiseErrorString:'invalid character combination'
                    ].
                    val := val - prevDigitVal.
                    val := val + delta.
                    digitVal := prevDigitVal - 0.1.  "/ trick: prevent prevDigit from arriving again.
                ].
                countSame := 1.
            ].
            prevDigitVal := digitVal.
        ].
    ].
"/    val > 5000 ifTrue:[
"/        ^ RomanNumberFormatError raiseErrorStirng:'number out of range (1..5000)'
"/    ].    
    ^ val.

    "
     Integer readFromRomanString:'I'                                      
     Integer readFromRomanString:'II'      
     Integer readFromRomanString:'III'        
     Integer readFromRomanString:'IV'         
     Integer readFromRomanString:'clix'     
     Integer readFromRomanString:'MIX'       
     Integer readFromRomanString:'MCMXCIX'       

   Naive cases (which are accepted):
     Integer readFromRomanString:'IIII'        
     Integer readFromRomanString:'VIIII'         
     Integer readFromRomanString:'CLXXXXVIIII'        

    Error case (not proceedable):
     Integer readFromRomanString:'LC'      

    Error case (proceedable):
     Integer readFromRomanString:'MCCCCCCCCXXXXXXIIIIII'      

     BadRomanNumberFormatError ignoreIn:[
         Integer readFromRomanString:'MCCCCCCCCXXXXXXIIIIII'      
     ]   
    "


    "naive cases:
     #(
        'MCMXCIX'           1999
        'MCMXCVIIII'        1999
        'MCMLXXXXIX'        1999
        'MDCCCCXCIX'        1999
        'MDCCCCXCVIIII'     1999
        'MDCCCCLXXXXIX'     1999
        'MDCCCCLXXXXVIIII'  1999
     ) pairWiseDo:[:goodString :expectedValue |
        (Integer readFromRomanString:goodString onError:nil) ~= expectedValue ifTrue:[self halt].
     ]
    "


    "error cases:
      #( 
        'XIIX'      
        'VV'        
        'VVV'        
        'XXL'         
        'XLX'        
        'LC'        
        'LL'        
        'DD'        
     ) do:[:badString |
        (Integer readFromRomanString:badString onError:nil) notNil ifTrue:[self halt].
     ]
    "

    "good cases:
     #( 'I'     1
        'II'    2
        'III'   3
        'IV'    4
        'V'     5
        'VI'    6
        'VII'   7
        'VIII'  8
        'IX'    9
        'X'     10
        'XI'    11      
        'XII'   12   
        'XIII'  13    
        'XIV'   14   
        'XV'    15  
        'XVI'   16   
        'XVII'  17    
        'XVIII' 18     
        'XIX'   19   
        'XX'    20      
        'XXX'   30   
        'L'     50   
        'XL'    40    
        'LX'    60    
        'LXX'   70     
        'LXXX'  80      
        'CXL'   140    
        'CL'    150    
        'CLX'   160     
        'MMM'                   3000      
        'MMMM'                  4000      
        'MMMMCMXCIX'            4999    
        'MMMMMMMMMCMXCIX'       9999 
     ) pairWiseDo:[:goodString :expectedValue |
        (Integer readFromRomanString:goodString onError:nil) ~= expectedValue ifTrue:[self halt].
     ]
    "

    "
      1 to:9999 do:[:n |
        |romanString|

        romanString := String streamContents:[:stream | n printRomanOn:stream].
        (Integer readFromRomanString:romanString onError:nil) ~= n ifTrue:[self halt].
     ]
    "
!

readFromRomanString:aStringOrStream onError:exceptionalValue
    "convert a string or stream containing a roman representation into an integer.
     Raises an exception, if the inputs format is wrong. 
     Does allow reading of naive (more than 3 in a row) and 
     bad (not using L and D) roman numbers.
     (Such numbers can be seen on some medevial buildings. "

    |val|

    RomanNumberFormatError 
        handle:[:ex |
            val := exceptionalValue value
        ]
        do:[
            val := self readFromRomanString:aStringOrStream
        ].
    ^ val


    "
     Integer readFromRomanString:'I'    onError:nil                                      
     Integer readFromRomanString:'II'   onError:nil  
     Integer readFromRomanString:'III'  onError:nil   
     Integer readFromRomanString:'IV'   onError:nil     
     Integer readFromRomanString:'clix' onError:nil       
     Integer readFromRomanString:'MCMXCIX' onError:nil       

   Naive cases (which are accepted):
     Integer readFromRomanString:'IIII' onError:nil       
     Integer readFromRomanString:'VIIII' onError:nil        
     Integer readFromRomanString:'CLXXXXVIIII' onError:nil       

   Error cases:
\     Integer readFromRomanString:'LC'   onError:nil        
    "

    "error cases:
      #( 
        'XIIX'      
        'VV'        
        'VVV'        
        'XXL'         
        'XLX'        
        'LC'        
        'LL'        
        'DD'        
     ) do:[:badString |
        (Integer readFromRomanString:badString onError:nil) notNil ifTrue:[self halt].
     ]
    "

    "naive (but handled) cases:
      #( 
        'IIII'   4
        'VIIII'  9
        'XIIII'  14
        'XVIIII' 19
     ) pairWiseDo:[:goodString :expectedValue |
        (Integer readFromRomanString:goodString onError:nil) ~= expectedValue ifTrue:[self halt].
     ]
    "

    "good cases:
     #( 'I'     1
        'II'    2
        'III'   3
        'IV'    4
        'V'     5
        'VI'    6
        'VII'   7
        'VIII'  8
        'IX'    9
        'X'     10
        'XI'    11      
        'XII'   12   
        'XIII'  13    
        'XIV'   14   
        'XV'    15  
        'XVI'   16   
        'XVII'  17    
        'XVIII' 18     
        'XIX'   19   
        'XX'    20      
        'XXX'   30   
        'L'     50   
        'XL'    40    
        'LX'    60    
        'LXX'   70     
        'LXXX'  80      
        'CXL'   140    
        'CL'    150    
        'CLX'   160     
        'MMM'                   3000      
        'MMMM'                  4000      
        'MMMMCMXCIX'            4999    
        'MMMMMMMMMCMXCIX'       9999 
     ) pairWiseDo:[:goodString :expectedValue |
        (Integer readFromRomanString:goodString onError:nil) ~= expectedValue ifTrue:[self halt].
     ]
    "

    "
      1 to:9999 do:[:n |
        |romanString|

        romanString := String streamContents:[:stream | n printRomanOn:stream].
        (Integer readFromRomanString:romanString onError:nil) ~= n ifTrue:[self halt].
     ]
    "

    "reading naive numbers:

      1 to:9999 do:[:n |
        |romanString|

        romanString := String streamContents:[:stream | n printRomanOn:stream naive:true].
        (Integer readFromRomanString:romanString onError:nil) ~= n ifTrue:[self halt].
     ]
    "
! !

!Integer class methodsFor:'Signal constants'!

bcdConversionErrorSignal
    "return the signal which is raised when bcd conversion fails
     (i.e. when trying to decode an invalid BCD number)"

    ^ BCDConversionErrorSignal

    "Modified: / 15.11.1999 / 20:35:20 / cg"
! !

!Integer class methodsFor:'constants'!

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

    ^ 1

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

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

    ^ 0

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

!Integer class methodsFor:'misc'!

displayRadix:aNumber
    "being tired of always sending #printStringRadix: in the inspectors,
     this allows you to change the default print radix for the displayString
     method."

    DefaultDisplayRadix := aNumber

    "
     Integer displayRadix:16. 123456 inspect
     Integer displayRadix:10. 123456 inspect
    "
! !

!Integer class methodsFor:'queries'!

hasSharedInstances
    "return true if this class has shared instances, that is, instances
     with the same value are identical.
     Although not always shared (LargeIntegers), these should be treated
     so, to be independent of the number of bits in a SmallInt"

    ^ true


! !

!Integer methodsFor:'Compatibility - Dolphin'!

highWord
    "return the high 16 bits of a 32 bit value"

    ^ self bitShift:-16

    "
     (16r12345678 highWord) hexPrintString 
     (16r12345678 lowWord) hexPrintString 
    "
!

lowWord
    "return the low 16 bits of a 32 bit value"

    ^ self bitAnd:16rFFFF

    "
     (16r12345678 lowWord) hexPrintString    
     (16r12345678 highWord) hexPrintString   
    "
!

mask:integerMask set:aBoolean
    "Answer the result of setting/resetting the specified mask in the receiver."

    ^ aBoolean 
            ifTrue:  [self maskSet:integerMask]
            ifFalse: [self maskClear:integerMask]

    "turn on the 1-bit:
         |v|

         v := 2r0100.
         v mask:1 set:true   

     turn off the 1-bit:
         |v|

         v := 2r0101.
         v mask:1 set:false   
    "
! !

!Integer methodsFor:'Compatibility - Squeak'!

atRandom
    "return a random number between 1 amd myself"

    self < 1 ifTrue:[^ self].
    ^ (1 to:self) atRandom
!

printStringBase:base
    "return my printString in a base;
     same as printStringRadix:"

    ^ self printStringRadix:base
! !

!Integer methodsFor:'Compatibility - V''Age'!

<< aNumber
    "left shift"

    ^ self bitShift:aNumber

    "
     1 << 5 
     64 << -5 
    "
!

>> aNumber
    "right shift"

    ^ self bitShift:(aNumber negated)

    "
     1 >> -5  
     64 >> 5  
    "
! !

!Integer methodsFor:'bcd conversion'!

decodeFromBCD
    "return a number representing the value of the BCD encoded receiver."

    |v rslt multiplier nibble|

    v := self.
    rslt := 0.
    multiplier := 1.
    [v > 0] whileTrue:[
        nibble := v bitAnd:16r0F.
        nibble > 9 ifTrue:[
            ^ BCDConversionErrorSignal 
                    raiseRequestWith:self
                    errorString:'bad BCD coded value'
        ].
        rslt := rslt + (nibble * multiplier).
        multiplier := multiplier * 10.
        v := v bitShift:-4.
    ].
    ^ rslt

    "
     16r1234567890123 decodeFromBCD
     16r1073741823 decodeFromBCD       
     16r1073741824 decodeFromBCD       
     16r1073741825 decodeFromBCD       

     16r55 decodeFromBCD   
     16r127 decodeFromBCD    
     16r800000 decodeFromBCD    
     16r8000000 decodeFromBCD    
     16r80000000 decodeFromBCD    
     16r800000000 decodeFromBCD    
     16r127567890 decodeFromBCD    
     16r1234567890 decodeFromBCD     

     16r5A decodeFromBCD   
     16rFF decodeFromBCD   
    "

    "Modified: / 15.11.1999 / 20:37:20 / cg"
!

encodeAsBCD
    "return a BCD encoded number representing the same value as the
     receiver."

    |v rslt shift|

    v := self.
    rslt := shift := 0.
    [v > 0] whileTrue:[
        rslt := rslt + ((v \\ 10) bitShift:shift).
        shift := shift + 4.
        v := v // 10.
    ].
    ^ rslt

    "
     55 encodeAsBCD hexPrintString 
     127 encodeAsBCD hexPrintString        
     127 encodeAsBCD hexPrintString        
     8912345 encodeAsBCD hexPrintString        
     89123456 encodeAsBCD hexPrintString        
     891234567 encodeAsBCD hexPrintString        
     900000000 encodeAsBCD hexPrintString        
     1073741823 encodeAsBCD hexPrintString       
     1073741824 encodeAsBCD hexPrintString       
     1073741825 encodeAsBCD hexPrintString       
     1891234567 encodeAsBCD hexPrintString        
     8912345678 encodeAsBCD hexPrintString        
     1234567890 encodeAsBCD hexPrintString  
    "

! !

!Integer methodsFor:'bit operators'!

allMask:anInteger
    "return true if all 1-bits in anInteger are also 1 in the receiver"

    ^ (self bitAnd:anInteger) == anInteger

    "2r00001111 allMask:2r00000001"
    "2r00001111 allMask:2r00011110"
    "2r00001111 allMask:2r00000000"
!

anyMask:anInteger
    "return true if any 1-bits in anInteger is also 1 in the receiver.
     (somewhat incorrect, if the mask is zero)"

    ^ (self bitAnd:anInteger) ~~ 0

    "2r00001111 anyMask:2r00000001"
    "2r00001111 anyMask:2r11110000"
!

bitAnd:anInteger
    "return the bitwise-and of the receiver and the argument, anInteger.
     This is a general and slow implementation, walking over the bytes of
     the receiver and the argument."

    |n "{ Class: SmallInteger }"
     result byte|

    anInteger isInteger ifFalse:[
        ^ anInteger bitAndFromInteger:self.
    ].

    n := (anInteger digitLength) min:(self digitLength).
    result := self class basicNew numberOfDigits:n.

    1 to:n do:[:index |
        byte := (anInteger digitAt:index) bitAnd:(self digitAt:index).
        result digitAt:index put:byte.
    ].
    (byte == 0 or:[n <= SmallInteger maxBytes]) ifTrue:[
        ^ result compressed
    ].
    ^ result

    "
     (16r112233445566778899 bitAnd:16rFF                ) printStringRadix:16 
     (16r112233445566778899 bitAnd:16rFFFFFFFFFFFFFFFF00) printStringRadix:16 
     (16r112233445566778899 bitAnd:16rFF0000000000000000) printStringRadix:16 
     (16r112233445566778899 bitAnd:16r00000000000000FFFF) printStringRadix:16 
    "

    "Modified: 5.11.1996 / 14:06:26 / cg"
!

bitAt:index
    "return the value of the index's bit (index starts at 1).
     Notice: the result of bitShift: on negative receivers is not 
             defined in the language standard (since the implementation
             is free to choose any internal representation for integers)"

    |i "{Class: SmallInteger}"|

    index <= 0 ifTrue:[
        ^ SubscriptOutOfBoundsSignal 
                raiseRequestWith:index
                errorString:'index out of bounds'
    ].
    i := index - 1.
    ^ (self digitAt:(i // 8 + 1)) bitAt:(i \\ 8 + 1)

    "
     1 bitAt:1                     => 1 
     1 bitAt:2                     => 0
     1 bitAt:0                     index error
     2r1000100010001000100010001000100010001000100010001000 bitAt:48 => 1  
     2r1000100010001000100010001000100010001000100010001000 bitAt:47 => 0  

     (1 bitShift:1000) bitAt:1000  => 0
     (1 bitShift:1000) bitAt:1001  => 1
     (1 bitShift:1000) bitAt:1002  => 0

     (1 bitShift:30) bitAt:30    
     (1 bitShift:30) bitAt:31    
     (1 bitShift:30) bitAt:32     
     (1 bitShift:31) bitAt:31     
     (1 bitShift:31) bitAt:32     
     (1 bitShift:31) bitAt:33    
     (1 bitShift:32) bitAt:32    
     (1 bitShift:32) bitAt:33    
     (1 bitShift:32) bitAt:34    
     (1 bitShift:64) bitAt:64     
     (1 bitShift:64) bitAt:65     
     (1 bitShift:64) bitAt:66     
    "
!

bitClear:anInteger
    "return the bitwise-and of the receiver and the complement of argument, anInteger.
     This is a general and slow implementation, walking over the bytes of
     the receiver and the argument."

    |n "{ Class: SmallInteger }"
     result byte|

    n := (anInteger digitLength) max:(self digitLength).
    result := self class basicNew numberOfDigits:n.

    1 to:n do:[:index |
        byte :=  (self digitAt:index) bitClear:(anInteger digitAt:index).
        result digitAt:index put:byte.
    ].
    (byte == 0 or:[n <= SmallInteger maxBytes]) ifTrue:[
        ^ result compressed
    ].
    ^ result
!

bitInvert
    "return a new integer, where all bits are complemented.
     This does not really make sense for negative largeIntegers,
     since the digits are stored as absolute value."

"/    ^ -1 - self

    |n "{ Class: SmallInteger }"
     result byte|

    n := self digitLength.
    result := self class basicNew numberOfDigits:n.

    1 to:n do:[:index |
        byte := self digitAt:index.
        result digitAt:index put:(byte bitInvert bitAnd:16rFF).
    ].
    (byte == 255 or:[n <= SmallInteger maxBytes]) ifTrue:[
        ^ result compressed
    ].
    ^ result

     "
      16rffffffff bitInvert     
      16rff00ff00 bitInvert hexPrintString  
     "
!

bitInvert32
    "return a new integer, where the low32 bits are complemented."

    ^ self bitXor: 16rFFFFFFFF

    "
     16r80000000 bitInvert32 hexPrintString  
     16r7FFFFFFF bitInvert32 hexPrintString  
     16rFFFFFFFF bitInvert32 hexPrintString  
     0 bitInvert32 hexPrintString   
    "
!

bitOr:anInteger
    "return the bitwise-or of the receiver and the argument, anInteger.
     This is a general and slow implementation, walking over the bytes of
     the receiver and the argument."

    |n "{ Class: SmallInteger }"
     result byte|

    anInteger isInteger ifFalse:[
        ^ anInteger bitOrFromInteger:self.
    ].

    n := (anInteger digitLength) max:(self digitLength).
    result := self class basicNew numberOfDigits:n.

    1 to:n do:[:index |
        byte := (anInteger digitAt:index) bitOr:(self digitAt:index).
        result digitAt:index put:byte.
    ].
"/ no need to normalize - if the operands were correct
"/    byte == 0 ifTrue:[
"/        ^ result normalize
"/    ].
    ^ result
!

bitShift:shiftCount
    "return the value of the receiver shifted by shiftCount bits;
     leftShift if shiftCount > 0; rightShift otherwise.

     Notice: the result of bitShift: on negative receivers is not 
             defined in the language standard (since the implementation
             is free to choose any internal representation for integers)"

    |result 
     prev       "{ Class: SmallInteger }"
     next       "{ Class: SmallInteger }"
     byte       "{ Class: SmallInteger }"
     byte2      "{ Class: SmallInteger }"
     bitShift   "{ Class: SmallInteger }"
     revShift   "{ Class: SmallInteger }"
     digitShift "{ Class: SmallInteger }"
     n          "{ Class: SmallInteger }" 
     nn         "{ Class: SmallInteger }"
     nDigits    "{ Class: SmallInteger }" |

    shiftCount isInteger ifFalse:[
        ^ shiftCount bitShiftFromInteger:self.
    ].

    shiftCount > 0 ifTrue:[
        "left shift"

        digitShift := shiftCount // 8.
        bitShift := shiftCount \\ 8.
        n := self digitLength.

        "
         modulo 8 shifts can be done faster ...
        "
        bitShift == 0 ifTrue:[
            n := n + digitShift.
            result := self class basicNew numberOfDigits:n.
            result sign:self sign.
            result digitBytes replaceFrom:(digitShift + 1) to:n with:self digitBytes.
            "
             no normalize needed, since receiver was already normalized
            "
            ^ result
        ].

        "
         less-than-8 shifts can be done faster ...
        "
        digitShift == 0 ifTrue:[
            nn := n+1.
            result := self class basicNew numberOfDigits:nn.
            result sign:self sign.
            prev := 0.
            1 to:n do:[:index |
                byte := self digitAt:index.
                byte := (byte bitShift:bitShift) bitOr:prev.
                result digitAt:index put:(byte bitAnd:16rFF).
                prev := byte bitShift:-8.
            ].
            result digitAt:nn put:prev.
            "
             might have stored a 0-byte ...
            "
            prev == 0 ifTrue:[
                ^ result compressed
            ].
            ^ result.
        ].

        "
         slow case ...
        "
        n := n + digitShift + 1.
        result := self class basicNew numberOfDigits:n.
        result sign:self sign.
        byte := self digitAt:1.
        byte := (byte bitShift:bitShift) bitAnd:16rFF.
        result digitAt:(digitShift + 1) put:byte.
        revShift := -8 + bitShift.
        nDigits := self digitLength.
        2 to:nDigits do:[:index |
            byte := self digitAt:index.
            byte2 := self digitAt:index-1.
            byte := byte bitShift:bitShift.
            byte2 := byte2 bitShift:revShift.
            byte := (byte bitOr:byte2) bitAnd:16rFF.
            result digitAt:(index + digitShift) put:byte.
        ].
        byte2 := self digitAt:nDigits.
        byte2 := (byte2 bitShift:revShift) bitAnd:16rFF.
        result digitAt:(nDigits + digitShift + 1) put:byte2.
        "
         might have stored a 0-byte ...
        "
        byte2 == 0 ifTrue:[
            ^ result compressed
        ].
        ^ result
    ].

    shiftCount < 0 ifTrue:[
        "right shift"

        digitShift := shiftCount negated // 8.
        bitShift := shiftCount negated \\ 8.
        n := self digitLength.

        digitShift >= n ifTrue:[
            ^ 0
        ].

        "
         modulo 8 shifts can be done faster ...
        "
        bitShift == 0 ifTrue:[
            n := n-digitShift.
            result := self class basicNew numberOfDigits:n.
            result sign:self sign.
            result digitBytes replaceFrom:1 to:n with:self digitBytes startingAt:(digitShift + 1) .
            n <= SmallInteger maxBytes ifTrue:[
                ^ result compressed
            ].
            ^ result
        ].

        "
         less-than-8 shifts can be done faster ...
        "
        digitShift == 0 ifTrue:[
            result := self class basicNew numberOfDigits:n.
            result sign:self sign.
            prev := 0.
            bitShift := bitShift negated.
            revShift := 8 + bitShift.
            n to:1 by:-1 do:[:index |
                byte := self digitAt:index.
                next := (byte bitShift:revShift) bitAnd:16rFF.
                byte := (byte bitShift:bitShift) bitOr:prev.
                result digitAt:index put:(byte bitAnd:16rFF).
                prev := next.
            ].
            (n <= 5) ifTrue:[
                ^ result compressed
            ].
            ^ result
        ].

        "
         slow case ...
        "
        nn := n-digitShift.
        result := self class basicNew numberOfDigits:nn.
        result sign:self sign.

        prev := 0.
        bitShift := bitShift negated.
        revShift := 8 + bitShift.
        nn := digitShift + 1.
        n to:nn by:-1 do:[:index |
            byte := self digitAt:index.
            next := (byte bitShift:revShift) bitAnd:16rFF.
            byte := (byte bitShift:bitShift) bitOr:prev.
            result digitAt:(index - digitShift) put:byte.
            prev := next.
        ].
        "the last stored byte ..."
        ^ result compressed
    ].

    ^ self "no shift"

    "Modified: / 8.7.1998 / 12:45:24 / cg"
    "Modified: / 5.5.1999 / 16:05:05 / stefan"
!

bitTest:anInteger
    "return true, if any bit from aMask is set in the receiver.
     I.e. true, if the bitwise-AND of the receiver and the argument, anInteger
     is non-0, false otherwise.
     This is a general and slow implementation, walking over the bytes of
     the receiver and the argument."

    |n "{ Class: SmallInteger }"
     byte|

    n := (anInteger digitLength) min:(self digitLength).

    1 to:n do:[:index |
        byte := (anInteger digitAt:index) bitAnd:(self digitAt:index).
        byte ~~ 0 ifTrue:[^ true].
    ].
    ^ false

    "
     16r112233445566778899 bitTest:16rFF  
     16r112233445566778800 bitTest:16rFF  
     16r112233445566778899 bitTest:16rFFFFFFFFFFFFFFFF00  
     16r112233445566778899 bitTest:16rFF0000000000000000  
     16r112233445566778899 bitTest:16r00000000000000FFFF  
     16r1234567800000000 bitTest:16r8000000000000000  
     16r8765432100000000 bitTest:16r8000000000000000  
     16r12345678 bitTest:16r80000000  
     16r87654321 bitTest:16r80000000  
    "

    "Modified: / 6.6.1999 / 15:10:33 / cg"
!

bitXor:anInteger
    "return the bitwise-or of the receiver and the argument, anInteger.
     This is a general and slow implementation, walking over the bytes of
     the receiver and the argument."

    |n "{ Class: SmallInteger }"
     result byte|

    anInteger isInteger ifFalse:[
        ^ anInteger bitXorFromInteger:self.
    ].

    n := (anInteger digitLength) max:(self digitLength).
    result := self class basicNew numberOfDigits:n.

    1 to:n do:[:index |
        byte := (anInteger digitAt:index) bitXor:(self digitAt:index).
        result digitAt:index put:byte.
    ].
    (byte == 0 or:[n <= SmallInteger maxBytes]) ifTrue:[
        ^ result compressed
    ].
    ^ result

    "
     (16r112233445566778899 bitXor:16rFF                ) printStringRadix:16 '112233445566778866' 
     (16r112233445566778899 bitXor:16rFFFFFFFFFFFFFFFF00) printStringRadix:16 'EEDDCCBBAA99887799'
     (16r112233445566778899 bitXor:16rFF0000000000000000) printStringRadix:16 'EE2233445566778899'
     (16r112233445566778899 bitXor:16r112233445566778800) printStringRadix:16 
    "

    "Modified: 5.11.1996 / 14:06:40 / cg"
!

changeBit:index to:aBooleanOrNumber
    "return a new number where the specified bit is on or off,
     sepending on aBooleanOrNumber.
     Bits are counted from 1 starting with the least significant.
     The methods name may be missleading: the receiver is not changed,
     but a new number is returned. Should be named #withBitChanged:to:"

    (aBooleanOrNumber == 0 or:[aBooleanOrNumber == false]) ifTrue:[
        ^ self bitClear:index
    ].
    ^ self setBit:index

    "
     0 changeBit:3 to:1         => 4 (2r100)
    "
!

clearBit:index
    "return a new number where the specified bit is off.
     Bits are counted from 1 starting with the least significant.
     The methods name may be missleading: the receiver is not changed,
     but a new number is returned. Should be named #withBitCleared:"

    |n         "{ Class: SmallInteger }"
     byteIndex "{ Class: SmallInteger }"
     bitIndex "{ Class: SmallInteger }"
     result byte|

    index <= 0 ifTrue:[
        ^ SubscriptOutOfBoundsSignal 
                raiseRequestWith:index
                errorString:'index out of bounds'
    ].
    byteIndex := ((index - 1) // 8) + 1.
    n := self digitLength.
    byteIndex > n ifTrue:[
        ^ self
    ].

    result := self copy.
    bitIndex := ((index - 1) \\ 8) + 1.
    byte := (result digitAt:byteIndex) clearBit:bitIndex.
    result digitAt:byteIndex put:byte.
    (byte == 0 or:[n == byteIndex and:[n <= SmallInteger maxBytes]]) ifTrue:[
        ^ result compressed
    ].
    ^ result

    "
     3111111111 clearBit:1 
    "

    "Modified: / 28.7.1998 / 18:35:50 / cg"
!

even
    "return true if the receiver is even"

    ^ (self bitTest:1) not

    "
     16r112233445566778899 even  
     16r112233445566778800 even  
     1 even  
     2 even  
    "

    "Created: / 6.6.1999 / 15:00:40 / cg"
!

highBit
    "return the bitIndex of the highest bit set. The returned bitIndex
     starts at 1 for the least significant bit. 
     Returns 0 if no bit is set."

    |byteNr highByte|

    byteNr := self digitLength.
    byteNr == 0 ifTrue:[
        ^ 0
    ].
    highByte := self digitAt:byteNr.
    ^ (byteNr - 1) * 8 + highByte highBit

    "
     0 highBit
     -1 highBit
     (1 bitShift:1) highBit     
     (1 bitShift:30) highBit    
     (1 bitShift:31) highBit    
     (1 bitShift:32) highBit    
     (1 bitShift:33) highBit    
     (1 bitShift:64) highBit     
     (1 bitShift:1000) highBit   
     (1 bitShift:1000) negated highBit   
     ((1 bitShift:64)-1) highBit  
    "

    "Modified: / 3.5.1999 / 09:20:57 / stefan"
!

invertBit:index
    "return a new number where the specified bit is inverted.
     Bits are counted from 1 starting with the least significant.
     The methods name may be missleading: the receiver is not changed,
     but a new number is returned. Should be named #withBitInverted:"

    index <= 0 ifTrue:[
        ^ SubscriptOutOfBoundsSignal 
                raiseRequestWith:index
                errorString:'index out of bounds'
    ].
    ^ self bitXor:(1 bitShift:index-1)

    "
     0 invertBit:3         => 4 (2r100)
     0 invertBit:48        => 140737488355328 (2r1000.....000)
     ((0 invertBit:99) invertBit:100) printStringRadix:2  
    "
!

isBitSet:index
    "return true if the index' bit is set; false otherwise.
     Bits are counted from 1 starting with the least significant."

    ^ (self bitAt:index) ~~ 0

    "
     5 isBitSet:3       => true
     2r0101 isBitSet:2  => false
     2r0101 isBitSet:1  => true
     2r0101 isBitSet:0  index error
    "
!

lowBit
    "return the bitIndex of the lowest bit set. The returned bitIndex
     starts at 1 for the least significant bit. 
     Returns 0 if no bit is set."

    |maxBytes "{ Class: SmallInteger }"
     bitIndex "{ Class: SmallInteger }" 
     byte|

    maxBytes := self digitLength.
    bitIndex := 0.
    1 to:maxBytes do:[:byteIndex |
        byte := self digitAt:byteIndex.
        byte ~~ 0 ifTrue:[
            ^ bitIndex + byte lowBit
        ].
        bitIndex := bitIndex + 8
    ].
    ^ 0 "/ should not happen

    "
     0 lowBit                  
     1 lowBit                  
     (1 bitShift:1) lowBit     
     (1 bitShift:1) highBit     
     (1 bitShift:30) lowBit    
     (1 bitShift:30) highBit    
     (1 bitShift:31) lowBit    
     (1 bitShift:31) highBit    
     (1 bitShift:32) lowBit    
     (1 bitShift:32) highBit    
     (1 bitShift:33) lowBit    
     (1 bitShift:33) highBit    
     (1 bitShift:64) lowBit     
     (1 bitShift:64) highBit     
     (1 bitShift:1000) lowBit   
     (1 bitShift:1000) highBit   
     ((1 bitShift:64)-1) lowBit  
     ((1 bitShift:64)-1) highBit  
    "

    "Modified: 1.3.1997 / 16:54:23 / cg"
!

maskClear:aMask
    ^ self bitAnd:aMask bitInvert
!

maskSet:aMask
    ^ self bitOr:aMask
!

noMask:anInteger
    "return true if no 1-bit in anInteger is 1 in the receiver"

    ^ (self bitAnd:anInteger) == 0

    "2r00001111 noMask:2r00000001"
    "2r00001111 noMask:2r11110000"
!

odd
    "return true if the receiver is odd"

    ^ self bitTest:1

    "
     16r112233445566778899 odd  
     16r112233445566778800 odd  
     1 odd  
     2 odd  
    "

    "Created: / 6.6.1999 / 15:00:55 / cg"
!

setBit:index
    "return a new number where the specified bit is on.
     Bits are counted from 1 starting with the least significant.
     The methods name may be missleading: the receiver is not changed,
     but a new number is returned. Should be named #withBitCleared:"

    index <= 0 ifTrue:[
        ^ SubscriptOutOfBoundsSignal 
                raiseRequestWith:index
                errorString:'index out of bounds'
    ].
    ^ self bitOr:(1 bitShift:index-1)

    "
     0 setBit:3         => 4 (2r100)
     0 setBit:48        => 140737488355328 (2r1000.....000)
     ((0 setBit:99) setBit:100) printStringRadix:2  
    "
! !

!Integer methodsFor:'byte access'!

digitByteLength
    "return the number bytes required for a 2's complement
     binary representation of this Integer.
     For positive receivers, thats the same as the digitLength."

    "
     check if there is a 0-byte ...
     this allows to ask unnormalized LargeIntegers 
     for their digitLength
    "
    |l "{ Class: SmallInteger }" |

    self >= 0 ifTrue:[^ self digitLength].

    l := self negated digitLength.
    (self digitByteAt:l) == 16rFF ifTrue:[
        ^ (l - 1) max:1
    ].
    ^ l

    "
     -129 digitByteLength 
    "

    "Created: / 25.10.1998 / 14:58:09 / cg"
    "Modified: / 25.10.1998 / 19:20:33 / cg"
! !

!Integer methodsFor:'coercing & converting'!

asFixedPoint
    "return the receiver as a fixedPoint number"

    ^ FixedPoint basicNew
        setNumerator:self denominator:1 scale:1

    "
     100 asFixedPoint      
     100 asFixedPoint + 0.1 asFixedPoint    
    "

    "Modified: 5.11.1996 / 15:13:17 / cg"
!

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

    ^ FixedPoint basicNew
        setNumerator:self denominator:1 scale:scale

    "
     100 asFixedPoint:2      
     100 asFixedPoint + (0.1 asFixedPoint:2)    
    "

    "Modified: 10.1.1997 / 20:00:08 / cg"
!

asFraction
    "return a Fraction with same value as receiver"

    ^ Fraction basicNew setNumerator:self denominator:1

    "Modified: 28.7.1997 / 19:26:06 / cg"
!

asInteger
    "return the receiver truncated towards zero - 
     for integers this is self"

    ^ self
!

asModuloNumber
    "return a precomputed modulo number"

    ^ ModuloNumber modulus:self.

    "Created: / 3.5.1999 / 14:48:03 / stefan"
!

signExtendedByteValue
    "return a smallInteger from sign-extending the 8'th bit.
     May be useful for communication interfaces"

    ^ (self bitAnd:16rFF) signExtendedByteValue

    "Created: 7.5.1996 / 09:31:52 / cg"
!

signExtendedShortValue
    "return a smallInteger from sign-extending the 16'th bit.
     May be useful for communication interfaces"

    ^ (self bitAnd:16rFFFF) signExtendedShortValue

    "Modified: 7.5.1996 / 09:31:57 / cg"
! !

!Integer methodsFor:'comparing'!

hash
    "redefined to return smallInteger hashValues"

    ^ self bitAnd:16r3FFFFFFF.

    "
        -20000000000000 hash 
         20000000000000 hash
    "

    "Created: / 14.11.1996 / 12:12:27 / cg"
    "Modified: / 24.2.1998 / 10:07:29 / stefan"
! !

!Integer methodsFor:'double dispatching'!

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

    |d|

    d := aFraction denominator.
    ^ (Fraction numerator:(aFraction numerator - (self * d))
	      denominator:d)

    "Modified: 28.7.1997 / 19:08:30 / cg"
!

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

    ^ (Fraction numerator:(self * aFraction numerator)
	      denominator:aFraction denominator)

    "Modified: 28.7.1997 / 19:08:27 / cg"
!

quotientFromFraction:aFraction
    "sent when a fraction does not know how to divide the receiver, an integer"

    ^ Fraction 
	numerator:aFraction numerator
	denominator:(self * aFraction denominator)

    "Modified: 28.7.1997 / 19:08:23 / cg"
!

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

    |d|

    d := aFraction denominator.
    ^ Fraction numerator:(aFraction numerator + (self * d))
	      denominator:d

    "Modified: 28.7.1997 / 19:08:11 / cg"
! !

!Integer methodsFor:'encoding'!

encodeOn:anEncoder with:aParameter

    anEncoder encodeInteger:self with:aParameter


! !

!Integer methodsFor:'helpers'!

gcd_helper:anInteger 
    "a helper for the greatest common divisor of the receiver and anInteger.
     Knuth's algorithm for large positive integers, with receiver being
     larger than the arg."

    | selfAbs argAbs selfLowBit argLowBit shift t |

    selfAbs := self.
    argAbs := anInteger.

    selfLowBit := selfAbs lowBit - 1.
    argLowBit := argAbs lowBit - 1.
    shift := selfLowBit min:argLowBit.
    argAbs := argAbs bitShift:(argLowBit negated).
    [selfAbs = 0] whileFalse:[
	selfAbs := selfAbs bitShift:(selfLowBit negated).
	selfAbs < argAbs ifTrue:[
	    t := selfAbs. selfAbs := argAbs. argAbs := t
	].
	selfAbs := selfAbs - argAbs.
	selfLowBit := selfAbs lowBit - 1.
    ].
    ^ argAbs bitShift:shift

    "Created: 1.3.1997 / 16:38:17 / cg"
    "Modified: 1.3.1997 / 16:45:17 / cg"
! !



!Integer methodsFor:'misc math'!

acker:n
    "return the value of acker(self, n).
      ;-) Do not try with receivers > 3"

    (self == 0) ifTrue:[^ n + 1].
    (n == 0) ifTrue:[^ (self - 1) acker: 1].
    ^ (self - 1) acker:(self acker:(n - 1))

    "
     3 acker:2  
    "

    "Modified: 18.7.1996 / 13:08:16 / cg"
!

divMod:aNumber
    "return an array filled with self // aNumber and
     self \\ aNumber. 
     The result is only defined for positive receiver and argument.
     This may be redefined in some integer classes for
     more performance (where the remainder is generated as a side effect of division)"

    ^ Array
	with:(self // aNumber)
	with:(self \\ aNumber)

    "  
     10 divMod:3  
     100 factorial divMod:103
    "

    "Modified: 29.10.1996 / 21:18:58 / cg"
!

extendedEuclid:tb
    "return the solution of 'ax + by = gcd(a,b)'.
     An array conatining x, y and gcd(a,b) is returned."

    |a b gcd gcd1 u u1 v v1 tmp t swap shift "{SmallInteger}"|

    self < tb ifTrue:[
        a := self.
        b := tb.
        swap := false.
    ] ifFalse:[
        a := tb.
        b := self.
        swap := true.
    ].

    shift := ((a lowBit) min:(b lowBit))-1.
    shift > 0 ifTrue:[
        tmp := shift negated.
        a := a bitShift:tmp.
        b := b bitShift:tmp.
    ].

    gcd  := a copy.
    gcd1 := b copy.        
    u := 1.
    u1 := 0.
    v := 0.
    v1 := 1.

    [
"/      The following condition is true:
"/        (a * u1) + (b * v1) ~= gcd1 ifTrue:[self halt].
        t := gcd1 divMod:gcd.
        gcd1 := gcd.
        gcd := t at:2.
        t := t at:1.
        tmp := v.
"/v1 - (v * t) - v1 + (v * t) ~= 0 ifTrue:[self halt].
        v := v1 - (v * t).
        v1 := tmp.
        tmp := u.
"/u1 - (u * t) - u1 + (u * t) ~= 0 ifTrue:[self halt].
        u := u1 - (u * t).
        u1 := tmp.
    ] doWhile:[gcd > 0].

    shift > 0 ifTrue:[
        gcd1 := gcd1 bitShift:shift.
    ].

    swap ifTrue:[
        ^ Array with:v1 with:u1 with:gcd1.
    ].
    ^ Array with:u1 with:v1 with:gcd1.


    " 
     14 extendedEuclid:5
     14 extendedEuclid:2  
     25 extendedEuclid:15
    "

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

factorial
    "return fac(self) (i.e. 1*2*3...*self) using an iterative algorithm.
     This is slightly faster than the recursive algorithm, and does not
     suffer from stack overflow problems (with big receivers)"

    |p i|

    (self < 2) ifTrue:[
        self < 0 ifTrue:[
            "/
            "/ requested factorial of a negative number
            "/
            ^ self class
                raise:#domainErrorSignal
                receiver:self
                selector:#factorial
                arguments:#()
                errorString:'factorial of negative number'
        ].
        ^ 1
    ].
    p := 2.
    i := 3.
    [i <= self] whileTrue:[
        p := p * i.
        i := i + 1.
    ].
    ^ p

    "  
     10 factorial
     1000 factorial
     10000 factorial
     10000 factorialR

     Time millisecondsToRun:[2000 factorial] 
     Time millisecondsToRun:[2000 factorialR] 
     -1 factorial
    "

    "Modified: / 16.11.2001 / 14:14:55 / cg"
!

factorialR
    "return fac(self) (i.e. 1*2*3...*self) using a recursive algorithm.
     This is included to demonstration purposes - if you really need
     factorial numbers, use the iterative #factorial, which is slightly
     faster and does not suffer from stack overflow problems (with big receivers)."

    (self >= 2) ifTrue:[
        ^ self * (self - 1) factorialR
    ].
    ^ 1

    "
     10 factorialR
     1000 factorialR
     Time millisecondsToRun:[10000 factorial]
    "

    "Created: / 18.7.1996 / 12:48:36 / cg"
    "Modified: / 8.5.1999 / 18:40:13 / cg"
!

fib
    "compute the fibionacci number for the receiver.
     (same result as returned by #recursiveFib.
      This method shows how a changed algorithm can
      change things much more drastic than tuning ...
      ... compare 30 recursiveFib with 30 fib;
      and dont even try 60 recursiveFib)"

    |a1 a2 an|

    a1 := 1.
    a2 := 0.
    an := self.
    (self - 1) timesRepeat:[
        an := a1 + a2.
        a2 := a1.
        a1 := an
    ].
    ^ an

    "
     Transcript showCR:(Time millisecondsToRun:[30 fib])            
     Transcript showCR:(Time millisecondsToRun:[30 recursiveFib]) 
     Transcript showCR:(Time millisecondsToRun:[60 fib])
     Transcript showCR:(Time millisecondsToRun:[200 fib])
     Transcript showCR:(Time millisecondsToRun:[1500 fib])
    "
!

gcd:anInteger 
    "return the greatest common divisor of the receiver and anInteger.
     Euclids & Knuths algorithm."

    |selfAbs argAbs t|

    selfAbs := self abs.
    argAbs := anInteger abs.

    selfAbs < argAbs ifTrue:[
	t := selfAbs.
	selfAbs := argAbs.
	argAbs := t.
    ].

    argAbs = 0 ifTrue: [^ selfAbs].
    selfAbs := selfAbs \\ argAbs.
    selfAbs = 0 ifTrue:[^ argAbs].
    ^ argAbs gcd_helper:selfAbs

    "                     
     3141589999999999 gcd:1000000000000000
    "

    "Modified: / 25.10.1997 / 16:08:45 / cg"
!

integerReciprocal
    "return an integer representing 1/self * 2**n.
     Where an integer is one bit longer than self."

    |b rem result|                                   

    b := self highBit.
    rem := 1 bitShift:b.
    result := 0 asLargeInteger numberOfDigits:(b // 8)+1.
    b := b+1.
    [b > 0] whileTrue:[
        rem >= self ifTrue:[
            rem := rem -= self.
            result digitBytes bitSetAt:b.
        ].
        rem := rem mul2.               
        b := b - 1.
    ].
    ^ result compressed.          


    "                                     
     333 integerReciprocal                (2 raisedTo:18) // 333
     393 integerReciprocal          
     8 integerReciprocal              
     15 integerReciprocal 
     15112233445566 integerReciprocal 
     10239552311579 integerReciprocal
   "

    "Modified: / 3.5.1999 / 14:27:18 / stefan"
!

inverseMod:n
    "find the modular inverse for myself to n.
     This is defined as the solution of: '1 = (self * x) mod n"

    |e ret|

    "the following expression returns #(x y (self gcd:n)), the solution of the equation
     (self * x) + (n * y) = self gcd:n"

    e := self extendedEuclid:n.

    (e at:3) == 1 ifTrue:[
        ret := e at:1.
        ret negative ifTrue:[
            ^ ret + n
        ].
        ^ ret.
    ].

    ^ 0

    "
     14 inverseMod:5      -> 4
     5 inverseMod:14      -> 3
     14 inverseMod:11     -> 4                (4 * 14) \\ 11 
     11 inverseMod:14     -> 9                (9 * 11) \\ 14 
     79 inverseMod:3220   -> 1019
     3220 inverseMod:79   -> 54               (54 * 3220) \\ 79
     1234567891 inverseMod:1111111111119          
                          -> 148726663534     (148726663534*1234567891) \\ 1111111111119


     14 extendedEuclid:11 
     5 extendedEuclid:14 
     14 extendedEuclid:2
     3220 extendedEuclid:79    
    "

    "Created: / 27.4.1999 / 15:19:22 / stefan"
    "Modified: / 18.11.1999 / 16:21:37 / stefan"
!

lcm:anInteger
    "return the least common multiple (using gcd:)"

    ^ (self * anInteger) abs // (self gcd: anInteger)

    "
     65 lcm:15
     3 lcm:15
    "
!

raisedTo:exp mod:mod
    "return the modulu (remainder) of 
     the receiver raised to exp (an Integer) and mod (another Integer)"

    |result m t 
"/     eI   "{Class: SmallInteger}"
     bits "{Class: SmallInteger}"|

    "use the addition chaining algorithm"

    exp negative ifTrue:[
        ^ self class
            raise:#domainErrorSignal
            receiver:self
            selector:#raisedTo:mod:
            arguments:(Array with:exp with:mod)
            errorString:'modulo arithmethic with negative exponent'
    ].

    m := mod asModuloNumber.

    result := 1.
    t := m modulusOf:self.

    "/ to be validated ...
"/    (exp class == SmallInteger) ifTrue:[
"/        eI := exp.
"/        [eI ~~ 0] whileTrue:[
"/            [(eI bitAnd:1) == 0] whileTrue:[
"/                eI := eI bitShift:-1.
"/                t := m modulusOf:(t * t).
"/            ].
"/            eI := eI - 1.
"/            result := m modulusOf:(result * t).
"/        ].
"/    ] ifFalse:[
        bits := exp highBit.

        1 to:bits do:[:i|
            (exp bitAt:i) == 1 ifTrue:[
                result := m modulusOf:(result * t).
            ].
            t := m modulusOf:(t * t).
        ].
"/    ].

    ^ result

    "                                       
     2 raisedTo:2 mod:3  
      20000000000000 raisedTo:200 mod:190  ->  30
     (20000000000000 raisedTo:200) \\ 190 

      Time millisecondsToRun:[100 timesRepeat:[
                                20000000000000 raisedTo:200 mod:190
                              ]
                             ]      

     Time millisecondsToRun:[100 timesRepeat:[
                                (20000000000000 raisedTo:200) \\ 190
                             ]
                            ]    
    "

    "Created: / 27.4.1999 / 15:19:22 / stefan"
    "Modified: / 5.5.1999 / 11:18:20 / stefan"
    "Modified: / 16.11.2001 / 14:15:21 / cg"
!

raisedToCrtModP:p q:q ep:ep eq:eq u:u
    "Application of the Chinese Remainder Theorem (CRT).

     This is a faster modexp for moduli with a known factorisation into two
     relatively prime factors p and q, and an input relatively prime to the
     modulus, the Chinese Remainder Theorem to do the computation mod p and
     mod q, and then combine the results.  This relies on a number of
     precomputed values, but does not actually require the modulus n or the
     exponent e.

     expout = expin ^ e mod (p*q).
     We form this by evaluating
     p2 = (expin ^ e) mod p and
     q2 = (expin ^ e) mod q
     and then combining the two by the CRT.

     Two optimisations of this are possible.  First, we can reduce expin
     modulo p and q before starting.

     Second, since we know the factorisation of p and q (trivially derived
     from the factorisation of n = p*q), and expin is relatively prime to
     both p and q, we can use Euler's theorem, expin^phi(m) = 1 (mod m),
     to throw away multiples of phi(p) or phi(q) in e.
     Letting ep = e mod phi(p) and
              eq = e mod phi(q)
     then combining these two speedups, we only need to evaluate
     p2 = ((expin mod p) ^ ep) mod p and
     q2 = ((expin mod q) ^ eq) mod q.

     Now we need to apply the CRT.  Starting with
     expout = p2 (mod p) and
     expout = q2 (mod q)
     we can say that expout = p2 + p * k, and if we assume that 0 <= p2 < p,
     then 0 <= expout < p*q for some 0 <= k < q.  Since we want expout = q2
     (mod q), then p*k = q2-p2 (mod q).  Since p and q are relatively prime,
     p has a multiplicative inverse u mod q.  In other words, u = 1/p (mod q).

     Multiplying by u on both sides gives k = u*(q2-p2) (mod q).
     Since we want 0 <= k < q, we can thus find k as
     k = (u * (q2-p2)) mod q.

     Once we have k, evaluating p2 + p * k is easy, and
     that gives us the result
    "  

    |result t mp mq|


    mp := p asModuloNumber.
    t := mp modulusOf:self.
    result := t raisedTo:ep mod:mp.

    mq := q asModuloNumber.
    t := mq modulusOf:self.
    t := t raisedTo:eq mod:mq.

    "now p2 is in result, q2 in t"

    t := t -= result.
    t < 0 ifTrue:[
        t := t + q.
    ].
    t := t *= u.
    t := mq modulusOf:t.
    t := t *= p.
    result := result += t.

    ^ result.



    "                                       
     2 raisedTo:2 mod:3
      20000000000000 raisedTo:200 mod:190
     (20000000000000 raisedTo:200) \\ 190
    "

    "Created: / 30.4.1999 / 15:53:15 / stefan"
    "Modified: / 5.5.1999 / 11:01:15 / stefan"
!

recursiveFib
    "compute the fibionacci number for the receiver.
     WARNING:
         Dont use this method if you need fibionacci numbers -
         this method is for benchmarking purposes only.
         (use #fib instead and dont ever try 60 recursiveFib ...)"

    (self > 1) ifTrue:[
        ^ (self - 1) recursiveFib + (self - 2) recursiveFib
    ].
    ^ self

    "
     30 fib
     30 recursiveFib
     Transcript showCR:(Time millisecondsToRun:[30 recursiveFib])
     Transcript showCR:(Time millisecondsToRun:[30 fib])
    "

    "Modified: 18.7.1996 / 12:47:19 / cg"
! !

!Integer methodsFor:'printing & storing'!

asBCDBytes
    "return a byteArray containing the receiver in BCD encoding.
     The byteArray will contain the BCD encoded decimal string,
     starting with the most significant digits first.
     This conversion is useful for some communication protocols,
     or control systems, which represent big numbers this way...
    "

    |s rest twoDigits hi lo|

    self == 0 ifTrue:[
        ^ #[ 16r00 ]
    ].

    "/ a very rough estimate on the final size ...
    s := (ByteArray new:(self digitLength * 2)) writeStream.

    rest := self.
    [rest > 0] whileTrue:[
        twoDigits := rest \\ 100.
        rest := rest // 100.
        hi := twoDigits \\ 10.
        lo := twoDigits // 10.
        s nextPut:(lo bitShift:4)+hi
    ].

    ^ s contents reverse

    "
     12345678 asBCDBytes 
     12345678901234567890 asBCDBytes
    "


!

displayString
    "return a string for displaying in a view (as in inspector).
     The output radix is usually 10, but can be changed by setting
     DefaultDisplayRadix (see Integer>>displayRadix:)"

    (DefaultDisplayRadix isNil or:[DefaultDisplayRadix == 10]) ifTrue:[
	^ self printString
    ].
    ^ self radixPrintStringRadix:DefaultDisplayRadix

    "
     Integer displayRadix:16. 12345 
     Integer displayRadix:2.  12345 
     Integer displayRadix:10. 12345
    "
!

errorPrintHex
    "print the receiver as a hex number on the standard error stream"

     (self printStringRadix:16) errorPrint
!

hexPrintString
    "return a hex string representation of the receiver"

    ^ self printStringRadix:16

    "
     127 hexPrintString
     -1 hexPrintString
    "

    "Modified: / 11.10.1998 / 01:15:43 / cg"
!

hexPrintString:size
    "return a hex string representation of the receiver,
     padded to size characters"

"/    ^ (self printStringRadix:16) leftPaddedTo:size with:$0
    ^ self printStringRadix:16 size:size fill:$0

    "
     12345 hexPrintString:4   
     123 hexPrintString:4   
    "

    "Created: 18.2.1997 / 13:32:33 / cg"
!

printHex
    "print the receiver as a hex number on the standard output stream"

     (self printStringRadix:16) print
!

printOn:aStream
    "append a printed description of the receiver to aStream"

    self printOn:aStream base:10

    "Modified: / 20.1.1998 / 14:10:45 / stefan"
!

printOn:aStream base:b
    "return a string representation of the receiver in the specified
     radix (without the initial XXr)"

    ^ self printOn:aStream base:b showRadix:false

    "
     10 printOn:Transcript base:3
     31 printOn:Transcript base:3
     -20 printOn:Transcript base:16
     -20 printOn:Transcript base:10
     3000 factorial printOn:Transcript base:10
    "

    "Modified: / 20.1.1998 / 18:05:02 / stefan"
    "Modified: / 7.9.2001 / 13:52:17 / cg"
!

printOn:aStream base:b showRadix:showRadix
    "append a string representation of the receiver in the specified numberBase to aStream
     (if showRadix is true, with initial XXr)
     The radix argument should be between 2 and 36."

    |base num s divMod mod r r2 r4 nD numN|

    base := b.
    (base between:2 and:36) ifFalse:[
        self error:'invalid base' mayProceed:true.
        base := 10.
    ].

    showRadix ifTrue:[
        base printOn:aStream.
        aStream nextPutAll:'r'.    
    ].

    (self = 0) ifTrue:[aStream nextPut:$0. ^ self].
    (self < 0) ifTrue:[
        aStream nextPut:$- . 
        num := self negated.
    ] ifFalse:[
        num := self.
    ].

    "
     claus: changed it from a recursive algorithm;
     (it used to trigger stack-overflow exceptions when printing
      3000 factorial ...)
    "
"/    leftPart := num // base.
"/    (leftPart ~= 0) ifTrue:[
"/        leftPart printOn:aStream base:base.
"/        aStream nextPut:(Character digitValue:(num \\ base).
"/        ^ self
"/    ].
"/    aStream nextPut:(Character digitValue:num).

    "/ instead of computing the quotient and remainder
    "/ against radix, do it in junks of 5 or 6 digits.
    "/ This reduces the number of LargeInt-divisions
    "/ by that factor (turning them into smallInt divisions
    "/ within that junk) and speeds up the conversions noticably.

    r2 := base*base.   "/ radix^2
    r4 := r2*r2.             "/ radix^4
    base <= 10 ifTrue:[
        r := r4*r2.        "/ radix^6
        nD := 6.
    ] ifFalse:[
        r := r4*base.    "/ radix^5
        nD := 5.
    ].

    "get a Stream with space for the digits we are going to print.
     We need ((num log:base) ceiling) digits, which is equivalent
     to ((num log:2)/(base log:2) ceiling)
    "
    s := WriteStream on:(String new:((num highBit // base highBit - 1) + 1)).

    [num >= r] whileTrue:[
        "/
        "/ chop off nD digits.
        "/
        divMod := num divMod:r.
        num := divMod at:1.
        numN := divMod at:2.

        "/ process them
        nD timesRepeat:[
            divMod := numN divMod:base.
            numN := divMod at:1.
            mod := divMod at:2.
            s nextPut:(Character digitValue:mod).
        ].
    ].

    [num ~= 0] whileTrue:[
        divMod := num divMod:base.
        num := divMod at:1.
        mod := divMod at:2.
        s nextPut:(Character digitValue:mod).
    ].

    aStream nextPutAll:(s contents reverse).

    "
        3000 factorial printOn:Transcript base:10
        10 printOn:Transcript base:3
        31 printOn:Transcript base:3
        -20  printOn:Transcript base:16
        -20  printOn:Transcript base:10
        Time millisecondsToRun:[10000 factorial printString]   7650
    "

    "Modified: / 20.1.1998 / 18:05:02 / stefan"
    "Created: / 7.9.2001 / 13:51:33 / cg"
    "Modified: / 7.9.2001 / 13:54:50 / cg"
!

printOn:aStream radix:base
    "append a printed description of the receiver to aStream.
     The receiver is printed in radix base (instead of the default, 10).
     This method is obsoleted by #printOn:base:, which is ST-80 & ANSI compatible."

    self printOn:aStream base:base

    "Modified: / 20.1.1998 / 14:10:45 / stefan"
    "Modified: / 7.9.2001 / 13:58:29 / cg"
!

printRomanOn:aStream
    "print the receiver as roman number to the receiver, aStream.
     This converts correct (i.e. prefix notation for 4,9,40,90, etc.)."

    ^ self printRomanOn:aStream naive:false

    "
     1 to:10 do:[:i | i printRomanOn:Transcript. Transcript cr.].
     1999 printRomanOn:Transcript. Transcript cr.
     Date today year printRomanOn:Transcript. Transcript cr.
    "

    "test all between 1 and 9999:
      1 to:9999 do:[:n |
        |romanString|

        romanString := String streamContents:[:stream | n printRomanOn:stream].
        (Integer readFromRomanString:romanString onError:nil) ~= n ifTrue:[self halt].
     ]
    "
!

printRomanOn:aStream naive:naive
    "print the receiver as roman number to the receiver, aStream.
     The naive argument controls if the conversion is
     correct (i.e. subtracting prefix notation for 4,9,40,90, etc.),
     or naive (i.e. print 4 as IIII and 9 as VIIII); also called simple.
     The naive version is often used for page numbers in documents."

    |restValue spec|

    restValue := self.
    restValue > 0 ifFalse:[self error:'negative roman'].

    naive ifTrue:[
        spec := #(
                " value string repeat "    
                   1000 'M'    true
                    500 'D'    false
                    100 'C'    true
                     50 'L'    false
                     10 'X'    true
                      5 'V'    false
                      1 'I'    true
                 ).
    ] ifFalse:[
        spec := #(
                " value string repeat "    
                   1000 'M'    true
                    900 'CM'   false
                    500 'D'    false
                    400 'CD'   false
                    100 'C'    true
                     90 'XC'   false
                     50 'L'    false
                     40 'XL'   false
                     10 'X'    true
                      9 'IX'   false
                      5 'V'    false
                      4 'IV'   false
                      1 'I'    true
                 ).
    ].

    spec 
        inGroupsOf:3 
        do:[:rValue :rString :repeatFlag |

            [
                (restValue >= rValue) ifTrue:[
                    aStream nextPutAll:rString.
                    restValue := restValue - rValue.
                ].
            ] doWhile:[ repeatFlag and:[ restValue >= rValue] ].
        ].

    "
     1 to:10 do:[:i | i printRomanOn:Transcript naive:false. Transcript cr.].
     1 to:10 do:[:i | i printRomanOn:Transcript naive:true. Transcript cr.].

     1999 printRomanOn:Transcript. Transcript cr.
     Date today year printRomanOn:Transcript. Transcript cr.
    "

    "test all between 1 and 9999:
      1 to:9999 do:[:n |
        |romanString|

        romanString := String streamContents:[:stream | n printRomanOn:stream naive:false].
        (Integer readFromRomanString:romanString onError:nil) ~= n ifTrue:[self halt].
     ]
    "

    "test naive all between 1 and 9999:
      1 to:9999 do:[:n |
        |romanString|

        romanString := String streamContents:[:stream | n printRomanOn:stream naive:true].
        (Integer readFromRomanString:romanString onError:nil) ~= n ifTrue:[self halt].
     ]
    "
!

printStringRadix:base
    "return a string representation of the receiver in the specified
     base; does NOT prepend XXr to the string.
     See also: radixPrintStringRadix:
               printOn:base:showRadix:"

    |s|

    s := WriteStream on:(String new:20).
    self printOn:s base:base.
    ^ s contents

    "Created: / 19.1.1998 / 17:20:58 / stefan"
    "Modified: / 20.1.1998 / 14:10:54 / stefan"
    "Modified: / 7.9.2001 / 13:58:13 / cg"
!

printStringRadix:aRadix size:sz fill:fillCharacter
    "return a string representation of the receiver in the specified
     radix. The string is padded on the left with fillCharacter to make
     its size as specified in sz."

    |s actualSize|

    s := self printStringRadix:aRadix.
    actualSize := s size.
    actualSize < sz ifTrue:[
	s := ((String new:(sz - actualSize)) atAllPut:fillCharacter) , s
    ].
    ^ s

    "
     1024 printStringRadix:16 size:4 fill:$0
     1024 printStringRadix:2 size:16 fill:$.
     1024 printStringRadix:16 size:8 fill:(Character space)
    "
!

radixPrintStringRadix:radix
    "return a string representation of the receiver in the specified
     base; prepend XXr to the string"

    |s|

    s := WriteStream on:(String new:20).
    self printOn:s base:radix showRadix:true.
    ^ s contents

    "
     31 radixPrintStringRadix:2   
     31 radixPrintStringRadix:3    
     31 radixPrintStringRadix:10    
     31 radixPrintStringRadix:16    
     31 radixPrintStringRadix:36   
    "

    "Created: / 19.1.1998 / 17:38:00 / stefan"
    "Modified: / 20.1.1998 / 14:11:03 / stefan"
    "Modified: / 7.9.2001 / 13:57:00 / cg"
!

romanPrintString
    "return a roman number representation of the receiver as a string"

    ^ String streamContents:[:stream | self printRomanOn:stream].

    "
     1999 romanPrintString.    
     Date today year romanPrintString.
    "
! !

!Integer methodsFor:'queries'!

digitAt:n
    "return the n-th byte of the binary representation."

    self subclassResponsibility

    "This is a very stupid implementation, and should be redefined in
     concrete subclasses."

"/    |num count|
"/
"/    num := self.
"/    count := n.
"/    [count > 1] whileTrue:[
"/        num := num // 256.
"/        count := count - 1
"/    ].
"/    ^ num \\ 256

    "
     16r44332211 digitAt:1     
     16r44332211 digitAt:2    
     16r44332211 digitAt:3     
     16r44332211 digitAt:4     
     16r44332211 digitAt:5     
     16r00332211 digitAt:4     
     16r00332211 digitAt:5     
    "

    "Modified: / 26.9.2001 / 21:21:21 / cg"
!

digitByteAt:n
    "return 8 bits of my signed value, starting at byte index.
     For positive receivers, this is the same as #digitAt:;
     for negative ones, the actual bit representation is returned."

    self subclassResponsibility

    "Created: / 26.9.2001 / 21:18:43 / cg"
    "Modified: / 26.9.2001 / 21:20:19 / cg"
!

digitLength
    "return the number of bytes needed for the binary representation
     of the receiver.
     This method is redefined in concrete classes - the fallback here is
     never really used."

    ^ (self log:256) ceiling asInteger

    "Modified: 31.7.1997 / 13:19:06 / cg"
!

isInteger
    "return true, if the receiver is some kind of integer number"

    ^ true
!

isPowerOfTwo
    "return true, if the receiver is a power of 2"

    ^ (self bitAnd:(self - 1)) == 0

    "
     0 isPowerOfTwo     
     1 isPowerOfTwo     
     2 isPowerOfTwo     
     3 isPowerOfTwo     
     4 isPowerOfTwo     
     16r8000000000000000 isPowerOfTwo
     16r8000000000000001 isPowerOfTwo
    "

    "Modified: 15.10.1997 / 18:43:49 / cg"
! !

!Integer methodsFor:'special bit operators'!

bitAnd_32:anInteger
    "return a C-semantic 32bit locical-and of the receiver and
     the argument. Both must be either Small- or LargeIntegers.
     This (nonstandard) specialized method is provided to allow simulation of
     and operations with C semantics."

%{  /* NOCONTEXT */
    int val1, val2, rslt;

    if (__isSmallInteger(self)) {
	val1 = __intVal(self);
    } else if (__isLargeInteger(self)) {
	val1 = __longIntVal(self);
	if (!val1) goto bad;
    } else {
	goto bad;
    }
    if (__isSmallInteger(anInteger)) {
	val2 = __intVal(anInteger);
    } else if (__isLargeInteger(anInteger)) {
	val2 = __longIntVal(anInteger);
	if (!val2) goto bad;
    } else {
	goto bad;
    }
    rslt = val1 & val2;
    RETURN(__MKINT(rslt));

  bad: ;
%}.
    self primitiveFailed.
!

bitOr_32:anInteger
    "return a C-semantic 32bit locical-or of the receiver and
     the argument. Both must be either Small- or LargeIntegers.
     This (nonstandard) specialized method is provided to allow simulation of
     and operations with C semantics."

%{  /* NOCONTEXT */
    int val1, val2, rslt;

    if (__isSmallInteger(self)) {
	val1 = __intVal(self);
    } else if (__isLargeInteger(self)) {
	val1 = __longIntVal(self);
	if (!val1) goto bad;
    } else {
	goto bad;
    }
    if (__isSmallInteger(anInteger)) {
	val2 = __intVal(anInteger);
    } else if (__isLargeInteger(anInteger)) {
	val2 = __longIntVal(anInteger);
	if (!val2) goto bad;
    } else {
	goto bad;
    }
    rslt = val1 | val2;
    RETURN(__MKINT(rslt));

  bad: ;
%}.
    self primitiveFailed.
! !

!Integer methodsFor:'testing'!

isLiteral
    "return true, if the receiver can be used as a literal constant in ST syntax
     (i.e. can be used in constant arrays)"

    ^ true
! !

!Integer methodsFor:'tracing'!

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

    ^ aRequestor traceInteger:self level:level from:referrer


! !

!Integer methodsFor:'truncation & rounding'!

ceiling
    "return the smallest integer which is larger or equal to the receiver.
     For integers, this is the receiver itself."

    ^ self

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

compressed
    "if the receiver can be represented as a SmallInteger, return
     a SmallInteger with my value; otherwise return self with leading
     zeros removed. This method is redefined in LargeInteger."

    ^ self

    "Modified: 5.11.1996 / 14:07:41 / cg"
!

floor
    "return the largest integer which is smaller or equal to the receiver.
     For integers, this is the receiver itself."

    ^ self

    "Modified: 18.7.1996 / 12:44:00 / cg"
!

fractionPart
    "return a number with value from digits after the decimal point.
     (i.e. the receiver minus its truncated value)
     Since integers have no fraction, return 0 here."

    ^ 0

    "
     1234.56789 fractionPart      
     1.2345e6 fractionPart        
     1000 fractionPart              
     10000000000000000 fractionPart 
    "

    "Modified: 4.11.1996 / 20:27:44 / cg"
!

integerPart
    "return a number with value from digits before the decimal point.
     (i.e. the receivers truncated value)
     Since integers have no fraction, return the receiver here."

    ^ self

    "
     1234.56789 integerPart      
     1.2345e6 integerPart        
     1000 integerPart              
     10000000000000000 integerPart 
    "

    "Modified: 4.11.1996 / 20:28:22 / cg"
!

normalize
    "if the receiver can be represented as a SmallInteger, return
     a SmallInteger with my value; otherwise return self with leading
     zeros removed.
     This method is left for backward compatibility - it has been
     renamed to #compressed for ST-80 compatibility."

    ^ self compressed

    "Modified: 5.11.1996 / 14:08:24 / cg"
!

rounded
    "return the receiver rounded toward the next Integer -
     for integers this is the receiver itself."

    ^ self

    "Modified: 18.7.1996 / 12:44:24 / cg"
!

truncated
    "return the receiver truncated towards zero - 
     for integers this is the receiver itself."

    ^ self

    "Modified: 18.7.1996 / 12:44:33 / cg"
! !

!Integer::ModuloNumber class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1999 by eXept Software AG
              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
"
    This is a helper class to perform fast computation of the modulus.
    (with big numbers, this does make a difference)

    WARNING: this does only work with numbers which have no common
             divisor (which is true for cryptographic applications).
             So, use this only if you know what you are doing ...

    [author:]
        Stefan Vogel

    [see also:]
        Integer SmallInteger LargeInsteger

    [instance variables:]
        modulus       the modulus
        reciprocal    reciprocal of the modulus
        shift         shift count to cut off some bits
"
!

examples
"
                                                                [exBegin]
        17 asModuloNumber modulusOf:38
                                                                [exEnd]

                                                                [exBegin]
        38 \\ 17        
                                                                [exEnd]
"
! !

!Integer::ModuloNumber class methodsFor:'instance creation'!

modulus:anInteger

    ^ self new modulus:anInteger

    "Created: / 3.5.1999 / 11:13:15 / stefan"
    "Modified: / 3.5.1999 / 11:18:37 / stefan"
! !

!Integer::ModuloNumber methodsFor:'accessing'!

modulus
    "return the modulus"

    ^ modulus
!

modulus:n
    "set the modulus"

    modulus := n.
    reciprocal := n integerReciprocal.
    shift := n highBit negated.

    "Created: / 3.5.1999 / 10:02:39 / stefan"
    "Modified: / 3.5.1999 / 14:30:49 / stefan"
! !

!Integer::ModuloNumber methodsFor:'arithmetic'!

modulusOf:aNumber
    "compute the aNumber modulo myself.
     The shortcut works only, if aNumber is < modulo * modulo
     (When doing arithmethic modulo something).
     Otherwise do it the long way"

    |e t cnt|

    "throw off low nbits(modulus)"

    e := (aNumber bitShift:shift).
    e := e * reciprocal.
    e := (e bitShift:shift).
    e := e * modulus.
    e := aNumber - e.

    "this subtract is done max 2 times"
    cnt := 2.
    [(t := e - modulus) >= 0] whileTrue:[
        e := t.
        cnt == 0 ifTrue:[
            ^ e \\ modulus.
        ].
        cnt := cnt - 1.
    ].
    ^ e.

    "
     |m|

     m := self new modulus:7.
     m modulusOf:55.
    "

    "Shortcut does not work: (size of divisor vs. dividend):
     |m|

     m := self new modulus:7.
     m modulusOf:123456789901398721398721931729371293712943794254034548369328469438562948623498659238469234659823469823658423659823658.
    "

    "SLOW (using standard \\ operation):
     |m|

     m := 123456789901398721398721931729371293712943794254034548369328469438562948623498659238469234659823469823658423659823658.
     Time millisecondsToRun:[
        1000 timesRepeat:[
            874928459437598375937451931729371293712943794254034548369328469438562948623498659238469234659823469823658423659823658 \\ m
        ]
     ]
    "            

    "fast (using moduloNumber with almost same-sized dividend and divisor):
     |m|

     m := self new modulus:123456789901398721398721931729371293712943794254034548369328469438562948623498659238469234659823469823658423659823658.
     Time millisecondsToRun:[
        1000 timesRepeat:[
            m modulusOf:874928459437598375937451931729371293712943794254034548369328469438562948623498659238469234659823469823658423659823658.
        ]
     ]
    "            

    "Modified: / 3.5.1999 / 14:30:32 / stefan"
! !

!Integer::ModuloNumber methodsFor:'converting'!

asModuloNumber

    ^ self

    "Created: / 3.5.1999 / 14:48:27 / stefan"
! !

!Integer class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Integer.st,v 1.152 2002-11-15 12:15:28 cg Exp $'
! !

Integer initialize!