parsec2-1.0.1: Monadic parser combinators

Copyright(c) Daan Leijen 1999-2001
LicenseBSD-style (see the file libraries/parsec/LICENSE)
MaintainerAntoine Latter <aslatter@gmail.com>
Stabilityprovisional
Portabilitynon-portable (uses existentially quantified data constructors)
Safe HaskellSafe
LanguageHaskell98

Text.ParserCombinators.Parsec.Perm

Description

This module implements permutation parsers. The algorithm used is fairly complex since we push the type system to its limits :-) 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

Documentation

data PermParser tok st a Source

The type PermParser tok st a denotes a permutation parser that, when converted by the permute function, parses tok tokens with user state st 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.

permute :: PermParser tok st a -> GenParser tok st 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 <$?> ("",many1 (char 'a'))
                        <||> char 'b'
                        <|?> ('_',char 'c'))
       where
         tuple a b c  = (a,b,c)

(<||>) :: PermParser tok st (a -> b) -> GenParser tok st a -> PermParser tok st 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.

(<$$>) :: (a -> b) -> GenParser tok st a -> PermParser tok st 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.

(<|?>) :: PermParser tok st (a -> b) -> (a, GenParser tok st a) -> PermParser tok st 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.

(<$?>) :: (a -> b) -> (a, GenParser tok st a) -> PermParser tok st 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 can not be applied, the default value x will be used instead.