| License | BSD-3-Clause | 
|---|---|
| Maintainer | Jamie Willis, Gigaparsec Maintainers | 
| Stability | stable | 
| Safe Haskell | Safe | 
| Language | Haskell2010 | 
Text.Gigaparsec.Combinator
Description
This module contains a huge number of pre-made combinators that are very useful for a variety of purposes.
In particular, it contains combinators for: performing a parser iteratively, collecting all the results; querying whether or not any input is left; optionally performing parsers; parsing delimited constructions; handling multiple possible alternatives or parsers to sequence; handling more complex conditional execution; and more.
Since: 0.1.0.0
Synopsis
- manyN :: Int -> Parsec a -> Parsec [a]
- skipMany :: Parsec a -> Parsec ()
- skipSome :: Parsec a -> Parsec ()
- skipManyN :: Int -> Parsec a -> Parsec ()
- count :: Parsec a -> Parsec Int
- count1 :: Parsec a -> Parsec Int
- manyTill :: Parsec a -> Parsec end -> Parsec [a]
- someTill :: Parsec a -> Parsec end -> Parsec [a]
- option :: Parsec a -> Parsec (Maybe a)
- optional :: Parsec a -> Parsec ()
- optionalAs :: b -> Parsec a -> Parsec b
- decide :: Parsec (Maybe a) -> Parsec a
- fromMaybeS :: Parsec a -> Parsec (Maybe a) -> Parsec a
- sepBy :: Parsec a -> Parsec sep -> Parsec [a]
- sepBy1 :: Parsec a -> Parsec sep -> Parsec [a]
- sepEndBy :: Parsec a -> Parsec sep -> Parsec [a]
- sepEndBy1 :: Parsec a -> Parsec sep -> Parsec [a]
- endBy :: Parsec a -> Parsec sep -> Parsec [a]
- endBy1 :: Parsec a -> Parsec sep -> Parsec [a]
- choice :: [Parsec a] -> Parsec a
- sequence :: (Traversable t, Monad m) => t (m a) -> m (t a)
- traverse :: (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b)
- skip :: [Parsec a] -> Parsec ()
- exactly :: Int -> Parsec a -> Parsec [a]
- range :: Int -> Int -> Parsec a -> Parsec [a]
- range_ :: Int -> Int -> Parsec a -> Parsec ()
- countRange :: Int -> Int -> Parsec a -> Parsec Int
- ifS :: Parsec Bool -> Parsec a -> Parsec a -> Parsec a
- whenS :: Parsec Bool -> Parsec () -> Parsec ()
- guardS :: Parsec Bool -> Parsec ()
- whileS :: Parsec Bool -> Parsec ()
Iterative Combinators
These combinators all execute a given parser an unbounded number of times, until either it fails, or another
 parser succeeds, depending on the combinator. Depending on the combinator, all of the results produced by the
 repeated execution of the parser may be returned in a []. These are almost essential for any practical parsing
 task.
Arguments
| :: Int | the minimum number of  | 
| -> Parsec a | the parser  | 
| -> Parsec [a] | a parser that parses  | 
This combinator repeatedly parses a given parser n or more times, collecting the results into a list.
Parses a given parser, p, repeatedly until it fails. If p failed having consumed input,
this combinator fails. Otherwise when p fails without consuming input, this combinator
will return all of the results, x1 through xm (with m >= n), in a list: [x1, .., xm].
If p was not successful at least n times, this combinator fails.
Examples
>>>let p = manyN 2 (string "ab")>>>parse p ""Failure ..>>>parse p "ab"Failure ..>>>parse p "abababab"Success ["ab", "ab", "ab", "ab"]>>>parse p "aba"Failure ..
Notes
- many p == many 0 pand- some p == many 1 p.
Since: 0.1.0.0
Arguments
| :: Parsec a | the parser  | 
| -> Parsec () | a parser that parses  | 
This combinator repeatedly parses a given parser zero or more times, ignoring the results.
Parses a given parser, p, repeatedly until it fails. If p failed having consumed input,
this combinator fails. Otherwise when p fails without consuming input, this combinator
will succeed.
Examples
>>>let p = skipMany (string "ab")>>>parse p ""Success ()>>>parse p "ab"Success ()>>>parse p "abababab"Success ()>>>parse p "aba"Failure ..
Since: 0.1.0.0
Arguments
| :: Parsec a | 
 | 
