JsonGrammar-0.3.5: Combinators for bidirectional JSON parsing

Safe HaskellSafe-Inferred

Data.Iso.Core

Contents

Synopsis

Partial isomorphisms

data Iso a b Source

Bidirectional partial isomorphism.

Constructors

Iso (a -> Maybe b) (b -> Maybe a) 

Instances

convert :: Iso a b -> a -> Maybe bSource

Apply an isomorphism in one direction.

inverse :: Iso a b -> Iso b aSource

Inverse of an isomorphism.

many :: Iso a a -> Iso a aSource

Apply an isomorphism as many times as possible, greedily.

Stack-based isomorphisms

data h :- t Source

Heterogenous stack with a head and a tail.

Constructors

h :- t 

Instances

(Eq h, Eq t) => Eq (:- h t) 
(Show h, Show t) => Show (:- h t) 

stack :: Iso a b -> Iso (a :- t) (b :- t)Source

Convert to a stack isomorphism.

unstack :: Iso (a :- ()) (b :- ()) -> Iso a bSource

Convert from a stack isomorphism.

swap :: Iso (a :- (b :- t)) (b :- (a :- t))Source

Swap the top two arguments.

duck :: Iso t1 t2 -> Iso (h :- t1) (h :- t2)Source

Introduce a head value that is passed unmodified.

lit :: Eq a => a -> Iso t (a :- t)Source

Push or pop a specific value.

inverseLit :: Eq a => a -> Iso (a :- t) tSource

Inverse of lit.

matchWithDefault :: (a -> Bool) -> a -> Iso t (a :- t)Source

When converting from left to right, push the default value on top of the stack. When converting from right to left, pop the value, make sure it matches the predicate and then discard it.

ignoreWithDefault :: a -> Iso t (a :- t)Source

When converting from left to right, push the default value on top of the stack. When converting from right to left, pop the value and discard it.