parser-combinators-1.0.2: Lightweight package providing commonly useful parser combinators

Copyright© 2017–2019 Mark Karpov
LicenseBSD 3 clause
MaintainerMark Karpov <markkarpov92@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Control.Monad.Combinators

Contents

Description

The module provides more efficient versions of the combinators from Control.Applicative.Combinators defined in terms of Monad and MonadPlus instead of Applicative and Alternative. When there is no difference in performance we just re-export the combinators from Control.Applicative.Combinators.

Since: 0.4.0

Synopsis

Re-exports from Control.Applicative

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

An associative binary operation

This combinator implements choice. The parser p <|> q first applies p. If it succeeds, the value of p is returned. If p fails, parser q is tried.

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

One or none.

optional p tries to apply the parser p. It will parse p or Nothing. It only fails if p fails after consuming input. On success result of p is returned inside of Just, on failure Nothing is returned.

See also: option.

empty :: Alternative f => f a #

The identity of <|>

This parser fails unconditionally without providing any information about the cause of the failure.

Original combinators

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

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

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] Source #

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] Source #

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

Combine two alternatives.

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

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

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

endBy1 :: MonadPlus m => m a -> m sep -> m [a] Source #

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

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

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 '_')

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

manyTill p end applies parser p zero or more times until parser end succeeds. Returns the list of values returned by p.

See also: skipMany, skipManyTill.

some :: MonadPlus m => m a -> m [a] Source #

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

word = some letter

someTill :: MonadPlus m => m a -> m end -> m [a] Source #

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

See also: skipSome, skipSomeTill.

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

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] Source #

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

sepBy1 :: MonadPlus m => m a -> m sep -> m [a] Source #

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

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

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

sepEndBy1 :: MonadPlus m => m a -> m sep -> m [a] Source #

sepEndBy1 p sep parses one 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 () Source #

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

See also: manyTill, skipManyTill.

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

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

See also: someTill, skipSomeTill.

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

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

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

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.