Back: FileStream-testing
Up: Class reference
Forward: Float class-basic
 
Top: GNU Smalltalk User's Guide
Contents: Table of Contents
Index: Class index
About: About this document

6.70 Float

Defined in namespace Smalltalk
Category: Language-Data types
My instances represent floating point numbers that have 64 bits of precision (well, less than that in precision; they are precisely the same as C's "double" datatype). Besides the standard numerical operations, I provide transcendental operations too.

6.70.1 Float class: basic  (class)
6.70.2 Float class: byte-order dependancies  (class)
6.70.3 Float class: converting  (class)
6.70.4 Float: arithmetic  (instance)
6.70.5 Float: built ins  (instance)
6.70.6 Float: coercing  (instance)
6.70.7 Float: printing  (instance)
6.70.8 Float: storing  (instance)
6.70.9 Float: testing  (instance)
6.70.10 Float: testing functionality  (instance)


6.70.1 Float class: basic

e
Returns the value of e. Hope is that it is precise enough

epsilon
Return the smallest Float x for which is 1 + x ~= 1

infinity
Return a Float that represents positive infinity. I hope that it is big enough, IEEE 8 byte floating point values (C doubles) overflow at 1e308.

largest
Return the largest normalized Float that is not infinite.

ln10
Returns the value of ln 10. Hope is that it is precise enough

log10Base2
Returns the value of log2 10. Hope is that it is precise enough

mantissaBits
Answer the number of bits in the mantissa. 1 + (2^-mantissaBits) = 1

nan
Return a Float that represents a mathematically indeterminate value (e.g. Inf - Inf, Inf / Inf)

negativeInfinity
Return a Float that represents negative infinity. I hope that it is big enough, IEEE 8 byte floating point values (C doubles) overflow at -1e308.

pi
Returns the value of pi. Hope is that it is precise enough

smallest
Return the smallest normalized Float that is not infinite.

smallestAbs
Return the smallest normalized Float that is > 0


6.70.2 Float class: byte-order dependancies

exponentByte
Answer the byte of the receiver that contains the exponent

leastSignificantMantissaByte
Answer the least significant byte in the receiver among those that contain the mantissa


6.70.3 Float class: converting

coerce: aNumber
Answer aNumber converted to a Float


6.70.4 Float: arithmetic

// aNumber
Return the integer quotient of dividing the receiver by aNumber with truncation towards negative infinity.

\\ aNumber
Return the remainder of dividing the receiver by aNumber with truncation towards negative infinity.

integerPart
Return the receiver's integer part


6.70.5 Float: built ins

* arg
Multiply the receiver and arg and answer another Number

+ arg
Sum the receiver and arg and answer another Number

- arg
Subtract arg from the receiver and answer another Number

/ arg
Divide the receiver by arg and answer another Float

< arg
Answer whether the receiver is less than arg

<= arg
Answer whether the receiver is less than or equal to arg

= arg
Answer whether the receiver is equal to arg

> arg
Answer whether the receiver is greater than arg

>= arg
Answer whether the receiver is greater than or equal to arg

arcCos
Answer the arc-cosine of the receiver

arcSin
Answer the arc-sine of the receiver

arcTan
Answer the arc-tangent of the receiver

ceiling
Answer the integer part of the receiver, truncated towards +infinity

cos
Answer the cosine of the receiver

exp
Answer 'e' (2.718281828459...) raised to the receiver

exponent
Answer the exponent of the receiver in mantissa*2^exponent representation ( |mantissa|<=1 )

floor
Answer the integer part of the receiver, truncated towards -infinity

fractionPart
Answer the fractional part of the receiver

hash
Answer an hash value for the receiver

ln
Answer the logarithm of the receiver in base 'e' (2.718281828459...)

primHash
Private - Answer an hash value for the receiver

raisedTo: aNumber
Answer the receiver raised to its aNumber power

sin
Answer the sine of the receiver

sqrt
Answer the square root of the receiver

tan
Answer the tangent of the receiver

timesTwoPower: arg
Answer the receiver multiplied by 2^arg

truncated
Truncate the receiver towards zero and answer the result

~= arg
Answer whether the receiver is not equal to arg


6.70.6 Float: coercing

asExactFraction
Convert the receiver into a fraction with optimal approximation, but with usually huge terms.

asFloat
Just defined for completeness. Return the receiver.

asFraction
Convert the receiver into a fraction with a good (but undefined) approximation

coerce: aNumber
Coerce aNumber to the receiver's class

estimatedLog
Answer an estimate of (self abs floorLog: 10)

generality
Answer the receiver's generality

unity
Coerce 1 to the receiver's class

zero
Coerce 0 to the receiver's class


6.70.7 Float: printing

printOn: aStream
Print a representation of the receiver on aStream


6.70.8 Float: storing

storeOn: aStream
Print a representation of the receiver on aStream


6.70.9 Float: testing

isFinite
Answer whether the receiver does not represent infinity, nor a NaN

isInfinite
Answer whether the receiver represents positive or negative infinity

isNaN
Answer whether the receiver represents a NaN

negative
Answer whether the receiver is negative

positive
Answer whether the receiver is positive

sign
Answer 1 if the receiver is greater than 0, -1 if less than 0, else 0.

strictlyPositive
Answer whether the receiver is > 0


6.70.10 Float: testing functionality

isFloat
Answer `true'.




This document was generated on May, 12 2002 using texi2html