| -> Parsec () | a parser that parses  | 
This combinator repeatedly parses a given parser one or more times, ignoring the results.
Parses a given parser, p, repeatedly until it fails. If p failed having consumed input,
this combinator fails. Otherwise when p fails without consuming input, this combinator
will succeed. The parser p must succeed at least once.
Examples
>>>let p = skipSome (string "ab")>>>parse p ""Failure ..>>>parse p "ab"Success ()>>>parse p "abababab"Success ()>>>parse p "aba"Failure ..
Since: 0.1.0.0
Arguments
| :: Int | 
 | 
| -> Parsec a | 
 | 
| -> Parsec () | a parser that parses  | 
This combinator repeatedly parses a given parser n or more times, ignoring the results.
Parses a given parser, p, repeatedly until it fails. If p failed having consumed input,
this combinator fails. Otherwise when p fails without consuming input, this combinator
will succeed. The parser p must succeed at least n times.
Examples
>>>let p = skipManyN 2 (string "ab")>>>parse p ""Failure ..>>>parse p "ab"Failure ..>>>parse p "abababab"Success ()>>>parse p "aba"Failure ..
Since: 0.1.0.0
Arguments
| :: Parsec a | 
 | 
| -> Parsec Int | the number of times  | 
This combinator repeatedly parses a given parser zero or more times, returning how many times it succeeded.
Parses a given parser, p, repeatedly until it fails. If p failed having consumed input,
this combinator fails. Otherwise when p fails without consuming input, this combinator
will succeed. The number of times p succeeded is returned as the result.
Examples
>>>let p = count (string "ab")>>>parse p ""Success 0>>>parse p "ab"Success 1>>>parse p "abababab"Success 4>>>parse p "aba"Failure ..
Since: 0.1.0.0
Arguments
| :: Parsec a | 
 | 
| -> Parsec Int | the number of times  | 
This combinator repeatedly parses a given parser one or more times, returning how many times it succeeded.
Parses a given parser, p, repeatedly until it fails. If p failed having consumed input,
this combinator fails. Otherwise when p fails without consuming input, this combinator
will succeed. The parser p must succeed at least once. The number of times p succeeded is returned as the result.
Examples
>>>let p = count1 (string "ab")>>>parse p ""Failure ..>>>parse p "ab"Success 1>>>parse p "abababab"Success 4>>>parse p "aba"Failure ..
Since: 0.1.0.0
Arguments
| :: Parsec a | 
 | 
| -> Parsec end | 
 | 
| -> Parsec [a] | a parser that parses  | 
This combinator repeatedly parses a given parser zero or more times, until the end parser succeeds, collecting the results into a list.
First tries to parse end, if it fails without consuming input, then parses p, which must succeed. This repeats until end succeeds.
When end does succeed, this combinator will return all of the results generated by p, x1 through xn (with n >= 0), in a
list: [x1, .., xn]. If end could be parsed immediately, the empty list is returned.
Examples
This can be useful for scanning comments:
>>> let comment = string "--" *> manyUntil item endOfLine
>>> parse p "--hello world"
Failure ..
>>> parse p "--hello worldn"
Success [h, e, l, l, o, ' ', w, o, r, l, d]
>>> parse p "--n"
Success Nil
Since: 0.1.0.0
Arguments
| :: Parsec a | 
 | 
| -> Parsec end | 
 | 
