|
Class: SmallInteger
Object
|
+--Magnitude
|
+--ArithmeticValue
|
+--Number
|
+--Integer
|
+--SmallInteger
- Package:
- stx:libbasic
- Category:
- Magnitude-Numbers
- Version:
- rev:
1.409
date: 2024/04/22 16:42:35
- user: stefan
- file: SmallInteger.st directory: libbasic
- module: stx stc-classLibrary: libbasic
SmallIntegers are Integers which fit into a native machine word
(incl. any tags, if configured to use them).
Typically, on a 32bit machine, the range is +/- 2^30 i.e. effectively using 31 bits,
and on a 64bit machine it is +/- 2^62 i.e. using 63 bits,
under the JSchteam-VM, 64 bits are used (i.e. a full long integer)
under the CSchteam-VM, 44 bits are used
These are no real objects - they have no instances (not even storage !)
and cannot be subclassed.
The reason is to save both storage and runtime by not boxing and
garbage collecting SmallIntegers in the system.
SmallInts are marked by having the TAG_INT
bit set, in contrast to all other objects which do not.
Since this knowledge is hardwired into the system (and there is no
class-field stored with SmallIntegers) there can be no subclass of
SmallInteger (sorry).
If you really need this kind of thing, create a subclass of Integer,
with an instance variable holding the value.
Because the range and sharing of SmallIntegers is different among implementations
(both in different dialects, and in different architectures within the Smalltalk/X family),
you should not depend on the identity of two integers with the same value.
For portable code, when comparing integers, use #'=' and #'~=' (instead of #'==' / #'~~'),
unless you are comparing very small integers in low (let's say 30 bit) range.
In other words: you can savely compare an integer against (say) 0, -1, -100, 100 etc.
using == or ~~, but not so against 0xFFFFFFFF or similar (not even against 0x40000000,
because those are LargeIntegers on 32 bit machines).
copyrightCOPYRIGHT (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.
bit mask constants
-
bitMaskFor: index
-
return a bitmask for the index's bit (index starts at 1)
Q: who needs this?
class initialization
-
initialize
-
constants
-
maxBits
-
return the number of bits in instances of me.
For very special uses only - not constant across implementations
Usage example(s):
-
maxBytes
-
return the number of bytes in instances of me.
For very special uses only - not constant across implementations.
Notice: this is inlined by the compiler(s) as a constant,
therefore, a query like 'SmallInteger maxBytes == 8'
costs nothing; it is compiled in as a constant.
Usage example(s):
-
maxVal
-
return the largest Integer representable as SmallInteger.
For very special uses only - not constant across implementations
Usage example(s):
-
minVal
-
return the smallest Integer representable as SmallInteger.
For very special uses only - not constant across implementations
Usage example(s):
instance creation
-
basicNew
-
catch instance creation
- SmallIntegers cannot be created with new
-
basicNew: size
-
catch instance creation
- SmallIntegers cannot be created with new
-
random
( an extension from the stx:libbasic2 package )
-
SmallInteger random
queries
-
canBeSubclassed
-
return true, if it's allowed to create subclasses of the receiver.
Return false here - since it is NOT possible for SmallInteger
(due to the tagged representation of SmallIntegers)
-
hasImmediateInstances
-
return true if this class has immediate instances
i.e. if the instances are represented in the pointer itself and
no real object header/storage is used for the object.
Redefined from Behavior
-
isBuiltInClass
-
return true if this class is known by the run-time-system.
Here, true is returned.
Compatibility-Squeak
-
asEnglishThreeDigitName
( an extension from the stx:libcompat package )
-
english name of a small integer (1..999).
Returns an empty string for zero.
Don't use this directly; it's a helper for asWords
arithmetic
-
* aNumber
-
return the product of the receiver and the argument
Usage example(s):
3 * (1/2)
6 * (1/2)
6 * (-1/2)
6 * 0.5
0xFFFFFFFF * 2
0x3FFFFFFFFFFFFFFF * 2
0x3FFFFFFFFFFFFFFF perform:#* with:4
0x4000000000000000 perform:#* with:2
|
-
+ aNumber
-
return the sum of the receiver's value and the argument's value
-
- aNumber
-
return the difference of the receiver's value and the argument's value
-
/ aNumber
-
return the quotient of the receiver's value and the argument's value
Usage example(s):
8 / 4
9 / 4
9 // 4
9 quo:4
-8 / 4
-9 / 4
-9 // 4
-9 quo:4
self minVal / -1
|
-
// aNumber
-
return the integer part of the quotient of the receiver's value
and the argument's value.
The result is truncated toward negative infinity
and will be negative, if the operands signs differ.
The following is always true:
(receiver // aNumber) * aNumber + (receiver \\ aNumber) = receiver
Be careful with negative results: 9 // 4 -> 2, while -9 // 4 -> -3.
Especially surprising (because of truncation toward negative infinity):
-1 // 10 -> -1 (because -(1/10) is truncated towards next smaller integer, which is -1.
-10 // 3 -> -4 (because -(10/3) is truncated towards next smaller integer, which is -4.
See #quo: which truncates toward zero and returns -2 in the above case
and #rem: which is the corresponding remainder.
Usage example(s):
9 // 4 ~~ 2 ifTrue:[self halt].
-9 // 4 ~~ -3 ifTrue:[self halt].
9 // -4 ~~ -3 ifTrue:[self halt].
-9 // -4 ~~ 2 ifTrue:[self halt].
1 // 2 ~~ 0 ifTrue:[self halt].
-1 // 2 ~~ -1 ifTrue:[self halt].
1 // -2 ~~ -1 ifTrue:[self halt].
-1 // -2 ~~ 0 ifTrue:[self halt].
self minVal // -1
-7 // (4/3)
-7 quo: (4/3)
7 // (-4/3)
7 quo: (-4/3)
10000 // 3600000 ~~ 0 ifTrue:[self halt].
12 // (1 / 1000000000000000000)
12 // (1 / 100000000000000)
12 // 0.00000000000001s
9 quo:4 => 2
-9 quo:4 => -2
9 quo:-4 => -2
-9 quo:-4 => 2
|
-
\\ aNumber
-
Answer the integer remainder m defined by division with truncation toward
negative infinity.
m < |aNumber| AND there is an integer k with (k * aNumber + m) = self
The returned remainder has the same sign as aNumber.
The following is always true:
(receiver // aNumber) * aNumber + (receiver \\ aNumber) = receiver
Be careful with negative results: 9 // 4 -> 2, while -9 // 4 -> -3.
Especially surprising:
-1 \\ 10 -> 9 (because -(1/10) is truncated towards next smaller integer, which is -1,
and -1 multiplied by 10 gives -10, so we have to add 9 to get the original -1).
-10 \\ 3 -> 2 (because -(10/3) is truncated towards next smaller integer, which is -4,
and -4 * 4 gives -12, so we need to add 2 to get the original -10.
See #rem: which is the corresponding remainder for division via #quo:.
Redefined here for speed.
Usage example(s):
9 \\ 4 == 1 ifFalse:[self halt].
-9 \\ 4 == 3 ifFalse:[self halt].
9 \\ -4 == -3 ifFalse:[self halt].
-9 \\ -4 == -1 ifFalse:[self halt].
(9 rem:4) == 1 ifFalse:[self halt].
(-9 rem:4) == -1 ifFalse:[self halt].
1000 \\ 3600000 == 1000 ifFalse:[self halt]
|
-
abs
-
return the absolute value of the receiver
reimplemented here for speed
-
negated
-
return the negative value of the receiver
reimplemented here for speed
-
quo: aNumber
-
return the integer part of the quotient of the receiver's value
and the argument's value. The result is truncated towards zero
and negative, if the operands signs differ.
The following is always true:
(receiver quo: aNumber) * aNumber + (receiver rem: aNumber) = receiver
For positive results, this is the same as #//,
for negative results, the remainder is ignored.
I.e.: '9 // 4 = 2' and '-9 // 4 = -3'
in contrast: '9 quo: 4 = 2' and '-9 quo: 4 = -2'
Usage example(s):
9 // 4
-9 // 4
9 quo:4
-9 quo:4
self minVal quo: -1
-7 // (4/3)
-7 quo: (4/3)
7 // (-4/3)
7 quo: (-4/3)
|
-
sqrt
-
return the square root value of the receiver
reimplemented here for speed
Usage example(s):
2 sqrt
-2 sqrt
Number trapImaginary:[-2 sqrt]
|
bit operators
-
asLowBitMask
-
return a bit mask for the n lowest bits (self being n).
Usage example(s):
1 asLowBitMask hexPrintString '1'
4 asLowBitMask hexPrintString 'F'
6 asLowBitMask hexPrintString '3F'
8 asLowBitMask hexPrintString 'FF'
100 asLowBitMask hexPrintString '0xFFFFFFFFFFFFFFFFFFFFFFFFF'
0 asLowBitMask hexPrintString '0'
|
-
bitAnd: anInteger
-
return the bitwise-and of the receiver and the argument, anInteger
Usage example(s):
(2r001010100 bitAnd:2r00001111) radixPrintStringRadix:2
|
-
bitClear: anInteger
-
return the bitwise-and of the receiver and the complement of the argument, anInteger,
returning the receiver with bits of the argument cleared.
(i.e. the same as self bitAnd:aMaskInteger bitInvert).
The method's name may be misleading: the receiver is not changed,
but a new number is returned. Should be named #withBitCleared:
Usage example(s):
(2r001010100 bitClear:2r00001111) radixPrintStringRadix:2
(2r111111111 bitClear:2r00001000) radixPrintStringRadix:2
(2r001010100 bitAnd:2r00001111 bitInvert) radixPrintStringRadix:2
|
-
bitCount
-
return the number of 1-bits in the receiver
Usage example(s):
16rAA bitCount
TimeDuration toRun:[
1 to:10000000 do:[:n |
n bitCount
].
]
AL1: 967ms 958ms 971ms 930ms
AL2: 900ms 872ms 877ms 870ms
AL3: 879ms 849ms 831ms 849ms
AL4: 858ms 852ms 846ms 810ms
AL5: 830ms 843ms 835ms 845ms
Mac PB2012/2.6Ghz I7
AL3: 855ms 885ms 859ms 878ms 844ms
AL5: 877ms 877ms 846ms 890ms 853ms
1 to:1000000 do:[:n |
self assert:(n bitCount = ((n printStringRadix:2) occurrencesOf:$1))
].
#( 16r00000000
16r00010000 16r00100000 16r01000000 16r10000000
16r00020000 16r00200000 16r02000000 16r20000000
16r00040000 16r00400000 16r04000000 16r40000000
16r00080000 16r00800000 16r08000000 16r80000000
16rFFFFFFFF 16r7FFFFFFF 16r3FFFFFFF 16r1FFFFFFF
16rEEEEEEEE 16r7EEEEEEE 16r3EEEEEEE 16r1EEEEEEE
16rDDDDDDDD 16r7DDDDDDD 16r3DDDDDDD 16r1DDDDDDD
16rCCCCCCCC 16r7CCCCCCC 16r3CCCCCCC 16r1CCCCCCC
16r8000000000010000 16r8000000000100000 16r8000000001000000 16r8000000010000000
16r8000000000020000 16r8000000000200000 16r8000000002000000 16r8000000020000000
16r8000000000040000 16r8000000000400000 16r8000000004000000 16r8000000040000000
16r8000000000080000 16r8000000000800000 16r8000000008000000 16r8000000080000000
16r80000000FFFFFFFF 16r800000007FFFFFFF 16r800000003FFFFFFF 16r800000001FFFFFFF
16r80000000EEEEEEEE 16r800000007EEEEEEE 16r800000003EEEEEEE 16r800000001EEEEEEE
16r80000000DDDDDDDD 16r800000007DDDDDDD 16r800000003DDDDDDD 16r800000001DDDDDDD
16r80000000CCCCCCCC 16r800000007CCCCCCC 16r800000003CCCCCCC 16r800000001CCCCCCC
16rFFFFFFFFFFFFFFFF 16r7FFFFFFFFFFFFFFF 16r3FFFFFFFFFFFFFFF 16r1FFFFFFFFFFFFFFF
) do:[:n |
self assert:(n bitCount = ((n printStringRadix:2) occurrencesOf:$1))
]
1 to:10000000 do:[:n |
(n bitCount)
]
|
-
bitDeinterleave: n
-
extract count integers from an n-way Morton number as a vector;
This is the inverse operation from bitInterleave: - see comment there.
i.e. if count is 3,
and the receiver's bits are
cN bN aN ... c2 b2 a2 c1 b1 a1 c0 b0 a0
then the result will be a vector containing the numbers a,b,c with bits:
aN ... a2 a1 a0
bN ... b2 b1 b0
cN ... c2 c1 c0.
Morton numbers are great to linearize 2D coordinates
eg. to sort 2D points by distances
Usage example(s):
(2r1100 bitInterleaveWith:2r1001) bitDeinterleave:2 -> #(12 9)
(197 bitInterleaveWith:144) bitDeinterleave:2 -> #(197 144)
(197 bitInterleaveWith:144 and:62) bitDeinterleave:3 -> #(197 144 62)
|a b|
(0 to:31) do:[:bitA |
a := 1 << bitA.
(0 to:31) do:[:bitB |
b := 1 << bitB.
self assert:( (a bitInterleaveWith:b) bitDeinterleave:2 ) = {a . b }
].
].
|a b c|
(0 to:31) do:[:bitA |
a := 1 << bitA.
(0 to:31) do:[:bitB |
b := 1 << bitB.
(0 to:31) do:[:bitC |
c := 1 << bitC.
self assert:( (a bitInterleaveWith:b and:c) bitDeinterleave:3 ) = {a . b . c}
].
].
].
|
-
bitInterleaveWith: anInteger
-
generate a Morton number (-> https://en.wikipedia.org/wiki/Morton_number_(number_theory))
by interleaving bits of the receiver
(at even positions if counting from 1) with bits of the argument (at odd bit positions).
Thus, if the bits of the receiver are
aN ... a2 a1 a0
and those of the argument are:
bN ... b2 b1 b0
the result is
bN aN ... b2 a2 b1 a1 b0 a0.
Morton numbers are great to linearize 2D coordinates
eg. to sort 2D points by distances
Usage example(s):
(2r1100 bitInterleaveWith:2r1001) printStringRadix:2 -> '11 01 00 10'
(2r11000101 bitInterleaveWith:2r10010000) printStringRadix:2'1101001000010001 -> '11 01 00 10 00 01 00 01'
|a b|
(0 to:31) do:[:bitA |
a := 1 << bitA.
(0 to:31) do:[:bitB |
b := 1 << bitB.
self assert:( (a bitInterleaveWith:b) bitDeinterleave:2 ) = {a . b }
].
].
|
-
bitInvert
-
return the value of the receiver with all bits inverted.
The method's name may be misleading: the receiver is not changed,
but a new number is returned. Could be named #withBitsInverted
-
bitInvertByte
-
return a new integer, where the low 8 bits are masked and complemented.
This returns an unsigned version of what bitInvert would return.
(i.e. same as self bitInvert bitAnd:16rFF)
Usage example(s):
16r7f bitInvert
16r7f bitInvertByte
16r80 bitInvert
16r80 bitInvertByte
16rff bitInvert
16rff bitInvertByte
|
-
bitOr: anInteger
-
return the bitwise-or of the receiver and the argument, anInteger
Usage example(s):
(2r000000100 bitOr:2r00000011) radixPrintStringRadix:2
(0 bitOr:16r20000000) hexPrintString
(0 bitOr:16r40000000) hexPrintString
(0 bitOr:16r80000000) hexPrintString
|
-
bitReversed
-
swap (i.e. reverse) bits in an integer
i.e. a.b.c.d....x.y.z -> z.y.x...b.a.d.c.
Warning:
do not use this without care: it depends on the machine's
word size; i.e. a 64bit machine will return a different result as a 32bit machine.
Better use one of the bitReversedXX methods.
This my vanish or be replaced by something better
Usage example(s):
2r1001 bitReversed printStringRadix:2
2r100111010011 bitReversed printStringRadix:2
-1 bitReversed printStringRadix:2
|
-
bitReversed16
-
swap (i.e. reverse) the low 16 bits in an integer
the high bits are ignored and clear in the result
i.e. xxx.a.b.c.d....x.y.z -> 000.z.y.x...b.a.d.c.
Usage example(s):
2r1001 bitReversed16 printStringRadix:2
2r100111010011 bitReversed16 printStringRadix:2
16r1ABCD bitReversed16 printStringRadix:2
-1 bitReversed16 printStringRadix:2
|
-
bitReversed32
-
swap (i.e. reverse) the low 32 bits in an integer
the high bits are ignored and clear in the result
i.e. xxx.a.b.c.d....x.y.z -> 000.z.y.x...b.a.d.c.
Usage example(s):
2r1001 bitReversed32 printStringRadix:2
2r100111010011 bitReversed32 printStringRadix:2
-1 bitReversed32 printStringRadix:2
|
-
bitReversed64
-
swap (i.e. reverse) the low 64 bits in an integer
the high bits are ignored and clear in the result
i.e. xxx.a.b.c.d....x.y.z -> 000.z.y.x...b.a.d.c.
Usage example(s):
2r1001 bitReversed64 printStringRadix:2
2r100111010011 bitReversed64 printStringRadix:2
-1 bitReversed64 printStringRadix:2
|
-
bitReversed8
-
swap (i.e. reverse) the low 8 bits in an integer
the high bits are ignored and clear in the result
i.e. xxx.a.b.c.d....x.y.z -> 000.z.y.x...b.a.d.c.
Usage example(s):
2r1001 bitReversed8 printStringRadix:2
2r10011101 bitReversed8 printStringRadix:2
2r111110011101 bitReversed8 printStringRadix:2
16r1234 bitReversed8 printStringRadix:2
-1 bitReversed8 printStringRadix:2
|
-
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).
However, ST/X preserves the sign;
i.e. it is an arithmetic shift as long as you stay within the
number of bits supported by the platform.
Also notice:
because this is an arithmetic shift, negative numbers shifted
right will (conceptionally) shift in 1-bits.
Thus, -2>>1 will answer -1,
whereas 2>>1 will answer 0
Usage example(s):
^ self bitShift:shiftCount asInteger "/ is this a good idea ?
|
Usage example(s):
16 bitShift:-1
16 bitShift:-2
16 bitShift:-63
-16 bitShift:-1
-16 bitShift:-2
-16 bitShift:-63
4 rightShift:-2
-4 rightShift:-2
-4 rightShift:63
|
-
bitTest: aMask
-
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.
Usage example(s):
2r10001 bitTest:2r00001
2r10001 bitTest:2r00010
2r10001 bitTest:2r00100
2r10001 bitTest:2r01000
2r10001 bitTest:2r10000
2r10001 bitTest:2r10001
2r10001 bitTest:2r10010
|
-
bitXor: anInteger
-
return the bitwise-exclusive-or of the receiver and the argument, anInteger
-
changeMask: mask to: aBooleanOrNumber
-
return a new number where the specified mask-bit is on or off,
depending on aBooleanOrNumber.
The method's name may be misleading: the receiver is not changed,
but a new number is returned. Should be named #withMask:changedTo:
Usage example(s):
(16r3fffffff changeMask:16r80 to:0) hexPrintString -> '3FFFFF7F'
(16r3fff0000 changeMask:16r80 to:1) hexPrintString -> '3FFF0080'
(16r3fffffFF changeMask:16rFF to:0) hexPrintString -> '3FFFFF00'
(16r3fff0000 changeMask:16rFF to:1) hexPrintString -> '3FFF00FF'
(16r3fffffFF changeMask:16rFF to:false) hexPrintString -> '3FFFFF00'
(16r3fff0000 changeMask:16rFF to:true) hexPrintString -> '3FFF00FF'
|
-
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.
Notice for negative numbers, the returned value is undefined (actually: nonsense),
because for 2's complement representation, conceptionally all high bits are 1.
But because we use a sign-magnitude representation for large integers,
you'll get the high bit of the absolute magnitude for numbers above the SmallInteger
range, in contrast to the highbit of the negative number if within the SmallInt range.
Usage example(s):
2r0 highBit
2r1 highBit
2r10 highBit
2r100 highBit
2r1000 highBit
2r100000000000 highBit
((0 to:64) collect:[:s | 1 bitShift:s])
collect:[:n | n highBit]
(((0 to:64) collect:[:s | 1 bitShift:s])
collect:[:n | n highBit]) = (1 to:65)
|
Usage example(s):
Time millisecondsToRun:[
1000000 timesRepeat:[
2r1 highBit
]
]
|
Usage example(s):
Time millisecondsToRun:[
1000000 timesRepeat:[
2r1111 highBit
]
]
|
Usage example(s):
Time millisecondsToRun:[
1000000 timesRepeat:[
2r11111111111111 highBit
]
]
|
Usage example(s):
Time millisecondsToRun:[
1000000 timesRepeat:[
2r11111111111111111111111111 highBit
]
]
|
Usage example(s):
2r000100 highBit
2r010100 highBit
2r000001 highBit
0 highBit
SmallInteger maxVal highBit
|
-
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.
Usage example(s):
0 lowBit => 0
2r0001 lowBit => 1
2r0010 lowBit => 2
2r0100 lowBit => 3
2r1000 lowBit => 4
2r000100 lowBit => 3
2r010010 lowBit => 2
2r100001 lowBit => 1
16r1000 lowBit => 13
16r1000000 lowBit => 25
16r1000000000000000 lowBit => 61
16r10000000000000000 lowBit => 65
Time millisecondsToRun:[
1000000 timesRepeat:[
2r1000 lowBit
]
]
Time millisecondsToRun:[
1000000 timesRepeat:[
2r11110000000 lowBit
]
]
Time millisecondsToRun:[
1000000 timesRepeat:[
2r1000000000000 lowBit
]
]
Time millisecondsToRun:[
1000000 timesRepeat:[
2r1000000000000000000000000000 lowBit
]
]
|
-
lowBits: nBits
-
return the n lowest bits
Usage example(s):
(0xFA lowBits:4) hexPrintString 'A'
(0xFA lowBits:6) hexPrintString '3A'
(0xFA lowBits:8) hexPrintString 'FA'
(0xFFFA lowBits:100) hexPrintString 'FFFA'
(0x1234567890 lowBits:8) hexPrintString '90'
(0x1234567890123456 lowBits:8) hexPrintString '56'
(0x3FFFFFAA lowBits:8) hexPrintString 'AA'
(0x7FFFFFAA lowBits:8) hexPrintString 'AA'
(0x3FFFFFFFFFFFFFAA lowBits:8) hexPrintString 'AA'
(0x7FFFFFFFFFFFFFAA lowBits:8) hexPrintString 'AA'
(0x3FFFFFFFFFFFFFFF lowBits:100) = 0x3FFFFFFFFFFFFFFF
(0x3FFFFFFFFFFFFFFF lowBits:65) = 0x3FFFFFFFFFFFFFFF
(0x3FFFFFFFFFFFFFFF lowBits:64) = 0x3FFFFFFFFFFFFFFF
(0x3FFFFFFFFFFFFFFF lowBits:63) = 0x3FFFFFFFFFFFFFFF
(0x3FFFFFFFFFFFFFFF lowBits:62) = 0x3FFFFFFFFFFFFFFF
(0x3FFFFFFFFFFFFFFF lowBits:61) = 0x1FFFFFFFFFFFFFFF
(0x3FFFFFFFFFFFFFFF lowBits:60) = 0x0FFFFFFFFFFFFFFF
|
-
rightShift: shiftCount
-
return the value of the receiver shifted by shiftCount bits;
right shift if shiftCount > 0; left shift 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).
However, ST/X preserves the sign,
i.e. it is an arithmetic shift as long as you stay within the
number of bits supported by the platform.
Usage example(s):
16 rightShift:1 8
16 rightShift:2 4
16 rightShift:63 0
-16 rightShift:1 -8
-16 rightShift:2 -4
-16 rightShift:63 -1
1 rightShift:-2 4
-1 rightShift:-2 -4
4 rightShift:-2 16
-4 rightShift:0 -4
-4 rightShift:-1 -8
-4 rightShift:-2 -16
-4 rightShift:63 -1
(1 bitShift:100) negated rightShift:200
(1 bitShift:63) negated rightShift:62
(1 bitShift:63) negated rightShift:199
|
bit operators - indexed
-
bitAt: anIntegerIndex
-
return the value of the index's bit (index starts at 1) as 0 or 1.
Notice: the result of bitAt: on negative receivers is not
defined in the language standard (since the implementation
is free to choose any internal representation for integers)
Usage example(s):
16r000000001 bitAt:0 -> error
16r000000001 bitAt:1
16r000000001 bitAt:2
16r000008000 bitAt:16
16r000800000 bitAt:24
16r008000000 bitAt:28
16r010000000 bitAt:29
16r020000000 bitAt:30
16r040000000 bitAt:31
16r080000000 bitAt:32
16r100000000 bitAt:33
|
-
clearBit: anInteger
-
return a new integer where the specified bit is off.
Bits are counted from 1 starting with the least significant.
The method's name may be misleading: the receiver is not changed,
but a new number is returned. Should be named #withBitCleared:
Usage example(s):
(16r401 clearBit:1 ) hexPrintString
(16r401 clearBit:0 ) hexPrintString
(16r3fffffff clearBit:1) hexPrintString
(16r3fffffff clearBit:29) hexPrintString
(16r3fffffff clearBit:30) hexPrintString
(16r3fffffff clearBit:31) hexPrintString
(16r3fffffff bitAt:29) hexPrintString
(16r3fffffff bitAt:30) hexPrintString
(16r3fffffff bitAt:31) hexPrintString
(16r40000001 clearBit:1) hexPrintString
(16rF0000001 clearBit:29) hexPrintString
(16rF0000001 clearBit:30) hexPrintString
(16rF0000001 clearBit:31) hexPrintString
(16rF0000001 clearBit:32) hexPrintString
(16r1F0000001 clearBit:33) hexPrintString
|
-
invertBit: anInteger
-
return a new number where the specified bit is inverted.
Bits are counted from 1 starting with the least significant.
The method's name may be misleading: the receiver is not changed,
but a new number is returned. Should be named #withBitInverted:
Usage example(s):
(16r401 invertBit:2 ) hexPrintString
(16r401 invertBit:1 ) hexPrintString
(16r30000000 invertBit:1) hexPrintString
(16r40000000 invertBit:0) hexPrintString
(16r0 invertBit:29) hexPrintString
(16r0 invertBit:30) hexPrintString
(16r0 invertBit:31) hexPrintString
(16r0 invertBit:32) hexPrintString
(16r0 invertBit:33) hexPrintString
(16r0 invertBit:100) hexPrintString
|
-
setBit: anInteger
-
return a new integer where the specified bit is on.
Bits are counted from 1 starting with the least significant.
The method's name may be misleading: the receiver is not changed,
but a new number is returned. Should be named #withBitSet:
Usage example(s):
(16r401 setBit:2 ) hexPrintString
(16r30000000 setBit:1) hexPrintString
(16r40000000 setBit:0) hexPrintString
(16r0 setBit:29) hexPrintString
(16r0 setBit:30) hexPrintString
(16r0 setBit:31) hexPrintString
(16r0 setBit:32) hexPrintString
(16r0 setBit:33) hexPrintString
(16r0 setBit:100) hexPrintString
|
byte access
-
byteSwapped
-
lsb -> msb;
i.e. a.b.c.d -> d.c.b.a
BAD BAD BAD:
notice, the dependency on the wordLength; so do not use it!
on a 64bit machine, you'll get 16r11223344 byteSwapped -> 0x4433221100000000
on a 32bit machine, you'll get 16r11223344 byteSwapped -> 0x44332211
Usage example(s):
16r11223344 byteSwapped hexPrintString
16r44332211 byteSwapped hexPrintString
|
-
byteSwapped16
-
for 16bit values only:
lsb -> msb;
i.e. a.b -> b.a
Usage example(s):
16r1122 byteSwapped16 hexPrintString
16r2211 byteSwapped16 hexPrintString
16r332211 byteSwapped16 hexPrintString
|
-
byteSwapped32
-
for 32bit values only:
lsb -> msb;
i.e. a.b.c.d -> d.c.b.a
Any higher bits are ignored.
Usage example(s):
16r11223344 byteSwapped32 hexPrintString
16r44332211 byteSwapped32 hexPrintString
|
-
byteSwapped64
-
for 64bit values only:
lsb -> msb;
i.e. a.b.c.d.e.f.g.h -> h.g.f.e.d.c.b.a
Any higher bits are ignored.
Usage example(s):
16r11223344 byteSwapped64 hexPrintString
16r44332211 byteSwapped64 hexPrintString
|
-
digitAt: index
-
return 8 bits of the absolute value, starting at byte index.
The name 'digit' is a bit misleading: 'digit' here means byte (not decimal digit).
See also digitByteAt:
Usage example(s):
(16r12345678 digitAt:1) printStringRadix:16
(16r12345678 digitAt:3) printStringRadix:16
(16r12345678 digitAt:15) printStringRadix:16
(16r12345678 digitAt:0) printStringRadix:16
(16r12345678 digitAt:-10) printStringRadix:16
(16r12345678 digitAt:-10) printStringRadix:16
|
-
digitByteAt: index
-
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.
The name 'digit' is a bit misleading: 'digit' here means byte (not decimal digit).
Usage example(s):
(10 digitByteAt:1) printStringRadix:16
(10 digitByteAt:3) printStringRadix:16
(-10 digitByteAt:1) printStringRadix:16
(-10 digitByteAt:3) printStringRadix:16
|
-
digitBytes
-
return a byteArray filled with the receiver's magnitude bits
(8 bits of the absolute value per element),
least significant byte is first (LSB).
The name 'digit' is a bit misleading: 'digit' here means byte (not decimal digit)
Usage example(s):
16r12 digitBytes hexPrintString
16r1234 digitBytes hexPrintString
16r12345678 digitBytes hexPrintString -> '78563412'
16r12345678 digitBytes -> #[120 86 52 18]
16r-12345678 digitBytes -> #[120 86 52 18]
|
-
digitBytesMSB
-
return a byteArray filled with the receiver's bits
(8 bits of the absolute value per element),
most significant byte is first (MSB).
The name 'digit' is a bit misleading: 'digit' here means byte (not decimal digit).
Usage example(s):
16r12 digitBytesMSB hexPrintString
16r1234 digitBytesMSB hexPrintString
16r12345678 digitBytesMSB hexPrintString -> '12345678'
16r12345678 digitBytes hexPrintString -> '78563412'
|
-
digitBytesSigned
-
return a byteArray filled with the receiver's bits
the number of bytes returned depends on the underlying machine's wordsize
(i.e. 4 or 8)
The least significant byte comes first.
The name 'digit' is a bit misleading: 'digit' here means byte (not decimal digit).
Usage example(s):
16r12 digitBytesSigned -> #[18 0 0 0 0 0 0 0]
16r1234 digitBytesSigned -> #[52 18 0 0 0 0 0 0]
16r12345678 digitBytesSigned -> #[120 86 52 18 0 0 0 0]
-1 digitBytesSigned -> #[255 255 255 255 255 255 255 255]
-2 digitBytesSigned -> #[254 255 255 255 255 255 255 255]
-0x8000 digitBytesSigned -> #[0 128 255 255 255 255 255 255]
|
-
digitLength
-
return the number of bytes needed for the unsigned binary representation of the receiver.
The name 'digit' is a bit misleading: 'digit' here means byte (not decimal digit).
For negative receivers, the result is not defined by the language standard.
ST/X returns the digitLength of its absolute value.
Therefore, do not use this to find out how many bytes are needed
for a negative integer; use #signedDigitLength
Usage example(s):
16rFF00000000000000 digitLength
16r-FF00000000000000 digitLength
16r100000000 digitLength -> 5
16rFFFFFFFF digitLength -> 4
16rFF000000 digitLength -> 4
16rFF0000 digitLength -> 3
16rFF00 digitLength -> 2
16rFF digitLength -> 1
16r-100000000 digitLength -> 5 - careful
16r-FF000000 digitLength -> 4
16r-FF0000 digitLength
16r-FF00 digitLength
16r-FF digitLength
|
-
swapBytes
-
swap bytes pair-wise (i.e. of int16s) in a positive integer
i.e. a.b.c.d -> b.a.d.c.
The name may be misleading; actually a new integer is returned,
and the receiver is not modified.
Redefined here for speed.
Swapping of negative integers is undefined and therefore not supported.
This case is handled in the superclass.
Usage example(s):
-1 swapBytes hexPrintString => error
16r11223344 swapBytes hexPrintString => '22114433'
16r44332211 swapBytes hexPrintString => '33441122'
self maxVal swapBytes hexPrintString => 'FF3FFFFFFFFFFFFF'
self maxVal swapBytes swapBytes hexPrintString => '3FFFFFFFFFFFFFFF'
16r1122334455667788 swapBytes hexPrintString => '2211443366558877'
16r11223344556677889900 swapBytes hexPrintString => '22114433665588770099'
|
catching messages
-
basicAt: index
-
catch indexed access - report an error
defined here since basicAt: in Object omits the SmallInteger check.
-
basicAt: index put: anObject
-
catch indexed access - report an error
defined here since basicAt:put: in Object omits the SmallInteger check.
-
basicSize
-
return the number of indexed instvars - SmallIntegers have none.
Defined here since basicSize in Object omits the SmallInteger check.
-
size
-
return the number of indexed instvars - SmallIntegers have none.
coercing & converting
-
asCharacter
-
Return a character with the receiver as ascii (actually: unicode) value
-
asFixedDecimal
( an extension from the stx:libbasic2 package )
-
return a FixedDecimal with same value as the receiver.
Here a scale of 1 is assumed
Usage example(s):
'123' asFixedDecimal -> 123.0
'123' asFixedDecimal:2 -> 123.00
123 asFixedDecimal -> 123.0
123 asFixedDecimal:2 -> 123.00
123 asScaledDecimal -> 123.0
123 asScaledDecimal:2 -> 123.00
|
-
asFloat
-
return a Float (i.e. an IEEE double) with same value as the receiver.
Redefined for performance (machine can do it faster)
-
asLargeInteger
-
return a LargeInteger with same value as receiver.
Not for general use:
Notice, that this returns an unnormalized large int (i.e. a large with a smallint value),
which are normally not present in the system, and not handled correctly by many functions.
This exists only as a helper for some algorithms and converters
-
asShortFloat
-
return a ShortFloat with same value as receiver.
Redefined for performance (machine can do it faster)
-
asUnsignedInt
-
return an integer representing my unsigned INT value.
Notice, that the returned integer's size
depends heavily on the underlying INT size;
You will get 16rFFFFFFFF on 32bit machines,
but 16rFFFFFFFFFFFFFFFF on 64 bit machines.
So use this only for printing or certain bit operations (emulating C semantics).
Usage example(s):
-1 asUnsignedInt hexPrintString -> 'FFFFFFFFFFFFFFFF'
16r-8000 asUnsignedInt hexPrintString -> ''FFFFFFFFFFFF8000''
|
-
codePoint
-
for compatibility with Characters.
(Allows for integers to be stored into U16/U32 strings)
-
generality
-
return the generality value - see ArithmeticValue>>retry:coercing:
-
signExtended24BitValue
-
return a smallInteger from sign-extending the 24'th bit.
May be useful for communication interfaces
Usage example(s):
16rFFFFFF signExtended24BitValue
16r800000 signExtended24BitValue
16r7FFFFF signExtended24BitValue
|
-
signExtendedByteValue
-
return a smallInteger from sign-extending the 8'th bit.
May be useful for communication interfaces
Usage example(s):
16r00 signExtendedByteValue
16rFF signExtendedByteValue
16r80 signExtendedByteValue
16r7F signExtendedByteValue
|
-
signExtendedLongValue
-
return a smallInteger from sign-extending the 32'th bit.
May be useful for communication interfaces
Usage example(s):
16rFFFFFFFF signExtendedLongValue -> -1
16r80000000 signExtendedLongValue -> -2147483648
16r7FFFFFFF signExtendedLongValue -> 2147483647
|
-
signExtendedShortValue
-
return a smallInteger from sign-extending the 16'th bit.
May be useful for communication interfaces
Usage example(s):
16r10000 signExtendedShortValue
16r1FFFF signExtendedShortValue
16r0000 signExtendedShortValue
16rFFFF signExtendedShortValue
16r8000 signExtendedShortValue
16r7FFF signExtendedShortValue
|
comparing
-
< aNumber
-
return true, if the argument is greater than the receiver
Usage example(s):
^ self retry:#< coercing:aNumber
|
-
<= aNumber
-
return true, if the argument is greater or equal
-
= aNumber
-
return true, if the argument represents the same numeric value
as the receiver, false otherwise
-
> aNumber
-
return true, if the argument is less than the receiver
-
>= aNumber
-
return true, if the argument is less or equal
-
clampBetween: min and: max
-
return the receiver if it is between min .. max,
or min if it is less than min, or max if it is greater than max.
This is only a lazy-typer's helper for: ((something min:max) max:min)
Usage example(s):
1 clampBetween:2 and:5
3 clampBetween:2 and:5
6 clampBetween:2 and:5
(-5 to:5) collect:[:n | n clampBetween:-1 and:3]
|
-
hash
-
return an integer useful for hashing on value
-
hashMultiply
-
used in some squeak code to generate an alternative hash value for integers
Usage example(s):
1 hashMultiply
2 hashMultiply
3 hashMultiply
100 hashMultiply
|
-
identityHash
-
return an integer useful for hashing on identity
-
max: aNumber
-
return the receiver or the argument, whichever is greater
-
min: aNumber
-
return the receiver or the argument, whichever is smaller
-
~= aNumber
-
return true, if the arguments value is not equal to mine
copying
-
deepCopy
-
return a deep copy of myself
- reimplemented here since smallintegers are unique
-
deepCopyUsing: aDictionary postCopySelector: postCopySelector
-
return a deep copy of myself
- reimplemented here since smallintegers are unique
-
shallowCopy
-
return a shallow copy of myself
- reimplemented here since smallintegers are unique
-
simpleDeepCopy
-
return a deep copy of myself
- reimplemented here since smallintegers are unique
inspecting
-
inspectorExtraAttributes
( an extension from the stx:libtool package )
-
extra (pseudo instvar) entries to be shown in an inspector.
iteration
-
timesRepeat: aBlock
-
evaluate the argument, aBlock self times.
Reimplemented as primitive for speed
-
to: stop by: incr do: aBlock
-
reimplemented as primitive for speed
Usage example(s):
1 to:10 by:3 do:[:i | i printNewline]
|
-
to: stop do: aBlock
-
evaluate aBlock for every integer between (and including) the receiver
and the argument, stop.
Reimplemented as primitive for speed
Usage example(s):
1 to:10 do:[:i | i printNewline]
|
mathematical functions
-
bernoulli
-
returns the nth Bernoulli number.
The series runs this:
1, 1/2, 1/6, 0, -1/30, 0, 1/42, 0, -1/30, 0, 5/66, 0, -691/2730, etc
Uses a table of the first 30 even bernoulli numbers.
bernoulli(x>=62) will be computed (slow).
Used with taylor series for tan
See eg. https://www.wolframalpha.com/input/?i=bernoulli+%2864%29
Usage example(s):
0 bernoulli 1
1 bernoulli (1/2)
2 bernoulli (1/6)
3 bernoulli 0
4 bernoulli (-1/30)
5 bernoulli 0
6 bernoulli (1/42)
8 bernoulli (-1/30)
38 bernoulli (2929993913841559/6)
40 bernoulli (-261082718496449122051/13530)
41 bernoulli 0
42 bernoulli (1520097643918070802691/1806)
60 bernoulli (-1215233140483755572040304994079820246041491/56786730)
62 bernoulli (12300585434086858541953039857403386151/6)
64 bernoulli (-106783830147866529886385444979142647942017/510)
100 bernoulli (-94598037819122125295227433069493721872702841533066936133385696204311395415197247711/33330)
200 bernoulli (-498384049428333414764928632140399662108495887457206674968055822617263669621523687568865802302210999132601412697613279391058654527145340515840099290478026350382802884371712359337984274122861159800280019110197888555893671151/1366530)
1672 bernoulli
|
-
divMod: aNumber
-
return an array filled with
(self // aNumber) and (self \\ aNumber).
The returned remainder has the same sign as aNumber.
The following is always true:
(receiver // something) * something + (receiver \\ something) = receiver
Be careful with negative results: 9 // 4 -> 2, while -9 // 4 -> -3.
Especially surprising:
-1 \\ 10 -> 9 (because -(1/10) is truncated towards next smaller integer, which is -1,
and -1 multiplied by 10 gives -10, so we have to add 9 to get the original -1).
-10 \\ 3 -> 2 (because -(10/3) is truncated towards next smaller integer, which is -4,
and -4 * 4 gives -12, so we need to add 2 to get the original -10.
This is redefined here for more performance
Usage example(s):
10 // 3 -> 3
10 \\ 3 -> 1
10 // -3 -> -4
10 \\ -3 -> -2
-10 // 3 -> -4
-10 \\ 3 -> 2
-10 // -3 -> 3
-10 \\ -3 -> -1
-78 \\ 10 2
-78 // 10 -8
10 divMod:3 -> #(3 1) because 3*3 + 1 = 10
10 divMod:-3 -> #(-4 -2) because -4*-3 + (-2) = 10
-10 divMod:3 -> #(-4 2) because -4*3 + 2 = -10
-10 divMod:-3 -> #(3 -1) because -3*3 + (-1) = -10
1000000000000000000000 divMod:3 -> #(333333333333333333333 1)
1000000000000000000000 divMod:-3 -> #(-333333333333333333334 -2)
-1000000000000000000000 divMod:3 -> #(-333333333333333333334 2)
-1000000000000000000000 divMod:-3 -> #(333333333333333333333 -1)
100 factorial divMod:103
|
-
gcd: anInteger
-
return the greatest common divisor (Euclid's algorithm).
This has been redefined here for more speed since due to the
use of gcd in Fraction code, it has become time-critical for
some code. (thanx to MessageTally)
Usage example(s):
45 gcd:30 15
-45 gcd:30 15
45 gcd:-30 15
-45 gcd:-30 -15
|
-
gcd_helper: anInteger
-
same as gcd - see knuth & Integer>>gcd:
-
integerCbrt
-
return the largest integer which is less or equal to the receiver's cubic root.
For large integers, this provides better results than the float cbrt method
(which actually fails for very large numbers)
This might be needed for some number theoretic problems with large numbers
(and also in cryptography).
Uses Newton's method.
Usage example(s):
and integerCbrtWithGuess:initialGuess will find a solution with 2-3 iterations
|
Usage example(s):
Transcript showCR: e'guess: {initialGuess} result: {meAbs integerCbrtWithGuess:initialGuess}'.
|
Usage example(s):
|n cbrt|
n := 1000 factorial.
cbrt := n integerCbrt.
self assert:(cbrt cubed <= n).
self assert:((cbrt+1) cubed >= n).
[ n integerCbrt] benchmark:'integerCbrt'
333 cbrt -> 6.93130076842881
342 cbrt -> 6.99319065718087
343 cbrt -> 7.0
344 cbrt -> 7.00679612077345
333 integerCbrt -> 6
342 integerCbrt -> 6
343 integerCbrt -> 7
344 integerCbrt -> 7
8 integerCbrt -> 2
-8 integerCbrt -> -2
10239552004900 integerCbrt
10239552004900 cbrt
10239552311579 integerCbrt
10239552311579 cbrt
100000 cubed integerCbrt
100000 squared cubed integerCbrt integerSqrt
1000 factorial integerCbrt
1000 factorial asFloat cbrt
1000 factorial asLargeFloat cbrt
500 factorial cubed - 500 factorial cubed integerCbrt cubed -> 0
1000 factorial - (1000 factorial integerCbrt + 1) cubed
1000 factorial between:(1000 factorial integerCbrt cubed) and:((1000 factorial integerCbrt + 1) cubed)
|n|
n := 1000 factorial cubed.
self assert:n isPerfectCube.
[n isPerfectCube] benchmark:'cube check bigNr hit'
|n|
n := 1000 factorial cubed - 1.
self assert:n isPerfectCube not.
[n isPerfectCube] benchmark:'cube check bigNr miss'.
1 to:1000000 do:[:n |
self assert:(n integerCbrt cubed = n) == n isPerfectCube
]
1 to:10000000 do:[:n |
self assert:(n integerCbrt) == (n cbrt truncated)
]
(1 to:SmallInteger maxVal byFactor:2) do:[:n |
self assert:(n integerCbrt) == (n cbrt truncated)
]
|
-
integerCbrtWithGuess: initialGuess
-
return the largest integer which is less or equal to the receiver's cubic root.
For large integers, this provides better results than the float cbrt method
(which actually fails for very large numbers)
This might be needed for some number theoretic problems with large numbers
(and also in cryptography).
Uses Newton's method.
-
integerLog10
-
return the truncation of log10 of the receiver.
The same as (self log:10) floor.
Stupid implementation, which is used to find out the number of digits needed
to print a number/and for conversion to a LargeInteger.
Implemented that way, to allow for tiny systems (PDAs) without a Float class
(i.e. without log).
Usage example(s):
99 integerLog10
100 integerLog10
101 integerLog10
(101 log:10) floor
120 integerLog10
999 integerLog10
100 integerLog10
-1 integerLog10
0 integerLog10
Number trapInfinity:[ 0 integerLog10 ] -> -INF
Number trapImaginary:[ -1 integerLog10 ] -> (0+1i)
|
-
intlog10
-
return the truncation of log10 of the receiver.
The same as (self log:10) floor.
Stupid implementation, which is used to find out the number of digits needed
to print a number/and for conversion to a LargeInteger.
Implemented that way, to allow for tiny systems (PDAs) without a Float class
(i.e. without log).
** This is an obsolete interface - do not use it (it may vanish in future versions) **
-
log2
-
return the log2 of the receiver.
this computes a float value, except for powers of two,
Usage example(s):
1 log2 => 0.0
8 log2 => 3.0
(1<<62) log2 => 62.0
(1<<63) log2 => 63.0
(1<<64) log2 => 64.0
(1<<100) log2 => 100.0
(1<<100000) log2 => 100000.0
0 log2 => error
1 to:100 do:[:n |
self assert:( (1 << n) log2 = (1 << n) asFloat log2 )
]
|
-
raisedToInteger: exp
-
return the receiver raised to an integer exp.
The caller must ensure that the arg is actually an integer
Usage example(s):
-1 raisedToInteger:0
-1 raisedToInteger:2
-1 raisedToInteger:3
-1 raisedToInteger:2000
-1 raisedToInteger:2001
-1 isPowerOf2
2 raisedToInteger:0
2 raisedToInteger:1
2 raisedToInteger:2
-2 raisedToInteger:2
-2 raisedToInteger:3
2 raisedToInteger:10
-2 isPowerOf2
4 raisedToInteger:4
4 raisedToInteger:0
4 raisedToInteger:1
4 raisedToInteger:2
4 raisedToInteger:10
8 raisedToInteger:10
-10 to:100 do:[:a |
-10 to:100 do:[:b |
(a = 0 and:[b<0]) ifFalse:[
Transcript showCR:e'a: {a} b: {b} old: {(a perform:#raisedToInteger: inClass:ArithmeticValue withArguments:{b})} new: {(a raisedToInteger:b)}'.
self assert:(a raisedToInteger:b) = (a perform:#raisedToInteger: inClass:ArithmeticValue withArguments:{b})
]
]
]
Time microsecondsToRun:[(2 raisedTo:448)]
Time microsecondsToRun:[(2 raisedToInteger:448)]
Time microsecondsToRun:[(2 perform:#raisedToInteger: inClass:ArithmeticValue withArguments:#(448))]
Time microsecondsToRun:[(2 raisedTo:2000)]
Time microsecondsToRun:[(2 raisedTo:2001)]
Time microsecondsToRun:[(-2 raisedTo:2000)]
Time microsecondsToRun:[(-2 raisedTo:2001)]
Time microsecondsToRun:[(2 perform:#raisedToInteger: inClass:ArithmeticValue withArguments:#(2000))]
|
printing & storing
-
asBCD
-
return an integer which represents the BCD encoded value of the receiver;
that is: each digit of its decimal representation is placed into a nibble
of the result. (aka 162 -> 0x162).
The BCD hex string looks like the original decimal.
This conversion is useful for some communication protocols,
or control systems, which represent numbers this way...
Notice: the receiver should be non-negative (you'll get the BCD of the unsigned bit pattern then).
Usage example(s):
99999999 asBCD hexPrintString => '99999999'
12812345 asBCD hexPrintString => '12812345'
128123 asBCD hexPrintString => '128123'
128901 asBCD hexPrintString => '128901'
12890 asBCD hexPrintString => '12890'
1289 asBCD hexPrintString => '1289'
999 asBCD hexPrintString => '999'
256 asBCD hexPrintString => '256'
255 asBCD hexPrintString => '255'
128 asBCD hexPrintString => '128'
162 asBCD hexPrintString => '162'
55 asBCD hexPrintString => '55'
5 asBCD hexPrintString => '5'
0 asBCD hexPrintString => '0'
-1 asBCD hexPrintString => '255'
-2 asBCD hexPrintString => '254'
999999999 asBCD hexPrintString
128123456 asBCD hexPrintString
|
-
printOn: aStream
-
append my printstring (base 10) to aStream.
I use #printString instead of #printOn: as basic print mechanism.
-
printOn: aStream base: base showRadix: showRadix
-
append a string representation of the receiver in the specified numberBase to aStream
(if showRadix is true, with initial XXr)
The base argument should be between 2 and 36.
-
printString
-
return my printstring (base 10)
Usage example(s):
since this was heavily used in some applications,
here is an exception to the rule of basing printString
upon the printOn: method.
|
Usage example(s):
1234 printString
0 printString
-100 printString
Time millisecondsToRun:[ 1000000 timesRepeat:[ 123456789012 printString ]] 180 180 180 170 180
Time millisecondsToRun:[ 1000000 timesRepeat:[ 12345678 printString ]] 140 150 140 150 140
Time millisecondsToRun:[ 1000000 timesRepeat:[ 1234 printString ]] 130 140 130 130 130
Time millisecondsToRun:[ 1000000 timesRepeat:[ 12 printString ]] 130 120 120 120 110
Time millisecondsToRun:[ 1000000 timesRepeat:[ 5 printString ]] 110 110 100 110 90
Time millisecondsToRun:[ 1000000 timesRepeat:[ 0 printString ]] 60
|
-
printStringBase: base
-
return my printstring (optimized for bases 16, 10 and 8).
Print digits > 0 as uppercase chars if base > 0,
as lowercase chars if base < 0.
-
printfPrintString: formatString
-
non-standard, but sometimes useful.
return a printed representation of the receiver
as specified by formatString, which is defined by the C-function 'printf'.
No checking for string overrun - the resulting string
must be shorter than 1000 chars or else ...
Notice that a conversion may not be portable; for example,
to correctly convert an int on a 64-bit alpha, a %ld is required,
on 64bit mingw or visualc, %lld is required,
while other systems may be happy with a %d.
You cannot use lld unconditionally, because some (old) c printfs do not support it!)
Use at your own risk (if at all).
This method is NONSTANDARD and may be removed without notice;
it is provided to allow special conversions in very special situations.
WARNING: this goes directly to the C-printf function and may therefore be inherently unsafe.
Please use the printf: method, which is safe as it is completely implemented in Smalltalk.
Usage example(s):
123 printfPrintString:'%%d -> %d'
123 printfPrintString:'%%6d -> %6d'
123 printfPrintString:'%%x -> %x'
123 printfPrintString:'%%4x -> %4x'
123 printfPrintString:'%%04x -> %04x'
|
private
-
numberOfDigits: n8BitDigits
-
private: for protocol completeness with LargeIntegers.
initialize the instance to store n8BitDigits.
It is a no-op for SmallIntegers.
-
numberOfDigits: n8BitDigits sign: sign
-
private: for protocol completeness with LargeIntegers.
Returns a smallInteger with my absValue and the sign of the argument.
The method's name may be misleading: the receiver is not changed,
but a new number is returned.
special modulo arithmetic
-
plus32: aNumber
-
return the sum of the receiver and the argument, as SmallInteger.
The argument must be another SmallInteger.
If the result overflows the 32 bit range, the value modulo 16rFFFFFFFF is returned.
This is of course not always correct, but allows for C/Java behavior to be emulated.
Usage example(s):
16r7FFFFFFF + 1 => 2147483648
16r7FFFFFFF plus32: 1 => 2147483648
16rFFFFFFFF + 1 => 4294967296
16rFFFFFFFF plus32: 1 => 0
|
-
plus: aNumber
-
return the sum of the receiver and the argument, as SmallInteger.
The argument must be another SmallInteger.
If the result overflows the smallInteger range, the value modulo the
smallInteger range is returned (i.e. the low bits of the sum).
This is of course not always correct, but some code does a modulo anyway
and can therefore speed things up by not going through LargeIntegers.
Usage example(s):
5 plus:-1
5 plus:1
1 plus:-5
self maxVal plus:1
self maxVal + 1
|
-
subtract: aNumber
-
return the difference of the receiver and the argument, as SmallInteger.
The argument must be another SmallInteger.
If the result overflows the smallInteger range, the value modulo the
smallInteger range is returned (i.e. the low bits of the sum).
This is of course not always correct, but some code does a modulo anyway
and can therefore speed things up by not going through LargeIntegers.
Usage example(s):
-1 subtract:5
5 subtract:1
1 subtract:-5
self minVal subtract:1
self minVal - 1
|
-
times: aNumber
-
return the product of the receiver and the argument, as SmallInteger.
The argument must be another SmallInteger.
If the result overflows the smallInteger range, the value modulo the
smallInteger range is returned (i.e. the low bits of the product).
This is of course not always correct, but some code does a modulo anyway
and can therefore speed things up by not going through LargeIntegers.
Usage example(s):
5 times:-1 -5
5 times:1 5
self maxVal times:1 4611686018427387903
-5 times:1 -5
-5 times:-1 5
self minVal times:1 0
self minVal+1 times:1 -4611686018427387903
self maxVal * 2 9223372036854775806 16r7FFFFFFFFFFFFFFE
self maxVal times:2 4611686018427387902 16r3FFFFFFFFFFFFFFE
self maxVal-1 times:2 4611686018427387900
self maxVal-2 times:2 4611686018427387898
self maxVal-1 times:-2 -4611686018427387900
(self maxVal-1)*2 bitAnd:16r3fffffff 1073741820
|
special modulo bit operators
-
bitInvert32
-
return the value of the receiver with all bits inverted in 32bit signed int space
(changes the sign)
Usage example(s):
1 bitInvert32
16r40000000 bitInvert32
16r80000000 bitInvert32
|
-
bitRotate32: shiftCount
-
return the value of the receiver rotated by shiftCount bits,
but only within 32 bits, rotating left for positive, right for negative counts.
Rotates through the sign bit.
Useful for crypt algorithms, or to emulate C/Java semantics.
-
bitShift32: shiftCount
-
return the value of the receiver shifted by shiftCount bits,
but only within 32 bits, shifting into/out-of the sign bit.
May be useful for communication interfaces, to create ST-numbers
from a signed 32bit int value given as individual bytes,
or to emulate C/Java semantics.
Usage example(s):
1 bitShift:30 -> 1073741824
1 bitShift32:30 -> 1073741824
128 bitShift:24 -> 2147483648
128 bitShift32:24 -> -2147483648 -- shifting into the sign bit
1 bitShift:31 -> 2147483648
1 bitShift32:31 -> -2147483648 -- shifting into the sign bit
2 bitShift:30 -> 2147483648
2 bitShift32:30 -> -2147483648 -- shifting into the sign bit
- bitShift:-16 -> 2147483648
16r800000000000 bitShift32:-16 -> 0 (because onlz the low 32 bits are looked t)
-2 bitShift:-1 -> -1
-2 bitShift32:-1 -> -1
|
-
bitXor32: aNumber
-
return the xor of the receiver and the argument.
The argument must be another SmallInteger or a 4-byte LargeInteger.
If the result overflows the 32 bit range, the value modulo 16rFFFFFFFF is returned.
This is of course not always correct, but allows for C/Java behavior to be emulated.
Usage example(s):
16r7FFFFFFF bitXor: 16r80000000 4294967295
16r7FFFFFFF bitXor32: 16r80000000
|
-
unsignedBitShift32: shiftCount
-
return the value of the receiver shifted by shiftCount bits,
but only within 32 unsigned bits.
May be useful for communication interfaces, to create ST-numbers
from an unsigned 32bit int value given as individual byte,
or to emulate C/Java semantics.
Usage example(s):
128 unsignedBitShift:24
128 unsignedBitShift32:24
1 unsignedBitShift:31
1 unsignedBitShift32:31
-1 unsignedBitShift32:-1
-1 unsignedBitShift32:1
|
testing
-
between: min and: max
-
return true if the receiver is greater than or equal to the argument min
and less than or equal to the argument max.
- reimplemented here for speed
-
even
-
return true, if the receiver is even
-
isImmediate
-
return true if I am an immediate object
i.e. I am represented in the pointer itself and
no real object header/storage is used by me.
-
isPowerOf10
-
return true, if the receiver is a power of 10
Usage example(s):
0 isPowerOf10 => error
1 isPowerOf10 => true
2 isPowerOf10 => false
10 isPowerOf10 => true
100 isPowerOf10 => true
1000 isPowerOf10 => true
10000 isPowerOf10 => true
100000000 isPowerOf10 => true
100000000000000 isPowerOf10 => true
1 to:100 do:[:exp |
self assert:((10 raisedTo:exp) isPowerOf10).
self assert:((10 raisedTo:exp) isPowerOf:10).
].
|
-
isPowerOf2
-
return true, if the receiver is a power of 2
Usage example(s):
0 isPowerOf2
1 isPowerOf2
2 isPowerOf2
3 isPowerOf2
4 isPowerOf2
5 isPowerOf2
16r8000000000000000 isPowerOf2
16r8000000000000001 isPowerOf2
16r40000000 isPowerOf2
16r80000000 isPowerOf2
16r100000000 isPowerOf2
(1 bitShift:10000) isPowerOf2
10000 factorial isPowerOf2
|n| n := 10000 factorial. Time millisecondsToRun:[10000 timesRepeat:[ n isPowerOf2]]
1 to:100 do:[:exp |
self assert:((2 raisedTo:exp) isPowerOf2).
self assert:((2 raisedTo:exp) isPowerOf:2).
].
|
-
negative
-
return true, if the receiver is less than zero
reimplemented here for speed
-
nextPowerOf2
-
return the power of 2 at or above the receiver.
Useful for padding.
Notice, that for a powerOf2, the receiver is returned.
Also notice, that (because it is used for padding),
0 is returned for zero.
Usage example(s):
0 nextPowerOf2
1 nextPowerOf2
2 nextPowerOf2
3 nextPowerOf2
4 nextPowerOf2
5 nextPowerOf2
6 nextPowerOf2
7 nextPowerOf2
8 nextPowerOf2
9 nextPowerOf2
22 nextPowerOf2
32 nextPowerOf2
16rFFFF nextPowerOf2 = 16r10000
16rFFFFFFFF nextPowerOf2 = 16r100000000
16r1FFFFFFFFFFFFFFF nextPowerOf2 = 16r2000000000000000
16r3FFFFFFFFFFFFFFF nextPowerOf2 = 16r4000000000000000
16r7FFFFFFFFFFFFFFF nextPowerOf2 = 16r8000000000000000
16rFFFFFFFFFFFFFFFF nextPowerOf2 = 16r10000000000000000
10 factorial nextPowerOf2
20 factorial nextPowerOf2
100 factorial nextPowerOf2
|
-
odd
-
return true, if the receiver is odd
-
parityOdd
-
return true, if an odd number of bits are set in the receiver, false otherwise.
(i.e. true for odd parity)
Undefined for negative values (smalltalk does not require the machine to use 2's complement)
Usage example(s):
self assert:
(((0 to:255) collect:[:i | i parityOdd ifTrue:1 ifFalse:0])
asByteArray collect:[:c | c + $0 asciiValue]) asString
=
'0110100110010110100101100110100110010110011010010110100110010110100101100110100101101001100101100110100110010110100101100110100110010110011010010110100110010110011010011001011010010110011010010110100110010110100101100110100110010110011010010110100110010110'
self assert:(16r0FFFFFFF parityOdd = 16r0FFFFFFF bitCount odd).
self assert:(16r1FFFFFFF parityOdd = 16r1FFFFFFF bitCount odd).
self assert:(16r3FFFFFFF parityOdd = 16r3FFFFFFF bitCount odd).
self assert:(16r7FFFFFFF parityOdd = 16r7FFFFFFF bitCount odd).
self assert:(16rFFFFFFFF parityOdd = 16rFFFFFFFF bitCount odd).
self assert:(16r3FFFFFFFFFFFFFFF parityOdd = 16r3FFFFFFFFFFFFFFF bitCount odd).
self assert:(16r7FFFFFFFFFFFFFFF parityOdd = 16r7FFFFFFFFFFFFFFF bitCount odd).
self assert:(16rFFFFFFFFFFFFFFFF parityOdd = 16rFFFFFFFFFFFFFFFF bitCount odd).
|
-
positive
-
return true, if the receiver is greater or equal to zero (not negative)
reimplemented here for speed
-
sign
-
return the sign of the receiver (-1, 0 or 1).
reimplemented here for speed
Usage example(s):
-5 sign
-1 sign
0 sign
1 sign
5 sign
|
-
strictlyPositive
-
return true, if the receiver is greater than zero
reimplemented here for speed
Usage example(s):
0 strictlyPositive
1 strictlyPositive
-1 strictlyPositive
|
|