| Safe Haskell | Safe | 
|---|---|
| Language | Haskell98 | 
Data.Generics.Multiplate
Description
Suppose we are given mutually recursive data types A, B, and C.
 Here are some definitions of terms.
- child
- A maximal subexpression of A,B, orC. A child does not necessarily have to have the same type as the parent.Amight have some children of typeBand other children of typeCor evenA.
- children
- A list of all children. In particular children are ordered from left to right.
- descendant
- Any subexpression of of A,B, orC. Specifically a descendant of an expression is either the expression itself or a descendant of one of its children.
- family
- A list of all descendant.
 The order is a context dependent.
 preorderFolduses preorder, whilepostorderFoldandmapFamilyMuses postorder.
- plate
- A plate is a record parametrized by a functor fwith one field of typeA -> f Afor each type belonging to the mutually recursive set of types. For example, a plate forA,B, andCwould look like
data ABCPlate f = ABCPlate
                { fieldA :: A -> f A
                , fieldB :: B -> f B
                , fieldC :: C -> f C
                }
Although this above is the original motivation behind multiplate,but you can make
 any structure you want into a Multiplate as long as you satisfy the two multiplate laws listed
 below.
The names of the functions in this module are based on Sebastian Fischer's Refactoring Uniplate: http://www-ps.informatik.uni-kiel.de/~sebf/projects/traversal.html
- type Projector p a = forall f. p f -> a -> f a
- class Multiplate p where- multiplate :: Applicative f => p f -> p f
- mkPlate :: (forall a. Projector p a -> a -> f a) -> p f
 
- applyNaturalTransform :: forall p f g. Multiplate p => (forall a. f a -> g a) -> p f -> p g
- purePlate :: (Multiplate p, Applicative f) => p f
- emptyPlate :: (Multiplate p, Alternative f) => p f
- kleisliComposePlate :: forall p m. (Multiplate p, Monad m) => p m -> p m -> p m
- composePlate :: forall p f g. (Multiplate p, Functor g) => p f -> p g -> p (Compose g f)
- composePlateRightId :: forall p f. Multiplate p => p f -> p Identity -> p f
- composePlateLeftId :: forall p f. (Multiplate p, Functor f) => p Identity -> p f -> p f
- appendPlate :: forall p o. (Multiplate p, Monoid o) => p (Constant o) -> p (Constant o) -> p (Constant o)
- mChildren :: forall p o. (Multiplate p, Monoid o) => p (Constant o) -> p (Constant o)
- preorderFold :: forall p o. (Multiplate p, Monoid o) => p (Constant o) -> p (Constant o)
- postorderFold :: forall p o. (Multiplate p, Monoid o) => p (Constant o) -> p (Constant o)
- mapChildren :: Multiplate p => p Identity -> p Identity
- mapFamily :: Multiplate p => p Identity -> p Identity
- mapChildrenM :: (Multiplate p, Applicative m, Monad m) => p m -> p m
- mapFamilyM :: (Multiplate p, Applicative m, Monad m) => p m -> p m
- evalFamily :: Multiplate p => p Maybe -> p Identity
- evalFamilyM :: forall p m. (Multiplate p, Applicative m, Monad m) => p (MaybeT m) -> p m
- always :: Multiplate p => p Maybe -> p Identity
- alwaysM :: forall p f. (Multiplate p, Functor f) => p (MaybeT f) -> p f
- traverseFor :: Multiplate p => Projector p a -> p Identity -> a -> a
- traverseMFor :: (Multiplate p, Monad m) => Projector p a -> p m -> a -> m a
- foldFor :: Multiplate p => Projector p a -> p (Constant o) -> a -> o
- unwrapFor :: Multiplate p => (o -> b) -> Projector p a -> p (Constant o) -> a -> b
- sumFor :: Multiplate p => Projector p a -> p (Constant (Sum n)) -> a -> n
- productFor :: Multiplate p => Projector p a -> p (Constant (Product n)) -> a -> n
- allFor :: Multiplate p => Projector p a -> p (Constant All) -> a -> Bool
- anyFor :: Multiplate p => Projector p a -> p (Constant Any) -> a -> Bool
- firstFor :: Multiplate p => Projector p a -> p (Constant (First b)) -> a -> Maybe b
- lastFor :: Multiplate p => Projector p a -> p (Constant (Last b)) -> a -> Maybe b
Documentation
type Projector p a = forall f. p f -> a -> f a Source
A plate over f consists of several fields of type A -> f A for various As.
 Projector is the type of the projection functions of plates. 
