| Copyright | © 2017 Mark Karpov | 
|---|---|
| License | BSD 3 clause | 
| Maintainer | Mark Karpov <markkarpov92@gmail.com> | 
| Stability | experimental | 
| Portability | portable | 
| Safe Haskell | Safe | 
| Language | Haskell2010 | 
Control.Applicative.Combinators
Description
The module provides parser combinators defined for instances of
 Applicative and Alternative. It also re-exports functions that are
 commonly used in parsing from Control.Applicative with additional
 parsing-related comments added.
Due to the nature of the Applicative and Alternative abstractions,
 they are prone to memory leaks and not as efficient as their monadic
 counterparts. Although all the combinators we provide in this module are
 perfectly expressible in terms of Applicative and Alternative, please
 prefer Control.Monad.Combinators instead when possible.
If you wish that the combinators that cannot return empty lists return
 values of the NonEmpty data type, use the
 Control.Applicative.Combinators.NonEmpty module.
A note on backtracking
Certain parsing libraries, such as Megaparsec, do not backtrack every
 branch of parsing automatically for the sake of performance and better
 error messages. They typically backtrack only “atomic” parsers, e.g.
 those that match a token or several tokens in a row. To backtrack an
 arbitrary complex parser/branch, a special combinator should be used,
 typically called try. Combinators in this module are defined in terms
 Applicative and Alternative operations. Being quite abstract, they
 cannot know anything about inner workings of any concrete parsing
 library, and so they cannot use try.
The essential feature of the Alternative type class is the (
 operator that allows to express choice. In libraries that do not
 backtrack everything automatically, the choice operator and everything
 that is build on top of it require the parser on the left hand side to
 backtrack in order for the alternative branch of parsing to be tried.
 Thus it is the responsibility of the programmer to wrap more complex,
 composite parsers in <|>)try to achieve correct behavior.
- (<|>) :: Alternative f => forall a. f a -> f a -> f a
- many :: Alternative f => forall a. f a -> f [a]
- some :: Alternative f => forall 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 :: Applicative m => Int -> m a -> m [a]
- count' :: Alternative m => Int -> Int -> m a -> m [a]
- eitherP :: Alternative m => m a -> m b -> m (Either a b)
- endBy :: Alternative m => m a -> m sep -> m [a]
- endBy1 :: Alternative m => m a -> m sep -> m [a]
- manyTill :: Alternative m => m a -> m end -> m [a]
- someTill :: Alternative m => m a -> m end -> m [a]
- option :: Alternative m => a -> m a -> m a
- sepBy :: Alternative m => m a -> m sep -> m [a]
- sepBy1 :: Alternative m => m a -> m sep -> m [a]
- sepEndBy :: Alternative m => m a -> m sep -> m [a]
- sepEndBy1 :: Alternative m => m a -> m sep -> m [a]
- skipMany :: Alternative m => m a -> m ()
- skipSome :: Alternative m => m a -> m ()
- skipCount :: Applicative m => Int -> m a -> m ()
- skipManyTill :: Alternative m => m a -> m end -> m end
- skipSomeTill :: Alternative 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.
many :: Alternative f => forall a. f a -> f [a] #
Zero or more.
many pp zero or more times and returns a list
 of the values returned by p.
identifier = (:) <$> letter <*> many (alphaNumChar <|> char '_')
some :: Alternative f => forall a. f a -> f [a] #
One or more.
some pp one or more times and returns a list
 of the values returned by p.
word = some letter
optional :: Alternative f => f a -> f (Maybe a) #
One or none.
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.
Since: 0.4.0
Original combinators
between :: Applicative m => m open -> m close -> m a -> m a Source #
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 #
choice psps in order,
 until one of them succeeds. Returns the value of the succeeding parser.
choice = asum
count :: Applicative m => Int -> m a -> m [a] Source #
eitherP :: Alternative m => m a -> m b -> m (Either a b) Source #
Combine two alternatives.
eitherP a b = (Left <$> a) <|> (Right <$> b)
endBy :: Alternative m => m a -> m sep -> m [a] Source #
endBy p sepp, separated and
 ended by sep. Returns a list of values returned by p.
cStatements = cStatement `endBy` semicolon
endBy1 :: Alternative m => m a -> m sep -> m [a] Source #
endBy1 p sepp, separated and
 ended by sep. Returns a list of values returned by p.
manyTill :: Alternative m => m a -> m end -> m [a] Source #
manyTill p endp zero or more times until parser
 end succeeds. Returns the list of values returned by p.
See also: skipMany, skipManyTill.
someTill :: Alternative m => m a -> m end -> m [a] Source #
someTill p endmanyTill p endp
 should succeed at least once.
See also: skipSome, skipSomeTill.
option :: Alternative m => a -> m a -> m a Source #
sepBy :: Alternative m => m a -> m sep -> m [a] Source #
sepBy p sepp, separated by
 sep. Returns a list of values returned by p.
commaSep p = p `sepBy` comma
sepBy1 :: Alternative m => m a -> m sep -> m [a] Source #
sepBy1 p sepp, separated by
 sep. Returns a list of values returned by p.
sepEndBy :: Alternative m => m a -> m sep -> m [a] Source #
sepEndBy p sepp, separated
 and optionally ended by sep. Returns a list of values returned by p.
sepEndBy1 :: Alternative m => m a -> m sep -> m [a] Source #
sepEndBy1 p sepp, separated
 and optionally ended by sep. Returns a list of values returned by p.
skipMany :: Alternative m => m a -> m () Source #
skipMany pp zero or more times, skipping
 its result.
See also: manyTill, skipManyTill.
skipSome :: Alternative m => m a -> m () Source #
skipSome pp one or more times, skipping its
 result.
See also: someTill, skipSomeTill.
skipCount :: Applicative m => Int -> m a -> m () Source #
skipManyTill :: Alternative m => m a -> m end -> m end Source #
skipManyTill p endp zero or more times
 skipping results until parser end succeeds. Result parsed by end is
 then returned.
skipSomeTill :: Alternative m => m a -> m end -> m end Source #
skipSomeTill p endp one or more times
 skipping results until parser end succeeds. Result parsed by end is
 then returned.