boomerang-1.4.1: Library for invertible parsing and printing

Safe HaskellNone

Text.Boomerang.Combinators

Description

a collection of generic parsing combinators that can work with any token and error type.

Synopsis

Documentation

(<>) :: Monoid m => m -> m -> m

An infix synonym for mappend.

duck :: Boomerang e tok r1 r2 -> Boomerang e tok (h :- r1) (h :- r2)Source

Convert a router to do what it does on the tail of the stack.

duck1 :: Boomerang e tok r1 (a :- r2) -> Boomerang e tok (h :- r1) (a :- (h :- r2))Source

Convert a router to do what it does on the tail of the stack.

opt :: Boomerang e tok r r -> Boomerang e tok r rSource

Make a router optional.

manyr :: Boomerang e tok r r -> Boomerang e tok r rSource

Repeat a router zero or more times, combining the results from left to right.

somer :: Boomerang e tok r r -> Boomerang e tok r rSource

Repeat a router one or more times, combining the results from left to right.

chainr :: Boomerang e tok r r -> Boomerang e tok r r -> Boomerang e tok r rSource

chainr p op repeats p zero or more times, separated by op. The result is a right associative fold of the results of p with the results of op.

chainr1 :: Boomerang e tok r (a :- r) -> Boomerang e tok (a :- (a :- r)) (a :- r) -> Boomerang e tok r (a :- r)Source

chainr1 p op repeats p one or more times, separated by op. The result is a right associative fold of the results of p with the results of op.

manyl :: Boomerang e tok r r -> Boomerang e tok r rSource

Repeat a router zero or more times, combining the results from right to left.

somel :: Boomerang e tok r r -> Boomerang e tok r rSource

Repeat a router one or more times, combining the results from right to left.

chainl :: Boomerang e tok r r -> Boomerang e tok r r -> Boomerang e tok r rSource

chainl1 p op repeats p zero or more times, separated by op. The result is a left associative fold of the results of p with the results of op.

chainl1 :: Boomerang e tok r (a :- r) -> Boomerang e tok (a :- (a :- r)) (a :- r) -> Boomerang e tok r (a :- r)Source

chainl1 p op repeats p one or more times, separated by op. The result is a left associative fold of the results of p with the results of op.

rFilter :: (a -> Bool) -> Boomerang e tok () (a :- ()) -> Boomerang e tok r (a :- r)Source

Filtering on routers.

TODO: We remove any parse errors, not sure if the should be preserved. Also, if the predicate fails we silently remove the element, but perhaps we should replace the value with an error message?

printAs :: Boomerang e [tok] a b -> tok -> Boomerang e [tok] a bSource

r `printAs` s uses ther serializer of r to test if serializing succeeds, and if it does, instead serializes as s.

TODO: can this be more general so that it can work on tok instead of [tok]

push :: (Eq a, Error e) => a -> Boomerang e tok r (a :- r)Source

Push a value on the stack (during parsing, pop it from the stack when serializing).

rNil :: Boomerang e tok r ([a] :- r)Source

rCons :: Boomerang e tok (a :- ([a] :- r)) ([a] :- r)Source

rList :: Boomerang e tok r (a :- r) -> Boomerang e tok r ([a] :- r)Source

Converts a router for a value a to a router for a list of a.

rList1 :: Boomerang e tok r (a :- r) -> Boomerang e tok r ([a] :- r)Source

Converts a router for a value a to a router for a list of a.

rListSep :: Boomerang e tok r (a :- r) -> Boomerang e tok ([a] :- r) ([a] :- r) -> Boomerang e tok r ([a] :- r)Source

Converts a router for a value a to a router for a list of a, with a separator.

rPair :: Boomerang e tok (f :- (s :- r)) ((f, s) :- r)Source

rLeft :: forall tok e r a b. Boomerang e tok (:- a r) (:- (Either a b) r)Source

rRight :: forall tok e r a b. Boomerang e tok (:- b r) (:- (Either a b) r)Source

rEither :: Boomerang e tok r (a :- r) -> Boomerang e tok r (b :- r) -> Boomerang e tok r (Either a b :- r)Source

Combines a router for a value a and a router for a value b into a router for Either a b.

rNothing :: forall tok e r a. Boomerang e tok r (:- (Maybe a) r)Source

rJust :: forall tok e r a. Boomerang e tok (:- a r) (:- (Maybe a) r)Source

rMaybe :: Boomerang e tok r (a :- r) -> Boomerang e tok r (Maybe a :- r)Source

Converts a router for a value a to a router for a Maybe a.

rTrue :: forall tok e r. Boomerang e tok r (:- Bool r)Source

rFalse :: forall tok e r. Boomerang e tok r (:- Bool r)Source

rBoolSource

Arguments

:: Boomerang e tok a r

True parser

-> Boomerang e tok a r

False parser

-> Boomerang e tok a (Bool :- r) 

rUnit :: Boomerang e tok r (() :- r)Source