stack-prism-0.1: Stack prisms

Safe HaskellNone

Data.StackPrism

Contents

Synopsis

Stack prisms

type StackPrism a b = forall p f. (Choice p, Applicative f) => p a (f a) -> p b (f b)Source

A stack prism is a bidirectional isomorphism that is partial in the backward direction. These prisms are compatible with the lens library.

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

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

 cons :: StackPrism (a :- [a] :- t) ([a] :- t)
 cons = stackPrism 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.

Modules Data.StackPrism.Generic and Data.StackPrism.TH offer generic ways of deriving StackPrisms for custom datatypes.

stackPrism :: (a -> b) -> (b -> Maybe a) -> StackPrism a bSource

Construct a prism.

forward :: StackPrism a b -> a -> bSource

Apply a prism in forward direction.

backward :: StackPrism a b -> b -> Maybe aSource

Apply a prism in backward direction.

data h :- t Source

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

Constructors

h :- t 

Instances

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