|
|
6.76 Integer
- Defined in namespace Smalltalk
- Category: Language-Data types
- I am the integer class of the GNU Smalltalk system. My instances can
represent signed 30 bit integers and are as efficient as possible.
6.76.1 Integer class: converting
- coerce: aNumber
- Answer aNumber converted to a kind of Integer
6.76.2 Integer class: getting limits
- bits
- Answer the number of bits (excluding the sign) that can be represented directly in an object pointer
- largest
- Answer the largest integer represented directly in an object pointer
- smallest
- Answer the smallest integer represented directly in an object pointer
6.76.3 Integer class: testing
- isIdentity
- Answer whether x = y implies x == y for instances of the receiver
6.76.4 Integer: accessing
- denominator
- Answer `1'.
- numerator
- Answer the receiver.
6.76.5 Integer: bit operators
- allMask: anInteger
- True if all 1 bits in anInteger are 1 in the receiver
- anyMask: anInteger
- True if any 1 bits in anInteger are 1 in the receiver
- bitAt: index
- Answer the index-th bit of the receiver (LSB: index = 1
- bitClear: aMask
- Answer an Integer equal to the receiver, except that all the bits that are set in aMask are cleared.
- bitInvert
- Return the 1's complement of the bits of the receiver
- clearBit: index
- Clear the index-th bit of the receiver and answer a new Integer
- highBit
- Return the index of the highest order 1 bit of the receiver
- isBitSet: index
- Answer whether the index-th bit of the receiver is set
- noMask: anInteger
- True if no 1 bits in anInteger are 1 in the receiver
- setBit: index
- Set the index-th bit of the receiver and answer a new Integer
6.76.6 Integer: Coercion methods (heh heh heh)
- asCharacter
- Return self as an ascii character
- ceiling
- Return the receiver - it's already truncated
- coerce: aNumber
- Coerce aNumber to the receiver's class
- floor
- Return the receiver - it's already truncated
- generality
- Return the receiver's generality
- rounded
- Return the receiver - it's already truncated
- truncated
- Return the receiver - it's already truncated
- unity
- Coerce 1 to the receiver's class
- zero
- Coerce 0 to the receiver's class
6.76.7 Integer: converting
- asFraction
- Return the receiver converted to a fraction
6.76.8 Integer: extension
- alignTo: anInteger
- Answer the receiver, truncated to the first higher or equal multiple of anInteger (which must be a power of two)
6.76.9 Integer: Math methods
- estimatedLog
- Answer an estimate of (self abs floorLog: 10)
- even
- Return whether the receiver is even
- factorial
- Return the receiver's factorial
- floorLog: radix
- return (self log: radix) floor. Optimized to answer an integer.
- gcd: anInteger
- Return the greatest common divisor (Euclid's algorithm) between the receiver and anInteger
- lcm: anInteger
- Return the least common multiple between the receiver and anInteger
- odd
- Return whether the receiver is odd
6.76.10 Integer: Misc math operators
- hash
- Answer an hash value for the receiver
6.76.11 Integer: Other iterators
- timesRepeat: aBlock
- Evaluate aBlock a number of times equal to the receiver's value. Compiled in-line for no argument aBlocks without temporaries, and therefore not overridable.
6.76.12 Integer: printing
- printOn: aStream
- Print on aStream the base 10 representation of the receiver
- printOn: aStream base: b
- Print on aStream the base b representation of the receiver
- printString: baseInteger
- Return the base b representation of the receiver
- radix: baseInteger
- Return the base b representation of the receiver, with BBr in front of it
- storeOn: aStream base: b
- Print on aStream Smalltalk code compiling to the receiver, represented in base b
6.76.13 Integer: storing
- storeOn: aStream
- Print on aStream the base 10 representation of the receiver
6.76.14 Integer: testing functionality
- isInteger
- Answer `true'.
- isRational
- Answer whether the receiver is rational - true
- isSmallInteger
- Answer `true'.
|