category-extras-0.53.5: Various modules and constructs inspired by category theory

Portabilitynon-portable (rank-2 polymorphism)
Stabilityexperimental
MaintainerEdward Kmett <ekmett@gmail.com>

Control.Morphism.Prepro

Description

See Maarten Fokkinga''s PhD Dissertation for cascade and prepro. g_prepro is an obvious generalization. The prepro variants of other morphisms are distributed through the corresponding files.

Synopsis

Documentation

prepro :: Functor f => Algebra f c -> (f :~> f) -> FixF f -> cSource

Fokkinga's Prepromorphism

g_prepro :: (Functor f, Comonad w) => Dist f w -> GAlgebra f w a -> (f :~> f) -> FixF f -> aSource

Generalized prepromorphisms, parameterized by a comonad This is used to generate most of the specialized prepromorphisms in other modules. You can use the distributive law combinators to build up analogues of other recursion schemes.

cascade :: Bifunctor s Hask Hask Hask => (a -> a) -> Fix s a -> Fix s aSource

cascade f . map f = map f . cascade f
cascade f = biprepro InB (first f)
cascade f = x where x = InB . bimap id (x . fmap f) . outB
cascade f = x where x = InB . bimap id (fmap f . x) . outB

biprepro :: Bifunctor f Hask Hask Hask => Algebra (f a) c -> (f a :~> f a) -> Fix f a -> cSource

Prepromorphisms for bifunctors

g_biprepro :: (Bifunctor f Hask Hask Hask, Comonad w) => Dist (f a) w -> GAlgebra (f a) w c -> (f a :~> f a) -> Fix f a -> cSource

Generalized bifunctor prepromorphism, parameterized by a comonad