bff-mono-0.2.3: "Bidirectionalization for Free" for Monomorphic Transformations

Safe HaskellSafe-Inferred

Data.BffMono

Description

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 Either String for the result of bwd).

bwd h s (fwd h s) = Right s
bwd h s v = Right s'  implies fwd h s' = v

Synopsis

Documentation

class Pack conc abs | abs -> conc whereSource

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.

Methods

new :: conc -> absSource

class (Pack conc abs, Monad m, Functor m) => PackM conc abs m whereSource

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.

Methods

liftO :: Eq r => ([conc] -> r) -> [abs] -> m rSource

Lifts conc-level observations to abs level, with recording the examined values and the observed result.

eqSync :: Eq conc => abs -> abs -> m BoolSource

Lifts conc-level equivalence with synchronization

compareSync :: Ord conc => abs -> abs -> m OrderingSource

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 rSource

A special version of liftO for unary observations.

liftO2 :: (PackM conc abs m, Eq r) => (conc -> conc -> r) -> abs -> abs -> m rSource

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 cSource

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.