emgm-0.4: Extensible and Modular Generics for the Masses

Portabilitynon-portable
Stabilityexperimental
Maintainergenerics@haskell.org

Generics.EMGM.Base

Contents

Description

Summary: Type classes used for generic functions with one generic argument.

A generic function is defined as an instance of Generic, Generic2, or Generic3. Each method in the class serves for a case in the datatype representation

A representation dispatcher simplifies the use of a generic function. There must be an instance of each of the classes Rep, FRep, FRep2, etc. (that apply) for every datatype.

Synopsis

Documentation

Re-export the types and related functions for the structure representation.

Classes for Generic Functions

class Generic g whereSource

This class forms the foundation for defining generic functions with a single generic argument. Each method represents a type case. There are cases for primitive types, structural representation types, and for user-defined datatypes.

The included modules using Generic are:

Methods

rint :: g IntSource

Case for the primitive type Int.

rinteger :: g IntegerSource

Case for the primitive type Integer.

rfloat :: g FloatSource

Case for the primitive type Float.

rdouble :: g DoubleSource

Case for the primitive type Double.

rchar :: g CharSource

Case for the primitive type Char.

runit :: g UnitSource

Case for the structural representation type Unit. Represents a constructor with no arguments.

rsum :: g a -> g b -> g (a :+: b)Source

Case for the structural representation type :+: (sum). Represents alternative constructors.

rprod :: g a -> g b -> g (a :*: b)Source

Case for the structural representation type :*: (product). Represents the fields of a constructor.

rcon :: ConDescr -> g a -> g aSource

Case for constructors. It is used to hold the meta-information about a constructor, e.g. name, arity, fixity, etc. This is not needed for many generic functions, so the default implementation is:

   rcon = const id

rlbl :: LblDescr -> g a -> g aSource

Case for labeled field. Contains the label string. This is not needed for many generic functions, so the default implementation is:

   rlbl = const id

rtype :: EP b a -> g a -> g bSource

Case for datatypes. This method is used to define the structural representation of an arbitrary Haskell datatype. The first argument is the embedding-projection pair, necessary for establishing the isomorphism between datatype and representation. The second argument is the run-time representation using the methods of Generic.

class Generic2 g whereSource

This class forms the foundation for defining generic functions with two generic arguments. See Generic for details.

The included modules using Generic2 are:

Methods

rint2 :: g Int IntSource

rinteger2 :: g Integer IntegerSource

rfloat2 :: g Float FloatSource

rdouble2 :: g Double DoubleSource

rchar2 :: g Char CharSource

runit2 :: g Unit UnitSource

rsum2 :: g a1 a2 -> g b1 b2 -> g (a1 :+: b1) (a2 :+: b2)Source

rprod2 :: g a1 a2 -> g b1 b2 -> g (a1 :*: b1) (a2 :*: b2)Source

rcon2 :: ConDescr -> g a1 a2 -> g a1 a2Source

rlbl2 :: LblDescr -> g a1 a2 -> g a1 a2Source

rtype2 :: EP a2 a1 -> EP b2 b1 -> g a1 b1 -> g a2 b2Source

See rtype. This case is the primary difference that separates Generic2 from Generic. Since we have two generic type parameters, we need to have two EP values. Each translates between the Haskell type and its generic representation.

Instances

Generic2 Map 
(Monad m, FRep2 Map f, FRep3 (ZipWith m) f) => Generic2 (Transpose m f c) 

class Generic3 g whereSource

This class forms the foundation for defining generic functions with three generic arguments. See Generic for details.

The included modules using Generic3 are:

Methods

rint3 :: g Int Int IntSource

rinteger3 :: g Integer Integer IntegerSource

rfloat3 :: g Float Float FloatSource

rdouble3 :: g Double Double DoubleSource

rchar3 :: g Char Char CharSource

runit3 :: g Unit Unit UnitSource

rsum3 :: g a1 a2 a3 -> g b1 b2 b3 -> g (a1 :+: b1) (a2 :+: b2) (a3 :+: b3)Source

rprod3 :: g a1 a2 a3 -> g b1 b2 b3 -> g (a1 :*: b1) (a2 :*: b2) (a3 :*: b3)Source

rcon3 :: ConDescr -> g a1 a2 a3 -> g a1 a2 a3Source

rlbl3 :: LblDescr -> g a1 a2 a3 -> g a1 a2 a3Source

rtype3 :: EP a2 a1 -> EP b2 b1 -> EP c2 c1 -> g a1 b1 c1 -> g a2 b2 c2Source

See rtype. This case is the primary difference that separates Generic3 from Generic. Since we have three generic type parameters, we need three EP values. Each translates between the Haskell type and its generic representation.

Instances

Classes for Representation Dispatchers

class Rep g a whereSource

Representation dispatcher for monomorphic types (kind *) used with Generic. Every structure type and supported datatype should have an instance of Rep.

Methods

rep :: g aSource

Instances

