emgm-0.4: Extensible and Modular Generics for the Masses

Portabilitynon-portable
Stabilityexperimental
Maintainergenerics@haskell.org

Generics.EMGM

Contents

Description

EMGM is "Extensible and Modular Generics for the Masses," a library for datatype-generic programming in Haskell.

This module exports the most commonly used types, classes, and functions. The documentation is organized by topic for convenient access.

Synopsis

Foundation

This is the collection of types, classes, and functions used to define generic functions and to build representations for datatypes.

Datatype Representation

These are the types and functions required to represent a datatype for use by generic functions.

Structure Representation Types

The unit, sum, and product types form the sum-of-products view for a Haskell datatype.

data Unit Source

Encodes a constructor with no arguments. An analogous standard Haskell type is ().

Constructors

Unit

The only value of type Unit (ignoring _|_).

Instances

data a :+: b Source

The "sum" encodes 2 constructor alternatives. An analogous standard Haskell type is Either a b.

Constructors

L a

Left alternative

R b

Right alternative

Instances

HasEP Bool BoolS 
(Generic g, Rep g a, Rep g b) => Rep g (:+: a b) 
HasEP [a] (ListS a) 
HasEP (Maybe a) (MaybeS a) 
(Eq a, Eq b) => Eq (:+: a b) 
(Ord a, Ord b) => Ord (:+: a b) 
(Read a, Read b) => Read (:+: a b) 
(Show a, Show b) => Show (:+: a b) 
HasEP (Either a b) (EitherS a b) 

data a :*: b Source

The "product" encodes 2 constructor arguments. An analogous standard Haskell type is (a, b).

Constructors

a :*: b

A pair of arguments

Instances

(Generic g, Rep g a, Rep g b) => Rep g (:*: a b) 
HasEP [a] (ListS a) 
Integral a => HasEP (Ratio a) (RatioS a) 
(Eq a, Eq b) => Eq (:*: a b) 
(Ord a, Ord b) => Ord (:*: a b) 
(Read a, Read b) => Read (:*: a b) 
(Show a, Show b) => Show (:*: a b) 
HasEP (a, b) (Tuple2S a b) 
HasEP (a, b, c) (Tuple3S a b c) 
HasEP (a, b, c, d) (Tuple4S a b c d) 
HasEP (a, b, c, d, e) (Tuple5S a b c d e) 
HasEP (a, b, c, d, e, f) (Tuple6S a b c d e f) 
HasEP (a, b, c, d, e, f, h) (Tuple7S a b c d e f h) 

Embedding-Projection Pair

A pair of a function and its inverse form the isomorphism between a datatype and its structure representation.

data EP d r Source

The embedding-projection pair contains two functions for converting between the datatype and its representation. An EP value preserves an isomorphism (ignoring _|_s) between a datatype and its structure representation.

Constructors

EP 

Fields

from :: d -> r

Embed a datatype into its representation.

to :: r -> d

Project datatype from its representation.

Constructor Description

A description of the syntax of each constructor provides useful auxiliary information for some generic functions.

data ConDescr Source

Contains useful meta-information about the syntax used in a constructor declaration.

NOTE: It is important that the ConDescr value accurately describe the syntax in a constructor declaration. An incorrect description may lead to faulty Read or Show operation.

Constructors

ConDescr 

Fields

conName :: String

Name of the constructor (without parenthesese if infix).

conArity :: Int

Number of fields.

conRecord :: Bool

Uses labeled fields (a.k.a. record syntax).

conFixity :: Fixity

Fixity, associativity, precedence.

Instances

newtype LblDescr Source

Encodes the string label for a field in a constructor defined with labeled fields (a.k.a. record syntax).

Constructors

LblDescr String 

data Fixity Source

A constructor's fixity, associativity, and precedence.

Constructors

Prefix

Associativity and precedence are the same as function application.

Infix Associativity Prec 

data Associativity Source

A constructor's associativity.

Constructors

LeftAssoc

Declared with infixl

RightAssoc

Declared with infixr

NonAssoc

Declared with infix

type Prec = Int

prec :: Fixity -> PrecSource

Get the precedence of a fixity value.

Generic Function Classes

Generic functions are instances of these classes. The value-level structure representation of datatypes is implemented using the members of these classes. Thus, a generic function is simply a case statement on the value-level structure.

