module Data.Generics.Fixplate.Morphisms where
import Data.Foldable
import Data.Generics.Fixplate.Base
#ifdef WITH_QUICKCHECK
import Test.QuickCheck
import Data.Generics.Fixplate.Traversals
import Data.Generics.Fixplate.Test.Tools
#endif
para :: Functor f => (Mu f -> f a -> a) -> Mu f -> a
para h = go where
go t = h t (fmap go $ unFix t)
para' :: Functor f => (f (Mu f, a) -> a) -> Mu f -> a
para' h = go where
go (Fix t) = h (fmap go' $ t)
go' t = (t, go t)
paraList :: (Functor f, Foldable f) => (Mu f -> [a] -> a) -> Mu f -> a
paraList f = go where
go t = f t (toList $ fmap go $ unFix t)
cata :: Functor f => (f a -> a) -> Mu f -> a
cata h = go where
go = h . fmap go . unFix
ana :: Functor f => (a -> f a) -> a -> Mu f
ana h = go where
go = Fix . fmap go . h
hylo :: Functor f => (f a -> a) -> (b -> f b) -> (b -> a)
hylo g h = cata g . ana h