Generic g => Rep g Unit 
Generic g => Rep g Char 
Generic g => Rep g Double 
Generic g => Rep g Float 
Generic g => Rep g Integer 
Generic g => Rep g Int 
Generic g => Rep g Bool 
Generic g => Rep g () 
Rep Read String

Ad-hoc instance for strings

Rep Read ()

Ad-hoc instance for ()

Rep Show String

Ad-hoc instance for strings

Rep Show ()

Ad-hoc instance for ()

(Generic g, Rep g a) => Rep g [a] 
(Generic g, Rep g a) => Rep g (Maybe a) 
(Integral a, Generic g, Rep g a) => Rep g (Ratio a) 
Rep Read a => Rep Read [a]

Ad-hoc instance for lists

Rep Show a => Rep Show [a]

Ad-hoc instance for lists

(Generic g, Rep g a, Rep g b) => Rep g (:*: a b) 
(Generic g, Rep g a, Rep g b) => Rep g (:+: a b) 
(Generic g, Rep g a, Rep g b) => Rep g (Either a b) 
(Generic g, Rep g a, Rep g b) => Rep g (a, b) 
(Rep Read a, Rep Read b) => Rep Read (a, b)

Ad-hoc instance for (a,b)

(Rep Show a, Rep Show b) => Rep Show (a, b)

Ad-hoc instance for (a,b)

(Generic g, Rep g a, Rep g b, Rep g c) => Rep g (a, b, c) 
(Rep Read a, Rep Read b, Rep Read c) => Rep Read (a, b, c)

Ad-hoc instance for (a,b,c)

(Rep Show a, Rep Show b, Rep Show c) => Rep Show (a, b, c)

Ad-hoc instance for (a,b,c)

(Generic g, Rep g a, Rep g b, Rep g c, Rep g d) => Rep g (a, b, c, d) 
(Rep Read a, Rep Read b, Rep Read c, Rep Read d) => Rep Read (a, b, c, d)

Ad-hoc instance for (a,b,c,d)

(Rep Show a, Rep Show b, Rep Show c, Rep Show d) => Rep Show (a, b, c, d)

Ad-hoc instance for (a,b,c,d)

(Generic g, Rep g a, Rep g b, Rep g c, Rep g d, Rep g e) => Rep g (a, b, c, d, e) 
(Rep Read a, Rep Read b, Rep Read c, Rep Read d, Rep Read e) => Rep Read (a, b, c, d, e)

Ad-hoc instance for (a,b,c,d,e)

(Rep Show a, Rep Show b, Rep Show c, Rep Show d, Rep Show e) => Rep Show (a, b, c, d, e)

Ad-hoc instance for (a,b,c,d,e)

(Generic g, Rep g a, Rep g b, Rep g c, Rep g d, Rep g e, Rep g f) => Rep g (a, b, c, d, e, f) 
(Rep Read a, Rep Read b, Rep Read c, Rep Read d, Rep Read e, Rep Read f) => Rep Read (a, b, c, d, e, f)

Ad-hoc instance for (a,b,c,d,e,f)

(Rep Show a, Rep Show b, Rep Show c, Rep Show d, Rep Show e, Rep Show f) => Rep Show (a, b, c, d, e, f)

Ad-hoc instance for (a,b,c,d,e,f)

(Generic g, Rep g a, Rep g b, Rep g c, Rep g d, Rep g e, Rep g f, Rep g h) => Rep g (a, b, c, d, e, f, h) 
(Rep Read a, Rep Read b, Rep Read c, Rep Read d, Rep Read e, Rep Read f, Rep Read h) => Rep Read (a, b, c, d, e, f, h)

Ad-hoc instance for (a,b,c,d,e,f,h)

(Rep Show a, Rep Show b, Rep Show c, Rep Show d, Rep Show e, Rep Show f, Rep Show h) => Rep Show (a, b, c, d, e, f, h)

Ad-hoc instance for (a,b,c,d,e,f,h)

