Uniplate-style traversals.
- 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)
- 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
- foldRight :: Foldable f => (Mu f -> a -> a) -> a -> Mu f -> a
- holes :: Traversable f => f a -> f (a, a -> f a)
- holesList :: Traversable f => f a -> [(a, a -> f a)]
- apply :: Traversable f => (a -> a) -> f a -> f (f a)
- builder :: Traversable f => f a -> [b] -> f b
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.
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 fSource
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
rewrite :: Functor f => (Mu f -> Maybe (Mu f)) -> Mu f -> Mu fSource
Bottom-up transformation until a normal form is reached.
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
.
Folds
foldLeft :: Foldable f => (a -> Mu f -> a) -> a -> Mu f -> aSource
Left fold. Since Mu f
is not a functor, but a type, we cannot make
it an instance of the Foldable
type class.
Open functions
holes :: Traversable f => f a -> f (a, a -> f a)Source
The children together with functions replacing that particular child.
holesList :: Traversable f => f a -> [(a, a -> f a)]Source
apply :: Traversable f => (a -> a) -> f a -> f (f a)Source
Apply the given function to each child in turn.
builder :: Traversable f => f a -> [b] -> f bSource
Builds up a structure from a list of the children.