recursion-0.1.0.1: A recursion schemes library for GHC.

Safe HaskellSafe
LanguageHaskell2010

Control.Recursion

Contents

Synopsis

Typeclasses

class Base t (f :: * -> *) Source #

Instances
Base Natural Maybe Source # 
Instance details

Defined in Control.Recursion

Base b (ListF a) Source # 
Instance details

Defined in Control.Recursion

Base (Fix t) f Source # 
Instance details

Defined in Control.Recursion

class (Functor f, Base t f) => Recursive f t where Source #

Minimal complete definition

project

Methods

project :: t -> f t Source #

Instances
Recursive Maybe Natural Source # 
Instance details

Defined in Control.Recursion

Recursive (ListF a) [a] Source # 
Instance details

Defined in Control.Recursion

Methods

project :: [a] -> ListF a [a] Source #

class (Functor f, Base t f) => Corecursive f t where Source #

Minimal complete definition

embed

Methods

embed :: f t -> t Source #

Instances
Corecursive Maybe Natural Source # 
Instance details

Defined in Control.Recursion

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

Defined in Control.Recursion

Methods

embed :: ListF a [a] -> [a] Source #

Types

newtype Fix f Source #

Constructors

Fix 

Fields

Instances
Base (Fix t) f Source # 
Instance details

Defined in Control.Recursion

data ListF a b Source #

Constructors

Cons a b 
Nil 
Instances
Base b (ListF a) Source # 
Instance details

Defined in Control.Recursion

Functor (ListF a) Source # 
Instance details

Defined in Control.Recursion

Methods

fmap :: (a0 -> b) -> ListF a a0 -> ListF a b #

(<$) :: a0 -> ListF a b -> ListF a a0 #

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

Defined in Control.Recursion

Methods

embed :: ListF a [a] -> [a] Source #

Recursive (ListF a) [a] Source # 
Instance details

Defined in Control.Recursion

Methods

project :: [a] -> ListF a [a] Source #

Recursion schemes

cata :: Recursive f t => (f a -> a) -> t -> a Source #

Catamorphism. Folds a structure. (see here)

ana :: Corecursive f t => (a -> f a) -> a -> t Source #

Anamorphism, meant to build up a structure recursively.

hylo :: Functor f => (f b -> b) -> (a -> f a) -> a -> b Source #

Hylomorphism; fold a structure while buildiung it up.

prepro :: (Recursive f t, Corecursive f t) => (f t -> f t) -> (f a -> a) -> t -> a Source #

Prepromorphism. Fold a structure while applying a natural transformation at each step.

postpro :: (Recursive f t, Corecursive f t) => (f t -> f t) -> (a -> f a) -> a -> t Source #

Postpromorphism. Build up a structure, applying a natural transformation along the way.

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

A mutumorphism.

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

Zygomorphism (see here for a neat example)

para :: (Recursive f t, Corecursive f t) => (f (t, a) -> a) -> t -> a Source #

Paramorphism

apo :: Corecursive f t => (a -> f (Either t a)) -> a -> t Source #

Apomorphism

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

Elgot algebra (see this paper)

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

Elgot coalgebra

micro :: Corecursive f a => (b -> Either a (f b)) -> b -> a Source #

Anamorphism that allows shortcuts.

meta :: (Corecursive f t', Recursive g t) => (a -> f a) -> (b -> a) -> (g b -> b) -> t -> t' Source #

Gibbons' metamorphism. Tear down a structure, transform it, and then build up a new structure

meta' :: Functor g => (f a -> a) -> (forall c. g c -> f c) -> (b -> g b) -> b -> a Source #

Erwig's metamorphism. Essentially a hylomorphism with a natural transformation in between. This allows us to use more than one functor in a hylomorphism.

Mendler-style recursion schemes

mhisto :: (forall y. (y -> c) -> (y -> f y) -> f y -> c) -> Fix f -> c Source #

Mendler's histomorphism

mcata :: (forall y. (y -> c) -> f y -> c) -> Fix f -> c Source #

Mendler's catamorphism

Monadic recursion schemes

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

anaM :: (Corecursive f t, Traversable f, Monad m) => (a -> m (f a)) -> a -> m t Source #

hyloM :: (Traversable f, Monad m) => (f b -> m b) -> (a -> m (f a)) -> a -> m b Source #

Helper functions

lambek :: (Recursive f t, Corecursive f t) => t -> f t Source #

colambek :: (Recursive f t, Corecursive f t) => f t -> t Source #