multirec-0.7.5: Generic programming for families of recursive datatypes

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

Generics.MultiRec.Base

Contents

Description

This module is the base of the multirec library. It defines the view of a family of datatypes: All the datatypes of the family are represented as indexed functors that are built up from the structure types defined in this module. Furthermore, in order to use the library for a family, conversion functions have to be defined between the original datatypes and their representation. The type class that holds these conversion functions are also defined here.

Synopsis

Structure types

data I xi r ix Source

Represents recursive positions. The first argument indicates which type to recurse on.

Constructors

I 

Fields

unI :: r xi
 

Instances

El phi xi => HFunctor phi (I xi) 
El phi xi => HEq phi (I xi) 
El phi xi => HShow phi (I xi) 
El phi xi => HReadPrec phi (I xi) 
(Constructor c, HReadPrec phi (I xi)) => HReadPrec phi (C c (I xi)) 
ConNames (I a) 
Fold (I xi) 
Fold (I xi) 
CountAtoms (I xi) 
Functor f => Fold ((:.:) f (I xi)) 
Fold g => Fold ((:*:) (I xi) g) 
Fold g => Fold ((:*:) (I xi) g) 
type Alg (I xi) r = r -> r

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

type Comp (I xi) r ix = r xi 
type Alg (I xi) r ix = r xi -> r ix

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

