fixplate-0.1.5: Uniplate-style generic traversals for optionally annotated fixed-point types.

Safe HaskellSafe-Infered

Data.Generics.Fixplate.Morphisms

Contents

Description

Recursion schemes, also known as scary named folds...

Synopsis

Classic ana/cata/para/hylo-morphisms

cata :: Functor f => (f a -> a) -> Mu f -> aSource

A catamorphism is the generalization of right fold from lists to trees.

para :: Functor f => (f (Mu f, a) -> a) -> Mu f -> aSource

A paramorphism is a more general version of the catamorphism.

para' :: Functor f => (Mu f -> f a -> a) -> Mu f -> aSource

Another version of para (a bit less natural in some sense).

paraList :: (Functor f, Foldable f) => (Mu f -> [a] -> a) -> Mu f -> aSource

A list version of para (compare with Uniplate)

ana :: Functor f => (a -> f a) -> a -> Mu fSource

An anamorphism is simply an unfold. Probably not very useful in this context.

apo :: Functor f => (a -> f (Either (Mu f) a)) -> a -> Mu fSource

An apomorphism is a generalization of the anamorphism.

hylo :: Functor f => (f a -> a) -> (b -> f b) -> b -> aSource

A hylomorphism is the composition of a catamorphism and an anamorphism.

Zygomorphisms

zygo_ :: Functor f => (f b -> b) -> (f (b, a) -> a) -> Mu f -> aSource

A zygomorphism is a basically a catamorphism inside another catamorphism. It could be implemented (somewhat wastefully) by first annotating each subtree with the corresponding values of the inner catamorphism (synthCata), then running a paramorphims on the annotated tree:

 zygo_ g h == para u . synthCata g 
   where
     u = h . fmap (first attribute) . unAnn
     first f (x,y) = (f x, y)

zygo :: Functor f => (f b -> b) -> (f (b, a) -> a) -> Mu f -> (b, a)Source

Futu- and histomorphisms

histo :: Functor f => (f (Attr f a) -> a) -> Mu f -> aSource

Histomorphism. This is a kind of glorified cata/paramorphism, after all:

 cata f == histo (f . fmap attribute)
 para f == histo (f . fmap (\t -> (forget t, attribute t)))

futu :: Functor f => (a -> f (CoAttr f a)) -> a -> Mu fSource

Futumorphism. This is a more interesting unfold.

Monadic versions

cataM :: (Monad m, Traversable f) => (f a -> m a) -> Mu f -> m aSource

Monadic catamorphism.

cataM_ :: (Monad m, Traversable f) => (f a -> m a) -> Mu f -> m ()Source

paraM :: (Monad m, Traversable f) => (f (Mu f, a) -> m a) -> Mu f -> m aSource

Monadic paramorphism.

paraM_ :: (Monad m, Traversable f) => (f (Mu f, a) -> m a) -> Mu f -> m ()Source

paraM' :: (Monad m, Traversable f) => (Mu f -> f a -> m a) -> Mu f -> m aSource

Another version of paraM.