Z-Data-0.8.3.0: Array, vector and text
Copyright(c) Dong Han 2017-2019
LicenseBSD
Maintainerwinterland1989@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Z.Data.Parser.Numeric

Description

Textual numeric parsers.

Synopsis

Decimal

uint :: forall a. (Integral a, Bounded a) => Parser a Source #

Parse and decode an unsigned decimal number.

Will fail in case of overflow.

int :: forall a. (Integral a, Bounded a) => Parser a Source #

Parse a decimal number with an optional leading '+' or '-' sign character.

This parser will fail if overflow happens.

integer :: Parser Integer Source #

Parser specifically optimized for Integer.

uint_ :: forall a. (Integral a, Bounded a) => Parser a Source #

Same with uint, but sliently cast in case of overflow.

int_ :: (Integral a, Bounded a) => Parser a Source #

Same with int, but sliently cast if overflow happens.

digit :: Parser Int Source #

Take a single decimal digit and return as Int.

Hex

hex :: forall a. (Integral a, FiniteBits a) => Parser a Source #

Parse and decode an unsigned hex number, fail if input length is larger than (bit_size/4). 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, e.g.

>>> parse' hex "FF" == Right (-1 :: Int8)
>>> parse' hex "7F" == Right (127 :: Int8)
>>> parse' hex "7Ft" == Right (127 :: Int8)
>>> parse' hex "7FF" == Left ["Z.Data.Parser.Numeric.hex","hex numeric number overflow"]

hex' :: forall a. (Integral a, FiniteBits a) => Parser a Source #

Same with hex, but only take as many as (bit_size/4) bytes.

>>> parse' hex "FF" == Right (-1 :: Int8)
>>> parse' hex "7F" == Right (127 :: Int8)
>>> parse' hex "7Ft" == Right (127 :: Int8)
>>> parse' hex "7FF" == Right (127 :: Int8)

hex_ :: (Integral a, Bits a) => Parser a Source #

Same with hex, but silently cast in case of overflow.

>>> parse' hex "FF" == Right (-1 :: Int8)
>>> parse' hex "7F" == Right (127 :: Int8)
>>> parse' hex "7Ft" == Right (127 :: Int8)
>>> parse' hex "7FF" == 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.

float :: Parser Float Source #

Parse a rational number and round to Float.

Single precision version of double.

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.

float' :: Parser Float Source #

Parse a rational number and round to Float using stricter grammer.

Single precision version of double'.

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

w2iHex :: Integral a => Word8 -> a Source #

Convert A ASCII hex digit to Int value.

w2iDec :: Integral a => Word8 -> a Source #

Convert A ASCII decimal digit to Int value.

hexLoop Source #

Arguments

:: forall a. (Integral a, Bits a) 
=> a

accumulator, usually start from 0

-> Bytes 
-> a 

decode hex digits sequence within an array.

decLoop Source #

Arguments

:: Integral a 
=> a

accumulator, usually start from 0

-> Bytes 
-> a 

Decode digits sequence within an array.

This function may overflow if result can't fit into type.

decLoopIntegerFast :: Bytes -> Integer Source #

decode digits sequence within an array.

A fast version to decode Integer using machine word as much as possible.