stack-prism-0.1.1: Stack prisms

Safe HaskellSafe
LanguageHaskell98

Data.StackPrism.Generic

Contents

Synopsis

Deriving stack prisms

mkPrismList :: (Generic a, MkPrismList (Rep a)) => StackPrisms a Source

Derive a list of stack prisms. For more information on the shape of a PrismList, please see the documentation below.

type StackPrisms a = PrismList (Rep a) a Source

Convenient shorthand for a PrismList indexed by a type and its generic representation.

data family PrismList f a Source

A data family that is indexed on the building blocks from representation types from GHC.Generics. It builds up to a list of prisms, one for each constructor in the generic representation. The list is wrapped in the unary constructor PrismList. Within that constructor, the prisms are separated by the right-associative binary infix constructor :&. Finally, the individual prisms are wrapped in the unary constructor P.

As an example, here is how to define the prisms nil and cons for [a], which is an instance of Generic:

nil  :: StackPrism              t  ([a] :- t)
cons :: StackPrism (a :- [a] :- t) ([a] :- t)
PrismList (P nil :& P cons) = mkPrismList :: StackPrisms [a]

Instances

data PrismList ((:+:) f g) = (PrismList f a) :& (PrismList g a) Source 
data PrismList (M1 D c f) = PrismList (PrismList f a) Source 
data PrismList (M1 C c f) = P (forall t p f. (Choice p, Applicative f) => p (StackPrismLhs f t) (f (StackPrismLhs f t)) -> p ((:-) a t) (f ((:-) a t))) Source 

Re-exported types from Data.StackPrism

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).

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