base-3.0.1.0: Basic librariesSource codeContentsIndex
GHC.Float
Portabilitynon-portable (GHC Extensions)
Stabilityinternal
Maintainercvs-ghc@haskell.org
Description
The types Float and Double, and the classes Floating and RealFloat.
Synopsis
class Fractional a => Floating a where
pi :: a
exp :: a -> a
sqrt :: a -> a
log :: a -> a
(**) :: a -> a -> a
logBase :: a -> a -> a
sin :: a -> a
tan :: a -> a
cos :: a -> a
asin :: a -> a
atan :: a -> a
acos :: a -> a
sinh :: a -> a
tanh :: a -> a
cosh :: a -> a
asinh :: a -> a
atanh :: a -> a
acosh :: a -> a
class (RealFrac a, Floating a) => RealFloat a where
floatRadix :: a -> Integer
floatDigits :: a -> Int
floatRange :: a -> (Int, Int)
decodeFloat :: a -> (Integer, Int)
encodeFloat :: Integer -> Int -> a
exponent :: a -> Int
significand :: a -> a
scaleFloat :: Int -> a -> a
isNaN :: a -> Bool
isInfinite :: a -> Bool
isDenormalized :: a -> Bool
isNegativeZero :: a -> Bool
isIEEE :: a -> Bool
atan2 :: a -> a -> a
data Float = F# Float#
data Double = D# Double#
showFloat :: RealFloat a => a -> ShowS
data FFFormat
= FFExponent
| FFFixed
| FFGeneric
formatRealFloat :: RealFloat a => FFFormat -> Maybe Int -> a -> String
roundTo :: Int -> Int -> [Int] -> (Int, [Int])
floatToDigits :: RealFloat a => Integer -> a -> ([Int], Int)
fromRat :: RealFloat a => Rational -> a
fromRat' :: RealFloat a => Rational -> a
scaleRat :: Rational -> Int -> Rational -> Rational -> Int -> Rational -> (Rational, Int)
maxExpt :: Int
minExpt :: Int
expt :: Integer -> Int -> Integer
expts :: Array Int Integer
integerLogBase :: Integer -> Integer -> Int
minusFloat :: Float -> Float -> Float
timesFloat :: Float -> Float -> Float
divideFloat :: Float -> Float -> Float
plusFloat :: Float -> Float -> Float
negateFloat :: Float -> Float
geFloat :: Float -> Float -> Bool
eqFloat :: Float -> Float -> Bool
neFloat :: Float -> Float -> Bool
ltFloat :: Float -> Float -> Bool
leFloat :: Float -> Float -> Bool
gtFloat :: Float -> Float -> Bool
float2Int :: Float -> Int
int2Float :: Int -> Float
logFloat :: Float -> Float
sqrtFloat :: Float -> Float
expFloat :: Float -> Float
cosFloat :: Float -> Float
tanFloat :: Float -> Float
sinFloat :: Float -> Float
acosFloat :: Float -> Float
atanFloat :: Float -> Float
asinFloat :: Float -> Float
coshFloat :: Float -> Float
tanhFloat :: Float -> Float
sinhFloat :: Float -> Float
powerFloat :: Float -> Float -> Float
minusDouble :: Double -> Double -> Double
timesDouble :: Double -> Double -> Double
divideDouble :: Double -> Double -> Double
plusDouble :: Double -> Double -> Double
negateDouble :: Double -> Double
geDouble :: Double -> Double -> Bool
eqDouble :: Double -> Double -> Bool
neDouble :: Double -> Double -> Bool
leDouble :: Double -> Double -> Bool
ltDouble :: Double -> Double -> Bool
gtDouble :: Double -> Double -> Bool
double2Int :: Double -> Int
int2Double :: Int -> Double
double2Float :: Double -> Float
float2Double :: Float -> Double
logDouble :: Double -> Double
sqrtDouble :: Double -> Double
expDouble :: Double -> Double
cosDouble :: Double -> Double
tanDouble :: Double -> Double
sinDouble :: Double -> Double
acosDouble :: Double -> Double
atanDouble :: Double -> Double
asinDouble :: Double -> Double
coshDouble :: Double -> Double
tanhDouble :: Double -> Double
sinhDouble :: Double -> Double
powerDouble :: Double -> Double -> Double
encodeFloat# :: Int# -> ByteArray# -> Int -> Float
int_encodeFloat# :: Int# -> Int -> Float
isFloatNaN :: Float -> Int
isFloatInfinite :: Float -> Int
isFloatDenormalized :: Float -> Int
isFloatNegativeZero :: Float -> Int
encodeDouble# :: Int# -> ByteArray# -> Int -> Double
int_encodeDouble# :: Int# -> Int -> Double
isDoubleNaN :: Double -> Int
isDoubleInfinite :: Double -> Int
isDoubleDenormalized :: Double -> Int
isDoubleNegativeZero :: Double -> Int
Documentation
class Fractional a => Floating a whereSource

