multirec-0.7.9: Generic programming for families of recursive datatypes

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

Generics.MultiRec.FoldAlgK

Contents

Description

A variant of fold that allows the specification of the algebra in a convenient way, and that fixes the result type to a constant.

Synopsis
  • type family Alg (f :: (* -> *) -> * -> *) (r :: *) :: *
  • type Algebra phi r = forall ix. phi ix -> Alg (PF phi) r
  • class Fold (f :: (* -> *) -> * -> *) where
  • fold :: forall phi ix r. (Fam phi, HFunctor phi (PF phi), Fold (PF phi)) => Algebra phi r -> phi ix -> ix -> r
  • (&) :: a -> b -> (a, b)

The type family of convenient algebras.

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

The type family we use to describe the convenient algebras.

Instances
type Alg U r Source #

For a unit, no arguments are available.

Instance details

Defined in Generics.MultiRec.FoldAlgK

type Alg U r = r
type Alg (K a) r Source #

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

Instance details

Defined in Generics.MultiRec.FoldAlgK

type Alg (K a) r = a -> r
type Alg (I xi) r Source #

For an identity, we turn the recursive result into a final result. Note that the index can change.

Instance details

Defined in Generics.MultiRec.FoldAlgK

type Alg (I xi) r = r -> r
type Alg (C c f) r Source #

Constructors are ignored.

Instance details

Defined in Generics.MultiRec.FoldAlgK

type Alg (C c f) r = Alg f r
type Alg (f :>: xi) r Source #

Tags are ignored.

Instance details

Defined in Generics.MultiRec.FoldAlgK

type Alg (f :>: xi) r = Alg f r
type Alg (K a :*: g) r Source #

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

Instance details

Defined in Generics.MultiRec.FoldAlgK

type Alg (K a :*: g) r = a -> Alg g r
type Alg (I xi :*: g) r Source #

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

Instance details

Defined in Generics.MultiRec.FoldAlgK

type Alg (I xi :*: g) r = r -> Alg g r
type Alg (f :+: g) r Source #

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

Instance details

Defined in Generics.MultiRec.FoldAlgK

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

type Algebra phi r = forall ix. phi ix -> Alg (PF phi) r 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.

Methods

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

Instances
Fold U Source # 
Instance details

Defined in Generics.MultiRec.FoldAlgK

Methods

alg :: Alg U r -> U (K0 r) ix -> r Source #

Fold (K a) Source # 
Instance details

Defined in Generics.MultiRec.FoldAlgK

Methods

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

Fold (I xi) Source # 
Instance details

Defined in Generics.MultiRec.FoldAlgK

Methods

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

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

Defined in Generics.MultiRec.FoldAlgK

Methods

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

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

Defined in Generics.MultiRec.FoldAlgK

Methods

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

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

Defined in Generics.MultiRec.FoldAlgK

Methods

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

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

Defined in Generics.MultiRec.FoldAlgK

Methods

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

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

Defined in Generics.MultiRec.FoldAlgK

Methods

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

Interface

fold :: forall phi ix r. (Fam phi, HFunctor phi (PF phi), Fold (PF phi)) => Algebra phi r -> phi ix -> ix -> r 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.