multirec-0.7.1: Generic programming for families of recursive datatypes

Portabilitynon-portable
Stabilityexperimental
Maintainergenerics@haskell.org

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) 

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) 

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) 

data (f :+: g) r ix 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) 

data (f :*: g) r ix Source

Represents products (sequences of fields of a constructor).

Constructors

(f r ix) :*: (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) 
(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) 

data f :>: ix whereSource

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) 

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

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)) 

data C c f r ix whereSource

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) 

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

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 whereSource

Class for the members of a family.

Methods

proof :: phi ixSource

class Fam phi whereSource

Class that contains the shallow conversion functions for a family.

Methods

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

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

index :: El phi ix => phi ixSource

For backwards-compatibility: a synonym for proof.

Equality for indexed families

class EqS phi whereSource

Semi-decidable equality for types of a family.

Methods

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