Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- chrono :: Functor f => GAlgebra (->) (Cofree f) f b -> GCoalgebra (->) (Free f) f a -> a -> b
- codyna :: Functor f => Algebra (->) f b -> GCoalgebra (->) (Free f) f a -> a -> b
- coelgot :: Functor f => ElgotAlgebra (->) (Pair a) f b -> Coalgebra (->) f a -> a -> b
- cotraverse :: (Steppable (->) t (f a), Steppable (->) u (f b), Bitraversable f, Traversable (f b), Monad m) => (a -> m b) -> t -> m u
- dyna :: Functor f => GAlgebra (->) (Cofree f) f b -> Coalgebra (->) f a -> a -> b
- elgot :: Functor f => Algebra (->) f b -> ElgotCoalgebra (->) (Either b) f a -> a -> b
- fstream :: Coalgebra (->) (XNor c) b -> (b -> a -> b) -> Coalgebra (->) (XNor c) b -> b -> [a] -> [c]
- futu :: (Corecursive (->) t f, Functor f) => GCoalgebra (->) (Free f) f a -> a -> t
- 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
- 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
- stream :: Coalgebra (->) (XNor c) b -> (b -> a -> b) -> b -> [a] -> [c]
- 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
Documentation
chrono :: Functor f => GAlgebra (->) (Cofree f) f b -> GCoalgebra (->) (Free f) f a -> a -> b Source #
cotraverse :: (Steppable (->) t (f a), Steppable (->) u (f b), Bitraversable f, Traversable (f b), Monad m) => (a -> m b) -> t -> m u Source #
:: 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 #