module Data.Fixpoint.Base ( Fixpoint(..), #ifdef __HADDOCK__ Pre, #endif cata, fold, ana, unfold, hylo, para ) where #ifdef __HADDOCK__ -- | @Pre t :: * -> *@ is an associated data type of @t@ such that @t@ is the -- fixpoint of @Pre t@. data Pre t a #endif -- | The class of data types representable by fixpoints. class Functor (Pre t) => Fixpoint t where #ifndef __HADDOCK__ data Pre t :: * -> * #endif -- | Projection from the data type to its underlying functor. project :: t -> Pre t t -- | Injection from the underlying functor into the data type. inject :: Pre t t -> t -- | Catamorphism (same as 'fold') cata :: Fixpoint t => (Pre t s -> s) -> t -> s cata f = f . fmap (cata f) . project -- | Catamorphism (same as 'cata') fold :: Fixpoint t => (Pre t s -> s) -> t -> s fold = cata -- | Anamorphism (same as 'unfold') ana :: Fixpoint t => (s -> Pre t s) -> s -> t ana f = inject . fmap (ana f) . f -- | Anamorphism (same as 'ana') unfold :: Fixpoint t => (s -> Pre t s) -> s -> t unfold = ana -- | Hylomorphism hylo :: Fixpoint t => (Pre t s -> s) -> (p -> Pre t p) -> p -> s hylo f g = f . fmap (hylo f g) . g -- | Paramorphism para :: Fixpoint t => (Pre t (t, s) -> s) -> t -> s para f = f . fmap (\x -> (x, para f x)) . project {- class Difunctor (Dipre t) => Difixpoint t where data Dipre t :: * -> * -> * diproject :: t -> Dipre t t t diinject :: Dipre t t t -> t dicata :: Difixpoint t => (Dipre t r s -> s) -> (r -> Dipre t s r) -> t -> s dicata f g = f . dimap (diana f g) (dicata f g) . diproject diana :: Difixpoint t => (Dipre t r s -> s) -> (r -> Dipre t s r) -> r -> t diana f g = diinject . dimap (dicata f g) (diana f g) . g -}