type Alg ((:*:) (I xi) 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 ((:.:) f (I xi)) r ix = f (r xi) -> r ix 

data K a r ix Source

Represents constant types that do not belong to the family.

Constructors

K 

Fields

unK :: a
 

Instances

HFunctor phi (K x) 
Eq a => HEq phi (K a)

For constant types, we make use of the standard equality function.

Show a => HShow phi (K a)

For constant types, we make use of the standard show function.

Read a => HReadPrec phi (K a) 
(Constructor c, HReadPrec phi (K a)) => HReadPrec phi (C c (K a)) 
ConNames (K x) 
Fold (K a) 
Fold (K a) 
CountAtoms (K a) 
Fold g => Fold ((:*:) (K a) g) 
Fold g => Fold ((:*:) (K a) g) 
type Alg (K a) r = a -> r

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

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

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

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.

data U r ix Source

Represents constructors without fields.

Constructors

U 

Instances

ConNames U 
Fold U 
Fold U 
HFunctor phi U 
HEq phi U 
HShow phi U 
HReadPrec phi U 
Constructor c => HReadPrec phi (C c U) 
type Alg U r = r

For a unit, no arguments are available.

type Alg U r ix = r ix

For a unit, no arguments are available.

data (f :+: g) r ix infixr 5 Source

Represents sums (choices between constructors).

Constructors

L (f r ix) 
R (g r ix) 

Instances

(HFunctor phi f, HFunctor phi g) => HFunctor phi ((:+:) f g) 
(HEq phi f, HEq phi g) => HEq phi ((:+:) f g) 
(HShow phi f, HShow phi g) => HShow phi ((:+:) f g) 
(HReadPrec phi f, HReadPrec phi g) => HReadPrec phi ((:+:) f g) 
(ConNames f, ConNames g) => ConNames ((:+:) f g) 
(Fold f, Fold g) => Fold ((:+:) f g) 
(Fold f, Fold g) => Fold ((:+:) f g) 
type Alg ((:+:) f g) r = (Alg f r, Alg g r)

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

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

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

data (f :*: g) r ix infixr 7 Source

Represents products (sequences of fields of a constructor).

Constructors

(f r ix) :*: (g r ix) infixr 7 

Instances

(HFunctor phi f, HFunctor phi g) => HFunctor phi ((:*:) f g) 
(HEq phi f, HEq phi g) => HEq phi ((:*:) f g) 
(HShow phi f, HShow phi g) => HShow phi ((:*:) f g) 
(Constructor c, CountAtoms ((:*:) f g), HReadPrec phi f, HReadPrec phi g) => HReadPrec phi (C c ((:*:) f g)) 
(HReadPrec phi f, HReadPrec phi g) => HReadPrec phi ((:*:) f g) 
ConNames ((:*:) f g) 
Fold g => Fold ((:*:) (K a) g) 
Fold g => Fold ((:*:) (I xi) g) 
Fold g => Fold ((:*:) (K a) g) 
Fold g => Fold ((:*:) (I xi) g) 
(CountAtoms f, CountAtoms g) => CountAtoms ((:*:) f g) 
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 ((:*:) (I xi) 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 ((:*:) f g) r ix = Comp f r ix -> Alg g r ix

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

data (f :>: ix) r ix' where infix 6 Source

Is used to indicate the type that a particular constructor injects to.

Constructors

Tag :: f r ix -> (f :>: ix) r ix 

Instances

HFunctor phi f => HFunctor phi ((:>:) f ix) 
HEq phi f => HEq phi ((:>:) f ix) 
HShow phi f => HShow phi ((:>:) f ix) 
(HReadPrec phi f, EqS phi, El phi ix) => HReadPrec phi ((:>:) f ix) 
ConNames f => ConNames ((:>:) f ix) 
Fold f => Fold ((:>:) f xi) 
Fold f => Fold ((:>:) f xi) 
type Alg ((:>:) f xi) r = Alg f r

Tags are ignored.

type Alg ((:>:) f xi) r ix = Alg f r xi

A tag changes the index of the final result.

unTag :: (f :>: ix) r ix -> f r ix Source

Destructor for '(:>:)'.

data (f :.: g) r ix Source

Represents composition with functors of kind * -> *.

Constructors

D 

Fields

unD :: f (g r ix)
 

Instances

(Traversable f, HFunctor phi g) => HFunctor phi ((:.:) f g) 
(Eq1 f, HEq phi g) => HEq phi ((:.:) f g) 
(Show1 f, Traversable f, HShow phi g) => HShow phi ((:.:) f g) 
(Constructor c, HReadPrec phi ((:.:) f g)) => HReadPrec phi (C c ((:.:) f g)) 
(Read1 f, HReadPrec phi g) => HReadPrec phi ((:.:) f g) 
ConNames ((:.:) f g) 
Functor f => Fold ((:.:) f (I xi)) 
type Comp ((:.:) f g) r ix = f (Comp g r ix) 
type Alg ((:.:) f (I xi)) r ix = f (r xi) -> r ix 

data C c f r ix where Source

Represents constructors.

Constructors

C :: f r ix -> C c f r ix 

Instances

(Constructor c, HFunctor phi f) => HFunctor phi (C c f) 
(Constructor c, HEq phi f) => HEq phi (C c f) 
(Constructor c, HShow phi f) => HShow phi (C c f) 
(Constructor c, CountAtoms ((:*:) f g), HReadPrec phi f, HReadPrec phi g) => HReadPrec phi (C c ((:*:) f g)) 
(Constructor c, HReadPrec phi ((:.:) f g)) => HReadPrec phi (C c ((:.:) f g)) 
(Constructor c, HReadPrec phi (K a)) => HReadPrec phi (C c (K a)) 
(Constructor c, HReadPrec phi (I xi)) => HReadPrec phi (C c (I xi)) 
Constructor c => HReadPrec phi (C c U) 
Constructor c => ConNames (C c f) 
Fold f => Fold (C c f) 
Fold f => Fold (C c f) 
type Alg (C c f) r = Alg f r

Constructors are ignored.

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

Constructors are ignored.

unC :: C c f r ix -> f r ix Source

Destructor for C.

Constructor information

Unlifted variants

newtype I0 a Source

Unlifted version of I.

Constructors

I0 

Fields

unI0 :: a
 

Instances

newtype K0 a b Source

Unlifted version of K.

Constructors

K0 

Fields

unK0 :: a
 

Instances

Functor (K0 a) 

Indexed families

type family PF phi :: (* -> *) -> * -> * Source

Type family describing the pattern functor of a family.

class El phi ix where Source

Class for the members of a family.

Methods

proof :: phi ix Source

class Fam phi where Source

Class that contains the shallow conversion functions for a family.

Methods

from :: phi ix -> ix -> PF phi I0 ix Source

to :: phi ix -> PF phi I0 ix -> ix Source

index :: El phi ix => phi ix Source

For backwards-compatibility: a synonym for proof.

Equality for indexed families

class EqS phi where Source

Semi-decidable equality for types of a family.

Methods

eqS :: phi ix -> phi ix' -> Maybe (ix :=: ix') Source