| -> Parsec [a] | a parser that parses  | 
This combinator repeatedly parses a given parser one or more times, until the end parser succeeds, collecting the results into a list.
First ensures that trying to parse end fails, then tries to parse p. If it succeed then it will repeatedly: try to parse end, if it fails
without consuming input, then parses p, which must succeed. When end does succeed, this combinator will return all of the results
generated by p, x1 through xn (with n >= 1), in a list: [x1, .., xn]. The parser p must succeed at least once
before end succeeds.
Examples
This can be useful for scanning comments:
>>> let comment = string "--" *> someUntil item endOfLine
>>> parse p "--hello world"
Failure ..
>>> parse p "--hello worldn"
Success [h, e, l, l, o, ' ', w, o, r, l, d]
>>> parse p "--n"
Failure ..
>>> parse p "--an"
Success [a]
Since: 0.1.0.0
Optional Parsing Combinators
These combinators allow for the possible parsing of some parser. If the parser succeeds, that is ok so long as it did not consume input. Be aware that the result of the success may be replaced with these combinators, with the exception of "option", which still preserves the result.
This combinator tries to parse p, wrapping its result in a Just if it succeeds, or returns Nothing if it fails.
Tries to parse p. If p succeeded, producing x, then Just x is returned. Otherwise, if p failed
without consuming input, then Nothing is returned instead.
Examples
>>>let p = option (string "abc")>>>parse p ""Success Nothing>>>parse p "abc"Success (Just "abc")>>>parse p "ab"Failure ..
Since: 0.1.0.0
This combinator will parse p if possible, otherwise will do nothing.
Tries to parse p. If p succeeds, or fails without consuming input then this combinator is successful. Otherwise, if p failed
having consumed input, this combinator fails.
Examples
>>>let p = optional (string "abc")>>>parse p ""Success ()>>>parse p "abc"Success ()>>>parse p "ab"Failure ..
Since: 0.1.0.0
Arguments
| :: b | the value  | 
| -> Parsec a | the parser  | 
| -> Parsec b | a parser that tries to parse  | 
This combinator will parse p if possible, otherwise will do nothing.
Tries to parse p. If p succeeds, or fails without consuming input then this combinator is successful and returns x. Otherwise,
if p failed having consumed input, this combinator fails.
Examples
>>>let p = optionalAs 7 (string "abc")>>>parse p ""Success 7>>>parse p "abc"Success 7>>>parse p "ab"Failure ..
Since: 0.1.0.0
Arguments
| :: Parsec (Maybe a) | the parser  | 
| -> Parsec a | a parser that tries to extract the result from  | 
This combinator can eliminate an Maybe from the result of the parser p.
First parse p, if it succeeds returning Just x, then return x. However,
if p fails, or returned Nothing, then this combinator fails.
Examples
decide (option p) = p
Arguments
| :: Parsec a | a parser to execute when  | 
| -> Parsec (Maybe a) | the first parser  | 
| -> Parsec a | a parser that either just parses  | 
This combinator parses q depending only if p returns a Nothing.
First parses p. If p returned Just x, then x is returned.
Otherwise, if p returned Nothing then q is parsed, producing y,
and y is returned. If p or q fails, the combinator fails.
Examples
fromMaybe q (option p) = p | q
Since: 0.1.0.0
Separated Values Combinators
These combinators are concerned with delimited parsing, where one parser is repeated but delimited by another one.
 In each of these cases p is the parser of interest and sep is the delimeter. These combinators mainly differ
 in either the number of ps they require, or exactly where the delimeters are allowed (only between, always
 trailing, or either). In all cases, they return the list of results generated by the repeated parses of p.
Arguments
| :: Parsec a | 
 | 
| -> Parsec sep | 
 | 
