| 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
| :: Real a | |
| => (a -> ShowS) | a function that can show unsigned values  | 
| -> Int | the precedence of the enclosing context  | 
| -> a | the value to show  | 
| -> ShowS | 
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.
Arguments
| :: Num a | |
| => a | the base  | 
| -> (Char -> Bool) | a predicate distinguishing valid digits in this base  | 
| -> (Char -> Int) | a function converting a valid digit character to an   | 
| -> ReadS a | 
Reads an unsigned integral value in an arbitrary base.
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 bexp (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