Copyright | © 2017–2018 Mark Karpov |
---|---|
License | BSD 3 clause |
Maintainer | Mark Karpov <markkarpov92@gmail.com> |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
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
- (<|>) :: Alternative f => forall a. f a -> f a -> f a
- optional :: Alternative f => f a -> f (Maybe a)
- empty :: Alternative f => forall a. f a
- between :: Applicative m => m open -> m close -> m a -> m a
- choice :: (Foldable f, Alternative m) => f (m a) -> m a
- count :: Monad m => Int -> m a -> m [a]
- count' :: MonadPlus m => Int -> Int -> m a -> m [a]
- eitherP :: Alternative m => m a -> m b -> m (Either a b)
- endBy :: MonadPlus m => m a -> m sep -> m [a]
- endBy1 :: MonadPlus m => m a -> m sep -> m [a]
- many :: MonadPlus m => m a -> m [a]
- manyTill :: MonadPlus m => m a -> m end -> m [a]
- some :: MonadPlus m => m a -> m [a]
- someTill :: MonadPlus m => m a -> m end -> m [a]
- option :: Alternative m => a -> m a -> m a
- sepBy :: MonadPlus m => m a -> m sep -> m [a]
- sepBy1 :: MonadPlus m => m a -> m sep -> m [a]
- sepEndBy :: MonadPlus m => m a -> m sep -> m [a]
- sepEndBy1 :: MonadPlus m => m a -> m sep -> m [a]
- skipMany :: MonadPlus m => m a -> m ()
- skipSome :: MonadPlus m => m a -> m ()
- skipCount :: Monad m => Int -> m a -> m ()
- skipManyTill :: MonadPlus m => m a -> m end -> m end
- skipSomeTill :: MonadPlus m => m a -> m end -> m end
Re-exports from Control.Applicative
(<|>) :: Alternative f => forall a. f a -> f a -> f a infixl 3 #
An associative binary operation
This combinator implements choice. The parser p
first applies
<|>
qp
. 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.
tries to apply the parser optional
pp
. 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 => forall a. 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 #
parses between
open close popen
, 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 #
tries to apply the parsers in the list choice
psps
in order,
until one of them succeeds. Returns the value of the succeeding parser.
choice = asum
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 #
parses zero or more occurrences of endBy
p sepp
, 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 #
parses one or more occurrences of endBy1
p sepp
, separated and
ended by sep
. Returns a list of values returned by p
.
many :: MonadPlus m => m a -> m [a] Source #
applies the parser many
pp
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 #
applies parser manyTill
p endp
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 #
applies the parser some
pp
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 #
works similarly to someTill
p end
, but manyTill
p endp
should succeed at least once.
See also: skipSome
, skipSomeTill
.
option :: Alternative m => a -> m a -> m a Source #
sepBy :: MonadPlus m => m a -> m sep -> m [a] Source #
parses zero or more occurrences of sepBy
p sepp
, 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 #
parses one or more occurrences of sepBy1
p sepp
, separated by
sep
. Returns a list of values returned by p
.
sepEndBy :: MonadPlus m => m a -> m sep -> m [a] Source #
parses zero or more occurrences of sepEndBy
p sepp
, separated
and optionally ended by sep
. Returns a list of values returned by p
.
sepEndBy1 :: MonadPlus m => m a -> m sep -> m [a] Source #
parses one or more occurrences of sepEndBy1
p sepp
, separated
and optionally ended by sep
. Returns a list of values returned by p
.
skipMany :: MonadPlus m => m a -> m () Source #
applies the parser skipMany
pp
zero or more times, skipping
its result.
See also: manyTill
, skipManyTill
.
skipSome :: MonadPlus m => m a -> m () Source #
applies the parser skipSome
pp
one or more times, skipping its
result.
See also: someTill
, skipSomeTill
.
skipManyTill :: MonadPlus m => m a -> m end -> m end Source #
applies the parser skipManyTill
p endp
zero or more times
skipping results until parser end
succeeds. Result parsed by end
is
then returned.
skipSomeTill :: MonadPlus m => m a -> m end -> m end Source #
applies the parser skipSomeTill
p endp
one or more times
skipping results until parser end
succeeds. Result parsed by end
is
then returned.