emgm-0.3.1: Extensible and Modular Generics for the MassesSource codeContentsIndex
Generics.EMGM
Portabilitynon-portable
Stabilityexperimental
Maintainergenerics@haskell.org
Contents
Common Infrastructure
Datatype Representation
Structure Representation Types
Embedding-Projection Pair
Constructor Description
Representation Dispatchers
Monomorphic
Functor
Bifunctor
Generic Function Definition
Deriving Representation
Generic Functions
Collect Function
Compare Functions
Crush Functions
Enum Functions
Everywhere Functions
Map Functions
Read Functions
Show Functions
UnzipWith Functions
ZipWith Functions
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.

For more in-depth documentation, refer to one of the modules in these hierarchies:

Synopsis
data Unit = Unit
data a :+: b
= L a
| R b
data a :*: b = a :*: b
data EP d r = EP {
from :: d -> r
to :: r -> d
}
data ConDescr = ConDescr {
conName :: String
conArity :: Int
conLabels :: [String]
conFixity :: Fixity
}
data ConType
= ConStd
| ConRec [String]
| ConIfx String
data Fixity
= Nonfix
| Infix Prec
| Infixl Prec
| Infixr Prec
prec :: Fixity -> Prec
minPrec
maxPrec :: Prec
appPrec :: Prec
recPrec :: Prec
class Rep g a where
rep :: g a
class FRep g f where
frep :: g a -> g (f a)
class FRep2 g f where
frep2 :: g a b -> g (f a) (f b)
class FRep3 g f where
frep3 :: g a b c -> g (f a) (f b) (f c)
class BiFRep2 g f where
bifrep2 :: g a1 b1 -> g a2 b2 -> g (f a1 a2) (f b1 b2)
class Generic g where
rconstant :: (Enum a, Eq a, Ord a, Read a, Show a) => g a
rint :: g Int
rinteger :: g Integer
rfloat :: g Float
rdouble :: g Double
rchar :: g Char
runit :: g Unit
rsum :: g a -> g b -> g (a :+: b)
rprod :: g a -> g b -> g (a :*: b)
rcon :: ConDescr -> g a -> g a
rtype :: EP b a -> g a -> g b
class Generic2 g where
rconstant2 :: (Enum a, Eq a, Ord a, Read a, Show a) => g a a
rint2 :: g Int Int
rinteger2 :: g Integer Integer
rfloat2 :: g Float Float
rdouble2 :: g Double Double
rchar2 :: g Char Char
runit2 :: g Unit Unit
rsum2 :: g a1 a2 -> g b1 b2 -> g (a1 :+: b1) (a2 :+: b2)
rprod2 :: g a1 a2 -> g b1 b2 -> g (a1 :*: b1) (a2 :*: b2)
rcon2 :: ConDescr -> g a1 a2 -> g a1 a2
rtype2 :: EP a2 a1 -> EP b2 b1 -> g a1 b1 -> g a2 b2
class Generic3 g where
rconstant3 :: (Enum a, Eq a, Ord a, Read a, Show a) => g a a a
rint3 :: g Int Int Int
rinteger3 :: g Integer Integer Integer
rfloat3 :: g Float Float Float
rdouble3 :: g Double Double Double
rchar3 :: g Char Char Char
runit3 :: g Unit Unit Unit
rsum3 :: g a1 a2 a3 -> g b1 b2 b3 -> g (a1 :+: b1) (a2 :+: b2) (a3 :+: b3)
rprod3 :: g a1 a2 a3 -> g b1 b2 b3 -> g (a1 :*: b1) (a2 :*: b2) (a3 :*: b3)
rcon3 :: ConDescr -> g a1 a2 a3 -> g a1 a2 a3
rtype3 :: EP a2 a1 -> EP b2 b1 -> EP c2 c1 -> g a1 b1 c1 -> g a2 b2 c2
newtype Collect b a = Collect {
selCollect :: a -> [b]
}
collect :: Rep (Collect b) a => a -> [b]
newtype Compare a = Compare {
selCompare :: a -> a -> Ordering
}
compare :: Rep Compare a => a -> a -> Ordering
eq :: Rep Compare a => a -> a -> Bool
neq :: Rep Compare a => a -> a -> Bool
lt :: Rep Compare a => a -> a -> Bool
lteq :: Rep Compare a => a -> a -> Bool
gt :: Rep Compare a => a -> a -> Bool
gteq :: Rep Compare a => a -> a -> Bool
min :: Rep Compare a => a -> a -> a
max :: Rep Compare a => a -> a -> a
newtype Crush b a = Crush {
selCrush :: Assoc -> a -> b -> b
}
data Assoc
= AssocLeft
| AssocRight
crush :: FRep (Crush b) f => Assoc -> (a -> b -> b) -> b -> f a -> b
crushl :: FRep (Crush b) f => (a -> b -> b) -> b -> f a -> b
crushr :: FRep (Crush b) f => (a -> b -> b) -> b -> f a -> b
flatten :: FRep (Crush [a]) f => Assoc -> f a -> [a]
flattenl :: FRep (Crush [a]) f => f a -> [a]
flattenr :: FRep (Crush [a]) f => f a -> [a]
first :: FRep (Crush [a]) f => Assoc -> f a -> Maybe a
firstl :: FRep (Crush [a]) f => f a -> Maybe a
firstr :: FRep (Crush [a]) f => f a -> Maybe a
and :: FRep (Crush Bool) f => f Bool -> Bool
or :: FRep (Crush Bool) f => f Bool -> Bool
any :: FRep (Crush Bool) f => (a -> Bool) -> f a -> Bool
all :: FRep (Crush Bool) f => (a -> Bool) -> f a -> Bool
sum :: (Num a, FRep (Crush a) f) => f a -> a
product :: (Num a, FRep (Crush a) f) => f a -> a
minimum :: (Rep Compare a, FRep (Crush (Maybe a)) f) => f a -> Maybe a
maximum :: (Rep Compare a, FRep (Crush (Maybe a)) f) => f a -> Maybe a
elem :: (Rep Compare a, FRep (Crush Bool) f) => a -> f a -> Bool
notElem :: (Rep Compare a, FRep (Crush Bool) f) => a -> f a -> Bool
newtype Enum a = Enum {
selEnum :: [a]
}
enum :: Rep Enum a => [a]
enumN :: (Integral n, Rep Enum a) => n -> [a]
empty :: Rep Enum a => a
newtype Everywhere a b = Everywhere {
selEverywhere :: (a -> a) -> b -> b
}
everywhere :: Rep (Everywhere a) b => (a -> a) -> b -> b
newtype Everywhere' a b = Everywhere' {
selEverywhere' :: (a -> a) -> b -> b
}
everywhere' :: Rep (Everywhere' a) b => (a -> a) -> b -> b
newtype Map a b = Map {
selMap :: a -> b
}
map :: FRep2 Map f => (a -> b) -> f a -> f b
replace :: FRep2 Map f => f a -> b -> f b
bimap :: BiFRep2 Map f => (a -> c) -> (b -> d) -> f a b -> f c d
cast :: Rep (Map a) b => a -> b
newtype Read a = Read {
selRead :: ConType -> ReadPrec a
}
readPrec :: Rep Read a => ReadPrec a
readP :: Rep Read a => Int -> ReadP a
readsPrec :: Rep Read a => Int -> ReadS a
reads :: Rep Read a => ReadS a
read :: Rep Read a => String -> Maybe a
newtype Show a = Show {
selShow :: ConType -> Int -> a -> ShowS
}
showsPrec :: Rep Show a => Int -> a -> ShowS
shows :: Rep Show a => a -> ShowS
show :: Rep Show a => a -> String
newtype UnzipWith a b c = UnzipWith {
selUnzipWith :: a -> (b, c)
}
unzip :: FRep3 UnzipWith f => f (a, b) -> (f a, f b)
unzipWith :: FRep3 UnzipWith f => (a -> (b, c)) -> f a -> (f b, f c)
newtype ZipWith a b c = ZipWith {
selZipWith :: a -> b -> Maybe c
}
zip :: FRep3 ZipWith f => f a -> f b -> Maybe (f (a, b))
zipWith :: FRep3 ZipWith f => (a -> b -> c) -> f a -> f b -> Maybe (f c)
Common Infrastructure
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
The "unit" encodes a constructor with no arguments. An analogous standard Haskell type is ().
Constructors
UnitThe only value of type Unit (ignoring _|_).
show/hide Instances
data a :+: b Source
The "sum" encodes 2 constructor alternatives. An analogous standard Haskell type is Either a b.
Constructors
L aLeft alternative
R bRight alternative
show/hide Instances
(Generic g, Rep g a, Rep g b) => Rep g (a :+: b)
(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)
data a :*: b Source
The "product" encodes 2 constructor arguments. An analogous standard Haskell type is (a, b).
Constructors
a :*: bA pair of arguments
show/hide Instances
(Generic g, Rep g a, Rep g b) => Rep g (a :*: b)
(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)
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
from :: d -> rEmbed a datatype into its representation.
to :: r -> dProject 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

