| Copyright | (c) Dong Han 2017-2019 | 
|---|---|
| License | BSD | 
| Maintainer | winterland1989@gmail.com | 
| Stability | experimental | 
| Portability | non-portable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Z.Data.Parser.Numeric
Description
Textual numeric parsers.
Synopsis
- uint :: Integral a => Parser a
- int :: Integral a => Parser a
- hex :: (Integral a, Bits a) => Parser a
- rational :: Fractional a => Parser a
- float :: Parser Float
- double :: Parser Double
- scientific :: Parser Scientific
- scientifically :: (Scientific -> a) -> Parser a
- rational' :: Fractional a => Parser a
- float' :: Parser Float
- double' :: Parser Double
- scientific' :: Parser Scientific
- scientifically' :: (Scientific -> a) -> Parser a
- hexLoop :: (Integral a, Bits a) => a -> Bytes -> a
- decLoop :: Integral a => a -> Bytes -> a
- decLoopIntegerFast :: Bytes -> Integer
- isHexDigit :: Word8 -> Bool
- isDigit :: Word8 -> Bool
- floatToScientific :: Float -> Scientific
- doubleToScientific :: Double -> Scientific
Decimal
int :: Integral a => Parser a Source #
Parse a decimal number with an optional leading '+' or '-' sign
 character.
Hex
hex :: (Integral a, Bits a) => Parser a Source #
Parse and decode an unsigned hex number.  The hex digits
 'a' through 'f' may be upper or lower case.
This parser does not accept a leading "0x" string, and consider
 sign bit part of the binary hex nibbles, i.e.
 'parse hex "0xFF" == Right (-1 :: Int8)'
Fractional
rational :: Fractional a => Parser a Source #
Parse a rational number.
The syntax accepted by this parser is the same as for double.
Note: this parser is not safe for use with inputs from untrusted
 sources.  An input with a suitably large exponent such as
 "1e1000000000" will cause a huge Integer to be allocated,
 resulting in what is effectively a denial-of-service attack.
In most cases, it is better to use double or scientific
 instead.
double :: Parser Double Source #
Parse a rational number and round to Double.
This parser accepts an optional leading sign character, followed by
 at least one decimal digit.  The syntax similar to that accepted by
 the read function, with the exception that a trailing '.' or
 'e' not followed by a number is not consumed.
Examples with behaviour identical to read:
parse_ double "3"     == ("", Right 3.0)
parse_ double "3.1"   == ("", Right 3.1)
parse_ double "3e4"   == ("", Right 30000.0)
parse_ double "3.1e4" == ("", Right 31000.0)parse_ double ".3"    == (".3", Left ParserError)
parse_ double "e3"    == ("e3", Left ParserError)Examples of differences from read:
parse_ double "3.foo" == (".foo", Right 3.0)
parse_ double "3e"    == ("e",    Right 3.0)
parse_ double "-3e"   == ("e",    Right -3.0)This function does not accept string representations of "NaN" or "Infinity".
scientific :: Parser Scientific Source #
Parse a scientific number.
The syntax accepted by this parser is the same as for double.
scientifically :: (Scientific -> a) -> Parser a Source #
Parse a scientific number and convert to result using a user supply function.
The syntax accepted by this parser is the same as for double.
Stricter fractional(rfc8259)
rational' :: Fractional a => Parser a Source #
Parse a rational number.
The syntax accepted by this parser is the same as for double'.
Note: this parser is not safe for use with inputs from untrusted
 sources.  An input with a suitably large exponent such as
 "1e1000000000" will cause a huge Integer to be allocated,
 resulting in what is effectively a denial-of-service attack.
In most cases, it is better to use double' or scientific'
 instead.
double' :: Parser Double Source #
More strict number parsing(rfc8259).
scientific support parse 2314. and 21321exyz without eating extra dot or e via
 backtrack, this is not allowed in some strict grammer such as JSON, so we make an
 non-backtrack strict number parser separately using LL(1) lookahead. This parser also
 agree with read on extra dot or e handling:
parse_ double "3.foo" == Left ParseError parse_ double "3e" == Left ParseError
Leading zeros or + sign is also not allowed:
parse_ double "+3.14" == Left ParseError parse_ double "0014" == Left ParseError
If you have a similar grammer, you can use this parser to save considerable time.
     number = [ minus ] int [ frac ] [ exp ]
     decimal-point = %x2E       ; .
     digit1-9 = %x31-39         ; 1-9
     e = %x65 / %x45            ; e E
     exp = e [ minus / plus ] 1*DIGIT
     frac = decimal-point 1*DIGIT
This function does not accept string representations of "NaN" or "Infinity". reference: https://tools.ietf.org/html/rfc8259#section-6
scientific' :: Parser Scientific Source #
Parse a scientific number.
The syntax accepted by this parser is the same as for double'.
scientifically' :: (Scientific -> a) -> Parser a Source #
Parse a scientific number and convert to result using a user supply function.
The syntax accepted by this parser is the same as for double'.
Misc
decode hex digits sequence within an array.
decode digits sequence within an array.
decLoopIntegerFast :: Bytes -> Integer Source #
decode digits sequence within an array.
A fast version to decode Integer using machine word as much as possible.
isHexDigit :: Word8 -> Bool Source #
A fast digit predicate.
floatToScientific :: Float -> Scientific Source #