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

Safe HaskellNone
LanguageHaskell2010

Text.PariPari.Internal.Combinators

Contents

Synopsis

Basic combinators

void :: Functor f => f a -> f () #

void value discards or ignores the result of evaluation, such as the return value of an IO action.

Examples

Expand

Replace the contents of a Maybe Int with unit:

>>> void Nothing
Nothing
>>> void (Just 3)
Just ()

Replace the contents of an Either Int Int with unit, resulting in an Either Int '()':

>>> void (Left 8675309)
Left 8675309
>>> void (Right 8675309)
Right ()

Replace every element of a list with unit:

>>> void [1,2,3]
[(),(),()]

Replace the second element of a pair with unit:

>>> void (1,2)
(1,())

Discard the result of an IO action:

>>> mapM print [1,2]
1
2
[(),()]
>>> void $ mapM print [1,2]
1
2

(<|>) :: Alternative f => f a -> f a -> f a infixl 3 #

An associative binary operation

empty :: Alternative f => f a #

The identity of <|>

Control.Monad.Combinators.NonEmpty

some :: MonadPlus m => m a -> m (NonEmpty a) #

some p applies the parser p one or more times and returns a list of the values returned by p.

word = some letter

endBy1 :: MonadPlus m => m a -> m sep -> m (NonEmpty a) #

endBy1 p sep parses one or more occurrences of p, separated and ended by sep. Returns a non-empty list of values returned by p.

someTill :: MonadPlus m => m a -> m end -> m (NonEmpty a) #

someTill p end works similarly to manyTill p end, but p should succeed at least once.

See also: skipSome, skipSomeTill.

sepBy1 :: MonadPlus m => m a -> m sep -> m (NonEmpty a) #

sepBy1 p sep parses one or more occurrences of p, separated by sep. Returns a non-empty list of values returned by p.

sepEndBy1 :: MonadPlus m => m a -> m sep -> m (NonEmpty a) #

sepEndBy1 p sep parses one or more occurrences of p, separated and optionally ended by sep. Returns a non-empty list of values returned by p.

Control.Monad.Combinators

optional :: Alternative f => f a -> f (Maybe a) #

One or none.

many :: MonadPlus m => m a -> m [a] #

many p applies the parser p zero or more times and returns a list of the values returned by p.

identifier = (:) <$> letter <*> many (alphaNumChar <|> char '_')

between :: Applicative m => m open -> m close -> m a -> m a #

between open close p parses open, followed by p and close. Returns the value returned by p.

braces = between (symbol "{") (symbol "}")

choice :: (Foldable f, Alternative m) => f (m a) -> m a #

choice ps tries to apply the parsers in the list ps in order, until one of them succeeds. Returns the value of the succeeding parser.

choice = asum

count :: Monad m => Int -> m a -> m [a] #

count n p parses n occurrences of p. If n is smaller or equal to zero, the parser equals to return []. Returns a list of n values.

See also: skipCount, count'.

count' :: MonadPlus m => Int -> Int -> m a -> m [a] #

count' m n p parses from m to n occurrences of p. If n is not positive or m > n, the parser equals to return []. Returns a list of parsed values.

Please note that m may be negative, in this case effect is the same as if it were equal to zero.

See also: skipCount, count.

eitherP :: Alternative m => m a -> m b -> m (Either a b) #

Combine two alternatives.

eitherP a b = (Left <$> a) <|> (Right <$> b)

endBy :: MonadPlus m => m a -> m sep -> m [a] #

endBy p sep parses zero or more occurrences of p, separated and ended by sep. Returns a list of values returned by p.

cStatements = cStatement `endBy` semicolon

manyTill :: MonadPlus m => m a -> m end -> m [a] #

manyTill p end applies parser p zero or more times until parser end succeeds. Returns the list of values returned by p. Note that end result is consumed and lost. Use manyTill_ if you wish to keep it.

See also: skipMany, skipManyTill.

option :: Alternative m => a -> m a -> m a #

