pointless-haskell-0.0.8: Pointless Haskell library

Portabilitynon-portable
Stabilityexperimental
Maintainerhpacheco@di.uminho.pt

Generics.Pointless.RecursionPatterns

Description

Pointless Haskell: point-free programming with recursion patterns as hylomorphisms

This module defines recursion patterns as hylomorphisms.

Recursion patterns can be seen as high-order functions that encapsulate typical forms of recursion. The hylomorphism recursion pattern was first defined in http://research.microsoft.com/~emeijer/Papers/CWIReport.pdf, along with its relation with derived more specific recursion patterns such as catamorphisms, anamorphisms and paramorphisms.

The seminal paper that introduced point-free programming and defined many of the laws for catamorphisms and anamorphisms can be found in http://eprints.eemcs.utwente.nl/7281/01/db-utwente-40501F46.pdf.

More complex and exotic recursion patterns have been discovered later, such as accumulations, apomorphisms, zygomorphisms, histomorphisms, futumorphisms, dynamorphisms or chronomorphisms.

Synopsis

Documentation

hylo :: Functor (PF b) => Ann b -> (F b c -> c) -> (a -> F b a) -> a -> cSource

Definition of an hylomorphism

cata :: (Mu a, Functor (PF a)) => Ann a -> (F a b -> b) -> a -> bSource

Definition of a catamorphism as an hylomorphism.

Catamorphisms model the fundamental pattern of iteration, where constructors for recursive datatypes are repeatedly consumed by arbitrary functions. They are usually called folds.

cataRec :: (Mu a, Functor (PF a)) => Ann a -> (F a b -> b) -> a -> bSource

Recursive definition of a catamorphism.

ana :: (Mu b, Functor (PF b)) => Ann b -> (a -> F b a) -> a -> bSource

Definition of an anamorphism as an hylomorphism.

Anamorphisms resembles the dual of iteration and, hence, dene the inverse of catamorphisms. Instead of consuming recursive types, they produce values of those types.

anaRec :: (Mu b, Functor (PF b)) => Ann b -> (a -> F b a) -> a -> bSource

Recursive definition of an anamorphism.

type Para a = a :@!: (I :*!: K a)Source

The functor of the intermediate type of a paramorphism is the functor of the consumed type a extended with an extra annotation to itself in recursive definitions.

para :: (Mu a, Functor (PF a)) => Ann a -> (F a (b, a) -> b) -> a -> bSource

Definition of a paramorphism.

Paramorphisms supply the gene of a catamorphism with a recursively computed copy of the input.

The first introduction to paramorphisms is reported in http://www.cs.uu.nl/research/techreps/repo/CS-1990/1990-04.pdf.

paraRec :: (Mu a, Functor (PF a)) => Ann a -> (F a (b, a) -> b) -> a -> bSource

Recursive definition of a paramorphism.

type Apo b = b :@!: (I :+!: K b)Source

The functor of the intermediate type of an apomorphism is the functor of the generated type b with an alternative annotation to itself in recursive definitions.

apo :: (Mu b, Functor (PF b)) => Ann b -> (a -> F b (Either a b)) -> a -> bSource

Definition of an apomorphism as an hylomorphism.

Apomorphisms are the dual recursion patterns of paramorphisms, and therefore they can express functions defined by primitive corecursion.

They were introduced independently in http://www.cs.ut.ee/~varmo/papers/nwpt97.ps.gz and Program Construction and Generation Based on Recursive Types, MSc thesis.

apoRec :: (Mu b, Functor (PF b)) => Ann b -> (a -> F b (Either a b)) -> a -> bSource

Recursive definition of an apomorphism.

type Zygo a b = a :@!: (I :*!: K b)Source

In zygomorphisms we extend the recursive occurences in the base functor functor of type a with an extra annotation b.

zygo :: (Mu a, Functor (PF a), F a (a, b) ~ F (Zygo a b) a) => Ann a -> (F a b -> b) -> (F (Zygo a b) b -> b) -> a -> bSource

Definition of a zygomorphism as an hylomorphism.

Zygomorphisms were introduced in http://dissertations.ub.rug.nl/faculties/science/1990/g.r.malcolm/.

