boomerang-1.4.8.1: Library for invertible parsing and printing
Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.Boomerang.Prim

Synopsis

Types

newtype Parser e tok a Source #

Yet another parser.

Returns all possible parses and parse errors

Constructors

Parser 

Fields

Instances

Instances details
Alternative (Parser e tok) Source # 
Instance details

Defined in Text.Boomerang.Prim

Methods

empty :: Parser e tok a #

(<|>) :: Parser e tok a -> Parser e tok a -> Parser e tok a #

some :: Parser e tok a -> Parser e tok [a] #

many :: Parser e tok a -> Parser e tok [a] #

Applicative (Parser e tok) Source # 
Instance details

Defined in Text.Boomerang.Prim

Methods

pure :: a -> Parser e tok a #

(<*>) :: Parser e tok (a -> b) -> Parser e tok a -> Parser e tok b #

liftA2 :: (a -> b -> c) -> Parser e tok a -> Parser e tok b -> Parser e tok c #

(*>) :: Parser e tok a -> Parser e tok b -> Parser e tok b #

(<*) :: Parser e tok a -> Parser e tok b -> Parser e tok a #

Functor (Parser e tok) Source # 
Instance details

Defined in Text.Boomerang.Prim

Methods

fmap :: (a -> b) -> Parser e tok a -> Parser e tok b #

(<$) :: a -> Parser e tok b -> Parser e tok a #

Monad (Parser e tok) Source # 
Instance details

Defined in Text.Boomerang.Prim

Methods

(>>=) :: Parser e tok a -> (a -> Parser e tok b) -> Parser e tok b #

(>>) :: Parser e tok a -> Parser e tok b -> Parser e tok b #

return :: a -> Parser e tok a #

MonadPlus (Parser e tok) Source # 
Instance details

Defined in Text.Boomerang.Prim

Methods

mzero :: Parser e tok a #

mplus :: Parser e tok a -> Parser e tok a -> Parser e tok a #

data Boomerang e tok a b Source #

A Boomerang a b takes an a to parse a URL and results in b if parsing succeeds. And it takes a b to serialize to a URL and results in a if serializing succeeds.

Constructors

Boomerang 

Fields

  • prs :: Parser e tok (a -> b)
     
  • ser :: b -> [(tok -> tok, a)]
     

Instances

Instances details
Category (Boomerang e tok :: TYPE LiftedRep -> Type -> Type) Source # 
Instance details

Defined in Text.Boomerang.Prim

Methods

id :: forall (a :: k). Boomerang e tok a a #

(.) :: forall (b :: k) (c :: k) (a :: k). Boomerang e tok b c -> Boomerang e tok a b -> Boomerang e tok a c #

a ~ b => IsString (Boomerang StringError String a b) Source # 
Instance details

Defined in Text.Boomerang.String

a ~ b => IsString (Boomerang StringsError [String] a b) Source # 
Instance details

Defined in Text.Boomerang.Strings

a ~ b => IsString (Boomerang TextsError [Text] a b) Source # 
Instance details

Defined in Text.Boomerang.Texts

Monoid (Boomerang e tok a b) Source # 
Instance details

Defined in Text.Boomerang.Prim

Methods

mempty :: Boomerang e tok a b #

mappend :: Boomerang e tok a b -> Boomerang e tok a b -> Boomerang e tok a b #

mconcat :: [Boomerang e tok a b] -> Boomerang e tok a b #

Semigroup (Boomerang e tok a b) Source # 
Instance details

Defined in Text.Boomerang.Prim

Methods

(<>) :: Boomerang e tok a b -> Boomerang e tok a b -> Boomerang e tok a b #

sconcat :: NonEmpty (Boomerang e tok a b) -> Boomerang e tok a b #

stimes :: Integral b0 => b0 -> Boomerang e tok a b -> Boomerang e tok a b #

type PrinterParser = Boomerang Source #

Deprecated: Use Boomerang instead

(.~) :: Boomerang e tok a b -> Boomerang e tok b c -> Boomerang e tok a c infixr 9 Source #

Reverse composition, but with the side effects still in left-to-right order.

Running routers

parse :: forall e a p tok. InitialPosition e => Boomerang e tok () a -> tok -> [Either e (a, tok)] Source #

Give all possible parses or errors.

parse1 :: (ErrorPosition e, InitialPosition e, Show e, Ord (Pos e)) => (tok -> Bool) -> Boomerang e tok () (a :- ()) -> tok -> Either [e] a Source #

Give the first parse, for Boomerangs with a parser that yields just one value. Otherwise return the error (or errors) with the highest error position.

unparse :: tok -> Boomerang e tok () url -> url -> [tok] Source #

Give all possible serializations.

unparse1 :: tok -> Boomerang e tok () (a :- ()) -> a -> Maybe tok Source #

Give the first serialization, for Boomerangs with a serializer that needs just one value.

bestErrors :: (ErrorPosition e, Ord (Pos e)) => [e] -> [e] Source #

Attempt to extract the most relevant errors from a list of parse errors.

The current heuristic is to find error (or errors) where the error position is highest.

Constructing / Manipulating Boomerangs

xpure :: (a -> b) -> (b -> Maybe a) -> Boomerang e tok a b Source #

Lift a constructor-destructor pair to a pure router.

val :: forall e tok a r. Parser e tok a -> (a -> [tok -> tok]) -> Boomerang e tok r (a :- r) Source #

lift a Parser and a printer into a Boomerang

xmap :: (a -> b) -> (b -> Maybe a) -> Boomerang e tok r a -> Boomerang e tok r b Source #

Map over routers.

xmaph :: (a -> b) -> (b -> Maybe a) -> Boomerang e tok i (a :- o) -> Boomerang e tok i (b :- o) Source #

Like "xmap", but only maps over the top of the stack.