recursion-1.2.0.0: A recursion schemes library for GHC.

Safe HaskellNone
LanguageHaskell2010

Control.Recursion

Contents

Synopsis

Typeclasses

type family Base t :: * -> * Source #

Instances
type Base Natural Source # 
Instance details

Defined in Control.Recursion

type Base [a] Source # 
Instance details

Defined in Control.Recursion

type Base [a] = ListF a
type Base (NonEmpty a) Source # 
Instance details

Defined in Control.Recursion

type Base (NonEmpty a) = NonEmptyF a
type Base (Mu f) Source # 
Instance details

Defined in Control.Recursion

type Base (Mu f) = f
type Base (Nu f) Source # 
Instance details

Defined in Control.Recursion

type Base (Nu f) = f
type Base (Fix f) Source # 
Instance details

Defined in Control.Recursion

type Base (Fix f) = f

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

Minimal complete definition

project

Methods

project :: t -> Base t t Source #

Instances
Recursive Natural Source # 
Instance details

Defined in Control.Recursion

Recursive [a] Source # 
Instance details

Defined in Control.Recursion

Methods

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

Recursive (NonEmpty a) Source # 
Instance details

Defined in Control.Recursion

Methods

project :: NonEmpty a -> Base (NonEmpty a) (NonEmpty a) Source #

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

Defined in Control.Recursion

Methods

project :: Mu f -> Base (Mu f) (Mu f) Source #

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

Defined in Control.Recursion

Methods

project :: Nu f -> Base (Nu f) (Nu f) Source #

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

Minimal complete definition

embed

Methods

embed :: Base t t -> t Source #

Instances
Corecursive Natural Source # 
Instance details

Defined in Control.Recursion

Corecursive [a] Source # 
Instance details

Defined in Control.Recursion

Methods

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

Corecursive (NonEmpty a) Source # 
Instance details

Defined in Control.Recursion

Methods

embed :: Base (NonEmpty a) (NonEmpty a) -> NonEmpty a Source #

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

Defined in Control.Recursion

Methods

embed :: Base (Mu f) (Mu f) -> Mu f Source #

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

Defined in Control.Recursion

Methods

embed :: Base (Nu f) (Nu f) -> Nu f Source #

Types

newtype Fix f Source #

Constructors

Fix 

Fields

Instances
type Base (Fix f) Source # 
Instance details

Defined in Control.Recursion

type Base (Fix f) = f

newtype Mu f Source #

Constructors

Mu (forall a. (f a -> a) -> a) 
Instances
Functor f => Corecursive (Mu f) Source # 
Instance details

Defined in Control.Recursion

Methods

embed :: Base (Mu f) (Mu f) -> Mu f Source #

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

Defined in Control.Recursion

Methods

project :: Mu f -> Base (Mu f) (Mu f) Source #

type Base (Mu f) Source # 
Instance details

Defined in Control.Recursion

type Base (Mu f) = f

data Nu f Source #

Constructors

Nu (a -> f a) a 
Instances
Functor f => Corecursive (Nu f) Source # 
Instance details

Defined in Control.Recursion

Methods

embed :: Base (Nu f) (Nu f) -> Nu f Source #

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

Defined in Control.Recursion

Methods

project :: Nu f -> Base (Nu f) (Nu f) Source #

type Base (Nu f) Source # 
Instance details

Defined in Control.Recursion

type Base (Nu f) = f

data ListF a b Source #

Constructors

Cons a b 
Nil 
Instances
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 #

data NonEmptyF a b Source #

Constructors

NonEmptyF a (Maybe b) 
Instances
Functor (NonEmptyF a) Source # 
Instance details

Defined in Control.Recursion

Methods

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

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

Recursion schemes

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

Base functor for a list of type [a]. | Hylomorphism; fold a structure while buildiung it up.

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

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

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

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

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

A mutumorphism.

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

Zygomorphism (see here for a neat example)

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

Paramorphism

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

Apomorphism. Compare micro.

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 a => (b -> Either a (Base a b)) -> b -> a Source #

Anamorphism allowing shortcuts. Compare apo

meta :: (Corecursive t', Recursive t) => (a -> Base t' a) -> (b -> a) -> (Base t 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.

dicata :: Recursive t => (Base t (a, t) -> a) -> (Base t (a, t) -> t) -> t -> a Source #

Catamorphism collapsing along two data types simultaneously. Basically a fancy zygomorphism.

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 t, Traversable (Base t), Monad m) => (Base t a -> m a) -> t -> m a Source #

anaM :: (Corecursive t, Traversable (Base t), Monad m) => (a -> m (Base t 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 t, Corecursive t) => t -> Base t t Source #

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