parsec-numbers-0.1.0: Utilities for parsing numbers from strings

Portabilityportable
Stabilityprovisional
Maintainerchr.maeder@web.de
Safe HaskellSafe-Inferred

Text.ParserCombinators.Parsec.Number

Contents

Description

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, binFract, hexFloat and binFloat for hexadecimal or binary 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 wish to check for the end of a string using eof, i.e. "liftM2 const nat eof".

The returned values may be inaccurate. Int may overflow. Fractional numbers should be accurate as only one division is performed. Floating point numbers with decimal exponents may be inaccurate due to using **. Rational numbers are needed for correct conversions, but large positive or negative exponents may be a problem and the class RealFloat is needed to check for minimal and maximal exponents.

Synopsis

floats

floating :: Floating f => CharParser st fSource

parse a decimal unsigned floating point number containing a dot, e or E

floating2 :: Floating f => Bool -> CharParser st fSource

parse a floating point number possibly containing a decimal dot, e or E

floating3 :: Floating f => Bool -> CharParser st fSource

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.

decimalFloat :: (Integral i, Floating f) => CharParser st (Either i f)Source

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)Source

same as floating but returns a non-negative integral wrapped by Left if a fractional part and exponent is missing

hexFloat :: (Integral i, Floating f) => Bool -> CharParser st (Either i f)Source

parse a hexadecimal floating point number

binFloat :: (Integral i, Floating f) => Bool -> CharParser st (Either i f)Source

parse a binary floating point number

natFloat :: (Integral i, Floating f) => CharParser st (Either i f)Source

parse hexadecimal, octal or decimal integrals or floating

float parts

zeroNumFloat :: (Integral i, Floating f) => CharParser st (Either i f)Source

parse any hexadecimal, octal, decimal or floating point number following a zero

fractExponent :: Floating f => Integer -> CharParser st fSource

parse a floating point number given the number before a dot, e or E

hexFractExp :: Floating f => Integer -> Bool -> CharParser st fSource

parse a hex floating point number given the number before a dot, p or P

binFractExp :: Floating f => Integer -> Bool -> CharParser st fSource

parse a binary floating point number given the number before a dot, p or P

fractExp :: Floating f => Integer -> Bool -> CharParser st fSource

parse a floating point number given the number before a dot, e or E

genFractExp :: Floating f => Integer -> CharParser st f -> CharParser st (f -> f) -> CharParser st fSource

parse a floating point number given the number before the fraction and exponent

genFractAndExp :: Floating f => f -> CharParser st f -> CharParser st (f -> f) -> CharParser st fSource

parse a floating point number given the number before the fraction and exponent that must follow the fraction

exponentFactor :: Floating f => CharParser st (f -> f)Source

parse a floating point exponent starting with e or E

hexExponentFactor :: Floating f => CharParser st (f -> f)Source

parse a hexadecimal floating point starting with p (IEEE 754)

extExponentFactor :: Floating f => Int -> CharParser st (f -> f)Source

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.

exponentValue :: Floating f => Int -> Integer -> fSource

compute the factor given by the number following e or E. This implementation uses ** rather than ^ for more efficiency for large integers.

fractional numbers (with just a decimal point between digits)

fractional :: Fractional f => CharParser st fSource

parse a fractional number containing a decimal dot

fractional2 :: Fractional f => Bool -> CharParser st fSource

parse a fractional number possibly containing a decimal dot

fractional3 :: Fractional f => Bool -> CharParser st fSource

parse a fractional number possibly starting with a decimal dot

decFract :: (Integral i, Fractional f) => Bool -> CharParser st (Either i f)Source

a decimal fractional

hexFract :: (Integral i, Fractional f) => Bool -> CharParser st (Either i f)Source

a hexadecimal fractional

binFract :: (Integral i, Fractional f) => Bool -> CharParser st (Either i f)Source

a binary fractional

decimalFract :: (Integral i, Fractional f) => CharParser st (Either i f)Source

same as fractional but returns a non-negative integral wrapped by Left if a fractional part is missing

natFract :: (Integral i, Fractional f) => CharParser st (Either i f)Source

parse hexadecimal, octal or decimal integrals or fractional

zeroNumFract :: (Integral i, Fractional f) => CharParser st (Either i f)Source

parse any hexadecimal, octal, decimal or fractional number following a zero

fractional parts

fractFract :: Fractional f => Integer -> Bool -> CharParser st fSource

parse a fractional number given the number before the dot

genFractFract :: Fractional f => Integer -> CharParser st f -> CharParser st fSource

combine the given number before the dot with a parser for the fractional part

fraction :: Fractional f => Bool -> CharParser st fSource

parse a dot followed by decimal digits as fractional part

hexFraction :: Fractional f => Bool -> CharParser st fSource

parse a dot followed by hexadecimal digits as fractional part

binFraction :: Fractional f => Bool -> CharParser st fSource

parse a dot followed by binary digits as fractional part

baseFraction :: Fractional f => Bool -> Int -> CharParser st Char -> CharParser st fSource

parse a dot followed by base dependent digits as fractional part

fractionValue :: Fractional f => Int -> String -> fSource

compute the fraction given by a sequence of digits following the dot. Only one division is performed and trailing zeros are ignored.

integers and naturals

int :: Integral i => CharParser st iSource

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.

sign :: Num a => CharParser st (a -> a)Source

parse an optional plus or minus sign, returning negate or id

decimal :: Integral i => CharParser st iSource

parse plain non-negative decimal numbers given by a non-empty sequence of digits

binDigit :: CharParser st CharSource

parse 0 or 1

binary :: Integral i => CharParser st iSource

parse a binary number

nat :: Integral i => CharParser st iSource

parse non-negative hexadecimal, octal or decimal numbers

natural parts

zeroNumber :: Integral i => CharParser st iSource

parse a nat syntactically starting with a zero

hexOrOct :: Integral i => CharParser st iSource

hexadecimal or octal number

hexadecimal :: Integral i => CharParser st iSource

parse a hexadecimal number preceded by an x or X character

hexnum :: Integral i => CharParser st iSource

parse a hexadecimal number

octal :: Integral i => CharParser st iSource

parse an octal number preceded by an o or O character

number :: Integral i => Int -> GenParser tok st Char -> GenParser tok st iSource

parse a non-negative number given a base and a parser for the digits

numberValue :: Integral i => Int -> String -> iSource

compute the value from a string of digits using a base