They can be seen as the asymmetric form of mutual iteration, where both a data consumer and an auxiliary function are defined (http://www.fing.edu.uy/~pardo/papers/njc01.ps.gz).

type Accum a b = a :*!: K bSource

In accumulations we add an extra annotation b to the base functor of type a.

accum :: (Mu a, Functor (PF a)) => Ann a -> (F (Accum a b) c -> c) -> ((F a a, b) -> F a (a, b)) -> (a, b) -> cSource

Definition of an accumulation as an hylomorphism.

Accumulations http://www.fing.edu.uy/~pardo/papers/wcgp02.ps.gz are binary functions that use the second parameter to store intermediate results.

The so called accumulation technique is tipically used in functional programming to derive efficient implementations of some recursive functions.

type Histo a c = K c :*!: aSource

In histomorphisms we add an extra annotation c to the base functor of type a.

histo :: (Mu a, Functor (PF a)) => Ann a -> (F a (Histo a c) -> c) -> a -> cSource

Definition of an histomorphism as an hylomorphism (as long as the catamorphism is defined as an hylomorphism).

Histomorphisms (http://cs.ioc.ee/~tarmo/papers/inf.ps.gz) capture the powerfull schemes of course-of-value iteration, and differ from catamorphisms for being able to apply the gene function at a deeper depth of recursion. In other words, they allow to reuse sub-sub constructor results.

outl :: Histo a c -> cSource

The combinator outl unpacks the functor of an histomorphism and selects the annotation.

outr :: Histo a c -> F a (Histo a c)Source

The combinator outr unpacks the functor of an histomorphism and discards the annotation.

type Futu b c = K c :+!: bSource

In futumorphisms we add an alternative annotation c to the base functor of type b.

futu :: (Mu b, Functor (PF b)) => Ann b -> (a -> F b (Futu b a)) -> a -> bSource

Definition of a futumorphism as an hylomorphism (as long as the anamorphism is defined as an hylomorphism).

Futumorphisms are the dual of histomorphisms and are proposed as 'cocourse-of-argument' coiterators by their creators (http://cs.ioc.ee/~tarmo/papers/inf.ps.gz).

In the same fashion as histomorphisms, it allows to seed the gene with multiple levels of depth instead of having to do 'all at once' with an anamorphism.

innl :: c -> Futu b cSource

The combinator innl packs the functor of a futumorphism from the base functor.

innr :: F b (Futu b c) -> Futu b cSource

The combinator innr packs the functor of an futumorphism from an annotation.

dyna :: (Mu b, Functor (PF b)) => Ann b -> (F b (Histo b c) -> c) -> (a -> F b a) -> a -> cSource

Definition of a dynamorphism as an hylomorphisms.

Dynamorphisms (http://math.ut.ee/~eugene/kabanov-vene-mpc-06.pdf) are a more general form of histomorphisms for capturing dynaming programming constructions.

Instead of following the recursion pattern of the input via structural recursion (as in histomorphisms), dynamorphisms allow us to reuse the annotated structure in a bottom-up approach and avoiding rebuilding it every time an annotation is needed, what provides a more efficient dynamic algorithm.

chrono :: (Mu c, Functor (PF c)) => Ann c -> (F c (Histo c b) -> b) -> (a -> F c (Futu c a)) -> a -> bSource

Definition of a chronomorphism as an hylomorphism.

This recursion pattern subsumes histomorphisms, futumorphisms and dynamorphisms and can be seen as the natural hylomorphism generalization from composing an histomorphism after a futumorphism. Therefore, chronomorphisms can 'look back' when consuming a type and 'jump forward' when generating one, via it's fold/unfold operations, respectively.

The notion of chronomorphism is a recent recursion pattern (at least known as such). The first and single reference available is http://comonad.com/reader/2008/time-for-chronomorphisms/.

fix :: (a -> a) -> aSource

The Fixpoint combinator as an hylomorphism.

fix is a fixpoint combinator if fix = app . (id /\ fix).

After expanding the denitions of ., /\ and app we see that this corresponds to the expected pointwise equation fix f = f (fix f).