multirec-0.7.6: Generic programming for families of recursive datatypes

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

Generics.MultiRec.FoldAlg

Contents

Description

A variant of fold that allows the specification of the algebra in a convenient way.

Synopsis

The type family of convenient algebras.

type family Alg (f :: (* -> *) -> * -> *) (r :: * -> *) (ix :: *) :: * Source #

The type family we use to describe the convenient algebras.

Instances

type Alg U r ix Source # 
type Alg U r ix = r ix
type Alg (K a) r ix Source # 
type Alg (K a) r ix = a -> r ix
type Alg (I xi) r ix Source # 
type Alg (I xi) r ix = r xi -> r ix
type Alg (C c f) r ix Source # 
type Alg (C c f) r ix = Alg f r ix
type Alg ((:.:) f (I xi)) r ix Source # 
type Alg ((:.:) f (I xi)) r ix = f (r xi) -> r ix
type Alg ((:>:) f xi) r ix Source # 
type Alg ((:>:) f xi) r ix = Alg f r xi
type Alg ((:*:) f g) r ix Source # 
type Alg ((:*:) f g) r ix = Comp f r ix -> Alg g r ix
type Alg ((:+:) f g) r ix Source # 
type Alg ((:+:) f g) r ix = (Alg f r ix, Alg g r ix)

type family Comp (f :: (* -> *) -> * -> *) (r :: * -> *) (ix :: *) :: * Source #

Instances

type Comp (K a) r ix Source # 
type Comp (K a) r ix = a
type Comp (I xi) r ix Source # 
type Comp (I xi) r ix = r xi
type Comp ((:.:) f g) r ix Source # 
type Comp ((:.:) f g) r ix = f (Comp g r ix)

type Algebra phi r = forall ix. phi ix -> Alg (PF phi) r ix Source #

The algebras passed to the fold have to work for all index types in the family. The additional witness argument is required only to make GHC's typechecker happy.

The class to turn convenient algebras into standard algebras.

class Fold f where Source #

The class fold explains how to convert a convenient algebra Alg back into a function from functor to result, as required by the standard fold function.

Minimal complete definition

alg

Methods

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

Instances

Fold U Source # 

Methods

alg :: Alg U r ix -> U r ix -> r ix Source #

Fold (K a) Source # 

Methods

alg :: Alg (K a) r ix -> K a r ix -> r ix Source #

Fold (I xi) Source # 

Methods

alg :: Alg (I xi) r ix -> I xi r ix -> r ix Source #

Fold f => Fold (C c f) Source # 

Methods

alg :: Alg (C c f) r ix -> C c f r ix -> r ix Source #

Functor f => Fold ((:.:) f (I xi)) Source # 

Methods

alg :: Alg (f :.: I xi) r ix -> (f :.: I xi) r ix -> r ix Source #

Fold f => Fold ((:>:) f xi) Source # 

Methods

alg :: Alg (f :>: xi) r ix -> (f :>: xi) r ix -> r ix Source #

Fold g => Fold ((:*:) (K a) g) Source # 

Methods

alg :: Alg (K a :*: g) r ix -> (K a :*: g) r ix -> r ix Source #

Fold g => Fold ((:*:) (I xi) g) Source # 

Methods

alg :: Alg (I xi :*: g) r ix -> (I xi :*: g) r ix -> r ix Source #

(Fold f, Fold g) => Fold ((:+:) f g) Source # 

Methods

alg :: Alg (f :+: g) r ix -> (f :+: g) r ix -> r ix Source #

Interface

fold :: forall phi ix r. (Fam phi, HFunctor phi (PF phi), Fold (PF phi)) => Algebra phi r -> phi ix -> ix -> r ix Source #

Fold with convenient algebras.

Construction of algebras

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

For constructing algebras that are made of nested pairs rather than n-ary tuples, it is helpful to use this pairing combinator.