option x p tries to apply the parser p. If p fails without consuming input, it returns the value x, otherwise the value returned by p.

option x p = p <|> pure x

See also: optional.

sepBy :: MonadPlus m => m a -> m sep -> m [a] #

sepBy p sep parses zero or more occurrences of p, separated by sep. Returns a list of values returned by p.

commaSep p = p `sepBy` comma

sepEndBy :: MonadPlus m => m a -> m sep -> m [a] #

sepEndBy p sep parses zero or more occurrences of p, separated and optionally ended by sep. Returns a list of values returned by p.

skipMany :: MonadPlus m => m a -> m () #

skipMany p applies the parser p zero or more times, skipping its result.

See also: manyTill, skipManyTill.

skipSome :: MonadPlus m => m a -> m () #

skipSome p applies the parser p one or more times, skipping its result.

See also: someTill, skipSomeTill.

skipCount :: Monad m => Int -> m a -> m () #

skipCount n p parses n occurrences of p, skipping its result. If n is smaller or equal to zero, the parser equals to return []. Returns a list of n values.

See also: count, count'.

skipManyTill :: MonadPlus m => m a -> m end -> m end #

skipManyTill p end applies the parser p zero or more times skipping results until parser end succeeds. Result parsed by end is then returned.

See also: manyTill, skipMany.

skipSomeTill :: MonadPlus m => m a -> m end -> m end #

skipSomeTill p end applies the parser p one or more times skipping results until parser end succeeds. Result parsed by end is then returned.

See also: someTill, skipSome.

Labels

(<?>) :: Parser k p => p a -> String -> p a infix 0 Source #

Infix alias for label

Position

getLine :: P k Int Source #

Get current line number

getCol :: P k Int Source #

Get current column

withPos :: Parser k p => p a -> p (Pos, a) Source #

Decorate the parser result with the current position

withSpan :: Parser k p => p a -> p (Pos, Pos, a) Source #

Decorate the parser result with the position span

Indentation

getRefCol :: P k Int Source #

Get column number of the reference position

getRefLine :: P k Int Source #

Get line number of the reference position

withRefPos :: Parser k p => p a -> p a Source #

Update reference position with current position

align :: P k () Source #

Parser succeeds on the same column as the reference column

indented :: P k () Source #

Parser succeeds for columns greater than the current reference column

line :: P k () Source #

Parser succeeds on the same line as the reference line

linefold :: P k () Source #

Parser succeeds either on the reference line or for columns greater than the current reference column

Char combinators

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

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

integer :: (Num a, Parser 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, Parser 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 => P k a Source #

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

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

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

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

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

digit :: Parser 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 :: (Parser k f, Num a) => f (a -> a) Source #

Parse plus or minus sign

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

Parse a number with a plus or minus sign.

fractionHex :: (Num a, Parser 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, Parser 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' :: Parser k p => Char -> p Char Source #

Parse a case-insensitive character

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

Parse a character different from the given one.

anyChar :: P k Char Source #

Parse an arbitrary character.

anyAsciiByte :: P k Word8 Source #

Parse an arbitrary ASCII byte.

alphaNumChar :: P k Char Source #

Parse an alphanumeric character, including Unicode.

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

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

letterChar :: P k Char Source #

Parse a letter character, including Unicode.

lowerChar :: P k Char Source #

Parse a lowercase letter, including Unicode.

upperChar :: P k Char Source #

Parse a uppercase letter, including Unicode.

symbolChar :: P k Char Source #

Parse a symbol character, including Unicode.

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

Parse a character belonging to the given Unicode category

punctuationChar :: P k Char Source #

Parse a punctuation character, including Unicode.

spaceChar :: P k Char Source #

Parse a space character, including Unicode.

asciiChar :: P k Char Source #

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

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

Parse a single character with the given predicate

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

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

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

Skip the next n characters

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

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

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

Skip char while predicate is true

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

Take chars while predicate is true

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

Skip at least one char while predicate is true

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

Take at least one byte while predicate is true

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

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

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

Parse a string