-- Hoogle documentation, generated by Haddock
-- See Hoogle, http://www.haskell.org/hoogle/
-- | Utilities for parsing numbers from strings
--
-- parsec-numbers provides the number parsers without the need to use a
-- large (and unportable) token parser
@package parsec-numbers
@version 0.0.2
-- | adjusted and portable number parsers stolen from
-- Text.ParserCombinators.Parsec.Token
--
-- The basic top-level number parsers are decimal, nat,
-- int, fractional, decimalFract, natFract,
-- floating, decimalFloat, natFloat.
--
-- natFloat parses numeric literals as defined for Haskell. All
-- numbers are unsigned, i.e. non-negative. Leading zeros are allowed. At
-- least a single digit is required. A decimal point must be preceded and
-- followed by at least one digit.
--
-- A result type (Either Integer Double) can be converted to a
-- final Double using (either fromInteger id) as is
-- done for the parsers fractional2 and floating2.
--
-- The parser nat, natFract and natFloat parse
-- hexadecimal and octal integrals (beginning with 0x,
-- 0X, 0o or 0O) that are disallowed when
-- using decimal, decimalFract and decimalFloat.
--
-- The parsers decimalFract and natFract only allow a
-- decimal point, whereas decimalFloat and natFloat also
-- allow the exponent notation using e or E.
--
-- The parser fractional requires a decimal point between at least
-- two digits and floating requires either a decimal point or the
-- exponent notation using e or E. (Both parsers do not
-- return integral values and do not support hexadecimal or octal
-- values).
--
-- Signed numbers can be parsed using "ap sign" as is done
-- for the int parser.
--
-- A couple of parsers have been added that take a Bool
-- argument, where False does not require any digit following
-- the decimal dot. The parsers fractional3 and floating3
-- allow even to start a number with the decimal dot. Also parsers
-- hexFract and hexFloat for hexadecimal fractions and
-- floats have been added.
--
-- Note that most top-level parsers succeed on a string like
-- "1.0e-100", but only the floating point parsers consume the
-- whole string. The fractional parsers stop before the exponent and the
-- integral parsers before the decimal point. You may which to check for
-- the end of a string using eof, i.e. liftM2 const nat
-- eof.
module Text.ParserCombinators.Parsec.Number
-- | parse a decimal unsigned floating point number containing a dot, e or
-- E
floating :: Floating f => CharParser st f
-- | parse a floating point number possibly containing a decimal dot, e or
-- E
floating2 :: Floating f => Bool -> CharParser st f
-- | parse a floating point number possibly starting with a decimal dot.
-- Note, that a single decimal point or a number starting with
-- .E is illegal.
floating3 :: Floating f => Bool -> CharParser st f
-- | same as floating but returns a non-negative integral wrapped by
-- Left if a fractional part and exponent is missing
decimalFloat :: (Integral i, Floating f) => CharParser st (Either i f)
-- | same as floating but returns a non-negative integral wrapped by
-- Left if a fractional part and exponent is missing
decFloat :: (Integral i, Floating f) => Bool -> CharParser st (Either i f)
-- | parse a hexadecimal floating point number
hexFloat :: (Integral i, Floating f) => Bool -> CharParser st (Either i f)
-- | parse hexadecimal, octal or decimal integrals or floating
natFloat :: (Integral i, Floating f) => CharParser st (Either i f)
-- | parse any hexadecimal, octal, decimal or floating point number
-- following a zero
zeroNumFloat :: (Integral i, Floating f) => CharParser st (Either i f)
-- | parse a floating point number given the number before a dot, e or E
fractExponent :: Floating f => Integer -> CharParser st f
-- | parse a hex floating point number given the number before a dot or p
hexFractExp :: Floating f => Integer -> Bool -> CharParser st f
-- | parse a floating point number given the number before a dot, e or E
fractExp :: Floating f => Integer -> Bool -> CharParser st f
-- | parse a floating point number given the number before the fraction and
-- exponent
genFractExp :: Floating f => Integer -> CharParser st f -> CharParser st (f -> f) -> CharParser st f
-- | parse a floating point number given the number before the fraction and
-- exponent that must follow the fraction
genFractAndExp :: Floating f => f -> CharParser st f -> CharParser st (f -> f) -> CharParser st f
-- | parse a floating point exponent starting with e or E
exponentFactor :: Floating f => CharParser st (f -> f)
-- | pare a hexadecimal floating point starting with p (IEEE 754)
hexExponentFactor :: Floating f => CharParser st (f -> f)
-- | parse a signed decimal and compute the exponent factor given a base.
-- For hexadecimal exponential notation (IEEE 754) the base is 2 and the
-- leading character a p.
extExponentFactor :: Floating f => Int -> CharParser st (f -> f)
-- | compute the factor given by the number following e or E. This
-- implementation uses ** rather than ^ for more
-- efficiency for large integers.
exponentValue :: Int -> Floating f => Integer -> f
-- | parse a fractional number containing a decimal dot
fractional :: Fractional f => CharParser st f
-- | parse a fractional number possibly containing a decimal dot
fractional2 :: Fractional f => Bool -> CharParser st f
-- | parse a fractional number possibly starting with a decimal dot
fractional3 :: Fractional f => Bool -> CharParser st f
-- | a decimal fractional
decFract :: (Integral i, Fractional f) => Bool -> CharParser st (Either i f)
-- | a hexadecimal fractional
hexFract :: (Integral i, Fractional f) => Bool -> CharParser st (Either i f)
-- | same as fractional but returns a non-negative integral wrapped
-- by Left if a fractional part is missing
decimalFract :: (Integral i, Fractional f) => CharParser st (Either i f)
-- | parse hexadecimal, octal or decimal integrals or fractional
natFract :: (Integral i, Fractional f) => CharParser st (Either i f)
-- | parse any hexadecimal, octal, decimal or fractional number following a
-- zero
zeroNumFract :: (Integral i, Fractional f) => CharParser st (Either i f)
-- | parse a fractional number given the number before the dot
fractFract :: Fractional f => Integer -> Bool -> CharParser st f
genFractFract :: Fractional f => Integer -> CharParser st f -> CharParser st f
-- | parse a dot followed by decimal digits as fractional part
fraction :: Fractional f => Bool -> CharParser st f
-- | parse a dot followed by hexadecimal digits as fractional part
hexFraction :: Fractional f => Bool -> CharParser st f
-- | parse a dot followed by base dependent digits as fractional part
baseFraction :: Fractional f => Bool -> Int -> CharParser st Char -> CharParser st f
-- | compute the fraction given by a sequence of digits following the dot
fractionValue :: Fractional f => Int -> String -> f
-- | parse an optional sign immediately followed by a nat.
-- Note, that in Daan Leijen's code the sign was wrapped as lexeme in
-- order to skip comments and spaces in between.
int :: Integral i => CharParser st i
-- | parse an optional plus or minus sign, returning negate or
-- id
sign :: Num a => CharParser st (a -> a)
-- | parse plain non-negative decimal numbers given by a non-empty sequence
-- of digits
decimal :: Integral i => CharParser st i
-- | parse a binary number
binary :: Integral i => CharParser st i
-- | parse non-negative hexadecimal, octal or decimal numbers
nat :: Integral i => CharParser st i
-- | parse a nat syntactically starting with a zero
zeroNumber :: Integral i => CharParser st i
-- | hexadecimal or octal number
hexOrOct :: Integral i => CharParser st i
-- | parse a hexadecimal number preceded by an x or X character
hexadecimal :: Integral i => CharParser st i
-- | parse a hexadecimal number
hexnum :: Integral i => CharParser st i
-- | parse an octal number preceded by an o or O character
octal :: Integral i => CharParser st i
-- | parse a non-negative number given a base and a parser for the digits
number :: Integral i => Int -> GenParser tok st Char -> GenParser tok st i
-- | compute the value from a string of digits using a base
numberValue :: Integral i => Int -> String -> i