| -> Parsec [a] | a parser that parses  | 
This combinator parses zero or more occurrences of p, separated by sep.
Behaves just like sepBy1, except does not require an initial p, returning the empty list instead.
Examples
>>>...>>>let args = sepBy int (string ", ")>>>parse args "7, 3, 2"Success [7, 3, 2]>>>parse args ""Success []>>>parse args "1"Success [1]>>>parse args "1, 2, "Failure ..
Since: 0.1.0.0
Arguments
| :: Parsec a | 
 | 
| -> Parsec sep | 
 | 
| -> Parsec [a] | a parser that parses  | 
This combinator parses one or more occurrences of p, separated by sep.
First parses a p. Then parses sep followed by p until there are no more seps.
The results of the p's, x1 through xn, are returned as [x1, .., xn].
If p or sep fails having consumed input, the whole parser fails. Requires at least
one p to have been parsed.
Examples
>>>...>>>let args = sepBy1 int (string ", ")>>>parse args "7, 3, 2"Success [7, 3, 2]>>>parse args ""Failure ..>>>parse args "1"Success [1]>>>parse args "1, 2, "Failure ..
Since: 0.1.0.0
Arguments
| :: Parsec a | 
 | 
| -> Parsec sep | 
 | 
| -> Parsec [a] | a parser that parses  | 
This combinator parses zero or more occurrences of p, separated and optionally ended by sep.
Behaves just like sepEndBy1, except does not require an initial p, returning the empty list instead.
Examples
>>>...>>>let args = sepEndBy int (string ";\n")>>>parse args "7;\n3;\n2"Success [7, 3, 2]>>>parse args ""Success Nil>>>parse args "1"Success [1]>>>parse args "1;\n2;\n"Success [1, 2]
Since: 0.1.0.0
Arguments
| :: Parsec a | 
 | 
| -> Parsec sep | 
 | 
| -> Parsec [a] | a parser that parses  | 
This combinator parses one or more occurrences of p, separated and optionally ended by sep.
First parses a p. Then parses sep followed by p until there are no more: if a final sep exists, this is parsed.
The results of the p's, x1 through xn, are returned as [x1, .., xn].
If p or sep fails having consumed input, the whole parser fails. Requires at least
one p to have been parsed.
Examples
>>>...>>>let args = sepEndBy1 int (string ";\n")>>>parse args "7;\n3;\n2"Success [7, 3, 2]>>>parse args ""Failure ..>>>parse args "1"Success [1]>>>parse args "1;\n2;\n"Success [1, 2]
Since: 0.1.0.0
Arguments
| :: Parsec a | 
 | 
| -> Parsec sep | 
 | 
| -> Parsec [a] | a parser that parses  | 
This combinator parses zero or more occurrences of p, separated and ended by sep.
Behaves just like endBy1, except does not require an initial p and sep, returning the empty list instead.
Examples
>>>...>>>let args = endBy int (string ";\n")>>>parse args "7;\n3;\n2"Failure ..>>>parse args ""Success Nil>>>parse args "1;\n"Success [1]>>>parse args "1;\n2;\n"Success [1, 2]
Since: 0.1.0.0
Arguments
| :: Parsec a | 
 | 
| -> Parsec sep | 
 | 
| -> Parsec [a] | a parser that parses  | 
This combinator parses one or more occurrences of p, separated and ended by sep.
Parses p followed by sep one or more times.
The results of the p's, x1 through xn, are returned as [x1, .., xn].
If p or sep fails having consumed input, the whole parser fails.
Examples
>>>...>>>let args = endBy1 int (string ";\n")>>>parse args "7;\n3;\n2"Failure ..>>>parse args ""Failure ..>>>parse args "1;\n"Success [1]>>>parse args "1;\n2;\n"Success [1, 2]
Since: 0.1.0.0
Multiple Branching/Sequencing Combinators
These combinators allow for testing or sequencing a large number of parsers in one go.
Arguments
| :: [Parsec a] | the parsers,  | 
| -> Parsec a | a parser that tries to parse one of  | 
This combinator tries to parse each of the parsers ps in order, until one of them succeeds.
Finds the first parser in ps which succeeds, returning its result. If Nothing of the parsers
succeed, then this combinator fails. If a parser fails having consumed input, this combinator
fails immediately.
Examples
>>>let p = choice [string "abc", string "ab", string "bc", string "d"]>>>parse p "abc"Success "abc">>>parse p "ab"Failure ..>>>parse p "bc"Success "bc">>>parse p "x"Failure ..
Since: 0.1.0.0
sequence :: (Traversable t, Monad m) => t (m a) -> m (t a) #
Evaluate each monadic action in the structure from left to
 right, and collect the results. For a version that ignores the
 results see sequence_.