Note that the numerical suffix represents the number of generic type variables used in the generic function. No suffix represents 1 generic type variable.

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

Representation Dispatchers

Type classes simplify the application of generic functions by providing (a.k.a. "dispatching") the appropriate structure representation. These classes are divided into the kinds they support (monomorphic, functor, and bifunctor).

Note that the numerical suffix represents the number of generic type variables used in the generic function. No suffix represents 1 generic type variable.

Monomorphic

All types of kind * should have an instance here. This includes types applied to type variables: [a], Maybe a, Either a b, etc.

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) 

Functor

Types of kind * -> * should have an instance here. This includes [], Maybe, etc.

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

Bifunctor

Types of kind * -> * -> * should have an instance here. This includes (,), Either, etc.

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

Generic Functions

The following collection of functions use the common EMGM infrastructure to work on all datatypes that have instances for a certain representation dispatcher. These functions are categorized by the core generic functionality. For example, flattenr is a type of "crush" function, because it is defined by the Generic instance of the newtype Crush.

More information for each of these is available in its respective module.

Collect

Function that collects values of one type from values of a possibly different type.

For more details, see Generics.EMGM.Functions.Collect.

collect :: (Alternative f, Rep (Collect f b) a) => a -> f bSource

Collect values of type b from some value of type a. An empty means no values were collected. If you expected otherwise, be sure that you have an instance such as Rep (Collect B) B for the type B that you are collecting.

collect works by searching a datatype for values that are the same type as the return type specified. Here are some examples using the same value with different return types:

   ghci> let x = [Left 1, Right 'a', Left 2] :: [Either Int Char]
   ghci> collect x :: [Int]
   [1,2]
   ghci> collect x :: [Char]
   "a"
   ghci> collect x == x
   True

Note that the numerical constants have been declared Int using the type annotation. Since these natively have the type Num a => a, you may need to give explicit types. By design, there is no connection that can be inferred between the return type and the argument type.

collect only works if there is an instance for the return type as described in the newtype Collect.

Compare

Functions that compare two values to determine an ordering.

For more details, see Generics.EMGM.Functions.Compare.

compare :: Rep Compare a => a -> a -> OrderingSource

Compare two values and return an Ordering (i.e. LT, GT, or EQ). This is implemented exactly as if the datatype was deriving Ord.

eq :: Rep Compare a => a -> a -> BoolSource

Equal to. Returns x == y.

neq :: Rep Compare a => a -> a -> BoolSource

Not equal to. Returns x /= y.

lt :: Rep Compare a => a -> a -> BoolSource

Less than. Returns x < y.

lteq :: Rep Compare a => a -> a -> BoolSource

Less than or equal to. Returns x <= y.

gt :: Rep Compare a => a -> a -> BoolSource

Greater than. Returns x > y.

gteq :: Rep Compare a => a -> a -> BoolSource

Greater than or equal to. Returns x >= y.

min :: Rep Compare a => a -> a -> aSource

The minimum of two values.

max :: Rep Compare a => a -> a -> aSource

The maximum of two values.

Crush

Functions that crush a polymorphic functor container into an iteration over its elements.

For more details, see Generics.EMGM.Functions.Crush.

data Assoc Source

Associativity of the binary operator used for crush

Constructors

AssocLeft

Left-associative

AssocRight

Right-associative

crushSource

Arguments

:: FRep (Crush b) f 
=> Assoc

Associativity of the binary operator (left or right).

-> (a -> b -> b)

Binary operator on a-elements with an accumulator.

-> b

The initial b-value for the binary operator.

-> f a

Container of a-values.

-> b

The result after applying the above operator on all a-values.

Apply a function (a -> b -> b) to each element (a) of a container (f a) and an accumulator value (b) to produce an accumulated result (b).

This is the most general form in which you must specify the associativity. You may prefer to use crushr or crushl.

crushl :: FRep (Crush b) f => (a -> b -> b) -> b -> f a -> bSource

A left-associative variant of crush.

crushr :: FRep (Crush b) f => (a -> b -> b) -> b -> f a -> bSource

A right-associative variant of crush.

flatten :: FRep (Crush [a]) f => Assoc -> f a -> [a]Source

Flatten the elements of a container into a list.

This is the most general form in which you must specify the associativity. You may prefer to use flattenr or flattenl.