Rep (Everywhere' Bool) Bool 
Rep (Everywhere' Char) Char 
Rep (Everywhere' Double) Double 
Rep (Everywhere' Float) Float 
Rep (Everywhere' Int) Int 
Rep (Everywhere' Integer) Integer 
Rep (Everywhere' ()) () 
Rep (Everywhere Bool) Bool 
Rep (Everywhere Char) Char 
Rep (Everywhere Double) Double 
Rep (Everywhere Float) Float 
Rep (Everywhere Int) Int 
Rep (Everywhere Integer) Integer 
Rep (Everywhere ()) () 
Rep (Everywhere' [a]) [a] 
Rep (Everywhere' (Ratio a)) (Ratio a) 
Rep (Everywhere' (Maybe a)) (Maybe a) 
Rep (Everywhere [a]) a => Rep (Everywhere [a]) [a] 
(Integral a, Rep (Everywhere (Ratio a)) a) => Rep (Everywhere (Ratio a)) (Ratio a) 
Rep (Everywhere (Maybe a)) a => Rep (Everywhere (Maybe a)) (Maybe a) 
Rep (Everywhere' (Either a b)) (Either a b) 
Rep (Everywhere' (a, b)) (a, b) 
(Rep (Everywhere (Either a b)) a, Rep (Everywhere (Either a b)) b) => Rep (Everywhere (Either a b)) (Either a b) 
(Rep (Everywhere (a, b)) a, Rep (Everywhere (a, b)) b) => Rep (Everywhere (a, b)) (a, b) 
Rep (Everywhere' (a, b, c)) (a, b, c) 
(Rep (Everywhere (a, b, c)) a, Rep (Everywhere (a, b, c)) b, Rep (Everywhere (a, b, c)) c) => Rep (Everywhere (a, b, c)) (a, b, c) 
Rep (Everywhere' (a, b, c, d)) (a, b, c, d) 
(Rep (Everywhere (a, b, c, d)) a, Rep (Everywhere (a, b, c, d)) b, Rep (Everywhere (a, b, c, d)) c, Rep (Everywhere (a, b, c, d)) d) => Rep (Everywhere (a, b, c, d)) (a, b, c, d) 
Rep (Everywhere' (a, b, c, d, e)) (a, b, c, d, e) 
(Rep (Everywhere (a, b, c, d, e)) a, Rep (Everywhere (a, b, c, d, e)) b, Rep (Everywhere (a, b, c, d, e)) c, Rep (Everywhere (a, b, c, d, e)) d, Rep (Everywhere (a, b, c, d, e)) e) => Rep (Everywhere (a, b, c, d, e)) (a, b, c, d, e) 
Rep (Everywhere' (a, b, c, d, e, f)) (a, b, c, d, e, f) 
(Rep (Everywhere (a, b, c, d, e, f)) a, Rep (Everywhere (a, b, c, d, e, f)) b, Rep (Everywhere (a, b, c, d, e, f)) c, Rep (Everywhere (a, b, c, d, e, f)) d, Rep (Everywhere (a, b, c, d, e, f)) e, Rep (Everywhere (a, b, c, d, e, f)) f) => Rep (Everywhere (a, b, c, d, e, f)) (a, b, c, d, e, f) 
Rep (Everywhere' (a, b, c, d, e, f, h)) (a, b, c, d, e, f, h) 
(Rep (Everywhere (a, b, c, d, e, f, h)) a, Rep (Everywhere (a, b, c, d, e, f, h)) b, Rep (Everywhere (a, b, c, d, e, f, h)) c, Rep (Everywhere (a, b, c, d, e, f, h)) d, Rep (Everywhere (a, b, c, d, e, f, h)) e, Rep (Everywhere (a, b, c, d, e, f, h)) f, Rep (Everywhere (a, b, c, d, e, f, h)) h) => Rep (Everywhere (a, b, c, d, e, f, h)) (a, b, c, d, e, f, h) 
Alternative f => Rep (Collect f Char) Char 
Alternative f => Rep (Collect f Double) Double 
Alternative f => Rep (Collect f Float) Float 
Alternative f => Rep (Collect f Integer) Integer 
Alternative f => Rep (Collect f Int) Int 
Alternative f => Rep (Collect f Bool) Bool 
Alternative f => Rep (Collect f ()) () 
Alternative f => Rep (Collect f [a]) [a] 
Alternative f => Rep (Collect f (Maybe a)) (Maybe a) 
Alternative f => Rep (Collect f (Ratio a)) (Ratio a) 
Alternative f => Rep (Collect f (Either a b)) (Either a b) 
Alternative f => Rep (Collect f (a, b)) (a, b) 
Alternative f => Rep (Collect f (a, b, c)) (a, b, c) 
Alternative f => Rep (Collect f (a, b, c, d)) (a, b, c, d) 
Alternative f => Rep (Collect f (a, b, c, d, e)) (a, b, c, d, e) 
Alternative f => Rep (Collect f (a, b, c, d, e, h)) (a, b, c, d, e, h) 
Alternative f => Rep (Collect f (a, b, c, d, e, h, i)) (a, b, c, d, e, h, i) 

class FRep g f whereSource

Representation dispatcher for functor types (kind * -> *) used with Generic.

Methods

frep :: g a -> g (f a)Source

Instances

Generic g => FRep g [] 
Generic g => FRep g Maybe 

class FRep2 g f whereSource

Representation dispatcher for functor types (kind * -> *) used with Generic2.

Methods

frep2 :: g a b -> g (f a) (f b)Source

Instances

Generic2 g => FRep2 g [] 
Generic2 g => FRep2 g Maybe 

class BiFRep2 g f whereSource

Representation dispatcher for bifunctor types (kind * -> *) used with Generic2.

Methods

bifrep2 :: g a1 b1 -> g a2 b2 -> g (f a1 a2) (f b1 b2)Source

Instances

class FRep3 g f whereSource

Representation dispatcher for functor types (kind * -> *) used with Generic3.

Methods

frep3 :: g a b c -> g (f a) (f b) (f c)Source

Instances

Generic3 g => FRep3 g [] 
Generic3 g => FRep3 g Maybe