Copyright | (c) The University of Glasgow 1994-2002 Portions obtained from hbc (c) Lennart Augusstson |
---|---|
License | see libraries/base/LICENSE |
Maintainer | cvs-ghc@haskell.org |
Stability | internal |
Portability | non-portable (GHC Extensions) |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
GHC.Float
Description
Synopsis
- class Fractional a => Floating a where
- 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 FFFormat
- = FFExponent
- | FFFixed
- | FFGeneric
- clamp :: Int -> Int -> Int
- showFloat :: RealFloat a => a -> ShowS
- floatToDigits :: RealFloat a => Integer -> a -> ([Int], Int)
- fromRat :: RealFloat a => Rational -> a
- formatRealFloat :: RealFloat a => FFFormat -> Maybe Int -> a -> String
- log1mexpOrd :: (Ord a, Floating a) => a -> a
- plusFloat :: Float -> Float -> Float
- minusFloat :: Float -> Float -> Float
- negateFloat :: Float -> Float
- timesFloat :: Float -> Float -> Float
- fabsFloat :: Float -> Float
- integerToFloat# :: Integer -> Float#
- integerToBinaryFloat' :: RealFloat a => Integer -> a
- naturalToFloat# :: Natural -> Float#
- divideFloat :: Float -> Float -> Float
- rationalToFloat :: Integer -> Integer -> Float
- fromRat'' :: RealFloat a => Int -> Int -> Integer -> Integer -> a
- properFractionFloat :: Integral b => Float -> (b, Float)
- truncateFloat :: Integral b => Float -> b
- roundFloat :: Integral b => Float -> b
- floorFloat :: Integral b => Float -> b
- ceilingFloat :: Integral b => Float -> b
- expFloat :: Float -> Float
- logFloat :: Float -> Float
- sqrtFloat :: Float -> Float
- sinFloat :: Float -> Float
- cosFloat :: Float -> Float
- tanFloat :: Float -> Float
- asinFloat :: Float -> Float
- acosFloat :: Float -> Float
- atanFloat :: Float -> Float
- sinhFloat :: Float -> Float
- coshFloat :: Float -> Float
- tanhFloat :: Float -> Float
- powerFloat :: Float -> Float -> Float
- asinhFloat :: Float -> Float
- acoshFloat :: Float -> Float
- atanhFloat :: Float -> Float
- log1pFloat :: Float -> Float
- expm1Float :: Float -> Float
- isFloatFinite :: Float -> Int
- isFloatNaN :: Float -> Int
- isFloatInfinite :: Float -> Int
- isFloatDenormalized :: Float -> Int
- isFloatNegativeZero :: Float -> Int
- showSignedFloat :: RealFloat a => (a -> ShowS) -> Int -> a -> ShowS
- plusDouble :: Double -> Double -> Double
- minusDouble :: Double -> Double -> Double
- negateDouble :: Double -> Double
- timesDouble :: Double -> Double -> Double
- fabsDouble :: Double -> Double
- integerToDouble# :: Integer -> Double#
- naturalToDouble# :: Natural -> Double#
- divideDouble :: Double -> Double -> Double
- rationalToDouble :: Integer -> Integer -> Double
- expDouble :: Double -> Double
- logDouble :: Double -> Double
- sqrtDouble :: Double -> Double
- sinDouble :: Double -> Double
- cosDouble :: Double -> Double
- tanDouble :: Double -> Double
- asinDouble :: Double -> Double
- acosDouble :: Double -> Double
- atanDouble :: Double -> Double
- sinhDouble :: Double -> Double
- coshDouble :: Double -> Double
- tanhDouble :: Double -> Double
- powerDouble :: Double -> Double -> Double
- asinhDouble :: Double -> Double
- acoshDouble :: Double -> Double
- atanhDouble :: Double -> Double
- log1pDouble :: Double -> Double
- expm1Double :: Double -> Double
- properFractionDouble :: Integral b => Double -> (b, Double)
- truncateDouble :: Integral b => Double -> b
- roundDouble :: Integral b => Double -> b
- ceilingDouble :: Integral b => Double -> b
- floorDouble :: Integral b => Double -> b
- isDoubleFinite :: Double -> Int
- isDoubleNaN :: Double -> Int
- isDoubleInfinite :: Double -> Int
- isDoubleDenormalized :: Double -> Int
- isDoubleNegativeZero :: Double -> Int
- formatRealFloatAlt :: RealFloat a => FFFormat -> Maybe Int -> Bool -> a -> String
- roundTo :: Int -> Int -> [Int] -> (Int, [Int])
- expt :: Integer -> Int -> Integer
- roundingMode# :: Integer -> Int# -> Int#
- fromRat' :: RealFloat a => Rational -> a
- minExpt :: Int
- maxExpt :: Int
- expts :: Array Int Integer
- maxExpt10 :: Int
- expts10 :: Array Int Integer
- gtFloat :: Float -> Float -> Bool
- geFloat :: Float -> Float -> Bool
- ltFloat :: Float -> Float -> Bool
- leFloat :: Float -> Float -> Bool
- gtDouble :: Double -> Double -> Bool
- geDouble :: Double -> Double -> Bool
- leDouble :: Double -> Double -> Bool
- ltDouble :: Double -> Double -> Bool
- double2Float :: Double -> Float
- float2Double :: Float -> Double
- word2Double :: Word -> Double
- word2Float :: Word -> Float
- castWord32ToFloat :: Word32 -> Float
- stgWord32ToFloat :: Word32# -> Float#
- castFloatToWord32 :: Float -> Word32
- stgFloatToWord32 :: Float# -> Word32#
- castWord64ToDouble :: Word64 -> Double
- stgWord64ToDouble :: Word64# -> Double#
- castDoubleToWord64 :: Double -> Word64
- stgDoubleToWord64 :: Double# -> Word64#
- data Float = F# Float#
- data Double = D# Double#
- data Float# :: TYPE 'FloatRep
- data Double# :: TYPE 'DoubleRep
- double2Int :: Double -> Int
- int2Double :: Int -> Double
- float2Int :: Float -> Int
- int2Float :: Int -> Float
- eqFloat :: Float -> Float -> Bool
- eqDouble :: Double -> Double -> Bool
Documentation
class Fractional a => Floating a where Source #
Trigonometric and hyperbolic functions and related functions.
The Haskell Report defines no laws for Floating
. However, (
, +
)(
and *
)exp
are customarily expected to define an exponential field and have
the following properties:
exp (a + b)
=exp a * exp b
exp (fromInteger 0)
=fromInteger 1
Minimal complete definition
pi, exp, log, sin, cos, asin, acos, atan, sinh, cosh, asinh, acosh, atanh
Methods
(**) :: a -> a -> a infixr 8 Source #
logBase :: a -> a -> a Source #
computes log1p
x
, but provides more precise
results for small (absolute) values of log
(1 + x)x
if possible.
Since: base-4.9.0.0
computes expm1
x
, but provides more precise
results for small (absolute) values of exp
x - 1x
if possible.
Since: base-4.9.0.0
computes log1pexp
x
, but provides more
precise results if possible.log
(1 + exp
x)
Examples:
- if
x
is a large negative number,
will be imprecise for the reasons given inlog
(1 +exp
x)log1p
. - if
is close toexp
x-1
,
will be imprecise for the reasons given inlog
(1 +exp
x)expm1
.
Since: base-4.9.0.0
computes log1mexp
x
, but provides more
precise results if possible.log
(1 - exp
x)
Examples:
- if
x
is a large negative number,
will be imprecise for the reasons given inlog
(1 -exp
x)log1p
. - if
is close toexp
x1
,
will be imprecise for the reasons given inlog
(1 -exp
x)expm1
.
Since: base-4.9.0.0
Instances
Instances details
Instance details
Defined in Foreign.C.Types
Methods
exp :: CDouble -> CDouble Source #
log :: CDouble -> CDouble Source #
sqrt :: CDouble -> CDouble Source #
(**) :: CDouble -> CDouble -> CDouble Source #
logBase :: CDouble -> CDouble -> CDouble Source #
sin :: CDouble -> CDouble Source #
cos :: CDouble -> CDouble Source #
tan :: CDouble -> CDouble Source #
asin :: CDouble -> CDouble Source #
acos :: CDouble -> CDouble Source #
atan :: CDouble -> CDouble Source #
sinh :: CDouble -> CDouble Source #
cosh :: CDouble -> CDouble Source #
tanh :: CDouble -> CDouble Source #
asinh :: CDouble -> CDouble Source #
acosh :: CDouble -> CDouble Source #
atanh :: CDouble -> CDouble Source #
log1p :: CDouble -> CDouble Source #
expm1 :: CDouble -> CDouble Source #
Instance details
Defined in Foreign.C.Types
Methods
exp :: CFloat -> CFloat Source #
log :: CFloat -> CFloat Source #
sqrt :: CFloat -> CFloat Source #
(**) :: CFloat -> CFloat -> CFloat Source #
logBase :: CFloat -> CFloat -> CFloat Source #
sin :: CFloat -> CFloat Source #
cos :: CFloat -> CFloat Source #
tan :: CFloat -> CFloat Source #
asin :: CFloat -> CFloat Source #
acos :: CFloat -> CFloat Source #
atan :: CFloat -> CFloat Source #
sinh :: CFloat -> CFloat Source #
cosh :: CFloat -> CFloat Source #
tanh :: CFloat -> CFloat Source #
asinh :: CFloat -> CFloat Source #
acosh :: CFloat -> CFloat Source #
atanh :: CFloat -> CFloat Source #
log1p :: CFloat -> CFloat Source #
expm1 :: CFloat -> CFloat Source #
Instance details
Defined in GHC.Float
Methods
exp :: Double -> Double Source #
log :: Double -> Double Source #
sqrt :: Double -> Double Source #
(**) :: Double -> Double -> Double Source #
logBase :: Double -> Double -> Double Source #
sin :: Double -> Double Source #
cos :: Double -> Double Source #
tan :: Double -> Double Source #
asin :: Double -> Double Source #
acos :: Double -> Double Source #
atan :: Double -> Double Source #
sinh :: Double -> Double Source #
cosh :: Double -> Double Source #
tanh :: Double -> Double Source #
asinh :: Double -> Double Source #
acosh :: Double -> Double Source #
atanh :: Double -> Double Source #
log1p :: Double -> Double Source #
expm1 :: Double -> Double Source #
Instance details
Defined in GHC.Float
Methods
exp :: Float -> Float Source #
log :: Float -> Float Source #
sqrt :: Float -> Float Source #
(**) :: Float -> Float -> Float Source #
logBase :: Float -> Float -> Float Source #
sin :: Float -> Float Source #
cos :: Float -> Float Source #
tan :: Float -> Float Source #
asin :: Float -> Float Source #
acos :: Float -> Float Source #
atan :: Float -> Float Source #
sinh :: Float -> Float Source #
cosh :: Float -> Float Source #
tanh :: Float -> Float Source #
asinh :: Float -> Float Source #
acosh :: Float -> Float Source #
atanh :: Float -> Float Source #
log1p :: Float -> Float Source #
expm1 :: Float -> Float Source #
Instance details
Defined in Data.Complex
Methods
exp :: Complex a -> Complex a Source #
log :: Complex a -> Complex a Source #
sqrt :: Complex a -> Complex a Source #
(**) :: Complex a -> Complex a -> Complex a Source #
logBase :: Complex a -> Complex a -> Complex a Source #
sin :: Complex a -> Complex a Source #
cos :: Complex a -> Complex a Source #
tan :: Complex a -> Complex a Source #
asin :: Complex a -> Complex a Source #
acos :: Complex a -> Complex a Source #
atan :: Complex a -> Complex a Source #
sinh :: Complex a -> Complex a Source #
cosh :: Complex a -> Complex a Source #
tanh :: Complex a -> Complex a Source #
asinh :: Complex a -> Complex a Source #
acosh :: Complex a -> Complex a Source #
atanh :: Complex a -> Complex a Source #
log1p :: Complex a -> Complex a Source #
expm1 :: Complex a -> Complex a Source #
Instance details
Defined in Data.Functor.Identity
Methods
exp :: Identity a -> Identity a Source #
log :: Identity a -> Identity a Source #
sqrt :: Identity a -> Identity a Source #
(**) :: Identity a -> Identity a -> Identity a Source #
logBase :: Identity a -> Identity a -> Identity a Source #
sin :: Identity a -> Identity a Source #
cos :: Identity a -> Identity a Source #
tan :: Identity a -> Identity a Source #
asin :: Identity a -> Identity a Source #
acos :: Identity a -> Identity a Source #
atan :: Identity a -> Identity a Source #
sinh :: Identity a -> Identity a Source #
cosh :: Identity a -> Identity a Source #
tanh :: Identity a -> Identity a Source #
asinh :: Identity a -> Identity a Source #
acosh :: Identity a -> Identity a Source #
atanh :: Identity a -> Identity a Source #
log1p :: Identity a -> Identity a Source #
expm1 :: Identity a -> Identity a Source #
Instance details
Defined in Data.Ord
Methods
exp :: Down a -> Down a Source #
log :: Down a -> Down a Source #
sqrt :: Down a -> Down a Source #
(**) :: Down a -> Down a -> Down a Source #
logBase :: Down a -> Down a -> Down a Source #
sin :: Down a -> Down a Source #
cos :: Down a -> Down a Source #
tan :: Down a -> Down a Source #
asin :: Down a -> Down a Source #
acos :: Down a -> Down a Source #
atan :: Down a -> Down a Source #
sinh :: Down a -> Down a Source #
cosh :: Down a -> Down a Source #
tanh :: Down a -> Down a Source #
asinh :: Down a -> Down a Source #
acosh :: Down a -> Down a Source #
atanh :: Down a -> Down a Source #
log1p :: Down a -> Down a Source #
expm1 :: Down a -> Down a Source #
Instance details
Defined in Data.Functor.Contravariant
Methods
exp :: Op a b -> Op a b Source #
log :: Op a b -> Op a b Source #
sqrt :: Op a b -> Op a b Source #
(**) :: Op a b -> Op a b -> Op a b Source #
logBase :: Op a b -> Op a b -> Op a b Source #
sin :: Op a b -> Op a b Source #
cos :: Op a b -> Op a b Source #
tan :: Op a b -> Op a b Source #
asin :: Op a b -> Op a b Source #
acos :: Op a b -> Op a b Source #
atan :: Op a b -> Op a b Source #
sinh :: Op a b -> Op a b Source #
cosh :: Op a b -> Op a b Source #
tanh :: Op a b -> Op a b Source #
asinh :: Op a b -> Op a b Source #
acosh :: Op a b -> Op a b Source #
atanh :: Op a b -> Op a b Source #
log1p :: Op a b -> Op a b Source #
expm1 :: Op a b -> Op a b Source #
Instance details
Defined in Data.Functor.Const
Methods
exp :: Const a b -> Const a b Source #
log :: Const a b -> Const a b Source #
sqrt :: Const a b -> Const a b Source #
(**) :: Const a b -> Const a b -> Const a b Source #
logBase :: Const a b -> Const a b -> Const a b Source #
sin :: Const a b -> Const a b Source #
cos :: Const a b -> Const a b Source #
tan :: Const a b -> Const a b Source #
asin :: Const a b -> Const a b Source #
acos :: Const a b -> Const a b Source #
atan :: Const a b -> Const a b Source #
sinh :: Const a b -> Const a b Source #
cosh :: Const a b -> Const a b Source #
tanh :: Const a b -> Const a b Source #
asinh :: Const a b -> Const a b Source #
acosh :: Const a b -> Const a b Source #
atanh :: Const a b -> Const a b Source #
log1p :: Const a b -> Const a b Source #
expm1 :: Const a b -> Const a b Source #
class (RealFrac a, Floating a) => RealFloat a where Source #
Efficient, machine-independent access to the components of a floating-point number.
Minimal complete definition
floatRadix, floatDigits, floatRange, decodeFloat, encodeFloat, isNaN, isInfinite, isDenormalized, isNegativeZero, isIEEE
Methods
floatRadix :: a -> Integer Source #
a constant function, returning the radix of the representation
(often 2
)
floatDigits :: a -> Int Source #
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
yields decodeFloat
x(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) <=
, where abs
m < b^dd
is
the value of
.
In particular, floatDigits
x
. If the type
contains a negative zero, also decodeFloat
0 = (0,0)
.
The result of decodeFloat
(-0.0) = (0,0)
is unspecified if either of
decodeFloat
x
or isNaN
x
is isInfinite
xTrue
.
encodeFloat :: Integer -> Int -> a Source #
encodeFloat
performs the inverse of decodeFloat
in the
sense that for finite x
with the exception of -0.0
,
.
uncurry
encodeFloat
(decodeFloat
x) = x
is one of the two closest representable
floating-point numbers to encodeFloat
m nm*b^^n
(or ±Infinity
if overflow
occurs); usually the closer, but if m
contains too many bits,
the result may be rounded in the wrong direction.
exponent
corresponds to the second component of decodeFloat
.
and for finite nonzero exponent
0 = 0x
,
.
If exponent
x = snd (decodeFloat
x) + floatDigits
xx
is a finite floating-point number, it is equal in value to
, where significand
x * b ^^ exponent
xb
is the
floating-point radix.
The behaviour is unspecified on infinite or NaN
values.
significand :: a -> a Source #
The first component of decodeFloat
, scaled to lie in the open
interval (-1
,1
), either 0.0
or of absolute value >= 1/b
,
where b
is the floating-point radix.
The behaviour is unspecified on infinite or NaN
values.
scaleFloat :: Int -> a -> a Source #
multiplies a floating-point number by an integer power of the radix
True
if the argument is an IEEE "not-a-number" (NaN) value
isInfinite :: a -> Bool Source #
True
if the argument is an IEEE infinity or negative infinity
isDenormalized :: a -> Bool Source #
True
if the argument is too small to be represented in
normalized format
isNegativeZero :: a -> Bool Source #
True
if the argument is an IEEE negative zero
True
if the argument is an IEEE floating point number
a version of arctangent taking two real floating-point arguments.
For real floating x
and y
,
computes the angle
(from the positive x-axis) of the vector from the origin to the
point atan2
y x(x,y)
.
returns a value in the range [atan2
y x-pi
,
pi
]. It follows the Common Lisp semantics for the origin when
signed zeroes are supported.
, with atan2
y 1y
in a type
that is RealFloat
, should return the same value as
.
A default definition of atan
yatan2
is provided, but implementors
can provide a more accurate implementation.
Instances
Instances details
Instance details
Defined in Foreign.C.Types
Methods
floatRadix :: CDouble -> Integer Source #
floatDigits :: CDouble -> Int Source #
floatRange :: CDouble -> (Int, Int) Source #
decodeFloat :: CDouble -> (Integer, Int) Source #
encodeFloat :: Integer -> Int -> CDouble Source #
exponent :: CDouble -> Int Source #
significand :: CDouble -> CDouble Source #
scaleFloat :: Int -> CDouble -> CDouble Source #
isNaN :: CDouble -> Bool Source #
isInfinite :: CDouble -> Bool Source #
isDenormalized :: CDouble -> Bool Source #
isNegativeZero :: CDouble -> Bool Source #
Instance details
Defined in Foreign.C.Types
Methods
floatRadix :: CFloat -> Integer Source #
floatDigits :: CFloat -> Int Source #
floatRange :: CFloat -> (Int, Int) Source #
decodeFloat :: CFloat -> (Integer, Int) Source #
encodeFloat :: Integer -> Int -> CFloat Source #
exponent :: CFloat -> Int Source #
significand :: CFloat -> CFloat Source #
scaleFloat :: Int -> CFloat -> CFloat Source #
isNaN :: CFloat -> Bool Source #
isInfinite :: CFloat -> Bool Source #
isDenormalized :: CFloat -> Bool Source #
isNegativeZero :: CFloat -> Bool Source #
Instance details
Defined in GHC.Float
Methods
floatRadix :: Double -> Integer Source #
floatDigits :: Double -> Int Source #
floatRange :: Double -> (Int, Int) Source #
decodeFloat :: Double -> (Integer, Int) Source #
encodeFloat :: Integer -> Int -> Double Source #
exponent :: Double -> Int Source #
significand :: Double -> Double Source #
scaleFloat :: Int -> Double -> Double Source #
isNaN :: Double -> Bool Source #
isInfinite :: Double -> Bool Source #
isDenormalized :: Double -> Bool Source #
isNegativeZero :: Double -> Bool Source #
Instance details
Defined in GHC.Float
Methods
floatRadix :: Float -> Integer Source #
floatDigits :: Float -> Int Source #
floatRange :: Float -> (Int, Int) Source #
decodeFloat :: Float -> (Integer, Int) Source #
encodeFloat :: Integer -> Int -> Float Source #
exponent :: Float -> Int Source #
significand :: Float -> Float Source #
scaleFloat :: Int -> Float -> Float Source #
isNaN :: Float -> Bool Source #
isInfinite :: Float -> Bool Source #
isDenormalized :: Float -> Bool Source #
isNegativeZero :: Float -> Bool Source #
Instance details
Defined in Data.Functor.Identity
Methods
floatRadix :: Identity a -> Integer Source #
floatDigits :: Identity a -> Int Source #
floatRange :: Identity a -> (Int, Int) Source #
decodeFloat :: Identity a -> (Integer, Int) Source #
encodeFloat :: Integer -> Int -> Identity a Source #
exponent :: Identity a -> Int Source #
significand :: Identity a -> Identity a Source #
scaleFloat :: Int -> Identity a -> Identity a Source #
isNaN :: Identity a -> Bool Source #
isInfinite :: Identity a -> Bool Source #
isDenormalized :: Identity a -> Bool Source #
isNegativeZero :: Identity a -> Bool Source #
Instance details
Defined in Data.Ord
Methods
floatRadix :: Down a -> Integer Source #
floatDigits :: Down a -> Int Source #
floatRange :: Down a -> (Int, Int) Source #
decodeFloat :: Down a -> (Integer, Int) Source #
encodeFloat :: Integer -> Int -> Down a Source #
exponent :: Down a -> Int Source #
significand :: Down a -> Down a Source #
scaleFloat :: Int -> Down a -> Down a Source #
isNaN :: Down a -> Bool Source #
isInfinite :: Down a -> Bool Source #
isDenormalized :: Down a -> Bool Source #
isNegativeZero :: Down a -> Bool Source #
Instance details
Defined in Data.Functor.Const
Methods
floatRadix :: Const a b -> Integer Source #
floatDigits :: Const a b -> Int Source #
floatRange :: Const a b -> (Int, Int) Source #
decodeFloat :: Const a b -> (Integer, Int) Source #
encodeFloat :: Integer -> Int -> Const a b Source #
exponent :: Const a b -> Int Source #
significand :: Const a b -> Const a b Source #
scaleFloat :: Int -> Const a b -> Const a b Source #
isNaN :: Const a b -> Bool Source #
isInfinite :: Const a b -> Bool Source #
isDenormalized :: Const a b -> Bool Source #
isNegativeZero :: Const a b -> Bool Source #
clamp :: Int -> Int -> Int Source #
Used to prevent exponent over/underflow when encoding floating point numbers. This is also the same as
\(x,y) -> max (-x) (min x y)
Example
Expand
>>>
clamp (-10) 5
10
showFloat :: RealFloat a => a -> ShowS Source #
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.
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
n >= 1
x = 0.d1d2...dn * (base**e)
0 <= di <= base-1
log1mexpOrd :: (Ord a, Floating a) => a -> a Source #
negateFloat :: Float -> Float Source #
integerToFloat# :: Integer -> Float# Source #
Convert an Integer to a Float#
integerToBinaryFloat' :: RealFloat a => Integer -> a Source #
Converts a positive integer to a floating-point value.
The value nearest to the argument will be returned. If there are two such values, the one with an even significand will be returned (i.e. IEEE roundTiesToEven).
The argument must be strictly positive, and floatRadix (undefined :: a)
must be 2.
naturalToFloat# :: Natural -> Float# Source #
Convert a Natural to a Float#
truncateFloat :: Integral b => Float -> b Source #
roundFloat :: Integral b => Float -> b Source #
floorFloat :: Integral b => Float -> b Source #
ceilingFloat :: Integral b => Float -> b Source #
asinhFloat :: Float -> Float Source #
acoshFloat :: Float -> Float Source #
atanhFloat :: Float -> Float Source #
log1pFloat :: Float -> Float Source #
expm1Float :: Float -> Float Source #
isFloatFinite :: Float -> Int Source #
isFloatNaN :: Float -> Int Source #
isFloatInfinite :: Float -> Int Source #
isFloatDenormalized :: Float -> Int Source #
isFloatNegativeZero :: Float -> Int Source #
negateDouble :: Double -> Double Source #
fabsDouble :: Double -> Double Source #
integerToDouble# :: Integer -> Double# Source #
Convert an Integer to a Double#
naturalToDouble# :: Natural -> Double# Source #
Encode a Natural (mantissa) into a Double#
sqrtDouble :: Double -> Double Source #
asinDouble :: Double -> Double Source #
acosDouble :: Double -> Double Source #
atanDouble :: Double -> Double Source #
sinhDouble :: Double -> Double Source #
coshDouble :: Double -> Double Source #
tanhDouble :: Double -> Double Source #
asinhDouble :: Double -> Double Source #
acoshDouble :: Double -> Double Source #
atanhDouble :: Double -> Double Source #
log1pDouble :: Double -> Double Source #
expm1Double :: Double -> Double Source #
truncateDouble :: Integral b => Double -> b Source #
roundDouble :: Integral b => Double -> b Source #
ceilingDouble :: Integral b => Double -> b Source #
floorDouble :: Integral b => Double -> b Source #
isDoubleFinite :: Double -> Int Source #
isDoubleNaN :: Double -> Int Source #
isDoubleInfinite :: Double -> Int Source #
isDoubleDenormalized :: Double -> Int Source #
isDoubleNegativeZero :: Double -> Int Source #
double2Float :: Double -> Float Source #
float2Double :: Float -> Double Source #
word2Double :: Word -> Double Source #
word2Float :: Word -> Float Source #
castWord32ToFloat :: Word32 -> Float Source #
does a bit-for-bit copy from an integral value
to a floating-point value.castWord32ToFloat
w
Since: base-4.10.0.0
stgWord32ToFloat :: Word32# -> Float# Source #
castFloatToWord32 :: Float -> Word32 Source #
does a bit-for-bit copy from a floating-point value
to an integral value.castFloatToWord32
f
Since: base-4.10.0.0
stgFloatToWord32 :: Float# -> Word32# Source #
castWord64ToDouble :: Word64 -> Double Source #
does a bit-for-bit copy from an integral value
to a floating-point value.castWord64ToDouble
w
Since: base-4.10.0.0
stgWord64ToDouble :: Word64# -> Double# Source #
castDoubleToWord64 :: Double -> Word64 Source #
does a bit-for-bit copy from a floating-point value
to an integral value.castFloatToWord64
f
Since: base-4.10.0.0
stgDoubleToWord64 :: Double# -> Word64# 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.
Instances
Instances details
Instance details
Defined in Data.Data
Methods
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Float -> c Float Source #
gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Float Source #
toConstr :: Float -> Constr Source #
dataTypeOf :: Float -> DataType Source #
dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Float) Source #
dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Float) Source #
gmapT :: (forall b. Data b => b -> b) -> Float -> Float Source #
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Float -> r Source #
gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Float -> r Source #
gmapQ :: (forall d. Data d => d -> u) -> Float -> [u] Source #
gmapQi :: Int -> (forall d. Data d => d -> u) -> Float -> u Source #
gmapM :: Monad m => (forall d. Data d => d -> m d) -> Float -> m Float Source #
gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Float -> m Float Source #
gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Float -> m Float Source #
Instance details
Defined in Foreign.Storable
Methods
sizeOf :: Float -> Int Source #
alignment :: Float -> Int Source #
peekElemOff :: Ptr Float -> Int -> IO Float Source #
pokeElemOff :: Ptr Float -> Int -> Float -> IO () Source #
peekByteOff :: Ptr b -> Int -> IO Float Source #
pokeByteOff :: Ptr b -> Int -> Float -> IO () Source #
Instance details
Defined in GHC.Float
Methods
succ :: Float -> Float Source #
pred :: Float -> Float Source #
toEnum :: Int -> Float Source #
fromEnum :: Float -> Int Source #
enumFrom :: Float -> [Float] Source #
enumFromThen :: Float -> Float -> [Float] Source #
enumFromTo :: Float -> Float -> [Float] Source #
enumFromThenTo :: Float -> Float -> Float -> [Float] Source #
Instance details
Defined in GHC.Float
Methods
exp :: Float -> Float Source #
log :: Float -> Float Source #
sqrt :: Float -> Float Source #
(**) :: Float -> Float -> Float Source #
logBase :: Float -> Float -> Float Source #
sin :: Float -> Float Source #
cos :: Float -> Float Source #
tan :: Float -> Float Source #
asin :: Float -> Float Source #
acos :: Float -> Float Source #
atan :: Float -> Float Source #
sinh :: Float -> Float Source #
cosh :: Float -> Float Source #
tanh :: Float -> Float Source #
asinh :: Float -> Float Source #
acosh :: Float -> Float Source #
atanh :: Float -> Float Source #
log1p :: Float -> Float Source #
expm1 :: Float -> Float Source #
Instance details
Defined in GHC.Float
Methods
floatRadix :: Float -> Integer Source #
floatDigits :: Float -> Int Source #
floatRange :: Float -> (Int, Int) Source #
decodeFloat :: Float -> (Integer, Int) Source #
encodeFloat :: Integer -> Int -> Float Source #
exponent :: Float -> Int Source #
significand :: Float -> Float Source #
scaleFloat :: Int -> Float -> Float Source #
isNaN :: Float -> Bool Source #
isInfinite :: Float -> Bool Source #
isDenormalized :: Float -> Bool Source #
isNegativeZero :: Float -> Bool Source #
Note that due to the presence of NaN
, not all elements of Float
have an
additive inverse.
>>>
0/0 + (negate 0/0 :: Float)
NaN
Also note that due to the presence of -0, Float
's Num
instance doesn't
have an additive identity
>>>
0 + (-0 :: Float)
0.0
Since: base-2.1
Instance details
Defined in GHC.Float
Note that due to the presence of NaN
, not all elements of Float
have an
multiplicative inverse.
>>>
0/0 * (recip 0/0 :: Float)
NaN
Since: base-2.1
Instance details
Defined in Text.Printf
Methods
formatArg :: Float -> FieldFormatter Source #
parseFormat :: Float -> ModifierParser Source #
Note that due to the presence of NaN
, Float
's Eq
instance does not
satisfy reflexivity.
>>>
0/0 == (0/0 :: Float)
False
Also note that Float
's Eq
instance does not satisfy extensionality:
>>>
0 == (-0 :: Float)
True>>>
recip 0 == recip (-0 :: Float)
False
Note that due to the presence of NaN
, Float
's Ord
instance does not
satisfy reflexivity.
>>>
0/0 <= (0/0 :: Float)
False
Also note that, due to the same, Ord
's operator interactions are not
respected by Float
's instance:
>>>
(0/0 :: Float) > 1
False>>>
compare (0/0 :: Float) 1
GT
Instance details
Defined in GHC.Classes
Instance details
Defined in Data.Foldable
Methods
fold :: Monoid m => UFloat m -> m Source #
foldMap :: Monoid m => (a -> m) -> UFloat a -> m Source #
foldMap' :: Monoid m => (a -> m) -> UFloat a -> m Source #
foldr :: (a -> b -> b) -> b -> UFloat a -> b Source #
foldr' :: (a -> b -> b) -> b -> UFloat a -> b Source #
foldl :: (b -> a -> b) -> b -> UFloat a -> b Source #
foldl' :: (b -> a -> b) -> b -> UFloat a -> b Source #
foldr1 :: (a -> a -> a) -> UFloat a -> a Source #
foldl1 :: (a -> a -> a) -> UFloat a -> a Source #
toList :: UFloat a -> [a] Source #
null :: UFloat a -> Bool Source #
length :: UFloat a -> Int Source #
elem :: Eq a => a -> UFloat a -> Bool Source #
maximum :: Ord a => UFloat a -> a Source #
minimum :: Ord a => UFloat a -> a Source #
Instance details
Defined in Data.Traversable
Instance details
Defined in GHC.Generics
Methods
compare :: URec Float p -> URec Float p -> Ordering Source #
(<) :: URec Float p -> URec Float p -> Bool Source #
(<=) :: URec Float p -> URec Float p -> Bool Source #
(>) :: URec Float p -> URec Float p -> Bool Source #
(>=) :: URec Float p -> URec Float p -> Bool Source #
max :: URec Float p -> URec Float p -> URec Float p Source #
min :: URec Float p -> URec Float p -> URec Float p Source #
Instance details
Defined in GHC.Generics
Instance details
Defined in GHC.Generics
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.
Instances
Instances details
Instance details
Defined in Data.Data
Methods
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Double -> c Double Source #
gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Double Source #
toConstr :: Double -> Constr Source #
dataTypeOf :: Double -> DataType Source #
dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Double) Source #
dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Double) Source #
gmapT :: (forall b. Data b => b -> b) -> Double -> Double Source #
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Double -> r Source #
gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Double -> r Source #
gmapQ :: (forall d. Data d => d -> u) -> Double -> [u] Source #
gmapQi :: Int -> (forall d. Data d => d -> u) -> Double -> u Source #
gmapM :: Monad m => (forall d. Data d => d -> m d) -> Double -> m Double Source #
gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Double -> m Double Source #
gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Double -> m Double Source #
Instance details
Defined in Foreign.Storable
Methods
sizeOf :: Double -> Int Source #
alignment :: Double -> Int Source #
peekElemOff :: Ptr Double -> Int -> IO Double Source #
pokeElemOff :: Ptr Double -> Int -> Double -> IO () Source #
peekByteOff :: Ptr b -> Int -> IO Double Source #
pokeByteOff :: Ptr b -> Int -> Double -> IO () Source #
Instance details
Defined in GHC.Float
Methods
succ :: Double -> Double Source #
pred :: Double -> Double Source #
toEnum :: Int -> Double Source #
fromEnum :: Double -> Int Source #
enumFrom :: Double -> [Double] Source #
enumFromThen :: Double -> Double -> [Double] Source #
enumFromTo :: Double -> Double -> [Double] Source #
enumFromThenTo :: Double -> Double -> Double -> [Double] Source #
Instance details
Defined in GHC.Float
Methods
exp :: Double -> Double Source #
log :: Double -> Double Source #
sqrt :: Double -> Double Source #
(**) :: Double -> Double -> Double Source #
logBase :: Double -> Double -> Double Source #
sin :: Double -> Double Source #
cos :: Double -> Double Source #
tan :: Double -> Double Source #
asin :: Double -> Double Source #
acos :: Double -> Double Source #
atan :: Double -> Double Source #
sinh :: Double -> Double Source #
cosh :: Double -> Double Source #
tanh :: Double -> Double Source #
asinh :: Double -> Double Source #
acosh :: Double -> Double Source #
atanh :: Double -> Double Source #
log1p :: Double -> Double Source #
expm1 :: Double -> Double Source #
Instance details
Defined in GHC.Float
Methods
floatRadix :: Double -> Integer Source #
floatDigits :: Double -> Int Source #
floatRange :: Double -> (Int, Int) Source #
decodeFloat :: Double -> (Integer, Int) Source #
encodeFloat :: Integer -> Int -> Double Source #
exponent :: Double -> Int Source #
significand :: Double -> Double Source #
scaleFloat :: Int -> Double -> Double Source #
isNaN :: Double -> Bool Source #
isInfinite :: Double -> Bool Source #
isDenormalized :: Double -> Bool Source #
isNegativeZero :: Double -> Bool Source #
Note that due to the presence of NaN
, not all elements of Double
have an
additive inverse.
>>>
0/0 + (negate 0/0 :: Double)
NaN
Also note that due to the presence of -0, Double
's Num
instance doesn't
have an additive identity
>>>
0 + (-0 :: Double)
0.0
Since: base-2.1
Instance details
Defined in GHC.Float
Note that due to the presence of NaN
, not all elements of Double
have an
multiplicative inverse.
>>>
0/0 * (recip 0/0 :: Double)
NaN
Since: base-2.1
Instance details
Defined in Text.Printf
Methods
formatArg :: Double -> FieldFormatter Source #
parseFormat :: Double -> ModifierParser Source #
Note that due to the presence of NaN
, Double
's Eq
instance does not
satisfy reflexivity.
>>>
0/0 == (0/0 :: Double)
False
Also note that Double
's Eq
instance does not satisfy substitutivity:
>>>
0 == (-0 :: Double)
True>>>
recip 0 == recip (-0 :: Double)
False
Note that due to the presence of NaN
, Double
's Ord
instance does not
satisfy reflexivity.
>>>
0/0 <= (0/0 :: Double)
False
Also note that, due to the same, Ord
's operator interactions are not
respected by Double
's instance:
>>>
(0/0 :: Double) > 1
False>>>
compare (0/0 :: Double) 1
GT
Instance details
Defined in GHC.Classes
Instance details
Defined in Data.Foldable
Methods
fold :: Monoid m => UDouble m -> m Source #
foldMap :: Monoid m => (a -> m) -> UDouble a -> m Source #
foldMap' :: Monoid m => (a -> m) -> UDouble a -> m Source #
foldr :: (a -> b -> b) -> b -> UDouble a -> b Source #
foldr' :: (a -> b -> b) -> b -> UDouble a -> b Source #
foldl :: (b -> a -> b) -> b -> UDouble a -> b Source #
foldl' :: (b -> a -> b) -> b -> UDouble a -> b Source #
foldr1 :: (a -> a -> a) -> UDouble a -> a Source #
foldl1 :: (a -> a -> a) -> UDouble a -> a Source #
toList :: UDouble a -> [a] Source #
null :: UDouble a -> Bool Source #
length :: UDouble a -> Int Source #
elem :: Eq a => a -> UDouble a -> Bool Source #
maximum :: Ord a => UDouble a -> a Source #
minimum :: Ord a => UDouble a -> a Source #
Instance details
Defined in Data.Traversable
Instance details
Defined in GHC.Generics
Methods
compare :: URec Double p -> URec Double p -> Ordering Source #
(<) :: URec Double p -> URec Double p -> Bool Source #
(<=) :: URec Double p -> URec Double p -> Bool Source #
(>) :: URec Double p -> URec Double p -> Bool Source #
(>=) :: URec Double p -> URec Double p -> Bool Source #
max :: URec Double p -> URec Double p -> URec Double p Source #
min :: URec Double p -> URec Double p -> URec Double p Source #
Instance details
Defined in GHC.Generics
Instance details
Defined in GHC.Generics
double2Int :: Double -> Int Source #
int2Double :: Int -> Double Source #
Monomorphic equality operators
See GHC.Classes#matching_overloaded_methods_in_rules
Orphan instances
Instance details
Methods
succ :: Double -> Double Source #
pred :: Double -> Double Source #
toEnum :: Int -> Double Source #
fromEnum :: Double -> Int Source #
enumFrom :: Double -> [Double] Source #
enumFromThen :: Double -> Double -> [Double] Source #
enumFromTo :: Double -> Double -> [Double] Source #
enumFromThenTo :: Double -> Double -> Double -> [Double] Source #
Instance details
Methods
succ :: Float -> Float Source #
pred :: Float -> Float Source #
toEnum :: Int -> Float Source #
fromEnum :: Float -> Int Source #
enumFrom :: Float -> [Float] Source #
enumFromThen :: Float -> Float -> [Float] Source #
enumFromTo :: Float -> Float -> [Float] Source #
enumFromThenTo :: Float -> Float -> Float -> [Float] Source #
Note that due to the presence of NaN
, not all elements of Double
have an
additive inverse.
>>>
0/0 + (negate 0/0 :: Double)
NaN
Also note that due to the presence of -0, Double
's Num
instance doesn't
have an additive identity
>>>
0 + (-0 :: Double)
0.0
Since: base-2.1
Note that due to the presence of NaN
, not all elements of Float
have an
additive inverse.
>>>
0/0 + (negate 0/0 :: Float)
NaN
Also note that due to the presence of -0, Float
's Num
instance doesn't
have an additive identity
>>>
0 + (-0 :: Float)
0.0
Since: base-2.1
Note that due to the presence of NaN
, not all elements of Double
have an
multiplicative inverse.
>>>
0/0 * (recip 0/0 :: Double)
NaN
Since: base-2.1
Note that due to the presence of NaN
, not all elements of Float
have an
multiplicative inverse.
>>>
0/0 * (recip 0/0 :: Float)
NaN
Since: base-2.1
Instance details
Methods
toRational :: Double -> Rational Source #
Instance details
Methods
toRational :: Float -> Rational Source #