Piso-0.2: Partial isomorphisms

Safe HaskellSafe
LanguageHaskell98

Data.Piso

Contents

Synopsis

Partial isomorphisms

data Piso a b Source #

Bidirectional isomorphism that is total when applied in the forward direction (a -> b), but partial when applied in the backward direction (b -> Maybe a).

This can be used to express constructor-deconstructor pairs. For example:

nil :: Piso t ([a] :- t)
nil = Piso f g
  where
    f        t  = [] :- t
    g ([] :- t) = Just t
    g _         = Nothing

cons :: Piso (a :- [a] :- t) ([a] :- t)
cons = Piso f g
  where
    f (x :- xs  :- t) = (x : xs) :- t
    g ((x : xs) :- t) = Just (x :- xs :- t)
    g _               = Nothing

Here :- can be read as 'cons', forming a stack of values. For example, nil pushes [] onto the stack; or, in the backward direction, tries to remove [] from the stack. Representing constructor-destructor pairs as stack manipulators allows them to be composed more easily.

Module Data.Piso.Common contains Pisos for some common datatypes.

Modules Data.Piso.Generic and Data.Piso.TH offer generic ways of deriving Pisos for custom datatypes.

Constructors

Piso (a -> b) (b -> Maybe a) 

Instances

FromPiso Piso Source # 

Methods

fromPiso :: Piso a b -> Piso a b Source #

Category * Piso Source # 

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

forward :: Piso a b -> a -> b Source #

Apply an isomorphism in forward direction.

backward :: Piso a b -> b -> Maybe a Source #

Apply an isomorphism in backward direction.

class Category cat => FromPiso cat where Source #

A type class that expresses that a category is able to embed Piso values.

Minimal complete definition

fromPiso

Methods

fromPiso :: Piso a b -> cat a b Source #

Instances

FromPiso Piso Source # 

Methods

fromPiso :: Piso a b -> Piso a b Source #

data h :- t infixr 5 Source #

Heterogenous stack with a head and a tail. Or: an infix way to write (,).

Constructors

h :- t infixr 5 

Instances

Functor ((:-) h) Source # 

Methods

fmap :: (a -> b) -> (h :- a) -> h :- b #

(<$) :: a -> (h :- b) -> h :- a #

(Eq t, Eq h) => Eq ((:-) h t) Source # 

Methods

(==) :: (h :- t) -> (h :- t) -> Bool #

(/=) :: (h :- t) -> (h :- t) -> Bool #

(Show t, Show h) => Show ((:-) h t) Source # 

Methods

showsPrec :: Int -> (h :- t) -> ShowS #

show :: (h :- t) -> String #

showList :: [h :- t] -> ShowS #