Trigonometric and hyperbolic functions and related functions.

Minimal complete definition: pi, exp, log, sin, cos, sinh, cosh, asin, acos, atan, asinh, acosh and atanh

Methods
pi :: aSource
exp :: a -> aSource
sqrt :: a -> aSource
log :: a -> aSource
(**) :: a -> a -> aSource
logBase :: a -> a -> aSource
sin :: a -> aSource
tan :: a -> aSource
cos :: a -> aSource
asin :: a -> aSource
atan :: a -> aSource
acos :: a -> aSource
sinh :: a -> aSource
tanh :: a -> aSource
cosh :: a -> aSource
asinh :: a -> aSource
atanh :: a -> aSource
acosh :: a -> aSource
show/hide Instances
class (RealFrac a, Floating a) => RealFloat a whereSource

Efficient, machine-independent access to the components of a floating-point number.

Minimal complete definition: all except exponent, significand, scaleFloat and atan2

Methods
floatRadix :: a -> IntegerSource
a constant function, returning the radix of the representation (often 2)
floatDigits :: a -> IntSource
a constant function, returning the number of digits of floatRadix in the significand
floatRange :: a -> (Int, Int)Source
a constant function, returning the lowest and highest values the exponent may assume
decodeFloat :: a -> (Integer, Int)Source
The function decodeFloat applied to a real floating-point number returns the significand expressed as an Integer and an appropriately scaled exponent (an Int). If decodeFloat x yields (m,n), then x is equal in value to m*b^^n, where b is the floating-point radix, and furthermore, either m and n are both zero or else b^(d-1) <= m < b^d, where d is the value of floatDigits x. In particular, decodeFloat 0 = (0,0).
encodeFloat :: Integer -> Int -> aSource
encodeFloat performs the inverse of decodeFloat
exponent :: a -> IntSource
the second component of decodeFloat.
significand :: a -> aSource
the first component of decodeFloat, scaled to lie in the open interval (-1,1)
scaleFloat :: Int -> a -> aSource
multiplies a floating-point number by an integer power of the radix
isNaN :: a -> BoolSource
True if the argument is an IEEE "not-a-number" (NaN) value
isInfinite :: a -> BoolSource
True if the argument is an IEEE infinity or negative infinity
isDenormalized :: a -> BoolSource
True if the argument is too small to be represented in normalized format
isNegativeZero :: a -> BoolSource
True if the argument is an IEEE negative zero
isIEEE :: a -> BoolSource
True if the argument is an IEEE floating point number
atan2 :: a -> a -> aSource
a version of arctangent taking two real floating-point arguments. For real floating x and y, atan2 y x computes the angle (from the positive x-axis) of the vector from the origin to the point (x,y). atan2 y x returns a value in the range [-pi, pi]. It follows the Common Lisp semantics for the origin when signed zeroes are supported. atan2 y 1, with y in a type that is RealFloat, should return the same value as atan y. A default definition of atan2 is provided, but implementors can provide a more accurate implementation.
show/hide Instances
data Float Source
Single-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE single-precision type.
Constructors
F# Float#
show/hide Instances
data Double Source
Double-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE double-precision type.
Constructors
D# Double#
show/hide Instances
showFloat :: RealFloat a => a -> ShowSSource
Show a signed RealFloat value to full precision using standard decimal notation for arguments whose absolute value lies between 0.1 and 9,999,999, and scientific notation otherwise.
data FFFormat Source
Constructors
FFExponent
FFFixed
FFGeneric
formatRealFloat :: RealFloat a => FFFormat -> Maybe Int -> a -> StringSource
roundTo :: Int -> Int -> [Int] -> (Int, [Int])Source
floatToDigits :: RealFloat a => Integer -> a -> ([Int], Int)Source

