Copyright | (c) Edward Kmett 2011-2012 (c) Paolo Martini 2007 (c) Daan Leijen 1999-2001 |
---|---|
License | BSD-style |
Maintainer | ekmett@gmail.com |
Stability | provisional |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
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.
Synopsis
- data Permutation m a
- permute :: forall m a. Alternative m => Permutation m a -> m a
- (<||>) :: Functor m => Permutation m (a -> b) -> m a -> Permutation m b
- (<$$>) :: Functor m => (a -> b) -> m a -> Permutation m b
- (<|?>) :: Functor m => Permutation m (a -> b) -> (a, m a) -> Permutation m b
- (<$?>) :: Functor m => (a -> b) -> (a, m a) -> Permutation m b
Documentation
data Permutation m a Source #
The type Permutation m a
denotes a permutation parser that,
when converted by the permute
function, parses
using the base parsing monad m
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 permute
.
Instances
Functor m => Functor (Permutation m) Source # | |
Defined in Text.Parser.Permutation fmap :: (a -> b) -> Permutation m a -> Permutation m b # (<$) :: a -> Permutation m b -> Permutation m a # |
permute :: forall m a. Alternative m => Permutation m a -> m a Source #
The parser permute 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 = permute (tuple <$?> ("",some (char 'a')) <||> char 'b' <|?> ('_',char 'c')) where tuple a b c = (a,b,c)
(<||>) :: Functor m => Permutation m (a -> b) -> m a -> Permutation 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
.
(<$$>) :: Functor m => (a -> b) -> m a -> Permutation m b infixl 2 Source #
The expression f <$$> p
creates a fresh permutation parser
consisting of parser p
. 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.
(<|?>) :: Functor m => Permutation m (a -> b) -> (a, m a) -> Permutation 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 can
not be applied, the default value x
will be used instead. Returns
a new permutation parser that includes the optional parser p
.
(<$?>) :: Functor m => (a -> b) -> (a, m a) -> Permutation m b infixl 2 Source #
The expression f <$?> (x,p)
creates a fresh permutation parser
consisting of parser p
. 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 can not be applied, the default value
x
will be used instead.