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
- integerToFloat# :: Integer -> Float#
- integerToDouble# :: Integer -> Double#
- naturalToFloat# :: Natural -> Float#
- naturalToDouble# :: Natural -> Double#
- rationalToFloat :: Integer -> Integer -> Float
- rationalToDouble :: Integer -> Integer -> Double
- 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
- acosDouble :: Double -> Double
- acosFloat :: Float -> Float
- acoshDouble :: Double -> Double
- acoshFloat :: Float -> Float
- asinDouble :: Double -> Double
- asinFloat :: Float -> Float
- asinhDouble :: Double -> Double
- asinhFloat :: Float -> Float
- atanDouble :: Double -> Double
- atanFloat :: Float -> Float
- atanhDouble :: Double -> Double
- atanhFloat :: Float -> Float
- castDoubleToWord64 :: Double -> Word64
- castFloatToWord32 :: Float -> Word32
- castWord32ToFloat :: Word32 -> Float
- castWord64ToDouble :: Word64 -> Double
- clamp :: Int -> Int -> Int
- cosDouble :: Double -> Double
- cosFloat :: Float -> Float
- coshDouble :: Double -> Double
- coshFloat :: Float -> Float
- divideDouble :: Double -> Double -> Double
- divideFloat :: Float -> Float -> Float
- double2Float :: Double -> Float
- expDouble :: Double -> Double
- expFloat :: Float -> Float
- expm1Double :: Double -> Double
- expm1Float :: Float -> Float
- expt :: Integer -> Int -> Integer
- expts :: Array Int Integer
- expts10 :: Array Int Integer
- fabsDouble :: Double -> Double
- fabsFloat :: Float -> Float
- float2Double :: Float -> Double
- floatToDigits :: RealFloat a => Integer -> a -> ([Int], Int)
- formatRealFloat :: RealFloat a => FFFormat -> Maybe Int -> a -> String
- formatRealFloatAlt :: RealFloat a => FFFormat -> Maybe Int -> Bool -> a -> String
- fromRat :: RealFloat a => Rational -> a
- fromRat' :: RealFloat a => Rational -> a
- fromRat'' :: RealFloat a => Int -> Int -> Integer -> Integer -> a
- geDouble :: Double -> Double -> Bool
- geFloat :: Float -> Float -> Bool
- gtDouble :: Double -> Double -> Bool
- gtFloat :: Float -> Float -> Bool
- integerToBinaryFloat' :: RealFloat a => Integer -> a
- isDoubleDenormalized :: Double -> Int
- isDoubleFinite :: Double -> Int
- isDoubleInfinite :: Double -> Int
- isDoubleNaN :: Double -> Int
- isDoubleNegativeZero :: Double -> Int
- isFloatDenormalized :: Float -> Int
- isFloatFinite :: Float -> Int
- isFloatInfinite :: Float -> Int
- isFloatNaN :: Float -> Int
- isFloatNegativeZero :: Float -> Int
- leDouble :: Double -> Double -> Bool
- leFloat :: Float -> Float -> Bool
- log1mexpOrd :: (Ord a, Floating a) => a -> a
- log1pDouble :: Double -> Double
- log1pFloat :: Float -> Float
- logDouble :: Double -> Double
- logFloat :: Float -> Float
- ltDouble :: Double -> Double -> Bool
- ltFloat :: Float -> Float -> Bool
- maxExpt :: Int
- maxExpt10 :: Int
- minExpt :: Int
- minusDouble :: Double -> Double -> Double
- minusFloat :: Float -> Float -> Float
- negateDouble :: Double -> Double
- negateFloat :: Float -> Float
- plusDouble :: Double -> Double -> Double
- plusFloat :: Float -> Float -> Float
- powerDouble :: Double -> Double -> Double
- powerFloat :: Float -> Float -> Float
- roundTo :: Int -> Int -> [Int] -> (Int, [Int])
- roundingMode# :: Integer -> Int# -> Int#
- showFloat :: RealFloat a => a -> ShowS
- showSignedFloat :: RealFloat a => (a -> ShowS) -> Int -> a -> ShowS
- sinDouble :: Double -> Double
- sinFloat :: Float -> Float
- sinhDouble :: Double -> Double
- sinhFloat :: Float -> Float
- sqrtDouble :: Double -> Double
- sqrtFloat :: Float -> Float
- stgDoubleToWord64 :: Double# -> Word64#
- stgFloatToWord32 :: Float# -> Word32#
- stgWord32ToFloat :: Word32# -> Float#
- stgWord64ToDouble :: Word64# -> Double#
- tanDouble :: Double -> Double
- tanFloat :: Float -> Float
- tanhDouble :: Double -> Double
- tanhFloat :: Float -> Float
- timesDouble :: Double -> Double -> Double
- timesFloat :: Float -> Float -> Float
- word2Double :: Word -> Double
- word2Float :: Word -> Float
- data FFFormat
- 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
integerToFloat# :: Integer -> Float# #
Convert an Integer to a Float#
integerToDouble# :: Integer -> Double# #
Convert an Integer to a Double#
naturalToFloat# :: Natural -> Float# #
Convert a Natural to a Float#
naturalToDouble# :: Natural -> Double# #
Encode a Natural (mantissa) into a Double#
rationalToFloat :: Integer -> Integer -> Float #
rationalToDouble :: Integer -> Integer -> Double #
class Fractional a => Floating a where #
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 #
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
Instances
class (RealFrac a, Floating a) => RealFloat a where #
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 #
a constant function, returning the radix of the representation
(often 2
)
floatDigits :: a -> Int #
a constant function, returning the number of digits of
floatRadix
in the significand
floatRange :: a -> (Int, Int) #
a constant function, returning the lowest and highest values the exponent may assume
decodeFloat :: a -> (Integer, Int) #
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 #
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 #
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 #
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 #
True
if the argument is an IEEE infinity or negative infinity
isDenormalized :: a -> Bool #
True
if the argument is too small to be represented in
normalized format
isNegativeZero :: a -> Bool #
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
acosDouble :: Double -> Double #
acoshDouble :: Double -> Double #
acoshFloat :: Float -> Float #
asinDouble :: Double -> Double #
asinhDouble :: Double -> Double #
asinhFloat :: Float -> Float #
atanDouble :: Double -> Double #
atanhDouble :: Double -> Double #
atanhFloat :: Float -> Float #
castDoubleToWord64 :: Double -> Word64 #
does a bit-for-bit copy from a floating-point value
to an integral value.castFloatToWord64
f
Since: base-4.11.0.0
castFloatToWord32 :: Float -> Word32 #
does a bit-for-bit copy from a floating-point value
to an integral value.castFloatToWord32
f
Since: base-4.11.0.0
castWord32ToFloat :: Word32 -> Float #
does a bit-for-bit copy from an integral value
to a floating-point value.castWord32ToFloat
w
Since: base-4.11.0.0
castWord64ToDouble :: Word64 -> Double #
does a bit-for-bit copy from an integral value
to a floating-point value.castWord64ToDouble
w
Since: base-4.11.0.0
coshDouble :: Double -> Double #
divideDouble :: Double -> Double -> Double #
divideFloat :: Float -> Float -> Float #
double2Float :: Double -> Float #
expm1Double :: Double -> Double #
expm1Float :: Float -> Float #
fabsDouble :: Double -> Double #
float2Double :: Float -> Double #
floatToDigits :: RealFloat a => Integer -> a -> ([Int], Int) #
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
integerToBinaryFloat' :: RealFloat a => Integer -> a #
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.
isDoubleDenormalized :: Double -> Int #
isDoubleFinite :: Double -> Int #
isDoubleInfinite :: Double -> Int #
isDoubleNaN :: Double -> Int #
isDoubleNegativeZero :: Double -> Int #
isFloatDenormalized :: Float -> Int #
isFloatFinite :: Float -> Int #
isFloatInfinite :: Float -> Int #
isFloatNaN :: Float -> Int #
isFloatNegativeZero :: Float -> Int #
log1mexpOrd :: (Ord a, Floating a) => a -> a #
log1pDouble :: Double -> Double #
log1pFloat :: Float -> Float #
minusDouble :: Double -> Double -> Double #
minusFloat :: Float -> Float -> Float #
negateDouble :: Double -> Double #
negateFloat :: Float -> Float #
plusDouble :: Double -> Double -> Double #
powerDouble :: Double -> Double -> Double #
powerFloat :: Float -> Float -> Float #
roundingMode# :: Integer -> Int# -> Int# #
showFloat :: RealFloat a => a -> ShowS #
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.
sinhDouble :: Double -> Double #
sqrtDouble :: Double -> Double #
stgDoubleToWord64 :: Double# -> Word64# #
stgFloatToWord32 :: Float# -> Word32# #
stgWord32ToFloat :: Word32# -> Float# #
stgWord64ToDouble :: Word64# -> Double# #
tanhDouble :: Double -> Double #
timesDouble :: Double -> Double -> Double #
timesFloat :: Float -> Float -> Float #
word2Double :: Word -> Double #
word2Float :: Word -> Float #
Constructors
FFExponent | |
FFFixed | |
FFGeneric |
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
Data Float # | Since: base-4.0.0.0 |
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 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Float # dataTypeOf :: Float -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Float) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Float) # gmapT :: (forall b. Data b => b -> b) -> Float -> Float # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Float -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Float -> r # gmapQ :: (forall d. Data d => d -> u) -> Float -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Float -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Float -> m Float # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Float -> m Float # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Float -> m Float # | |
Storable Float # | Since: base-2.1 |
Enum Float # | Since: base-2.1 |
Floating Float # | Since: base-2.1 |
RealFloat Float # | Since: base-2.1 |
Defined in GHC.Float Methods floatRadix :: Float -> Integer # floatDigits :: Float -> Int # floatRange :: Float -> (Int, Int) # decodeFloat :: Float -> (Integer, Int) # encodeFloat :: Integer -> Int -> Float # significand :: Float -> Float # scaleFloat :: Int -> Float -> Float # isInfinite :: Float -> Bool # isDenormalized :: Float -> Bool # isNegativeZero :: Float -> Bool # | |
Num Float # | Note that due to the presence of
Also note that due to the presence of -0,
Since: base-2.1 |
Read Float # | Since: base-2.1 |
Fractional Float # | Note that due to the presence of
Since: base-2.1 |
Real Float # | Since: base-2.1 |
Defined in GHC.Float Methods toRational :: Float -> Rational # | |
RealFrac Float # | Since: base-2.1 |
Show Float # | Since: base-2.1 |
PrintfArg Float # | Since: base-2.1 |
Defined in Text.Printf | |
Eq Float | Note that due to the presence of
Also note that
|
Ord Float | Note that due to the presence of
Also note that, due to the same,
|
Defined in GHC.Classes | |
Generic1 (URec Float :: k -> Type) # | |
Foldable (UFloat :: TYPE LiftedRep -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Foldable Methods fold :: Monoid m => UFloat m -> m # foldMap :: Monoid m => (a -> m) -> UFloat a -> m # foldMap' :: Monoid m => (a -> m) -> UFloat a -> m # foldr :: (a -> b -> b) -> b -> UFloat a -> b # foldr' :: (a -> b -> b) -> b -> UFloat a -> b # foldl :: (b -> a -> b) -> b -> UFloat a -> b # foldl' :: (b -> a -> b) -> b -> UFloat a -> b # foldr1 :: (a -> a -> a) -> UFloat a -> a # foldl1 :: (a -> a -> a) -> UFloat a -> a # elem :: Eq a => a -> UFloat a -> Bool # maximum :: Ord a => UFloat a -> a # minimum :: Ord a => UFloat a -> a # | |
Traversable (UFloat :: Type -> Type) # | Since: base-4.9.0.0 |
Functor (URec Float :: TYPE LiftedRep -> Type) # | Since: base-4.9.0.0 |
Generic (URec Float p) # | |
Show (URec Float p) # | |
Eq (URec Float p) # | |
Ord (URec Float p) # | |
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 # | |
data URec Float (p :: k) # | Used for marking occurrences of Since: base-4.9.0.0 |
type Rep1 (URec Float :: k -> Type) # | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
type Rep (URec Float p) # | |
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
Data Double # | Since: base-4.0.0.0 |
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 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Double # toConstr :: Double -> Constr # dataTypeOf :: Double -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Double) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Double) # gmapT :: (forall b. Data b => b -> b) -> Double -> Double # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Double -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Double -> r # gmapQ :: (forall d. Data d => d -> u) -> Double -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Double -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Double -> m Double # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Double -> m Double # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Double -> m Double # | |
Storable Double # | Since: base-2.1 |
Enum Double # | Since: base-2.1 |
Defined in GHC.Float | |
Floating Double # | Since: base-2.1 |
RealFloat Double # | Since: base-2.1 |
Defined in GHC.Float Methods floatRadix :: Double -> Integer # floatDigits :: Double -> Int # floatRange :: Double -> (Int, Int) # decodeFloat :: Double -> (Integer, Int) # encodeFloat :: Integer -> Int -> Double # significand :: Double -> Double # scaleFloat :: Int -> Double -> Double # isInfinite :: Double -> Bool # isDenormalized :: Double -> Bool # isNegativeZero :: Double -> Bool # | |
Num Double # | Note that due to the presence of
Also note that due to the presence of -0,
Since: base-2.1 |
Read Double # | Since: base-2.1 |
Fractional Double # | Note that due to the presence of
Since: base-2.1 |
Real Double # | Since: base-2.1 |
Defined in GHC.Float Methods toRational :: Double -> Rational # | |
RealFrac Double # | Since: base-2.1 |
Show Double # | Since: base-2.1 |
PrintfArg Double # | Since: base-2.1 |
Defined in Text.Printf | |
Eq Double | Note that due to the presence of
Also note that
|
Ord Double | Note that due to the presence of
Also note that, due to the same,
|
Generic1 (URec Double :: k -> Type) # | |
Foldable (UDouble :: TYPE LiftedRep -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Foldable Methods fold :: Monoid m => UDouble m -> m # foldMap :: Monoid m => (a -> m) -> UDouble a -> m # foldMap' :: Monoid m => (a -> m) -> UDouble a -> m # foldr :: (a -> b -> b) -> b -> UDouble a -> b # foldr' :: (a -> b -> b) -> b -> UDouble a -> b # foldl :: (b -> a -> b) -> b -> UDouble a -> b # foldl' :: (b -> a -> b) -> b -> UDouble a -> b # foldr1 :: (a -> a -> a) -> UDouble a -> a # foldl1 :: (a -> a -> a) -> UDouble a -> a # elem :: Eq a => a -> UDouble a -> Bool # maximum :: Ord a => UDouble a -> a # minimum :: Ord a => UDouble a -> a # | |
Traversable (UDouble :: Type -> Type) # | Since: base-4.9.0.0 |
Functor (URec Double :: TYPE LiftedRep -> Type) # | Since: base-4.9.0.0 |
Generic (URec Double p) # | |
Show (URec Double p) # | Since: base-4.9.0.0 |
Eq (URec Double p) # | Since: base-4.9.0.0 |
Ord (URec Double p) # | Since: base-4.9.0.0 |
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 # | |
data URec Double (p :: k) # | Used for marking occurrences of Since: base-4.9.0.0 |
type Rep1 (URec Double :: k -> Type) # | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
type Rep (URec Double p) # | Since: base-4.9.0.0 |
Defined in GHC.Generics |
double2Int :: Double -> Int #
int2Double :: Int -> Double #
Monomorphic equality operators
See GHC.Classes#matching_overloaded_methods_in_rules
Orphan instances
Enum Double # | Since: base-2.1 |
Enum Float # | Since: base-2.1 |
Num Double # | Note that due to the presence of
Also note that due to the presence of -0,
Since: base-2.1 |
Num Float # | Note that due to the presence of
Also note that due to the presence of -0,
Since: base-2.1 |
Fractional Double # | Note that due to the presence of
Since: base-2.1 |
Fractional Float # | Note that due to the presence of
Since: base-2.1 |
Real Double # | Since: base-2.1 |
Methods toRational :: Double -> Rational # | |
Real Float # | Since: base-2.1 |
Methods toRational :: Float -> Rational # | |
RealFrac Double # | Since: base-2.1 |
RealFrac Float # | Since: base-2.1 |
Show Double # | Since: base-2.1 |
Show Float # | Since: base-2.1 |