class Multiplate p where Source
A Multiplate is a constructor of kind (* -> *) -> * operating on Applicative functors
 having functions multiplate and mkPlate that satisfy the following two laws:
- multiplate- purePlate=- purePlatewhere- purePlate=- mkPlate(\_ ->- pure)
- multiplate(- composePlatep1 p2) =- composePlate(- multiplatep1) (- multiplatep2) where- composePlatep1 p2 =- mkPlate(\proj a -> (- Compose(proj p1 `- fmap` proj p2 a)))
Note: By parametricity, it suffices for (1) to prove
multiplate(mkPlate(\_ ->Identity)) =mkPlate(\_ ->Identity)
Methods
multiplate :: Applicative f => p f -> p f Source
This is the heart of the Multiplate library.  Given a plate of functions over some
 applicative functor f, create a new plate that applies these functions to the children
 of each data type in the plate.
This process essentially defines the semantics what the children of these data types are.
 They don't have to literally be the syntactic children.  For example, if a language supports
 quoted syntax, that quoted syntax behaves more like a literal than as a sub-expression.
 Therefore, although quoted expressions may syntactically be subexpressions, the user may
 chose to implement multiplate so that they are not semantically considered subexpressions.
mkPlate :: (forall a. Projector p a -> a -> f a) -> p f Source
Given a generic builder creating an a -> f a, use the builder to construct each field
 of the plate p f.  The builder may need a little help to construct a field of type
 a -> f a, so to help out the builder pass it the projection function for the field
 being built.
