regular-0.3.4.4: Generic programming library for regular datatypes.

Copyright(c) 2008 Universiteit Utrecht
LicenseBSD3
Maintainergenerics@haskell.org
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe-Inferred
LanguageHaskell98

Generics.Regular.Functions.Fold

Contents

Description

Summary: Generic folding and unfolding.

Synopsis

Generic folding

type family Alg f r :: * Source

Instances

type Alg U r = r

For a unit, no arguments are available.

type Alg I r = r -> r

For an identity, we turn the recursive result into a final result.

type Alg (K a) r = a -> r

For a constant, we take the constant value to a result.

type Alg (S s f) r = Alg f r

Selectors are ignored.

type Alg (C c f) r = Alg f r

Constructors are ignored.

type Alg ((:*:) (S s (K a)) g) r = a -> Alg g r 
type Alg ((:*:) I g) r = r -> Alg g r

For a product where the left hand side is an identity, we take the recursive result as an additional argument.

type Alg ((:*:) (K a) g) r = a -> Alg g r

For a product where the left hand side is a constant, we take the value as an additional argument.

type Alg ((:+:) f g) r = (Alg f r, Alg g r)

For a sum, the algebra is a pair of two algebras.

type Algebra a r = Alg (PF a) r Source

class Fold f where Source

The class fold explains how to convert an algebra Alg into a function from functor to result.

Methods

alg :: Alg f r -> f r -> r Source

Instances

Fold U 
Fold I 
Fold (K a) 
Fold f => Fold (S s f) 
Fold f => Fold (C c f) 
Fold g => Fold ((:*:) I g) 
Fold g => Fold ((:*:) (K a) g) 
(Fold f, Fold g) => Fold ((:+:) f g) 

fold :: (Regular a, Fold (PF a), Functor (PF a)) => Algebra a r -> a -> r Source

Fold with convenient algebras.

Generic unfolding

type family CoAlg f s :: * Source

Instances

type CoAlg U s = ()

Units can only produce units, so we use the singleton type to encode the lack of choice.

type CoAlg I s = s

For an identity, we produce a new seed to create the recursive result.

type CoAlg (K a) s = a

For a constant, we produce a constant value as a result.

type CoAlg (S r f) s = CoAlg f s

Selectors are ignored.

type CoAlg (C c f) s = CoAlg f s

Constructors are ignored.

type CoAlg ((:*:) f g) s = (CoAlg f s, CoAlg g s)

For a produt, the coalgebra is a pair of the two arms.

type CoAlg ((:+:) f g) s = Either (CoAlg f s) (CoAlg g s)

For a sum, the coalgebra produces either the left or the right side.

type CoAlgebra a s = s -> CoAlg (PF a) s Source

class Unfold f where Source

The class unfold explains how to convert a coalgebra CoAlg and a seed into a representation.

Methods

coalg :: (s -> a) -> CoAlg f s -> f a Source

Instances

Unfold U 
Unfold I 
Unfold (K a) 
Unfold f => Unfold (S s f) 
Unfold f => Unfold (C c f) 
(Unfold f, Unfold g) => Unfold ((:*:) f g) 
(Unfold f, Unfold g) => Unfold ((:+:) f g) 

unfold :: (Unfold (PF a), Regular a) => CoAlgebra a s -> s -> a Source

Construction of algebras

(&) :: a -> b -> (a, b) infixr 5 Source

For constructing algebras it is helpful to use this pairing combinator.