floatToDigits takes a base and a non-negative RealFloat number, and returns a list of digits and an exponent. In particular, if x>=0, and

 floatToDigits base x = ([d1,d2,...,dn], e)

then

  1. n >= 1
  2. x = 0.d1d2...dn * (base**e)
  3. 0 <= di <= base-1
fromRat :: RealFloat a => Rational -> aSource
Converts a Rational value into any type in class RealFloat.
fromRat' :: RealFloat a => Rational -> aSource
scaleRat :: Rational -> Int -> Rational -> Rational -> Int -> Rational -> (Rational, Int)Source
maxExpt :: IntSource
minExpt :: IntSource
expt :: Integer -> Int -> IntegerSource
expts :: Array Int IntegerSource
integerLogBase :: Integer -> Integer -> IntSource
minusFloat :: Float -> Float -> FloatSource
timesFloat :: Float -> Float -> FloatSource
divideFloat :: Float -> Float -> FloatSource
plusFloat :: Float -> Float -> FloatSource
negateFloat :: Float -> FloatSource
geFloat :: Float -> Float -> BoolSource
eqFloat :: Float -> Float -> BoolSource
neFloat :: Float -> Float -> BoolSource
ltFloat :: Float -> Float -> BoolSource
leFloat :: Float -> Float -> BoolSource
gtFloat :: Float -> Float -> BoolSource
float2Int :: Float -> IntSource
int2Float :: Int -> FloatSource
logFloat :: Float -> FloatSource
sqrtFloat :: Float -> FloatSource
expFloat :: Float -> FloatSource
cosFloat :: Float -> FloatSource
tanFloat :: Float -> FloatSource
sinFloat :: Float -> FloatSource
acosFloat :: Float -> FloatSource
atanFloat :: Float -> FloatSource
asinFloat :: Float -> FloatSource
coshFloat :: Float -> FloatSource
tanhFloat :: Float -> FloatSource
sinhFloat :: Float -> FloatSource
powerFloat :: Float -> Float -> FloatSource
minusDouble :: Double -> Double -> DoubleSource
timesDouble :: Double -> Double -> DoubleSource
divideDouble :: Double -> Double -> DoubleSource
plusDouble :: Double -> Double -> DoubleSource
negateDouble :: Double -> DoubleSource
geDouble :: Double -> Double -> BoolSource
eqDouble :: Double -> Double -> BoolSource
neDouble :: Double -> Double -> BoolSource
leDouble :: Double -> Double -> BoolSource
ltDouble :: Double -> Double -> BoolSource
gtDouble :: Double -> Double -> BoolSource
double2Int :: Double -> IntSource
int2Double :: Int -> DoubleSource
double2Float :: Double -> FloatSource
float2Double :: Float -> DoubleSource
logDouble :: Double -> DoubleSource
sqrtDouble :: Double -> DoubleSource
expDouble :: Double -> DoubleSource
cosDouble :: Double -> DoubleSource
tanDouble :: Double -> DoubleSource
sinDouble :: Double -> DoubleSource
acosDouble :: Double -> DoubleSource
atanDouble :: Double -> DoubleSource
asinDouble :: Double -> DoubleSource
coshDouble :: Double -> DoubleSource
tanhDouble :: Double -> DoubleSource
sinhDouble :: Double -> DoubleSource
powerDouble :: Double -> Double -> DoubleSource
encodeFloat# :: Int# -> ByteArray# -> Int -> FloatSource
int_encodeFloat# :: Int# -> Int -> FloatSource
isFloatNaN :: Float -> IntSource
isFloatInfinite :: Float -> IntSource
isFloatDenormalized :: Float -> IntSource
isFloatNegativeZero :: Float -> IntSource
encodeDouble# :: Int# -> ByteArray# -> Int -> DoubleSource
int_encodeDouble# :: Int# -> Int -> DoubleSource
isDoubleNaN :: Double -> IntSource
isDoubleInfinite :: Double -> IntSource
isDoubleDenormalized :: Double -> IntSource
isDoubleNegativeZero :: Double -> IntSource
Produced by Haddock version 2.0.0.0