e.g. Given a plate of type
data ABCPlate f = ABCPlate {
                { fieldA :: A -> f B
                , fieldB :: B -> f B
                , fieldC :: C -> f C
                }
the instance of mkPlate for ABCPlate should be
 mkPlate builder = ABCPlate (builder fieldA) (builder fieldB) (builder fieldC)
applyNaturalTransform :: forall p f g. Multiplate p => (forall a. f a -> g a) -> p f -> p g Source
Given a natural transformation between two functors, f and g, and a plate over
 f, compose the natural transformation with each field of the plate.
purePlate :: (Multiplate p, Applicative f) => p f Source
Given an Applicative f, purePlate builds a plate
 over f whose fields are all pure.
Generally purePlate is used as the base of a record update. One constructs
 the expression 
purePlate{ fieldOfInterest = \a -> case a of | constructorOfInterest -> expr | _ ->purea }
and this is a typical parameter that is passed to most functions in this library.
emptyPlate :: (Multiplate p, Alternative f) => p f Source
Given an Alternative f, emptyPlate builds a plate
 over f whose fields are all const empty
Generally emptyPlate is used as the base of a record update. One constructs
 the expression 
emptyPlate{ fieldOfInterest = \a -> case a of | constructorOfInterest -> expr | _ ->empty}
and this is a typical parameter that is passed to evalFamily and evalFamilyM.
kleisliComposePlate :: forall p m. (Multiplate p, Monad m) => p m -> p m -> p m Source
Given two plates over a monad m, the fields of the plate can be
 Kleisli composed (<=<) fieldwise.
composePlate :: forall p f g. (Multiplate p, Functor g) => p f -> p g -> p (Compose g f) Source
Given two plates, they can be composed fieldwise yielding the composite functor.
composePlateRightId :: forall p f. Multiplate p => p f -> p Identity -> p f Source
Given two plates with one over the Identity functor, the two plates
 can be composed fieldwise.
composePlateLeftId :: forall p f. (Multiplate p, Functor f) => p Identity -> p f -> p f Source
Given two plates with one over the Identity functor, the two plates
 can be composed fieldwise.
appendPlate :: forall p o. (Multiplate p, Monoid o) => p (Constant o) -> p (Constant o) -> p (Constant o) Source
preorderFold :: forall p o. (Multiplate p, Monoid o) => p (Constant o) -> p (Constant o) Source
Given a plate whose fields all return a Monoid o,
 preorderFold produces a plate that returns the mconcat
 of the family of the input. The input itself produces the leftmost element
 of the concatenation, then this is followed by the family of the first child, then
 it is followed by the family of the second child, and so forth.
postorderFold :: forall p o. (Multiplate p, Monoid o) => p (Constant o) -> p (Constant o) Source
Given a plate whose fields all return a Monoid o,
 preorderFold produces a plate that returns the mconcat
 of the family of the input. The concatenation sequence begins with
 the family of the first child, then 
 it is followed by the family of the second child, and so forth until finally
 the input itself produces the rightmost element of the concatenation.
mapChildren :: Multiplate p => p Identity -> p Identity Source
Given a plate whose fields transform each type, mapChildren
 returns a plate whose fields transform the children of the input.
mapFamily :: Multiplate p => p Identity -> p Identity Source
Given a plate whose fields transform each type, mapFamily
 returns a plate whose fields transform the family of the input.
 The traversal proceeds bottom up, first transforming the families of
 the children, before finally transforming the value itself.
mapChildrenM :: (Multiplate p, Applicative m, Monad m) => p m -> p m Source
Given a plate whose fields transform each type, mapChildrenM
 returns a plate whose fields transform the children of the input.
 The processing is sequenced from the first child to the last child.
mapFamilyM :: (Multiplate p, Applicative m, Monad m) => p m -> p m Source
Given a plate whose fields transform each type, mapFamilyM
 returns a plate whose fields transform the family of the input.
 The sequencing is done in a depth-first postorder traversal.
evalFamily :: Multiplate p => p Maybe -> p Identity Source
Given a plate whose fields maybe transforms each type, evalFamily
 returns a plate whose fields exhaustively transform the family of the input.
 The traversal proceeds bottom up, first transforming the families of
 the children. If a transformation succeeds then the result is re-evalFamilyed.
A post-condition is that the input transform returns Nothing on all family members
 of the output, or more formally
preorderFold(applyNaturalTransformt f) `composePlate` (evalFamilyf) ⊑purePlatewhere t :: forall a.Maybea ->ConstantAlla t =Constant.All.isNothing
evalFamilyM :: forall p m. (Multiplate p, Applicative m, Monad m) => p (MaybeT m) -> p m Source
Given a plate whose fields maybe transforms each type, evalFamilyM
 returns a plate whose fields exhaustively transform the family of the input.
 The sequencing is done in a depth-first postorder traversal, but 
 if a transformation succeeds then the result is re-evalFamilyMed.
always :: Multiplate p => p Maybe -> p Identity Source
Given a plate used for evalFamily, replace returning Nothing
 with returning the input.  This transforms plates suitable for evalFamily
 into plates suitable form mapFamily.
alwaysM :: forall p f. (Multiplate p, Functor f) => p (MaybeT f) -> p f Source
Given a plate used for evalFamilyM, replace returning Nothing
 with returning the input.  This transforms plates suitable for evalFamilyM
 into plates suitable form mapFamilyM.
traverseFor :: Multiplate p => Projector p a -> p Identity -> a -> a Source
Given a projection function for a plate over the Identity functor,
 upgrade the projection function to strip off the wrapper.
traverseMFor :: (Multiplate p, Monad m) => Projector p a -> p m -> a -> m a Source
Instantiate a projection function at a monad.
foldFor :: Multiplate p => Projector p a -> p (Constant o) -> a -> o Source
Given a projection function for a plate over the Constant o
unwrapFor :: Multiplate p => (o -> b) -> Projector p a -> p (Constant o) -> a -> b Source
Given a projection function for a plate over the Constant oo, upgrade  the projection function to strip off the wrapper
 and run the continuation.
Typically the continuation simply strips off a wrapper for o.
productFor :: Multiplate p => Projector p a -> p (Constant (Product n)) -> a -> n Source