Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
The module provides an automatic way to construct a bidirectional transformation (rougly speaking, a getter/setter pair) from a uni-directional transformation (or, a getter function).
The module provides a class PackM
. Once we write a transformation of type
h :: (Traversable src, Traversable tgt) => forall a m.PackM c a m => src a -> m (tgt a)
then applying fwd
to obtain a forward transformation (so-called "get" or "getter")
fwd h :: src c -> tgt c
and applying bwd
to obtain a backward transformation (so-called "put" or "setter").
bwd h :: (MonadError e m, Error e) => src c -> tgt c -> m (src c)
assuming that c
is some concrete type and src
and tgt
are some
concrete containers (Traversable
instances) with Eq c
and Eq (tgt ())
.
The correctness of the obtained bidirectional transformation
(GetPut and PutGet) is guaranted for free. That is, the following laws hold
(assuming that we use
for the result of Either
String
bwd
).
bwd h s (fwd h s) = Right s
bwd h s v = Right s' implies fwd h s' = v
- class Pack conc abs | abs -> conc where
- new :: conc -> abs
- class (Pack conc abs, Monad m, Functor m) => PackM conc abs m where
- liftO1 :: (PackM conc abs m, Eq r) => (conc -> r) -> abs -> m r
- liftO2 :: (PackM conc abs m, Eq r) => (conc -> conc -> r) -> abs -> abs -> m r
- fwd :: (Traversable vf, Traversable sf) => (forall a m. PackM c a m => sf a -> m (vf a)) -> sf c -> vf c
- bwd :: (Eq (vf ()), Traversable vf, Traversable sf, Eq c, MonadError e n, Error e) => (forall a m. PackM c a m => sf a -> m (vf a)) -> sf c -> vf c -> n (sf c)
Documentation
class Pack conc abs | abs -> conc where Source
Pack conc abs
provides a way to abstract conc
by abs
.
The class is used just as an interface. Thus, no instances
are provided by this package.
class (Pack conc abs, Monad m, Functor m) => PackM conc abs m where Source
PackM
is the interface for our bidirectionalization.
See also fwd
and bwd
.
PackM conc abs monad
provides a way to abstract conc
by abs
,
with recording "observations" through monad
.
Similarly to Pack
, this class is also used just as an interface.
Thus, no instances are provided by this package.
liftO :: Eq r => ([conc] -> r) -> [abs] -> m r Source
Lifts conc
-level observations to abs
level, with
recording the examined values and the observed result.
eqSync :: Eq conc => abs -> abs -> m Bool Source
Lifts conc
-level equivalence with synchronization
compareSync :: Ord conc => abs -> abs -> m Ordering Source
Lifts conc
-level ordering.
It synchronizes the elements if the comparison result is EQ
liftO1 :: (PackM conc abs m, Eq r) => (conc -> r) -> abs -> m r Source
A special version of liftO
for unary observations.
liftO2 :: (PackM conc abs m, Eq r) => (conc -> conc -> r) -> abs -> abs -> m r Source
A special version of liftO
for binary observations.
fwd :: (Traversable vf, Traversable sf) => (forall a m. PackM c a m => sf a -> m (vf a)) -> sf c -> vf c Source
Constructs a forward transformation (or, "get" or "getter") from a given function.
bwd :: (Eq (vf ()), Traversable vf, Traversable sf, Eq c, MonadError e n, Error e) => (forall a m. PackM c a m => sf a -> m (vf a)) -> sf c -> vf c -> n (sf c) Source
Constructs a backward transformation (or, "put" or "setter") from a given function.