stack-prism-0.1.6: Stack prisms

Safe HaskellSafe
LanguageHaskell98

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.

Stack prisms can 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. cons takes a head x and tail xs from the stack and pushes x : xs onto the stack, or, in the backward direction, tries to take x : xs from the stack and replaces it with its two individual components.

Every constructor has its own stack prism version. You don't have to write them by hand; you can automatically generate them, either using Template Haskell (see module Data.StackPrism.TH) or using GHC generic programming (see module Data.StackPrism.Generic).

stackPrism :: (a -> b) -> (b -> Maybe a) -> StackPrism a b Source #

Construct a prism.

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

Apply a prism in forward direction.

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

Apply a prism in backward direction.

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 h, Eq t) => Eq ((:-) h t) Source # 

Methods

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

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

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

Methods

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

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

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