yaya-0.1.0.0: Total recursion schemes.

Safe HaskellSafe
LanguageHaskell2010

Yaya.Retrofit

Description

This module re-exports a subset of Fold, intended for when you want to define recursion scheme instances for your existing recursive types.

Synopsis

Documentation

class Corecursive t f | t -> f Source #

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

Minimal complete definition

ana

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 #

class Recursive t f | t -> f Source #

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

Minimal complete definition

cata

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 Projectable t f => Steppable t f | t -> f Source #

Structures you can walk through step-by-step.

Minimal complete definition

embed

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 Projectable t f | t -> f 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).

Minimal complete definition

project

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 #

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.