A constructor description containing useful meta-information about the syntax used in the data declaration. This is particularly useful in Read and Show but may also be helpful in other generic functions.

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
conName :: StringName of the constructor. If it is infix, don't provide parentheses.
conArity :: IntArity or number of arguments.
conLabels :: [String]A list of labels used in record syntax. They must be declared in the same order as the data declaration. The list should be empty if the constructor is not a record.
conFixity :: FixityInfix or not, associativity, precedence.
show/hide Instances
data ConType Source
The constructor type used in Read and Show to determine how to parse or print the constructor.
Constructors
ConStdStandard (function-type, nonfix)
ConRec [String]Record-style (nonfix or infix)
ConIfx StringInfix (no record syntax)
show/hide Instances
data Fixity Source
An identifier's fixity, associativity, and precedence. If not infix (Nonfix), the associativity and precedence of the identifier is the same as function application. If infix, the associativity is indicated by the constructor and the precedence is an argument to it.
Constructors
NonfixNot infix. Associativity and precedence are the same as function application.
Infix PrecNon-associative infix with precedence.
Infixl PrecLeft-associative infix with precedence.
Infixr PrecRight-associative Infix with precedence.
show/hide Instances
prec :: Fixity -> PrecSource
Get the precedence of a fixity value.
minPrec
maxPrec :: PrecSource
Maximum precedence: 11
appPrec :: PrecSource
Precedence for function application: 10
recPrec :: PrecSource
Precedence for record construction: 11
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
The Generic representation dispatcher for monomorphic types (kind *). Every structure type and supported datatype should have an instance of Rep. (No default implementation.)
Methods
rep :: g aSource
show/hide 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
Rep Read String
Rep Read ()
Rep Read ()
Rep Show String
Rep Show String
Rep Show ()
Rep Show ()
(Generic g, Rep g a) => Rep g ([] a)
(Generic g, Rep g a) => Rep g (Maybe a)
Rep Read a => Rep Read ([] a)
Rep Read a => Rep Read ([] a)
Rep Show a => Rep Show ([] a)
Rep Show a => Rep Show ([] a)
(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)
(Rep Read a, Rep Read b) => Rep Read ((,) a b)
(Rep Show a, Rep Show b) => Rep Show ((,) a b)
(Rep Show a, Rep Show b) => Rep Show ((,) 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)
(Rep Read a, Rep Read b, Rep Read c) => Rep Read ((,,) a b c)
(Rep Show a, Rep Show b, Rep Show c) => Rep Show ((,,) a b c)
(Rep Show a, Rep Show b, Rep Show c) => Rep Show ((,,) 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)
(Rep Read a, Rep Read b, Rep Read c, Rep Read d) => Rep Read ((,,,) a b c d)
(Rep Show a, Rep Show b, Rep Show c, Rep Show d) => Rep Show ((,,,) a b c d)
(Rep Show a, Rep Show b, Rep Show c, Rep Show d) => Rep Show ((,,,) 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)
(Rep Read a, Rep Read b, Rep Read c, Rep Read d, Rep Read e) => Rep Read ((,,,,) 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)
(Rep Show a, Rep Show b, Rep Show c, Rep Show d, Rep Show e) => Rep Show ((,,,,) 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)
(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)
(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)
(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)
(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)
(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)
(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)
(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)
Rep (Collect Bool) Bool
Rep (Collect Bool) Bool
Rep (Collect Char) Char
Rep (Collect Char) Char
Rep (Collect Double) Double
Rep (Collect Double) Double
Rep (Collect Float) Float
Rep (Collect Float) Float
Rep (Collect Int) Int
Rep (Collect Int) Int
Rep (Collect Integer) Integer
Rep (Collect Integer) Integer
Rep (Collect ()) ()
Rep (Collect ()) ()
Rep (Everywhere' Bool) Bool
Rep (Everywhere' Bool) Bool
Rep (Everywhere' Char) Char
Rep (Everywhere' Char) Char
Rep (Everywhere' Double) Double
Rep (Everywhere' Double) Double
Rep (Everywhere' Float) Float
Rep (Everywhere' Float) Float
Rep (Everywhere' Int) Int
Rep (Everywhere' Int) Int
Rep (Everywhere' Integer) Integer
Rep (Everywhere' Integer) Integer
Rep (Everywhere' ()) ()
Rep (Everywhere' ()) ()
Rep (Everywhere Bool) Bool
Rep (Everywhere Bool) Bool
Rep (Everywhere Char) Char
Rep (Everywhere Char) Char
Rep (Everywhere Double) Double
Rep (Everywhere Double) Double
Rep (Everywhere Float) Float
Rep (Everywhere Float) Float
Rep (Everywhere Int) Int
Rep (Everywhere Int) Int
Rep (Everywhere Integer) Integer
Rep (Everywhere Integer) Integer
Rep (Everywhere ()) ()
Rep (Everywhere ()) ()
Rep (Collect ([] a)) ([] a)
Rep (Collect ([] a)) ([] a)
Rep (Collect (Maybe a)) (Maybe a)
Rep (Collect (Maybe a)) (Maybe a)
Rep (Everywhere' ([] a)) ([] a)
Rep (Everywhere' ([] a)) ([] a)
Rep (Everywhere' (Maybe a)) (Maybe a)
Rep (Everywhere' (Maybe a)) (Maybe a)
Rep (Everywhere ([] a)) a => Rep (Everywhere ([] a)) ([] a)
Rep (Everywhere ([] a)) a => Rep (Everywhere ([] a)) ([] a)
Rep (Everywhere (Maybe a)) a => Rep (Everywhere (Maybe a)) (Maybe a)
Rep (Everywhere (Maybe a)) a => Rep (Everywhere (Maybe a)) (Maybe a)
Rep (Collect (Either a b)) (Either a b)
Rep (Collect (Either a b)) (Either a b)
Rep (Collect ((,) a b)) ((,) a b)
Rep (Collect ((,) a b)) ((,) a b)
Rep (Everywhere' (Either a b)) (Either a b)
Rep (Everywhere' (Either a b)) (Either a b)
Rep (Everywhere' ((,) a b)) ((,) 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 (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)) a, Rep (Everywhere ((,) a b)) b) => Rep (Everywhere ((,) a b)) ((,) a b)
Rep (Collect ((,,) a b c)) ((,,) a b c)
Rep (Collect ((,,) a b c)) ((,,) a b c)
Rep (Everywhere' ((,,) a b c)) ((,,) a b c)
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)) a, Rep (Everywhere ((,,) a b c)) b, Rep (Everywhere ((,,) a b c)) c) => Rep (Everywhere ((,,) a b c)) ((,,) a b c)
Rep (Collect ((,,,) a b c d)) ((,,,) a b c d)
Rep (Collect ((,,,) a b c d)) ((,,,) a b c d)
Rep (Everywhere' ((,,,) a b c d)) ((,,,) a b c d)
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)) 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 (Collect ((,,,,) a b c d e)) ((,,,,) a b c d e)
Rep (Collect ((,,,,) a b c d e)) ((,,,,) a b c d e)
Rep (Everywhere' ((,,,,) a b c d e)) ((,,,,) a b c d e)
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)) 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 (Collect ((,,,,,) a b c d e f)) ((,,,,,) a b c d e f)
Rep (Collect ((,,,,,) a b c d e f)) ((,,,,,) a b c d e f)
Rep (Everywhere' ((,,,,,) a b c d e f)) ((,,,,,) a b c d e f)
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)) 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 (Collect ((,,,,,,) a b c d e f h)) ((,,,,,,) a b c d e f h)
Rep (Collect ((,,,,,,) a b c d e f h)) ((,,,,,,) a b c d e f h)
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 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)
(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)
Functor
Types of kind * -> * should have an instance here. This includes [], Maybe, etc.
class FRep g f whereSource
The Generic representation dispatcher for functor types (kind * -> *), sometimes called container types. (No default implementation.)
Methods
frep :: g a -> g (f a)Source
show/hide Instances
Generic g => FRep g []
Generic g => FRep g Maybe
class FRep2 g f whereSource
The Generic2 representation dispatcher for functor types (kind * -> *), sometimes called container types. (No default implementation.)
Methods
frep2 :: g a b -> g (f a) (f b)Source
show/hide Instances
class FRep3 g f whereSource
The Generic3 representation dispatcher for functor types (kind * -> *), sometimes called container types. (No default implementation.)
Methods
frep3 :: g a b c -> g (f a) (f b) (f c)Source
show/hide Instances
Bifunctor
Types of kind * -> * -> * should have an instance here. This includes (,), Either, etc.
class BiFRep2 g f whereSource
The Generic2 representation dispatcher for bifunctor types (kind * -> * -> *). (No default implementation.)
Methods
bifrep2 :: g a1 b1 -> g a2 b2 -> g (f a1 a2) (f b1 b2)Source
show/hide Instances
Generic Function Definition

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. The class includes cases for primitive types, cases for the structural representation, and the rtype case for adding support for new datatypes.
Methods
rconstant :: (Enum a, Eq a, Ord a, Read a, Show a) => g aSource

Many functions perform the same operation on the non-structural cases (as well as Unit). The cases for constant datatypes (Int, Integer, Float, Double, Char, and Unit) have a default implementation of rconstant, thus a generic function may only override rconstant if desired. Note that there is no default implementation for rconstant itself.

The class context represents the intersection set of supported type classes.

rint :: g IntSource
Case for the primitive type Int. (Default implementation: rconstant.)
rinteger :: g IntegerSource
Case for the primitive type Integer. (Default implementation: rconstant.)
rfloat :: g FloatSource
Case for the primitive type Float. (Default implementation: rconstant.)
rdouble :: g DoubleSource
Case for the primitive type Double. (Default implementation: rconstant.)
rchar :: g CharSource
Case for the primitive type Char. (Default implementation: rconstant.)
runit :: g UnitSource
Case for the structural representation type Unit. It is used to represent a constructor with no arguments. (Default implementation: rconstant.)
rsum :: g a -> g b -> g (a :+: b)Source
Case for the structural representation type :+: (sum). It is used to represent alternative choices between constructors. (No default implementation.)
rprod :: g a -> g b -> g (a :*: b)Source
Case for the structural representation type :*: (product). It is used to represent multiple arguments to a constructor. (No default implementation.)
rcon :: ConDescr -> g a -> g aSource
Case for constructors. While not necessary for every generic function, this method is required for Read and Show. It is used to hold the meta-information about a constructor (ConDescr), e.g. name, arity, fixity, etc. (Since most generic functions do not use rcon and simply pass the value through, the default implementation is 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. (No default implementation.)
show/hide Instances
class Generic2 g whereSource
This class forms the foundation for defining generic functions with two generic arguments. Each method represents a type case. The class includes cases for primitive types, cases for the structural representation, and the rtype case for adding support for new datatypes.
Methods
rconstant2 :: (Enum a, Eq a, Ord a, Read a, Show a) => g a aSource

Many functions perform the same operation on the non-structural cases (as well as Unit). The cases for constant datatypes (Int, Integer, Float, Double, Char, and Unit) have a default implementation of rconstant2, thus a generic function may only override rconstant2 if desired. Note that there is no default implementation for rconstant2 itself.

The class context represents the intersection set of supported type classes.

rint2 :: g Int IntSource
Case for the primitive type Int. (Default implementation: rconstant2.)
rinteger2 :: g Integer IntegerSource
Case for the primitive type Integer. (Default implementation: rconstant2.)
rfloat2 :: g Float FloatSource
Case for the primitive type Float. (Default implementation: rconstant2.)
rdouble2 :: g Double DoubleSource
Case for the primitive type Double. (Default implementation: rconstant2.)
rchar2 :: g Char CharSource
Case for the primitive type Char. (Default implementation: rconstant2.)
runit2 :: g Unit UnitSource
Case for the structural representation type Unit. It is used to represent a constructor with no arguments. (Default implementation: rconstant2.)
rsum2 :: g a1 a2 -> g b1 b2 -> g (a1 :+: b1) (a2 :+: b2)Source
Case for the structural representation type :+: (sum). It is used to represent alternative choices between constructors. (No default implementation.)
rprod2 :: g a1 a2 -> g b1 b2 -> g (a1 :*: b1) (a2 :*: b2)Source
Case for the structural representation type :*: (product). It is used to represent multiple arguments to a constructor. (No default implementation.)
rcon2 :: ConDescr -> g a1 a2 -> g a1 a2Source
Case for constructors. It is used to hold the meta-information about a constructor (ConDescr), e.g. name, arity, fixity, etc. (Since most generic functions do not use rcon and simply pass the value through, the default implementation is const id.)
rtype2 :: EP a2 a1 -> EP b2 b1 -> g a1 b1 -> g a2 b2Source
Case for datatypes. This method is used to define the structural representation of an arbitrary Haskell datatype. The first two arguments are the embedding-projection pairs, necessary for establishing the isomorphisms between datatype and representation of the two generic types. The third argument is the run-time representation using the methods of Generic2. (No default implementation.)
show/hide Instances
class Generic3 g whereSource
This class forms the foundation for defining generic functions with three generic arguments. Each method represents a type case. The class includes cases for primitive types, cases for the structural representation, and the rtype case for adding support for new datatypes.
Methods
rconstant3 :: (Enum a, Eq a, Ord a, Read a, Show a) => g a a aSource

Many functions perform the same operation on the non-structural cases (as well as Unit). The cases for constant datatypes (Int, Integer, Float, Double, Char, and Unit) have a default implementation of rconstant3, thus a generic function may only override rconstant3 if desired. Note that there is no default implementation for rconstant3 itself.

The class context represents the intersection set of supported type classes.

rint3 :: g Int Int IntSource
Case for the primitive type Int. (Default implementation: rconstant3.)
rinteger3 :: g Integer Integer IntegerSource
Case for the primitive type Integer. (Default implementation: rconstant3.)
rfloat3 :: g Float Float FloatSource
Case for the primitive type Float. (Default implementation: rconstant3.)
rdouble3 :: g Double Double DoubleSource
Case for the primitive type Double. (Default implementation: rconstant3.)
rchar3 :: g Char Char CharSource
Case for the primitive type Char. (Default implementation: rconstant3.)
runit3 :: g Unit Unit UnitSource
Case for the structural representation type Unit. It is used to represent a constructor with no arguments. (Default implementation: rconstant3.)
rsum3 :: g a1 a2 a3 -> g b1 b2 b3 -> g (a1 :+: b1) (a2 :+: b2) (a3 :+: b3)Source
Case for the structural representation type :+: (sum). It is used to represent alternative choices between constructors. (No default implementation.)
rprod3 :: g a1 a2 a3 -> g b1 b2 b3 -> g (a1 :*: b1) (a2 :*: b2) (a3 :*: b3)Source
Case for the structural representation type :*: (product). It is used to represent multiple arguments to a constructor. (No default implementation.)
rcon3 :: ConDescr -> g a1 a2 a3 -> g a1 a2 a3Source
Case for constructors. It is used to hold the meta-information about a constructor (ConDescr), e.g. name, arity, fixity, etc. (Since most generic functions do not use rcon and simply pass the value through, the default implementation is const id.)
rtype3 :: EP a2 a1 -> EP b2 b1 -> EP c2 c1 -> g a1 b1 c1 -> g a2 b2 c2Source
Case for datatypes. This method is used to define the structural representation of an arbitrary Haskell datatype. The first three arguments are the embedding-projection pairs, necessary for establishing the isomorphisms between datatype and representation of the four generic types. The fourth argument is the run-time representation using the methods of Generic3. (No default implementation.)
show/hide Instances
Deriving Representation
The necessary values and instances for using EMGM with a user-defined datatype can be generated automatically using Template Haskell. By necessity, there are a number of exported values for this process that are unrelated to other uses of the EMGM library. In order to not export these signatures more than necessary, you should import Generics.EMGM.Derive for deriving the representation. Note that Generics.EMGM does not export anything in Generics.EMGM.Derive.
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

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

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

newtype Collect b a Source

The type of a generic function that takes a value of one type and returns a list of values of another type.

For datatypes to work with Collect, a special instance must be given. This instance is trivial to write. Given a type T, the Rep instance looks like this:

  {-# LANGUAGE OverlappingInstances #-}

  data T = ...

  instance Rep (Collect T) T where
    rep = Collect (:[])

(Note the requirement of overlapping instances.) This instance triggers when the result type (the first T) matches some value type (the second T) contained within the argument to collect. See the source of this module for more examples.

Constructors
Collect
selCollect :: a -> [b]
show/hide Instances
Generic (Collect b)
Rep (Collect Bool) Bool
Rep (Collect Char) Char
Rep (Collect Double) Double
Rep (Collect Float) Float
Rep (Collect Int) Int
Rep (Collect Integer) Integer
Rep (Collect ()) ()
Rep (Collect ([] a)) ([] a)
Rep (Collect (Maybe a)) (Maybe a)
Rep (Collect (Either a b)) (Either a b)
Rep (Collect ((,) a b)) ((,) a b)
Rep (Collect ((,,) a b c)) ((,,) a b c)
Rep (Collect ((,,,) a b c d)) ((,,,) a b c d)
Rep (Collect ((,,,,) a b c d e)) ((,,,,) a b c d e)
Rep (Collect ((,,,,,) a b c d e f)) ((,,,,,) a b c d e f)
Rep (Collect ((,,,,,,) a b c d e f h)) ((,,,,,,) a b c d e f h)
collect :: Rep (Collect b) a => a -> [b]Source

Collect values of type b from some value of type a. An empty list 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

Functions that compare two values to determine an ordering.

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

newtype Compare a Source
The type of a generic function that takes two values of the same type and returns an Ordering.
Constructors
Compare
selCompare :: a -> a -> Ordering
show/hide Instances
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

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

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

newtype Crush b a Source
The type of a generic function that takes an associativity and two arguments of different types and returns a value of the type of the second.
Constructors
Crush
selCrush :: Assoc -> a -> b -> b
show/hide Instances
data Assoc Source
Associativity of the binary operator used for crush
Constructors
AssocLeftLeft-associative
AssocRightRight-associative
crushSource
:: FRep (Crush b) f
=> AssocAssociativity of the binary operator (left or right).
-> a -> b -> bBinary operator on a-elements with an accumulator.
-> bThe initial b-value for the binary operator.
-> f aContainer of a-values.
-> bThe 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 :: FRep (Crush [a]) f => Assoc -> f a -> Maybe aSource

Extract the first element of a container. If the container is empty, return Nothing.

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

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

A left-associative 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 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

Functions that enumerate the values of a datatype.

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

newtype Enum a Source
The type of a generic function that takes no arguments and returns a list of some type.
Constructors
Enum
selEnum :: [a]
show/hide Instances
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

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.

newtype Everywhere a b Source

The type of a generic function that takes a function of one type, a value of another type, and returns a value of the value type.

For datatypes to work with Everywhere, a special instance must be given. This instance is trivial to write. For a non-recursive type, the instance is the same as described for Everywhere'. For a recursive type T, the Rep instance looks like this:

   {-# LANGUAGE OverlappingInstances #-}
   data T a = Val a | Rec (T a)
   instance (Rep (Everywhere (T a)) (T a), Rep (Everywhere (T a)) a) => Rep (Everywhere (T a)) (T a) where
     rep = Everywhere app
       where
         app f x =
           case x of
             Val v1 -> f (Val (selEverywhere rep f v1))
             Rec v1 -> f (Rec (selEverywhere rep f v1))

Note the requirement of overlapping instances.

This instance is triggered when the function type (the first T a in Rep (Everywhere (T a)) (T a)) matches some value type (the second T a) contained within the argument to everywhere.

Constructors
Everywhere
selEverywhere :: (a -> a) -> b -> b
show/hide Instances
Generic (Everywhere a)
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 ([] a)) ([] a)
Rep (Everywhere (Maybe a)) a => Rep (Everywhere (Maybe a)) (Maybe a)
(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, 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, 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, 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, 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, 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)
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.

newtype Everywhere' a b Source

This type servers the same purpose as Everywhere, except that Rep instances are designed to be top-down instead of bottom-up. That means, given any type U (recursive or not), the Rep instance looks like this:

   {-# LANGUAGE OverlappingInstances #-}
   data U = ...
   instance Rep (Everywhere' U) U where
     rep = Everywhere' ($)

Note the requirement of overlapping instances.

This instance is triggered when the function type (the first U in Rep (Everywhere U) U) matches some value type (the second U) contained within the argument to everywhere'.

Constructors
Everywhere'
selEverywhere' :: (a -> a) -> b -> b
show/hide Instances
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

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.

newtype Map a b Source
The type of a generic function that takes a value of one type and returns a value of a different type.
Constructors
Map
selMap :: a -> b
show/hide Instances
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 as with b. This is a convenience function for the implementation 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 is found, so you must define instances in order to use cast.

Read Functions

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

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

newtype Read a Source
The type of a generic function that takes a constructor-type argument and returns a parser combinator for some type.
Constructors
Read
selRead :: ConType -> ReadPrec a
show/hide Instances
Generic Read
Rep Read String
Rep Read ()
Rep Read a => Rep Read ([] a)
(Rep Read a, Rep Read b) => Rep Read ((,) a b)
(Rep Read a, Rep Read b, Rep Read c) => Rep Read ((,,) a b c)
(Rep Read a, Rep Read b, Rep Read c, Rep Read d) => Rep Read ((,,,) a b c d)
(Rep Read a, Rep Read b, Rep Read c, Rep Read d, Rep Read e) => Rep Read ((,,,,) a b c d e)
(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)
(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)
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
:: Rep Read a
=> IntOperator 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
:: Rep Read a
=> IntOperator precedence of the enclosing context (a number from 0 to 11).
-> ReadS aEquivalent 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

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

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

newtype Show a Source
The type of a generic function that takes a constructor-type argument, a number (precedence), and a value and returns a ShowS function.
Constructors
Show
selShow :: ConType -> Int -> a -> ShowS
show/hide Instances
Generic Show
Rep Show String
Rep Show ()
Rep Show a => Rep Show ([] a)
(Rep Show a, Rep Show b) => Rep Show ((,) a b)
(Rep Show a, Rep Show b, Rep Show c) => Rep Show ((,,) a b c)
(Rep Show a, Rep Show b, Rep Show c, Rep Show d) => Rep Show ((,,,) a b c d)
(Rep Show a, Rep Show b, Rep Show c, Rep Show d, Rep Show e) => Rep Show ((,,,,) a b c d e)
(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)
(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)
showsPrecSource
:: Rep Show a
=> IntOperator precedence of the enclosing context (a number from 0 to 11).
-> aThe 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.
UnzipWith Functions

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

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

newtype UnzipWith a b c Source
The type of a generic function that takes an argument of one type and returns a pair of values with two different types.
Constructors
UnzipWith
selUnzipWith :: a -> (b, c)
show/hide Instances
unzip :: FRep3 UnzipWith f => f (a, b) -> (f a, f b)Source
Transforms a container of pairs into a container of first components and a container of second components. This is a generic version of the Prelude function of the same name.
unzipWithSource
:: FRep3 UnzipWith f
=> a -> (b, c)Splitting function.
-> f aContainer of a-values.
-> (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.
ZipWith Functions

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

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

newtype ZipWith a b c Source
The type of a generic function that takes two arguments of two different types and optionally returns a value of a third type.
Constructors
ZipWith
selZipWith :: a -> b -> Maybe c
show/hide Instances
zip :: FRep3 ZipWith f => f a -> f b -> Maybe (f (a, b))Source
Combine two containers into a single container with pairs of the original elements. See zipWith for restrictions. This is a generic version of the Prelude function of the same name.
zipWithSource
:: FRep3 ZipWith f
=> a -> b -> cBinary operator on elements of containers.
-> f aContainer of a-values.
-> f bContainer of b-values.
-> Maybe (f c)Container of c-values if successful or Nothing if failed.
Combine two structurally equivalent containers into one by applying a function to every corresponding pair of elements. Returns Nothing if f a and f b have different shapes.
Produced by Haddock version 2.4.2