Copyright | (c) The University of Glasgow 2002 |
---|---|
License | BSD-style (see the file libraries/base/LICENSE) |
Maintainer | libraries@haskell.org |
Stability | provisional |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Numeric
Contents
Description
Odds and ends, mostly functions for reading and showing
RealFloat
-like kind of values.
Synopsis
- showSigned :: Real a => (a -> ShowS) -> Int -> a -> ShowS
- showIntAtBase :: Integral a => a -> (Int -> Char) -> a -> ShowS
- showInt :: Integral a => a -> ShowS
- showBin :: Integral a => a -> ShowS
- showHex :: Integral a => a -> ShowS
- showOct :: Integral a => a -> ShowS
- showEFloat :: RealFloat a => Maybe Int -> a -> ShowS
- showFFloat :: RealFloat a => Maybe Int -> a -> ShowS
- showGFloat :: RealFloat a => Maybe Int -> a -> ShowS
- showFFloatAlt :: RealFloat a => Maybe Int -> a -> ShowS
- showGFloatAlt :: RealFloat a => Maybe Int -> a -> ShowS
- showFloat :: RealFloat a => a -> ShowS
- showHFloat :: RealFloat a => a -> ShowS
- floatToDigits :: RealFloat a => Integer -> a -> ([Int], Int)
- readSigned :: Real a => ReadS a -> ReadS a
- readInt :: Num a => a -> (Char -> Bool) -> (Char -> Int) -> ReadS a
- readBin :: (Eq a, Num a) => ReadS a
- readDec :: (Eq a, Num a) => ReadS a
- readOct :: (Eq a, Num a) => ReadS a
- readHex :: (Eq a, Num a) => ReadS a
- readFloat :: RealFrac a => ReadS a
- lexDigits :: ReadS String
- fromRat :: RealFloat a => Rational -> a
- class Fractional a => Floating a where
Showing
Arguments
a function that can show unsigned values
the precedence of the enclosing context
the value to show
Converts a possibly-negative Real
value to a string.
showIntAtBase :: Integral a => a -> (Int -> Char) -> a -> ShowS Source #
Shows a non-negative Integral
number using the base specified by the
first argument, and the character representation specified by the second.
showEFloat :: RealFloat a => Maybe Int -> a -> ShowS Source #
Show a signed RealFloat
value
using scientific (exponential) notation (e.g. 2.45e2
, 1.5e-3
).
In the call
, if showEFloat
digs valdigs
is Nothing
,
the value is shown to full precision; if digs
is
,
then at most Just
dd
digits after the decimal point are shown.
showFFloat :: RealFloat a => Maybe Int -> a -> ShowS Source #
Show a signed RealFloat
value
using standard decimal notation (e.g. 245000
, 0.0015
).
In the call
, if showFFloat
digs valdigs
is Nothing
,
the value is shown to full precision; if digs
is
,
then at most Just
dd
digits after the decimal point are shown.
showGFloat :: RealFloat a => Maybe Int -> a -> ShowS Source #
Show a signed RealFloat
value
using standard decimal notation for arguments whose absolute value lies
between 0.1
and 9,999,999
, and scientific notation otherwise.
In the call
, if showGFloat
digs valdigs
is Nothing
,
the value is shown to full precision; if digs
is
,
then at most Just
dd
digits after the decimal point are shown.
showFFloatAlt :: RealFloat a => Maybe Int -> a -> ShowS Source #
Show a signed RealFloat
value
using standard decimal notation (e.g. 245000
, 0.0015
).
This behaves as showFFloat
, except that a decimal point
is always guaranteed, even if not needed.
Since: base-4.7.0.0
showGFloatAlt :: RealFloat a => Maybe Int -> a -> ShowS Source #
Show a signed RealFloat
value
using standard decimal notation for arguments whose absolute value lies
between 0.1
and 9,999,999
, and scientific notation otherwise.
This behaves as showFFloat
, except that a decimal point
is always guaranteed, even if not needed.
Since: base-4.7.0.0
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.
showHFloat :: RealFloat a => a -> ShowS Source #
Show a floating-point value in the hexadecimal format,
similar to the %a
specifier in C's printf.
>>>
showHFloat (212.21 :: Double) ""
"0x1.a86b851eb851fp7">>>
showHFloat (-12.76 :: Float) ""
"-0x1.9851ecp3">>>
showHFloat (-0 :: Double) ""
"-0x0p+0"
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
Reading
NB: readInt
is the 'dual' of showIntAtBase
,
and readDec
is the `dual' of showInt
.
The inconsistent naming is a historical accident.
readSigned :: Real a => ReadS a -> ReadS a Source #
Reads a signed Real
value, given a reader for an unsigned value.
readBin :: (Eq a, Num a) => ReadS a Source #
Read an unsigned number in binary notation.
>>>
readBin "10011"
[(19,"")]
readDec :: (Eq a, Num a) => ReadS a Source #
Read an unsigned number in decimal notation.
>>>
readDec "0644"
[(644,"")]
readOct :: (Eq a, Num a) => ReadS a Source #
Read an unsigned number in octal notation.
>>>
readOct "0644"
[(420,"")]
readHex :: (Eq a, Num a) => ReadS a Source #
Read an unsigned number in hexadecimal notation. Both upper or lower case letters are allowed.
>>>
readHex "deadbeef"
[(3735928559,"")]
readFloat :: RealFrac a => ReadS a Source #
Reads an unsigned RealFrac
value,
expressed in decimal scientific notation.
Miscellaneous
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 #