yaya-unsafe-0.4.1.1: Non-total extensions to the Yaya recursion scheme library.
Safe HaskellSafe
LanguageHaskell2010

Yaya.Unsafe.Zoo

Synopsis

Documentation

chrono :: Functor f => GAlgebra (->) (Cofree f) f b -> GCoalgebra (->) (Free f) f a -> a -> b Source #

codyna :: Functor f => Algebra (->) f b -> GCoalgebra (->) (Free f) f a -> a -> b Source #

coelgot :: Functor f => ElgotAlgebra (->) (Pair a) f b -> Coalgebra (->) f a -> a -> b Source #

The dual of elgot, coelgot allows the algebra to short-circuit in some cases – operating directly on a part of the seed.

cotraverse :: (Steppable (->) t (f a), Steppable (->) u (f b), Bitraversable f, Traversable (f b), Monad m) => (a -> m b) -> t -> m u Source #

elgot :: Functor f => Algebra (->) f b -> ElgotCoalgebra (->) (Either b) f a -> a -> b Source #

Unlike most hylos, elgot composes an algebra and coalgebra in a way that allows information to move between them. The coalgebra can return, effectively, a pre-folded branch, short-circuiting parts of the process.

fstream Source #

Arguments

:: Coalgebra (->) (XNor c) b 
-> (b -> a -> b) 
-> Coalgebra (->) (XNor c) b

The flusher.

-> b 
-> [a] 
-> [c] 

Basically the definition from Gibbons’ paper, except the flusher is a Coalgebra instead of an unfold.

The implementation shows how streamGApo generalizes Gibbons’ fstream (and stream' even more so).

futu :: (Corecursive (->) t f, Functor f) => GCoalgebra (->) (Free f) f a -> a -> t Source #

gpostpro :: (Steppable (->) t f, Corecursive (->) t f, Functor f, Monad m) => DistributiveLaw (->) m f -> (forall x. f x -> f x) -> GCoalgebra (->) m f a -> a -> t Source #

gprepro :: (Steppable (->) t f, Recursive (->) t f, Functor f, Comonad w) => DistributiveLaw (->) f w -> GAlgebra (->) w f a -> (forall x. f x -> f x) -> t -> a Source #

stream :: Coalgebra (->) (XNor c) b -> (b -> a -> b) -> b -> [a] -> [c] Source #

The metamorphism definition from Gibbons’ paper.

zygoHistoPrepro :: (Steppable (->) t f, Recursive (->) t f, Functor f) => (f b -> b) -> (f (EnvT b (Cofree f) a) -> a) -> (forall c. f c -> f c) -> t -> a Source #

Zygohistomorphic prepromorphism – everyone’s favorite recursion scheme joke.