Examples
Basic usage:
The first two examples are instances where the input and
 and output of sequence are isomorphic.
>>>sequence $ Right [1,2,3,4][Right 1,Right 2,Right 3,Right 4]
>>>sequence $ [Right 1,Right 2,Right 3,Right 4]Right [1,2,3,4]
The following examples demonstrate short circuit behavior
 for sequence.
>>>sequence $ Left [1,2,3,4]Left [1,2,3,4]
>>>sequence $ [Left 0, Right 1,Right 2,Right 3,Right 4]Left 0
traverse :: (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b) #
Map each element of a structure to an action, evaluate these actions
 from left to right, and collect the results. For a version that ignores
 the results see traverse_.
Examples
Basic usage:
In the first two examples we show each evaluated action mapping to the output structure.
>>>traverse Just [1,2,3,4]Just [1,2,3,4]
>>>traverse id [Right 1, Right 2, Right 3, Right 4]Right [1,2,3,4]
In the next examples, we show that Nothing and Left values short
 circuit the created structure.
>>>traverse (const Nothing) [1,2,3,4]Nothing
>>>traverse (\x -> if odd x then Just x else Nothing) [1,2,3,4]Nothing
>>>traverse id [Right 1, Right 2, Right 3, Right 4, Left 0]Left 0
Arguments
| :: [Parsec a] | parsers  | 
| -> Parsec () | a parser that parses each of  | 
This combinator will parse each of ps in order, discarding the results.
Given the parsers ps, consisting of p1 through pn, parses
each in order. If they all succeed, this combinator succeeds. If any of
the parsers fail, then the whole combinator fails.
Examples
>>>let p = skip [char'a', item, char 'c']>>>parse p "abc"Success ()>>>parse p "ab"Failure ..
Since: 0.1.0.0
Range Combinators
These combinators allow for the parsing of a specific parser either a specific number of times, or between a certain amount of times.
Arguments
| :: Int | 
 | 
| -> Parsec a | 
 | 
| -> Parsec [a] | a parser that parses  | 
This combinator parses exactly n occurrences of p, returning these n results in a list.
Parses p repeatedly up to n times. If p fails before n is reached, then this combinator
fails. It is not required for p to fail after the nth parse. The results produced by
p, x1 through xn, are returned as [x1, .., xn].
Examples
>>>let p = exactly 3 item>>>parse p "ab"Failure ..>>>parse p "abc"Success ['a', 'b', 'c']>>>parse p "abcd"Success ['a', 'b', 'c']
Since: 0.1.0.0
Arguments
| :: Int | 
 | 
| -> Int | 
 | 
| -> Parsec a | 
 | 
| -> Parsec [a] | the results of the successful parses of  | 
This combinator parses between min and max occurrences of p, returning these n results in a list.
Parses p repeatedly a minimum of min times and up to max times both inclusive. If p fails before
min is reached, then this combinator fails. It is not required for p to fail after the max^th^ parse.
The results produced by p, xmin through xmax, are returned as [xmin, .., xmax].
Examples
>>>let p = range 3 5 item>>>parse p "ab"Failure ..>>>parse p "abc"Success ['a', 'b', 'c']>>>parse p "abcd"Success ['a', 'b', 'c', 'd']>>>parse p "abcde"Success ['a', 'b', 'c', 'd', 'e']>>>parse p "abcdef"Success ['a', 'b', 'c', 'd', 'e']
Since: 0.1.0.0
Arguments
| :: Int | 
 | 