flattenl :: FRep (Crush [a]) f => f a -> [a]Source

A left-associative variant of flatten.

Note that, for a list ls :: [a], flattenl ls == reverse ls.

flattenr :: FRep (Crush [a]) f => f a -> [a]Source

A right-associative variant of flatten.

Note that, for a list ls :: [a], flattenr ls == ls.

first :: (Monad m, FRep (Crush [a]) f) => Assoc -> f a -> m aSource

Extract the first element of a container. fail if the container is empty.

This is the most general form in which you must specify the associativity and the Monad instance. You may prefer to use the more convenient firstr or firstl.

firstl :: FRep (Crush [a]) f => f a -> Maybe aSource

A left-associative Maybe variant of first.

Note that, for a list ls :: [a], fromJust (firstl ls) == last ls.

firstr :: FRep (Crush [a]) f => f a -> Maybe aSource

A right-associative Maybe variant of first.

Note that, for a list ls :: [a], fromJust (firstr ls) == head ls.

and :: FRep (Crush Bool) f => f Bool -> BoolSource

Compute the conjunction of all elements in a container. This is a generalization of the Prelude function of the same name.

or :: FRep (Crush Bool) f => f Bool -> BoolSource

Compute the disjunction of all elements in a container. This is a generalization of the Prelude function of the same name.

any :: FRep (Crush Bool) f => (a -> Bool) -> f a -> BoolSource

Determine if any element in a container satisfies the predicate p. This is a generalization of the Prelude function of the same name.

all :: FRep (Crush Bool) f => (a -> Bool) -> f a -> BoolSource

Determine if all elements in a container satisfy the predicate p. This is a generalization the Prelude function of the same name.

sum :: (Num a, FRep (Crush a) f) => f a -> aSource

Compute the sum of all elements in a container. This is a generalization of the Prelude function of the same name.

product :: (Num a, FRep (Crush a) f) => f a -> aSource

Compute the product of all elements in a container. This is a generalization of the Prelude function of the same name.

minimum :: (Rep Compare a, FRep (Crush (Maybe a)) f) => f a -> Maybe aSource

Determine the minimum element of a container. If the container is empty, return Nothing. This is a generalization of the Prelude function of the same name.

maximum :: (Rep Compare a, FRep (Crush (Maybe a)) f) => f a -> Maybe aSource

Determine the maximum element of a container. If the container is empty, return Nothing. This is a generalization of the Prelude function of the same name.

elem :: (Rep Compare a, FRep (Crush Bool) f) => a -> f a -> BoolSource

Determine if an element is a member of a container. This is a generalization of the Prelude function of the same name.

notElem :: (Rep Compare a, FRep (Crush Bool) f) => a -> f a -> BoolSource

Determine if an element is not a member of a container. This is a generalization of the Prelude function of the same name.

Enum

Functions that enumerate the values of a datatype.

For more details, see Generics.EMGM.Functions.Enum.

enum :: Rep Enum a => [a]Source

Enumerate the values of a datatype. If the number of values is infinite, the result will be an infinite list. The remaining functions are derived from enum.

enumN :: (Integral n, Rep Enum a) => n -> [a]Source

Enumerate the first n values of a datatype. This is a shortcut for genericTake n (enum).

empty :: Rep Enum a => aSource

Returns the first element of the enumeration from enum. This is often called the neutral or empty value.

Everywhere

Functions that apply a transformation at every location of one type in a value of a possibly different type.

For more details, see Generics.EMGM.Functions.Everywhere.

everywhere :: Rep (Everywhere a) b => (a -> a) -> b -> bSource

Apply a transformation a -> a to values of type a within the argument of type b in a bottom-up manner. Values that do not have type a are passed through id.

everywhere works by searching the datatype b for values that are the same type as the function argument type a. Here are some examples using the datatype declared in the documentation for Everywhere.

   ghci> let f t = case t of { Val i -> Val (i+(1::Int)); other -> other }
   ghci> everywhere f (Val (1::Int))
   Val 2
   ghci> everywhere f (Rec (Rec (Val (1::Int))))
   Rec (Rec (Val 2))
   ghci> let x = [Left 1, Right 'a', Left 2] :: [Either Int Char]
   ghci> everywhere (*(3::Int)) x
   [Left 3,Right 'a',Left 6]
   ghci> everywhere (\x -> x :: Float) x == x
   True

