yaya-0.4.2.1: Total recursion schemes.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Yaya.Zoo

Description

Contains all the commonly-named folds that aren’t core to the library. In general, this can be seen as a mapping from names you may have heard or read in a paper to how Yaya expects you to achieve the same end. Of course, you can always import this module and use the “common” name as well.

Synopsis

Documentation

apo :: (Projectable (->) t f, Corecursive (->) t f, Functor f) => GCoalgebra (->) (Either t) f a -> a -> t Source #

A recursion scheme that allows you to return a complete branch when unfolding.

cataM :: (Monad m, Recursive (->) t f, Traversable f) => AlgebraM (->) m f a -> t -> m a Source #

If you have a monadic algebra, you can fold it by distributing the monad over the algebra.

mutu :: (Recursive (->) t f, Functor f) => GAlgebra (->) ((,) a) f b -> GAlgebra (->) ((,) b) f a -> t -> a Source #

A recursion scheme that allows to algebras to see each others’ results. (A generalization of zygo.) This is an example that falls outside the scope of “comonadic folds”, but _would_ be covered by “adjoint folds”.

gmutu :: (Comonad w, Comonad v, Recursive (->) t f, Functor f) => DistributiveLaw (->) f w -> DistributiveLaw (->) f v -> GAlgebra (->) (EnvT a w) f b -> GAlgebra (->) (EnvT b v) f a -> t -> a Source #

comutu :: (Corecursive (->) t f, Functor f) => GCoalgebra (->) (Either a) f b -> GCoalgebra (->) (Either b) f a -> a -> t Source #

This could use a better name.

mutuM :: (Monad m, Recursive (->) t f, Traversable f) => GAlgebraM (->) m ((,) a) f b -> GAlgebraM (->) m ((,) b) f a -> t -> m a Source #

histo :: (Recursive (->) t f, Functor f) => GAlgebra (->) (Cofree f) f a -> t -> a Source #

para :: (Steppable (->) t f, Recursive (->) t f, Functor f) => GAlgebra (->) ((,) t) f a -> t -> a Source #

A recursion scheme that gives you access to the original structure as you fold. (A specialization of zygo.)

zygo :: (Recursive (->) t f, Functor f) => Algebra (->) f b -> GAlgebra (->) ((,) b) f a -> t -> a Source #

A recursion scheme that uses a “helper algebra” to provide additional information when folding. (A generalization of para, and specialization of mutu.)

zygoM :: (Monad m, Recursive (->) t f, Traversable f) => AlgebraM (->) m f b -> GAlgebraM (->) m ((,) b) f a -> t -> m a Source #

This definition is different from the one given by `gcataM (distTuple φ')` because it has a monadic “helper” algebra. But at least it gives us the opportunity to show how zygo is a specialization of mutu.

type Colist a = Nu (XNor a) Source #

Potentially-infinite lists, like `[]`.

type List a = Mu (XNor a) Source #

Finite lists.

type NonEmptyList a = Mu (AndMaybe a) Source #

Finite non-empty lists.

type Nat = Mu Maybe Source #

Finite natural numbers.

newtype Partial a Source #

Represents partial functions that may eventually return a value (Left). NB: This is a newtype so we can create the usual instances.

Constructors

Partial 

Fields

Instances

Instances details
Monad Partial Source # 
Instance details

Defined in Yaya.Zoo

Methods

(>>=) :: Partial a -> (a -> Partial b) -> Partial b #

(>>) :: Partial a -> Partial b -> Partial b #

return :: a -> Partial a #

Functor Partial Source # 
Instance details

Defined in Yaya.Zoo

Methods

fmap :: (a -> b) -> Partial a -> Partial b #

(<$) :: a -> Partial b -> Partial a #

Applicative Partial Source # 
Instance details

Defined in Yaya.Zoo

Methods

pure :: a -> Partial a #

(<*>) :: Partial (a -> b) -> Partial a -> Partial b #

liftA2 :: (a -> b -> c) -> Partial a -> Partial b -> Partial c #

(*>) :: Partial a -> Partial b -> Partial b #

(<*) :: Partial a -> Partial b -> Partial a #

insidePartial :: (Nu (Either a) -> Nu (Either b)) -> Partial a -> Partial b Source #

type Stream a = Nu ((,) a) Source #

Always-infinite streams (as opposed to Colist, which _may_ terminate).

map :: (Recursive (->) t (f a), Steppable (->) u (f b), Bifunctor f) => (a -> b) -> t -> u Source #

A more general implementation of fmap, because it can also work to, from, or within monomorphic structures, obviating the need for classes like MonoFunctor.

comap :: (Projectable (->) t (f a), Corecursive (->) u (f b), Bifunctor f) => (a -> b) -> t -> u Source #

A version of map that applies to Corecursive structures.

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

A more general implementation of traverse, because it can also work to, from, or within monomorphic structures, obviating the need for classes like MonoTraversable.

contramap :: (Recursive (->) t (f b), Steppable (->) u (f a), Profunctor f) => (a -> b) -> t -> u Source #

A more general implementation of contramap, because it can also work to, from, or within monomorphic structures.

cocontramap :: (Projectable (->) t (f b), Corecursive (->) u (f a), Profunctor f) => (a -> b) -> t -> u Source #