yaya-0.2.1.0: Total recursion schemes.

Safe HaskellSafe
LanguageHaskell2010

Yaya.Fold

Contents

Synopsis

Documentation

type Algebra f a = f a -> a Source #

type GAlgebra w f a = f (w a) -> a Source #

type ElgotAlgebra w f a = w (f a) -> a Source #

type AlgebraM m f a = f a -> m a Source #

type GAlgebraM m w f a = f (w a) -> m a Source #

type ElgotAlgebraM m w f a = w (f a) -> m a Source #

type Coalgebra f a = a -> f a Source #

type GCoalgebra m f a = a -> f (m a) Source #

type ElgotCoalgebra m f a = a -> m (f a) Source #

type CoalgebraM m f a = a -> m (f a) Source #

Note that using a CoalgebraM “directly” is partial (e.g., with anaM). However, `ana . Compose` can accept a CoalgebraM and produce something like an effectful stream.

type GCoalgebraM m n f a = a -> m (f (n a)) Source #

class Projectable t f | t -> f where Source #

This type class is lawless on its own, but there exist types that can’t implement the corresponding embed operation. Laws are induced by implementing either Steppable (which extends this) or Corecursive (which doesn’t).

Methods

project :: Coalgebra f t Source #

Instances
Projectable Natural Maybe Source # 
Instance details

Defined in Yaya.Fold

Projectable Void Identity Source # 
Instance details

Defined in Yaya.Fold

Functor f => Projectable (Nu f) f Source # 
Instance details

Defined in Yaya.Fold

Methods

project :: Coalgebra f (Nu f) Source #

Functor f => Projectable (Mu f) f Source # 
Instance details

Defined in Yaya.Fold

Methods

project :: Coalgebra f (Mu f) Source #

Projectable (Fix f) f Source # 
Instance details

Defined in Yaya.Fold.Native

Methods

project :: Coalgebra f (Fix f) Source #

Projectable [a] (XNor a) Source # 
Instance details

Defined in Yaya.Fold

Methods

project :: Coalgebra (XNor a) [a] Source #

Projectable (NonEmpty a) (AndMaybe a) Source # 
Instance details

Defined in Yaya.Fold

