| License | BSD-3-Clause |
|---|---|
| Maintainer | Jamie Willis, Gigaparsec Maintainers |
| Stability | stable |
| Safe Haskell | Trustworthy |
| Language | Haskell2010 |
Text.Gigaparsec
Description
This object contains the core combinators and parser type: all parsers will require something from within!
TODO: what is inside it?
Since: 0.1.0.0
Synopsis
- data Parsec a
- data Result a
- parse :: Parsec a -> String -> Result a
- atomic :: Parsec a -> Parsec a
- lookAhead :: Parsec a -> Parsec a
- notFollowedBy :: Parsec a -> Parsec ()
- eof :: Parsec ()
- unit :: Parsec ()
- pure :: Applicative f => a -> f a
- empty :: Alternative f => f a
- ($>) :: Parsec a -> b -> Parsec b
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- (<$) :: Functor f => a -> f b -> f a
- void :: Functor f => f a -> f ()
- (<~>) :: Parsec a -> Parsec b -> Parsec (a, b)
- (<:>) :: Parsec a -> Parsec [a] -> Parsec [a]
- (<*>) :: Applicative f => f (a -> b) -> f a -> f b
- liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c
- (*>) :: Applicative f => f a -> f b -> f b
- (<*) :: Applicative f => f a -> f b -> f a
- (<**>) :: Applicative f => f a -> f (a -> b) -> f b
- (<+>) :: Parsec a -> Parsec b -> Parsec (Either a b)
- (<|>) :: Alternative f => f a -> f a -> f a
- select :: Selective f => f (Either a b) -> f (a -> b) -> f b
- branch :: Selective f => f (Either a b) -> f (a -> c) -> f (b -> c) -> f c
- many :: Alternative f => f a -> f [a]
- some :: Alternative f => f a -> f [a]
- manyl :: (b -> a -> b) -> b -> Parsec a -> Parsec b
- manyr :: (a -> b -> b) -> b -> Parsec a -> Parsec b
- somel :: (b -> a -> b) -> b -> Parsec a -> Parsec b
- somer :: (a -> b -> b) -> b -> Parsec a -> Parsec b
Documentation
Primitive Combinators
These combinators are specific to parser combinators. In one way or another, they influence how a parser consumes input, or under what conditions a parser does or does not fail. These are really important for most practical parsing considerations, although lookAhead is much less well used.
Arguments
| :: Parsec a | the parser, |
| -> Parsec a | a parser that tries |
This combinator parses its argument p, but rolls back any consumed input on failure.
If the parser p succeeds, then atomic p has no effect. However, if p failed,
then any input that it consumed is rolled back. This has two uses: it ensures that
the parser p is all-or-nothing when consuming input, and it allows for
parsers that consume input to backtrack when they fail (with (<|>)). It should be
used for the latter purpose sparingly, however, since excessive backtracking in a
parser can result in much lower efficiency.
>>>parse (string "abc" <|> string "abd") "abd"Failure .. -- first parser consumed a, so no backtrack>>>parse (atomic (string "abc") <|> string "abd") "abd"Success "abd" -- first parser does not consume input on failure now
Since: 0.1.0.0
Arguments
| :: Parsec a | the parser, |
| -> Parsec a | a parser that parses |
This combinator parses its argument p, but does not consume input if it succeeds.
If the parser p succeeds, then lookAhead p will roll back any input consumed
whilst parsing p. If p fails, however, then the whole combinator fails and
any input consumed remains consumed. If this behaviour is not desirable,
consider pairing lookAhead with atomic.
Examples
>>>parse (lookAhead (string "aaa") *> string "aaa") "aaa"Success "aaa">>>parse (lookAhead (string "abc") <|> string "abd" "abd"Failure .. -- lookAhead does not roll back input consumed on failure
Since: 0.1.0.0
Arguments
| :: Parsec a | the parser, |
| -> Parsec () | a parser which fails when |
This combinator parses its argument p, and succeeds when p fails and vice-versa, never consuming
input.
If the parser p succeeds, then notFollowedBy p will fail, consuming no input.
Otherwise, should p fail, then notFollowedBy p will succeed, consuming no input
and returning ().
Examples
One use for this combinator is to allow for "longest-match" behaviour. For instance, keywords are normally only considered keywords if they are not part of some larger valid identifier (i.e. the keyword "if" should not parse successfully given "ifp"). This can be accomplished as follows:
keyword :: String -> Parsec () keyword kw = atomic $ string kw *> notFollowedBy letterOrDigit
Since: 0.1.0.0
Consumptionless Parsers
These combinators and parsers do not consume input: they are the most primitive ways of
producing successes and failures with the minimal possible effect on the parse. They are,
however, reasonably useful; in particular, pure and unit can be put to good use in
injecting results into a parser without needing to consume anything, or mapping another parser.
This parser produces () without having any other effect.
When this parser is ran, no input is required, nor consumed, and the given value will always be successfully returned. It has no other effect on the state of the parser.
Since: 0.1.0.0
Re-exported from Control.Applicative
pure :: Applicative f => a -> f a #
Lift a value.
empty :: Alternative f => f a #
The identity of <|>
Result Changing Combinators
These combinators change the result of the parser they are called on into a value of a different type. This new result value may or may not be derived from the previous result.
Re-exported from Data.Functor
(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 #
An infix synonym for fmap.
The name of this operator is an allusion to $.
Note the similarities between their types:
($) :: (a -> b) -> a -> b (<$>) :: Functor f => (a -> b) -> f a -> f b
Whereas $ is function application, <$> is function
application lifted over a Functor.
Examples
Convert from a to a Maybe Int using Maybe
Stringshow:
>>>show <$> NothingNothing>>>show <$> Just 3Just "3"
Convert from an to an
Either Int IntEither IntString using show:
>>>show <$> Left 17Left 17>>>show <$> Right 17Right "17"
Double each element of a list:
>>>(*2) <$> [1,2,3][2,4,6]
Apply even to the second element of a pair:
>>>even <$> (2,2)(2,True)
void :: Functor f => f a -> f () #
discards or ignores the result of evaluation, such
as the return value of an void valueIO action.
Examples
Replace the contents of a with unit:Maybe Int
>>>void NothingNothing>>>void (Just 3)Just ()
Replace the contents of an
with unit, resulting in an Either Int Int:Either Int ()
>>>void (Left 8675309)Left 8675309>>>void (Right 8675309)Right ()
Replace every element of a list with unit:
>>>void [1,2,3][(),(),()]
Replace the second element of a pair with unit:
>>>void (1,2)(1,())
Discard the result of an IO action:
>>>mapM print [1,2]1 2 [(),()]>>>void $ mapM print [1,2]1 2
Sequencing Combinators
These combinators all combine two parsers in sequence. The first argument of the combinator will be executed first, then the second argument second. The results of both parsers are combined in some way (depending on the individual combinator). If one of the parsers fails, the combinator as a whole fails.
Re-exported from Control.Applicative
(<*>) :: Applicative f => f (a -> b) -> f a -> f b infixl 4 #
Sequential application.
A few functors support an implementation of <*> that is more
efficient than the default one.
Example
Used in combination with (, <$>)( can be used to build a record.<*>)
>>>data MyState = MyState {arg1 :: Foo, arg2 :: Bar, arg3 :: Baz}
>>>produceFoo :: Applicative f => f Foo
>>>produceBar :: Applicative f => f Bar>>>produceBaz :: Applicative f => f Baz
>>>mkState :: Applicative f => f MyState>>>mkState = MyState <$> produceFoo <*> produceBar <*> produceBaz
liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c #
Lift a binary function to actions.
Some functors support an implementation of liftA2 that is more
efficient than the default one. In particular, if fmap is an
expensive operation, it is likely better to use liftA2 than to
fmap over the structure and then use <*>.
This became a typeclass method in 4.10.0.0. Prior to that, it was
a function defined in terms of <*> and fmap.
Example
>>>liftA2 (,) (Just 3) (Just 5)Just (3,5)
(*>) :: Applicative f => f a -> f b -> f b infixl 4 #
Sequence actions, discarding the value of the first argument.
Examples
If used in conjunction with the Applicative instance for Maybe,
you can chain Maybe computations, with a possible "early return"
in case of Nothing.
>>>Just 2 *> Just 3Just 3
>>>Nothing *> Just 3Nothing
Of course a more interesting use case would be to have effectful computations instead of just returning pure values.
>>>import Data.Char>>>import Text.ParserCombinators.ReadP>>>let p = string "my name is " *> munch1 isAlpha <* eof>>>readP_to_S p "my name is Simon"[("Simon","")]
(<*) :: Applicative f => f a -> f b -> f a infixl 4 #
Sequence actions, discarding the value of the second argument.
(<**>) :: Applicative f => f a -> f (a -> b) -> f b infixl 4 #
A variant of <*> with the arguments reversed.
Branching Combinators
These combinators allow for parsing one alternative or another. All of these combinators are left-biased, which means that the left-hand side of the combinator is tried first: the right-hand side of the combinator will only be tried when the left-hand one failed (and did not consume input in the process).
Re-exported from Control.Applicative
(<|>) :: Alternative f => f a -> f a -> f a infixl 3 #
An associative binary operation
Selective Combinators
These combinators will decide which branch to take next based on the result of another parser.
This differs from combinators like (<|>) which make decisions based on the success/failure of
a parser: here the result of a successful parse will direct which option is done.
Re-exported from Control.Selective
branch :: Selective f => f (Either a b) -> f (a -> c) -> f (b -> c) -> f c #
The branch function is a natural generalisation of select: instead of
skipping an unnecessary effect, it chooses which of the two given effectful
functions to apply to a given argument; the other effect is unnecessary. It
is possible to implement branch in terms of select, which is a good
puzzle (give it a try!).
We can also implement select via branch:
selectB :: Selective f => f (Either a b) -> f (a -> b) -> f b selectB x y = branch x y (pure id)
Filtering Combinators
These combinators perform filtering on the results of a parser. This means that, given the result of a parser, they will perform some function on that result, and the success of that function effects whether or not the parser fails.
Folding Combinators
These combinators repeatedly execute a parser (at least zero or one times depending on the specific combinator) until it fails. The results of the successes are then combined together using a folding function. An initial value for the accumulation may be given (for the folds), or the first successful result is the initial accumulator (for the reduces). These are implemented efficiently and do not need to construct any intermediate list with which to store the results.
many :: Alternative f => f a -> f [a] #
Zero or more.
some :: Alternative f => f a -> f [a] #
One or more.