Copyright | © 2015–2017 Megaparsec contributors © 2007 Paolo Martini © 1999–2001 Daan Leijen |
---|---|
License | FreeBSD |
Maintainer | Mark Karpov <markkarpov92@gmail.com> |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Commonly used generic combinators. Note that all the combinators work
with Applicative
and Alternative
instances.
- 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 ()
Documentation
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.
count :: Applicative 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.
count' :: Alternative 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.
eitherP :: Alternative m => m a -> m b -> m (Either a b) Source #
Combine two alternatives.
Since: 4.4.0
endBy :: Alternative 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 :: Alternative 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
.
manyTill :: Alternative 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
. This parser
can be used to scan comments:
simpleComment = string "<!--" >> manyTill anyChar (string "-->")
someTill :: Alternative m => m a -> m end -> m [a] Source #
someTill p end
works similarly to manyTill p end
, but p
should
succeed at least once.
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
.
priority = option 0 (digitToInt <$> digitChar)
sepBy :: Alternative 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 :: Alternative 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 :: Alternative 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 :: Alternative 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 :: Alternative m => m a -> m () Source #
skipMany p
applies the parser p
zero or more times, skipping its
result.
space = skipMany spaceChar
skipSome :: Alternative m => m a -> m () Source #
skipSome p
applies the parser p
one or more times, skipping its
result.