Safe Haskell | None |
---|---|
Language | Haskell2010 |
DEPRECATED: Use Data.Generics.Uniplate.Operations instead.
This is the main Uniplate module, which defines all the essential operations in a Haskell 98 compatible manner.
Most functions have an example of a possible use for the function.
To illustate, I have used the Expr
type as below:
data Expr = Val Int | Neg Expr | Add Expr Expr
Synopsis
- class Uniplate on where
- uniplate :: UniplateType on
- type UniplateType on = on -> (Str on, Str on -> on)
- uniplateList :: Uniplate on => on -> ([on], [on] -> on)
- universe :: Uniplate on => on -> [on]
- children :: Uniplate on => on -> [on]
- transform :: Uniplate on => (on -> on) -> on -> on
- transformM :: (Monad m, Uniplate on) => (on -> m on) -> on -> m on
- rewrite :: Uniplate on => (on -> Maybe on) -> on -> on
- rewriteM :: (Monad m, Uniplate on) => (on -> m (Maybe on)) -> on -> m on
- descend :: Uniplate on => (on -> on) -> on -> on
- descendM :: (Monad m, Uniplate on) => (on -> m on) -> on -> m on
- contexts :: Uniplate on => on -> [(on, on -> on)]
- holes :: Uniplate on => on -> [(on, on -> on)]
- para :: Uniplate on => (on -> [r] -> r) -> on -> r
- module Data.Generics.Str
Documentation
class Uniplate on where Source #
The standard Uniplate class, all operations require this.
uniplate :: UniplateType on Source #
The underlying method in the class.
Given uniplate x = (cs, gen)
cs
should be a Str on
, constructed of Zero
, One
and Two
,
containing all x
's direct children of the same type as x
. gen
should take a Str on
with exactly the same structure as cs
,
and generate a new element with the children replaced.
Example instance:
instance Uniplate Expr where uniplate (Val i ) = (Zero , \Zero -> Val i ) uniplate (Neg a ) = (One a , \(One a) -> Neg a ) uniplate (Add a b) = (Two (One a) (One b), \(Two (One a) (One b)) -> Add a b)
Instances
Uniplate Bool Source # | |
Defined in Data.Generics.PlateTypeable | |
Uniplate Char Source # | |
Defined in Data.Generics.PlateTypeable | |
Uniplate Double Source # | |
Defined in Data.Generics.PlateTypeable | |
Uniplate Float Source # | |
Defined in Data.Generics.PlateTypeable | |
Uniplate Int Source # | |
Defined in Data.Generics.PlateTypeable | |
Uniplate Integer Source # | |
Defined in Data.Generics.PlateTypeable | |
Uniplate () Source # | |
Defined in Data.Generics.PlateTypeable uniplate :: UniplateType () Source # | |
(Data a, Typeable a) => Uniplate a Source # | |
Defined in Data.Generics.PlateData uniplate :: UniplateType a Source # |
type UniplateType on = on -> (Str on, Str on -> on) Source #
The type of replacing all the children of a node
Taking a value, the function should return all the immediate children of the same type, and a function to replace them.
uniplateList :: Uniplate on => on -> ([on], [on] -> on) Source #
Compatibility method, for direct users of the old list-based uniplate
function
universe :: Uniplate on => on -> [on] Source #
Get all the children of a node, including itself and all children.
universe (Add (Val 1) (Neg (Val 2))) = [Add (Val 1) (Neg (Val 2)), Val 1, Neg (Val 2), Val 2]
This method is often combined with a list comprehension, for example:
vals x = [i | Val i <- universe x]
transform :: Uniplate on => (on -> on) -> on -> on Source #
Transform every element in the tree, in a bottom-up manner.
For example, replacing negative literals with literals:
negLits = transform f where f (Neg (Lit i)) = Lit (negate i) f x = x
transformM :: (Monad m, Uniplate on) => (on -> m on) -> on -> m on Source #
Monadic variant of transform
rewrite :: Uniplate on => (on -> Maybe on) -> on -> on Source #
Rewrite by applying a rule everywhere you can. Ensures that the rule cannot be applied anywhere in the result:
propRewrite r x = all (isNothing . r) (universe (rewrite r x))
Usually transform
is more appropriate, but rewrite
can give better
compositionality. Given two single transformations f
and g
, you can
construct f
which performs both rewrites until a fixed point.mplus
g
rewriteM :: (Monad m, Uniplate on) => (on -> m (Maybe on)) -> on -> m on Source #
Monadic variant of rewrite
descend :: Uniplate on => (on -> on) -> on -> on Source #
Perform a transformation on all the immediate children, then combine them back. This operation allows additional information to be passed downwards, and can be used to provide a top-down transformation.
contexts :: Uniplate on => on -> [(on, on -> on)] Source #
Return all the contexts and holes.
propUniverse x = universe x == map fst (contexts x) propId x = all (== x) [b a | (a,b) <- contexts x]
holes :: Uniplate on => on -> [(on, on -> on)] Source #
The one depth version of contexts
propChildren x = children x == map fst (holes x) propId x = all (== x) [b a | (a,b) <- holes x]
para :: Uniplate on => (on -> [r] -> r) -> on -> r Source #
Perform a fold-like computation on each value, technically a paramorphism
module Data.Generics.Str