| -> Int | 
 | 
| -> Parsec a | 
 | 
| -> Parsec () | 
This combinator parses between min and max occurrences of p but ignoring the results.
Parses p repeatedly a minimum of min times and up to max times both inclusive. If p fails before
min is reached, then this combinator fails. It is not required for p to fail after the maxth parse.
The results are discarded and () is returned instead.
Examples
>>>let p = range_ 3 5 item>>>parse p "ab"Failure ..>>>parse p "abc"Success ()>>>parse p "abcd"Success ()>>>parse p "abcde"Success ()>>>parse p "abcdef"Success ()
Since: 0.1.0.0
Arguments
| :: Int | 
 | 
| -> Int | 
 | 
| -> Parsec a | 
 | 
| -> Parsec Int | the number of times  | 
This combinator parses between min and max occurrences of p, returning the number of successes.
Parses p repeatedly a minimum of min times and up to max times both inclusive. If p fails before
min is reached, then this combinator fails. It is not required for p to fail after the maxth parse.
The results are discarded and the number of successful parses of p, n, is returned instead, such that
min <= n <= max.
Examples
>>>let p = count 3 5 item>>>parse p "ab"Failure ..>>>parse p "abc"Success 3>>>parse p "abcd"Success 4>>>parse p "abcde"Success 5>>>parse p "abcdef"Success 5
Since: 0.1.0.0
Selective Combinators
These combinators allow for the conditional extraction of a result, or the execution of a parser based on another. They are derived from "branch".
Arguments
| :: Parsec Bool | 
 | 
| -> Parsec a | 
 | 
| -> Parsec a | 
 | 
| -> Parsec a | a parser that conditionally parses  | 
This combinator parses one of thenP or elseP depending on the result of parsing condP.
This is a lifted if-statement. First, parse condP: if it is successful and returns
true, then parse thenP; else, if it returned false, parse elseP; or, if condP failed
then fail. If either of thenP or elseP fail, then this combinator also fails.
Most useful in conjunction with Registers, as this allows for decisions to be made based on state.
Examples
>>>ifP (pure true) p _ == p>>>ifP (pure false) _ p == p
Since: 0.1.0.0
Arguments
| :: Parsec Bool | 
 | 
| -> Parsec () | 
 | 
| -> Parsec () | a parser that conditionally parses  | 
This combinator conditionally parses thenP depending on the result of parsing condP.
This is a lifted if-statement. First, parse condP: if it is successful and returns
true, then parse thenP; else, if it returned false do nothing; or, if condP failed
then fail. If thenP fails, then this combinator also fails.
Most useful in conjunction with Registers, as this allows for decisions to be made based on state.
Examples
>>>when (pure true) p == p>>>when (pure false) _ == unit
Since: 0.1.0.0
This combinator verfies that the given parser returns true, or else fails.
First, parse p; if it succeeds then, so long at returns true, this guard p succeeds. Otherwise,
if p either fails, or returns false, guard p will fail.
Examples
>>>guard (pure true) == unit>>>guard (pure false) == empty>>>when (not <$> p) empty == guard p
Since: 0.1.0.0
Arguments
| :: Parsec Bool | 
 | 
| -> Parsec () | a parser that continues to parse  | 
This combinator repeatedly parses p so long as it returns true.
This is a lifted while-loop. First, parse p: if it is successful and
returns true, then repeat; else if it returned false stop; or, if it
failed then this combinator fails.
Most useful in conjunction with Registers, as this allows for decisions to be made
based on state. In particular, this can be used to define the forP combinator.
Since: 0.1.0.0