paripari-0.6.0.1: Parser combinators with fast-path and slower fallback for error reporting

Safe HaskellNone
LanguageHaskell2010

Text.PariPari.Internal.CharCombinators

Synopsis

Documentation

digitByte :: CharParser k p => Int -> p Word8 Source #

Parse a digit byte for the given base. Bases 2 to 36 are supported.

integer :: (Num a, CharParser k p) => p sep -> Int -> p a Source #

Parse an integer of the given base. Bases 2 to 36 are supported. Digits can be separated by separator, e.g. `optional (char '_')`. Signs are not parsed by this combinator.

integer' :: (Num a, CharParser k p) => p sep -> Int -> p (a, Int) Source #

Parse an integer of the given base. Returns the integer and the number of digits. Bases 2 to 36 are supported. Digits can be separated by separator, e.g. `optional (char '_')`. Signs are not parsed by this combinator.

decimal :: Num a => CharP k a Source #

Parses a decimal integer. Signs are not parsed by this combinator.

octal :: Num a => CharP k a Source #

Parses an octal integer. Signs are not parsed by this combinator.

hexadecimal :: Num a => CharP k a Source #

Parses a hexadecimal integer. Signs are not parsed by this combinator.

digit :: CharParser k p => Int -> p Word Source #

Parse a single digit of the given base and return its value. Bases 2 to 36 are supported.

sign :: (CharParser k f, Num a) => f (a -> a) Source #

Parse plus or minus sign

signed :: (Num a, CharParser k p) => p a -> p a Source #

Parse a number with a plus or minus sign.

fractionHex :: (Num a, CharParser k p) => p digitSep -> p (Either a (a, Int, a)) Source #

Parse a hexadecimal fraction, e.g., co.ffeep123, returning (mantissa, 2, exponent), corresponding to mantissa * 2^exponent. Digits can be separated by separator, e.g. `optional (char '_')`. Signs are not parsed by this combinator.

fractionDec :: (Num a, CharParser k p) => p digitSep -> p (Either a (a, Int, a)) Source #

Parse a decimal fraction, e.g., 123.456e-78, returning (mantissa, 10, exponent), corresponding to mantissa * 10^exponent. Digits can be separated by separator, e.g. `optional (char '_')`. Signs are not parsed by this combinator.

char' :: CharParser k p => Char -> p Char Source #

Parse a case-insensitive character

notChar :: CharParser k p => Char -> p Char Source #

Parse a character different from the given one.

anyChar :: CharP k Char Source #

Parse an arbitrary character.

anyAsciiByte :: CharP k Word8 Source #

Parse an arbitrary ASCII byte.

alphaNumChar :: CharP k Char Source #

Parse an alphanumeric character, including Unicode.

digitChar :: CharParser k p => Int -> p Char Source #

Parse a digit character of the given base. Bases 2 to 36 are supported.

letterChar :: CharP k Char Source #

Parse a letter character, including Unicode.

lowerChar :: CharP k Char Source #

Parse a lowercase letter, including Unicode.

upperChar :: CharP k Char Source #

Parse a uppercase letter, including Unicode.

symbolChar :: CharP k Char Source #

Parse a symbol character, including Unicode.

categoryChar :: CharParser k p => GeneralCategory -> p Char Source #

Parse a character belonging to the given Unicode category

punctuationChar :: CharP k Char Source #

Parse a punctuation character, including Unicode.

spaceChar :: CharP k Char Source #

Parse a space character, including Unicode.

asciiChar :: CharP k Char Source #

Parse a character beloning to the ASCII charset (< 128)

satisfy :: CharParser k p => (Char -> Bool) -> p Char Source #

Parse a single character with the given predicate

asciiSatisfy :: CharParser k p => (Word8 -> Bool) -> p Word8 Source #

Parse a single character within the ASCII charset with the given predicate

skipChars :: CharParser k p => Int -> p () Source #

Skip the next n characters

takeChars :: CharParser k p => Int -> p k Source #

Take the next n characters and advance the position by n characters

skipCharsWhile :: CharParser k p => (Char -> Bool) -> p () Source #

Skip char while predicate is true

takeCharsWhile :: CharParser k p => (Char -> Bool) -> p k Source #

Take chars while predicate is true

skipCharsWhile1 :: CharParser k p => (Char -> Bool) -> p () Source #

Skip at least one char while predicate is true

takeCharsWhile1 :: CharParser k p => (Char -> Bool) -> p k Source #

Take at least one byte while predicate is true

scanChars :: CharParser k p => (s -> Char -> Maybe s) -> s -> p s Source #

scanChars1 :: CharParser k p => (s -> Char -> Maybe s) -> s -> p s Source #

string :: CharParser k p => String -> p k Source #

Parse a string