Copyright | © 2015–2016 Megaparsec contributors © 2007 Paolo Martini © 1999–2001 Daan Leijen |
---|---|
License | FreeBSD |
Maintainer | Mark Karpov <markkarpov@opmbx.org> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
This module implements permutation parsers. The algorithm is described in: Parsing Permutation Phrases, by Arthur Baars, Andres Loh and Doaitse Swierstra. Published as a functional pearl at the Haskell Workshop 2001.
- data PermParser s m a
- makePermParser :: MonadParsec s m t => PermParser s m a -> m a
- (<$$>) :: MonadParsec s m t => (a -> b) -> m a -> PermParser s m b
- (<$?>) :: MonadParsec s m t => (a -> b) -> (a, m a) -> PermParser s m b
- (<||>) :: MonadParsec s m t => PermParser s m (a -> b) -> m a -> PermParser s m b
- (<|?>) :: MonadParsec s m t => PermParser s m (a -> b) -> (a, m a) -> PermParser s m b
Documentation
data PermParser s m a Source
The type PermParser s m a
denotes a permutation parser that,
when converted by the makePermParser
function, produces instance of
MonadParsec
m
that parses s
stream and returns a value of type a
on success.
Normally, a permutation parser is first build with special operators like
(<||>
) and than transformed into a normal parser using
makePermParser
.
makePermParser :: MonadParsec s m t => PermParser s m a -> m a Source
The parser makePermParser perm
parses a permutation of parser described
by perm
. For example, suppose we want to parse a permutation of: an
optional string of a
's, the character b
and an optional c
. This can
be described by:
test = makePermParser $ (,,) <$?> ("", some (char 'a')) <||> char 'b' <|?> ('_', char 'c')
(<$$>) :: MonadParsec s m t => (a -> b) -> m a -> PermParser s m b infixl 2 Source
The expression f <$$> p
creates a fresh permutation parser
consisting of parser p
. The the final result of the permutation parser
is the function f
applied to the return value of p
. The parser p
is
not allowed to accept empty input — use the optional combinator (<$?>
)
instead.
If the function f
takes more than one parameter, the type variable b
is instantiated to a functional type which combines nicely with the adds
parser p
to the (<||>
) combinator. This results in stylized code
where a permutation parser starts with a combining function f
followed
by the parsers. The function f
gets its parameters in the order in
which the parsers are specified, but actual input can be in any order.
(<$?>) :: MonadParsec s m t => (a -> b) -> (a, m a) -> PermParser s m b infixl 2 Source
The expression f <$?> (x, p)
creates a fresh permutation parser
consisting of parser p
. The the final result of the permutation parser
is the function f
applied to the return value of p
. The parser p
is
optional — if it cannot be applied, the default value x
will be used
instead.
(<||>) :: MonadParsec s m t => PermParser s m (a -> b) -> m a -> PermParser s m b infixl 1 Source
The expression perm <||> p
adds parser p
to the permutation
parser perm
. The parser p
is not allowed to accept empty input — use
the optional combinator (<|?>
) instead. Returns a new permutation
parser that includes p
.
(<|?>) :: MonadParsec s m t => PermParser s m (a -> b) -> (a, m a) -> PermParser s m b infixl 1 Source
The expression perm <||> (x, p)
adds parser p
to the
permutation parser perm
. The parser p
is optional — if it cannot be
applied, the default value x
will be used instead. Returns a new
permutation parser that includes the optional parser p
.