Projectable (Maybe a) (Const (Maybe a) :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

project :: Coalgebra (Const (Maybe a)) (Maybe a) Source #

Projectable (Either a b) (Const (Either a b) :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

project :: Coalgebra (Const (Either a b)) (Either a b) Source #

Projectable (Cofree f a) (EnvT a f) Source # 
Instance details

Defined in Yaya.Fold

Methods

project :: Coalgebra (EnvT a f) (Cofree f a) Source #

Projectable (Free f a) (FreeF f a) Source # 
Instance details

Defined in Yaya.Fold

Methods

project :: Coalgebra (FreeF f a) (Free f a) Source #

class Projectable t f => Steppable t f | t -> f where Source #

Structures you can walk through step-by-step.

Methods

embed :: Algebra f t Source #

Instances
Steppable Natural Maybe Source # 
Instance details

Defined in Yaya.Fold

Steppable Void Identity Source # 
Instance details

Defined in Yaya.Fold

Functor f => Steppable (Nu f) f Source # 
Instance details

Defined in Yaya.Fold

Methods

embed :: Algebra f (Nu f) Source #

Functor f => Steppable (Mu f) f Source # 
Instance details

Defined in Yaya.Fold

Methods

embed :: Algebra f (Mu f) Source #

Steppable (Fix f) f Source # 
Instance details

Defined in Yaya.Fold.Native

Methods

embed :: Algebra f (Fix f) Source #

Steppable [a] (XNor a) Source # 
Instance details

Defined in Yaya.Fold

Methods

embed :: Algebra (XNor a) [a] Source #

Steppable (NonEmpty a) (AndMaybe a) Source # 
Instance details

Defined in Yaya.Fold

Steppable (Maybe a) (Const (Maybe a) :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

embed :: Algebra (Const (Maybe a)) (Maybe a) Source #

Steppable (Either a b) (Const (Either a b) :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

embed :: Algebra (Const (Either a b)) (Either a b) Source #

Steppable (Cofree f a) (EnvT a f) Source # 
Instance details

Defined in Yaya.Fold

Methods

embed :: Algebra (EnvT a f) (Cofree f a) Source #

Steppable (Free f a) (FreeF f a) Source # 
Instance details

Defined in Yaya.Fold

Methods

embed :: Algebra (FreeF f a) (Free f a) Source #

class Recursive t f | t -> f where Source #

Inductive structures that can be reasoned about in the way we usually do – with pattern matching.

Methods

cata :: Algebra f a -> t -> a Source #

Instances
Recursive Natural Maybe Source # 
Instance details

Defined in Yaya.Fold.Native

Methods

cata :: Algebra Maybe a -> Natural -> a Source #

Recursive Void Identity Source # 
Instance details

Defined in Yaya.Fold

Methods

cata :: Algebra Identity a -> Void -> a Source #

Recursive (Mu f) f Source # 
Instance details

Defined in Yaya.Fold

Methods

cata :: Algebra f a -> Mu f -> a Source #

Recursive (Maybe a) (Const (Maybe a) :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

cata :: Algebra (Const (Maybe a)) a0 -> Maybe a -> a0 Source #

Recursive (Either a b) (Const (Either a b) :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

cata :: Algebra (Const (Either a b)) a0 -> Either a b -> a0 Source #

class Corecursive t f | t -> f where Source #

Coinductive (potentially-infinite) structures that guarantee _productivity_ rather than termination.

Methods

ana :: Coalgebra f a -> a -> t Source #

Instances
Corecursive (Nu f) f Source # 
Instance details

Defined in Yaya.Fold

Methods

ana :: Coalgebra f a -> a -> Nu f Source #

Functor f => Corecursive (Fix f) f Source # 
Instance details

Defined in Yaya.Fold.Native

Methods

ana :: Coalgebra f a -> a -> Fix f Source #

Corecursive [a] (XNor a) Source # 
Instance details

Defined in Yaya.Fold.Native

Methods

ana :: Coalgebra (XNor a) a0 -> a0 -> [a] Source #

Corecursive (NonEmpty a) (AndMaybe a) Source # 
Instance details

Defined in Yaya.Fold.Native

Methods

ana :: Coalgebra (AndMaybe a) a0 -> a0 -> NonEmpty a Source #

Corecursive (Maybe a) (Const (Maybe a) :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

ana :: Coalgebra (Const (Maybe a)) a0 -> a0 -> Maybe a Source #

Corecursive (Either a b) (Const (Either a b) :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

ana :: Coalgebra (Const (Either a b)) a0 -> a0 -> Either a b Source #

Functor f => Corecursive (Cofree f a) (EnvT a f) Source # 
Instance details

Defined in Yaya.Fold.Native

Methods

ana :: Coalgebra (EnvT a f) a0 -> a0 -> Cofree f a Source #

Functor f => Corecursive (Free f a) (FreeF f a) Source # 
Instance details

Defined in Yaya.Fold.Native

Methods

ana :: Coalgebra (FreeF f a) a0 -> a0 -> Free f a Source #

recursiveEq :: (Recursive t f, Steppable u f, Functor f, Foldable f, Eq1 f) => t -> u -> Bool Source #

An implementation of Eq for any Recursive instance. Note that this is actually more general than Eq, as it can compare between different fixed-point representations of the same functor.

recursiveShowsPrec :: (Recursive t f, Show1 f) => Int -> t -> ShowS Source #

An implementation of Show for any Recursive instance.

data Mu f Source #

A fixed-point operator for inductive / finite data structures.

Constructors

Mu (forall a. Algebra f a -> a) 
Instances
DFunctor Mu Source # 
Instance details

Defined in Yaya.Fold

Methods

dmap :: (forall a. f a -> g a) -> Mu f -> Mu g Source #

(Functor f, Foldable f, Eq1 f) => Eq (Mu f) Source # 
Instance details

Defined in Yaya.Fold

Methods

(==) :: Mu f -> Mu f -> Bool #

(/=) :: Mu f -> Mu f -> Bool #

Show1 f => Show (Mu f) Source # 
Instance details

Defined in Yaya.Fold

Methods

showsPrec :: Int -> Mu f -> ShowS #

show :: Mu f -> String #

showList :: [Mu f] -> ShowS #

Recursive (Mu f) f Source # 
Instance details

Defined in Yaya.Fold

Methods

cata :: Algebra f a -> Mu f -> a Source #

Functor f => Steppable (Mu f) f Source # 
Instance details

Defined in Yaya.Fold

Methods

embed :: Algebra f (Mu f) Source #

Functor f => Projectable (Mu f) f Source # 
Instance details

Defined in Yaya.Fold

Methods

project :: Coalgebra f (Mu f) Source #

data Nu f where Source #

A fixed-point operator for coinductive / potentially-infinite data structures.

Constructors

Nu :: Coalgebra f a -> a -> Nu f 
Instances
DFunctor Nu Source # 
Instance details

Defined in Yaya.Fold

Methods

dmap :: (forall a. f a -> g a) -> Nu f -> Nu g Source #

Corecursive (Nu f) f Source # 
Instance details

Defined in Yaya.Fold

Methods

ana :: Coalgebra f a -> a -> Nu f Source #

Functor f => Steppable (Nu f) f Source # 
Instance details

Defined in Yaya.Fold

Methods

embed :: Algebra f (Nu f) Source #

Functor f => Projectable (Nu f) f Source # 
Instance details

Defined in Yaya.Fold

Methods

project :: Coalgebra f (Nu f) Source #

zipAlgebras :: Functor f => Algebra f a -> Algebra f b -> Algebra f (a, b) Source #

Combines two Algebras with different carriers into a single tupled Algebra.

lowerDay :: Projectable t g => Algebra (Day f g) a -> Algebra f (t -> a) Source #

Algebras over Day convolution are convenient for binary operations, but aren’t directly handleable by cata.

cata2 :: (Recursive t f, Projectable u g) => Algebra (Day f g) a -> t -> u -> a Source #

By analogy with liftA2 (which also relies on Day, at least conceptually).

lowerAlgebra :: (Functor f, Comonad w) => DistributiveLaw f w -> GAlgebra w f a -> Algebra f (w a) Source #

Makes it possible to provide a GAlgebra to cata.

lowerAlgebraM :: (Applicative m, Traversable f, Comonad w, Traversable w) => DistributiveLaw f w -> GAlgebraM m w f a -> AlgebraM m f (w a) Source #

Makes it possible to provide a GAlgebraM to cataM.

lowerCoalgebra :: (Functor f, Monad m) => DistributiveLaw m f -> GCoalgebra m f a -> Coalgebra f (m a) Source #

Makes it possible to provide a GCoalgebra to ana.

lowerCoalgebraM :: (Applicative m, Traversable f, Monad n, Traversable n) => DistributiveLaw n f -> GCoalgebraM m n f a -> CoalgebraM m f (n a) Source #

Makes it possible to provide a GCoalgebraM to anaM.

gcata :: (Recursive t f, Functor f, Comonad w) => DistributiveLaw f w -> GAlgebra w f a -> t -> a Source #

elgotCata :: (Recursive t f, Functor f, Comonad w) => DistributiveLaw f w -> ElgotAlgebra w f a -> t -> a Source #

gcataM :: (Monad m, Recursive t f, Traversable f, Comonad w, Traversable w) => DistributiveLaw f w -> GAlgebraM m w f a -> t -> m a Source #

elgotCataM :: (Monad m, Recursive t f, Traversable f, Comonad w, Traversable w) => DistributiveLaw f w -> ElgotAlgebraM m w f a -> t -> m a Source #

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

gana :: (Corecursive t f, Functor f, Monad m) => DistributiveLaw m f -> GCoalgebra m f a -> a -> t Source #

elgotAna :: (Corecursive t f, Functor f, Monad m) => DistributiveLaw m f -> ElgotCoalgebra m f a -> a -> t Source #

type DistributiveLaw f g = forall a. f (g a) -> g (f a) Source #

There are a number of distributive laws, including sequenceA, distribute, and sequenceL. Yaya also provides others for specific recursion schemes.

attributeAlgebra :: (Steppable t (EnvT a f), Functor f) => Algebra f a -> Algebra f t Source #

Converts an Algebra to one that annotates the tree with the result for each node.

attributeCoalgebra :: Coalgebra f a -> Coalgebra (EnvT a f) a Source #

Converts a Coalgebra to one that annotates the tree with the seed that generated each node.

ignoringAttribute :: Algebra f a -> Algebra (EnvT b f) a Source #

This is just a more obvious name for composing lowerEnvT with your algebra directly.

unFree :: Steppable t f => Algebra (FreeF f t) t Source #

It is somewhat common to have a natural transformation that looks like `η :: forall a. f a -> Free g a`. This maps naturally to a GCoalgebra (to pass to apo) with `η . project`, but the desired Algebra is more likely to be `cata unFree . η` than `embed . η`. See yaya-streams for some examples of this.

instances for non-recursive types

constCata :: Algebra (Const b) a -> b -> a Source #

constAna :: Coalgebra (Const b) a -> a -> b Source #

Optics

type BialgebraIso f a = Iso' (f a) a Source #

type AlgebraPrism f a = Prism' (f a) a Source #

type CoalgebraPrism f a = Prism' a (f a) Source #