Note the type annotations. Since numerical constants have the type Num a => a, you may need to give explicit types. Also, the function \x -> x has type a -> a, but we need to give it some non-polymorphic type here. By design, there is no connection that can be inferred between the value type and the function type.

everywhere only works if there is an instance for the return type as described in the newtype Everywhere.

everywhere' :: Rep (Everywhere' a) b => (a -> a) -> b -> bSource

Apply a transformation a -> a to values of type a within the argument of type b in a top-down manner. Values that do not have type a are passed through id.

everywhere' is the same as everywhere with the exception of recursive datatypes. For example, compare the example used in the documentation for everywhere with the following.

   ghci> let f t = case t of { Val i -> Val (i+(1::Int)); other -> other }
   ghci> everywhere' f (Val (1::Int))
   Val 2
   ghci> everywhere' f (Rec (Rec (Val (1::Int))))
   Rec (Rec (Val 1))

everywhere' only works if there is an instance for the return type as described in the newtype Everywhere'.

Map

Functions that translate values of one type to values of another. This includes map-like functions that apply non-generic functions to every element in a polymorphic (functor or bifunctor) container. It also includes cast, a configurable, type-safe casting function.

For more details, see Generics.EMGM.Functions.Map.

map :: FRep2 Map f => (a -> b) -> f a -> f bSource

Apply a function to all elements of a container datatype (kind * -> *).

replace :: FRep2 Map f => f a -> b -> f bSource

Replace all a-values in f a with b. Defined as: replace as b = map (const b) as

bimap :: BiFRep2 Map f => (a -> c) -> (b -> d) -> f a b -> f c dSource

Given a datatype F a b, bimap f g applies the function f :: a -> c to every a-element and the function g :: b -> d to every b-element. The result is a value with transformed elements: F c d.

cast :: Rep (Map a) b => a -> bSource

Cast a value of one type into a value of another. This is a configurable function that allows you to define your own type-safe conversions for a variety of types.

cast works with instances of Rep (Map i) o in which you choose the input type i and the output type o and implement the function of type i -> o.

