Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Uniplate-style traversals.
Toy example: Consider our favourite data type
data Expr e = Kst Int | Var String | Add e e deriving (Eq,Show,Functor,Foldable,Traversable) instance ShowF Expr where showsPrecF = showsPrec
and write a function simplifying additions with zero:
simplifyAdd :: Mu Expr -> Mu Expr simplifyAdd = transform worker where worker expr = case expr of Fix (Add x (Fix (Kst 0))) -> x -- 0+x = x Fix (Add (Fix (Kst 0)) y) -> y -- x+0 = 0 _ -> expr
Unfortunately, all these Fix
wrappers are rather ugly; but they are straightforward to put in,
and in principle one could use Template Haskell quasi-quotation to generate patterns.
- children :: Foldable f => Mu f -> [Mu f]
- universe :: Foldable f => Mu f -> [Mu f]
- transform :: Functor f => (Mu f -> Mu f) -> Mu f -> Mu f
- transformM :: (Traversable f, Monad m) => (Mu f -> m (Mu f)) -> Mu f -> m (Mu f)
- topDownTransform :: Functor f => (Mu f -> Mu f) -> Mu f -> Mu f
- topDownTransformM :: (Traversable f, Monad m) => (Mu f -> m (Mu f)) -> Mu f -> m (Mu f)
- descend :: Functor f => (Mu f -> Mu f) -> Mu f -> Mu f
- descendM :: (Traversable f, Monad m) => (Mu f -> m (Mu f)) -> Mu f -> m (Mu f)
- rewrite :: Functor f => (Mu f -> Maybe (Mu f)) -> Mu f -> Mu f
- rewriteM :: (Traversable f, Monad m) => (Mu f -> m (Maybe (Mu f))) -> Mu f -> m (Mu f)
- restructure :: Functor f => (f (Mu g) -> g (Mu g)) -> Mu f -> Mu g
- restructureM :: (Traversable f, Monad m) => (f (Mu g) -> m (g (Mu g))) -> Mu f -> m (Mu g)
- context :: Traversable f => Mu f -> Attr f (Mu f -> Mu f)
- contextList :: Traversable f => Mu f -> [(Mu f, Mu f -> Mu f)]
- foldLeft :: Foldable f => (a -> Mu f -> a) -> a -> Mu f -> a
- foldLeftLazy :: Foldable f => (a -> Mu f -> a) -> a -> Mu f -> a
- foldRight :: Foldable f => (Mu f -> a -> a) -> a -> Mu f -> a
Queries
universe :: Foldable f => Mu f -> [Mu f] Source #
The list of all substructures. Together with list-comprehension syntax this is a powerful query tool. For example the following is how you get the list of all variable names in an expression:
variables expr = [ s | Fix (Var s) <- universe expr ]
Traversals
transformM :: (Traversable f, Monad m) => (Mu f -> m (Mu f)) -> Mu f -> m (Mu f) Source #
topDownTransform :: Functor f => (Mu f -> Mu f) -> Mu f -> Mu f Source #
Top-down transformation. This provided only for completeness;
usually, it is transform
what you want use instead.
topDownTransformM :: (Traversable f, Monad m) => (Mu f -> m (Mu f)) -> Mu f -> m (Mu f) Source #
descend :: Functor f => (Mu f -> Mu f) -> Mu f -> Mu f Source #
Non-recursive top-down transformation. This is basically just fmap
.
descendM :: (Traversable f, Monad m) => (Mu f -> m (Mu f)) -> Mu f -> m (Mu f) Source #
Similarly, this is basically just mapM
.
rewrite :: Functor f => (Mu f -> Maybe (Mu f)) -> Mu f -> Mu f Source #
Bottom-up transformation until a normal form is reached.
Structure change
restructure :: Functor f => (f (Mu g) -> g (Mu g)) -> Mu f -> Mu g Source #
Bottom-up transformation (typically "shallow", that is, restricted to a single level)
which can change the structure functor (actually transform
is a special case of this).
restructureM :: (Traversable f, Monad m) => (f (Mu g) -> m (g (Mu g))) -> Mu f -> m (Mu g) Source #
Context
context :: Traversable f => Mu f -> Attr f (Mu f -> Mu f) Source #
We annotate the nodes of the tree with functions which replace that particular subtree.
contextList :: Traversable f => Mu f -> [(Mu f, Mu f -> Mu f)] Source #
Flattened version of context
.