Here are some examples of instances (and flags you will need or want):

   {-# LANGUAGE MultiParamTypeClasses  #-}
   {-# LANGUAGE FlexibleContexts       #-}
   {-# LANGUAGE FlexibleInstances      #-}
   {-# OPTIONS_GHC -fno-warn-orphans   #-}
   instance Rep (Map Int) Char where
     rep = Map chr
   instance Rep (Map Float) Double where
     rep = Map realToFrac
   instance Rep (Map Integer) Integer where
     rep = Map (+42)

There are no pre-defined instances, and a call to cast will not compile if no instances for the input and output type pair are found, so you must define instances in order to use cast.

Meta

Functions for extracting meta-information about the representation.

For more details, see Generics.EMGM.Functions.Meta.

class HasEP a b | a -> b whereSource

A class to reveal the embedding-projection pair for a given datatype and its isomorphic representation type.

Methods

epOf :: a -> EP a bSource

The parameter is never evaluated, so undefined is acceptable.

Instances

HasEP Bool BoolS 
HasEP () Tuple0S 
HasEP [a] (ListS a) 
Integral a => HasEP (Ratio a) (RatioS a) 
HasEP (Maybe a) (MaybeS a) 
HasEP (Either a b) (EitherS a b) 
HasEP (a, b) (Tuple2S a b) 
HasEP (a, b, c) (Tuple3S a b c) 
HasEP (a, b, c, d) (Tuple4S a b c d) 
HasEP (a, b, c, d, e) (Tuple5S a b c d e) 
HasEP (a, b, c, d, e, f) (Tuple6S a b c d e f) 
HasEP (a, b, c, d, e, f, h) (Tuple7S a b c d e f h) 

conDescr :: Rep Con a => a -> Maybe ConDescrSource

Returns a constructor description if the value is not a primitive. The argument is not evaluated and may be undefined.

lblDescrs :: Rep Lbls a => a -> [LblDescr]Source

Returns a list of descriptions for all labels in the head constructor. Does not recurse into the children. The argument is not evaluated and may be undefined.

Read

Functions similar to deriving Prelude.Read that parse a string and return a value of a datatype.

For more details, see Generics.EMGM.Functions.Read.

readPrec :: Rep Read a => ReadPrec aSource

Generate a ReadPrec parser combinator for the datatype a that handles operator precedence. This uses the library in Text.ParserCombinators.ReadPrec and should be similar to a derived implementation of Text.Read.readPrec.

readPSource

Arguments

:: Rep Read a 
=> Int

Operator precedence of the enclosing context (a number from 0 to 11).

-> ReadP a 

Generate a ReadP parser combinator for the datatype a. This can be used with Text.ParserCombinators.ReadP.

readsPrecSource

Arguments

:: Rep Read a 
=> Int

Operator precedence of the enclosing context (a number from 0 to 11).

-> ReadS a

Equivalent to String -> [(a,String)].

Attempt to parse a value from the front of the string using the given precedence. readsPrec returns a list of (parsed value, remaining string) pairs. If parsing fails, readsPrec returns an empty list.

reads :: Rep Read a => ReadS aSource

A variant of readsPrec with the minimum precedence (0).

read :: Rep Read a => String -> Maybe aSource

A variant of reads that returns Just value on a successful parse. Otherwise, read returns Nothing. Note that a successful parse requires the input to be completely consumed.

Show

Functions similar to deriving Prelude.Show that return a string representation of a value of a datatype.

For more details, see Generics.EMGM.Functions.Show.

showsPrecSource

Arguments

:: Rep Show a 
=> Int

Operator precedence of the enclosing context (a number from 0 to 11).

-> a

The value to be converted to a String.

-> ShowS 

Convert a value to a readable string starting with the operator precedence of the enclosing context.

shows :: Rep Show a => a -> ShowSSource

A variant of showsPrec with the minimum precedence (0).

show :: Rep Show a => a -> StringSource

A variant of shows that returns a String instead of ShowS.

Transpose

Functions that transpose polymorphic functor values.

For more details, see Generics.EMGM.Functions.Transpose.

transpose :: (Monad m, FRep (Crush [g a]) f, FRep2 (Transpose m g a) f) => f (g a) -> m (g (f a))Source

Transposes the structure of nested containers (types f and g). fail if the outermost container is empty, because there is no generic way to guarantee that both have unit constructors or, if they do, decide which one to choose. See transposeE for an alternative approach.

transposeE :: (Rep Enum (g (f a)), FRep (Crush [g a]) f, FRep2 (Transpose Maybe g a) f) => f (g a) -> g (f a)Source

A convenient version of transpose that returns the empty value on failure.

UnzipWith

Functions that split a polymorphic functor values into two structurally equilvalent values.

For more details, see Generics.EMGM.Functions.UnzipWith.

unzipWithMSource

Arguments

:: (Monad m, FRep3 (UnzipWith m) f) 
=> (a -> m (b, c))

Splitting function.

-> f a

Container of a-values.

-> m (f b, f c)

Pair of containers.

Splits a container into two structurally equivalent containers by applying a function to every element, which splits it into two corresponding elements. Fails if the spliting function fails

unzipWith :: FRep3 (UnzipWith Id) f => (a -> (b, c)) -> f a -> (f b, f c)Source

A specialized version of unzipWithM using the identity monad and a splitting function that does not fail.

unzip :: FRep3 (UnzipWith Id) f => f (b, c) -> (f b, f c)Source

A specialized version of unzipWith for pairs. Generic version of Prelude.unzip.

ZipWith

Functions that combine two structurally equilvalent, polymorphic functor values into one.

For more details, see Generics.EMGM.Functions.ZipWith.

zipWithMSource

Arguments

:: (Monad m, FRep3 (ZipWith m) f) 
=> (a -> b -> m c)

Binary operator on elements of containers.

-> f a

Container of a-values.

-> f b

Container of b-values.

-> m (f c)

Container of c-values within a Monad m.

Combine two structurally equivalent containers into one by applying a function to every corresponding pair of elements. Fails if (1) the binary operator fails or (2) f a and f b have different shapes.

zipWith :: FRep3 (ZipWith Maybe) f => (a -> b -> c) -> f a -> f b -> Maybe (f c)Source

A specialized version of zipWithM for the Maybe monad and a binary operator that does not fail. Generic version of Prelude.zipWith.

zip :: FRep3 (ZipWith Maybe) f => f a -> f b -> Maybe (f (a, b))Source

A specialized version of zipWith for pairs. Generic version of Prelude.zip.