emgm-0.3: Extensible and Modular Generics for the MassesSource codeContentsIndex
Generics.EMGM.Derive
Portabilitynon-portable
Stabilityexperimental
Maintainergenerics@haskell.org
Contents
Automatic Instance Deriving
Manual Instance Deriving
Constructor Description Declaration
Embedding-Project Pair Declaration
Representation Value Declaration
Rep Instance Deriving
FRep Instance Deriving
BiFRep Instance Deriving
Function-Specific Instance Deriving
Datatype Representations
Bool
Either
List
Maybe
Tuples
Unit: ()
Pair: (a,b)
Triple: (a,b,c)
Quadruple: (a,b,c,d)
Quintuple: (a,b,c,d,e)
Sextuple: (a,b,c,d,e,f)
Septuple: (a,b,c,d,e,f,h)
Template Haskell
Derived Generic Functions
Exported Modules
Description

Summary: Functions for generating the representation for using a datatype with EMGM.

The simplest way to get a representation for a datatype is using derive in a Template Haskell declaration, e.g. $(derive ''MyType). This generates all of the appropriate instances, e.g. Rep, FRep, etc., for the type MyType.

Generating datatype support can be done in a fully automatic way using derive or deriveWith, or it can be done piecemeal using a number of other functions. For most needs, the automatic approach is fine. But if you find you need more control, use the manual deriving approach.

Naming conventions:

  • derive - Template Haskell function that generates instance declarations (and possibly also value declarations).
  • declare - Template Haskell function that generates only value declarations.
  • ep - Embedding-project pair.
  • con - Constructor description.
  • rep - Value representation meant for rep.
  • frep - Value representation meant for frep.
  • frep2 - Value representation meant for frep2.
  • frep3 - Value representation meant for frep3.
  • bifrep2 - Value representation meant for bifrep2.
Synopsis
derive :: Name -> Q [Dec]
deriveWith :: Modifiers -> Name -> Q [Dec]
data Modifier
= ChangeTo String
| DefinedAs String
type Modifiers = [(String, Modifier)]
deriveMono :: Name -> Q [Dec]
deriveMonoWith :: Modifiers -> Name -> Q [Dec]
declareConDescrs :: Name -> Q [Dec]
declareConDescrsWith :: Modifiers -> Name -> Q [Dec]
declareEP :: Name -> Q [Dec]
declareEPWith :: Modifiers -> Name -> Q [Dec]
declareRepValues :: Name -> Q [Dec]
declareRepValuesWith :: Modifiers -> Name -> Q [Dec]
declareMonoRep :: Name -> Q [Dec]
declareMonoRepWith :: Modifiers -> Name -> Q [Dec]
deriveRep :: Name -> Q [Dec]
deriveRepWith :: Modifiers -> Name -> Q [Dec]
deriveFRep :: Name -> Q [Dec]
deriveFRepWith :: Modifiers -> Name -> Q [Dec]
deriveBiFRep :: Name -> Q [Dec]
deriveBiFRepWith :: Modifiers -> Name -> Q [Dec]
deriveCollect :: Name -> Q [Dec]
deriveEverywhere :: Name -> Q [Dec]
deriveEverywhere' :: Name -> Q [Dec]
epBool :: EP Bool (Unit :+: Unit)
conFalse :: ConDescr
conTrue :: ConDescr
repBool :: Generic g => g Bool
frepBool :: Generic g => g Bool
frep2Bool :: Generic2 g => g Bool Bool
frep3Bool :: Generic3 g => g Bool Bool Bool
bifrep2Bool :: Generic2 g => g Bool Bool
epEither :: EP (Either a b) (a :+: b)
conLeft :: ConDescr
conRight :: ConDescr
repEither :: (Generic g, Rep g a, Rep g b) => g (Either a b)
frepEither :: Generic g => g a -> g b -> g (Either a b)
frep2Either :: Generic2 g => g a1 a2 -> g b1 b2 -> g (Either a1 b1) (Either a2 b2)
frep3Either :: Generic3 g => g a1 a2 a3 -> g b1 b2 b3 -> g (Either a1 b1) (Either a2 b2) (Either a3 b3)
bifrep2Either :: Generic2 g => g a1 a2 -> g b1 b2 -> g (Either a1 b1) (Either a2 b2)
epList :: EP [a] (Unit :+: (a :*: [a]))
conNil :: ConDescr
conCons :: ConDescr
repList :: (Generic g, Rep g a) => g [a]
frepList :: Generic g => g a -> g [a]
frep2List :: Generic2 g => g a b -> g [a] [b]
frep3List :: Generic3 g => g a b c -> g [a] [b] [c]
bifrep2List :: Generic2 g => g a b -> g [a] [b]
epMaybe :: EP (Maybe a) (Unit :+: a)
conNothing :: ConDescr
conJust :: ConDescr
repMaybe :: (Generic g, Rep g a) => g (Maybe a)
frepMaybe :: Generic g => g a -> g (Maybe a)
frep2Maybe :: Generic2 g => g a b -> g (Maybe a) (Maybe b)
frep3Maybe :: Generic3 g => g a b c -> g (Maybe a) (Maybe b) (Maybe c)
bifrep2Maybe :: Generic2 g => g a b -> g (Maybe a) (Maybe b)
epTuple0 :: EP () Unit
conTuple0 :: ConDescr
repTuple0 :: Generic g => g ()
frepTuple0 :: Generic g => g ()
frep2Tuple0 :: Generic2 g => g () ()
frep3Tuple0 :: Generic3 g => g () () ()
bifrep2Tuple0 :: Generic2 g => g () ()
epTuple2 :: EP (a, b) (a :*: b)
conTuple2 :: ConDescr
repTuple2 :: (Generic g, Rep g a, Rep g b) => g (a, b)
frepTuple2 :: Generic g => g a -> g b -> g (a, b)
frep2Tuple2 :: Generic2 g => g a1 a2 -> g b1 b2 -> g (a1, b1) (a2, b2)
frep3Tuple2 :: Generic3 g => g a1 a2 a3 -> g b1 b2 b3 -> g (a1, b1) (a2, b2) (a3, b3)
bifrep2Tuple2 :: Generic2 g => g a1 a2 -> g b1 b2 -> g (a1, b1) (a2, b2)
epTuple3 :: EP (a, b, c) (a :*: (b :*: c))
conTuple3 :: ConDescr
repTuple3 :: (Generic g, Rep g a, Rep g b, Rep g c) => g (a, b, c)
frepTuple3 :: Generic g => g a -> g b -> g c -> g (a, b, c)
frep2Tuple3 :: Generic2 g => g a1 a2 -> g b1 b2 -> g c1 c2 -> g (a1, b1, c1) (a2, b2, c2)
frep3Tuple3 :: Generic3 g => g a1 a2 a3 -> g b1 b2 b3 -> g c1 c2 c3 -> g (a1, b1, c1) (a2, b2, c2) (a3, b3, c3)
bifrep2Tuple3 :: Generic2 g => g a1 a2 -> g b1 b2 -> g c1 c2 -> g (a1, b1, c1) (a2, b2, c2)
epTuple4 :: EP (a, b, c, d) (a :*: (b :*: (c :*: d)))
conTuple4 :: ConDescr
repTuple4 :: (Generic g, Rep g a, Rep g b, Rep g c, Rep g d) => g (a, b, c, d)
frepTuple4 :: Generic g => g a -> g b -> g c -> g d -> g (a, b, c, d)
frep2Tuple4 :: Generic2 g => g a1 a2 -> g b1 b2 -> g c1 c2 -> g d1 d2 -> g (a1, b1, c1, d1) (a2, b2, c2, d2)
frep3Tuple4 :: Generic3 g => g a1 a2 a3 -> g b1 b2 b3 -> g c1 c2 c3 -> g d1 d2 d3 -> g (a1, b1, c1, d1) (a2, b2, c2, d2) (a3, b3, c3, d3)
bifrep2Tuple4 :: Generic2 g => g a1 a2 -> g b1 b2 -> g c1 c2 -> g d1 d2 -> g (a1, b1, c1, d1) (a2, b2, c2, d2)
epTuple5 :: EP (a, b, c, d, e) (a :*: (b :*: (c :*: (d :*: e))))
conTuple5 :: ConDescr
repTuple5 :: (Generic g, Rep g a, Rep g b, Rep g c, Rep g d, Rep g e) => g (a, b, c, d, e)
frepTuple5 :: Generic g => g a -> g b -> g c -> g d -> g e -> g (a, b, c, d, e)
frep2Tuple5 :: Generic2 g => g a1 a2 -> g b1 b2 -> g c1 c2 -> g d1 d2 -> g e1 e2 -> g (a1, b1, c1, d1, e1) (a2, b2, c2, d2, e2)
frep3Tuple5 :: Generic3 g => g a1 a2 a3 -> g b1 b2 b3 -> g c1 c2 c3 -> g d1 d2 d3 -> g e1 e2 e3 -> g (a1, b1, c1, d1, e1) (a2, b2, c2, d2, e2) (a3, b3, c3, d3, e3)
bifrep2Tuple5 :: Generic2 g => g a1 a2 -> g b1 b2 -> g c1 c2 -> g d1 d2 -> g e1 e2 -> g (a1, b1, c1, d1, e1) (a2, b2, c2, d2, e2)
epTuple6 :: EP (a, b, c, d, e, f) (a :*: (b :*: (c :*: (d :*: (e :*: f)))))
conTuple6 :: ConDescr
repTuple6 :: (Generic g, Rep g a, Rep g b, Rep g c, Rep g d, Rep g e, Rep g f) => g (a, b, c, d, e, f)
frepTuple6 :: Generic g => g a -> g b -> g c -> g d -> g e -> g f -> g (a, b, c, d, e, f)
frep2Tuple6 :: Generic2 g => g a1 a2 -> g b1 b2 -> g c1 c2 -> g d1 d2 -> g e1 e2 -> g f1 f2 -> g (a1, b1, c1, d1, e1, f1) (a2, b2, c2, d2, e2, f2)
frep3Tuple6 :: Generic3 g => g a1 a2 a3 -> g b1 b2 b3 -> g c1 c2 c3 -> g d1 d2 d3 -> g e1 e2 e3 -> g f1 f2 f3 -> g (a1, b1, c1, d1, e1, f1) (a2, b2, c2, d2, e2, f2) (a3, b3, c3, d3, e3, f3)
bifrep2Tuple6 :: Generic2 g => g a1 a2 -> g b1 b2 -> g c1 c2 -> g d1 d2 -> g e1 e2 -> g f1 f2 -> g (a1, b1, c1, d1, e1, f1) (a2, b2, c2, d2, e2, f2)
epTuple7 :: EP (a, b, c, d, e, f, h) (a :*: (b :*: (c :*: (d :*: (e :*: (f :*: h))))))
conTuple7 :: ConDescr
repTuple7 :: (Generic g, Rep g a, Rep g b, Rep g c, Rep g d, Rep g e, Rep g f, Rep g h) => g (a, b, c, d, e, f, h)
frepTuple7 :: Generic g => g a -> g b -> g c -> g d -> g e -> g f -> g h -> g (a, b, c, d, e, f, h)
frep2Tuple7 :: Generic2 g => g a1 a2 -> g b1 b2 -> g c1 c2 -> g d1 d2 -> g e1 e2 -> g f1 f2 -> g h1 h2 -> g (a1, b1, c1, d1, e1, f1, h1) (a2, b2, c2, d2, e2, f2, h2)
frep3Tuple7 :: Generic3 g => g a1 a2 a3 -> g b1 b2 b3 -> g c1 c2 c3 -> g d1 d2 d3 -> g e1 e2 e3 -> g f1 f2 f3 -> g h1 h2 h3 -> g (a1, b1, c1, d1, e1, f1, h1) (a2, b2, c2, d2, e2, f2, h2) (a3, b3, c3, d3, e3, f3, h3)
bifrep2Tuple7 :: Generic2 g => g a1 a2 -> g b1 b2 -> g c1 c2 -> g d1 d2 -> g e1 e2 -> g f1 f2 -> g h1 h2 -> g (a1, b1, c1, d1, e1, f1, h1) (a2, b2, c2, d2, e2, f2, h2)
newtype Collect b a = Collect {
selCollect :: a -> [b]
}
newtype Everywhere a b = Everywhere {
selEverywhere :: (a -> a) -> b -> b
}
newtype Everywhere' a b = Everywhere' {
selEverywhere' :: (a -> a) -> b -> b
}
module Generics.EMGM.Common
Automatic Instance Deriving

The functions derive and deriveWith determine which representations can be supported by your datatype. The indications are as follows for each class:

Rep
This instance will be generated for every type.
FRep, FRep2, FRep3
These instances will only be generated for functor types (kind * -> *).
BiFRep2
This instance will only be generated for bifunctor types (kind * -> * -> *).
derive :: Name -> Q [Dec]Source

Derive all appropriate instances for using EMGM with a datatype.

Here is an example module that shows how to use derive:

   {-# LANGUAGE TemplateHaskell       #-}
   {-# LANGUAGE MultiParamTypeClasses #-}
   {-# LANGUAGE FlexibleContexts      #-}
   {-# LANGUAGE FlexibleInstances     #-}
   {-# LANGUAGE OverlappingInstances  #-}
   {-# LANGUAGE UndecidableInstances  #-}
   module Example where
   import Generics.EMGM.Derive
   data T a = C a Int
   $(derive ''T)

The Template Haskell derive declaration in the above example generates the following (annotated) code:

   -- (1) Constructor description declarations
   conC :: ConDescr
   conC = ConDescr "C" 2 [] Nonfix
   -- (2) Embedding-projection pair declaration
   epT :: EP (T a) (a :*: Int)
   epT = EP fromT toT
     where fromT (C v1 v2) = v1 :*: v2
           toT (v1 :*: v2) = C v1 v2
   -- (3) Representation values
   repT :: (Generic g, Rep g a, Rep g Int) => g (T a)
   repT = rtype epT (rcon conC (rprod rep rep))
   frepT :: (Generic g) => g a1 -> g (T a1)
   frepT a = rtype epT (rcon conC (rprod a rint))
   frep2T :: (Generic2 g) => g a1 a2 -> g (T a1) (T a2)
   frep2T a = rtype2 epT epT (rcon2 conC (rprod2 a rint2))
   frep3T :: (Generic3 g) => g a1 a2 a3 -> g (T a1) (T a2) (T a3)
   frep3T a = rtype3 epT epT epT (rcon3 conC (rprod3 a rint3))
   bifrep2T :: (Generic2 g) => g a1 a2 -> g (T a1) (T a2)
   bifrep2T a = rtype2 epT epT (rcon2 conC (rprod2 a rint2))
   -- (4) Representation instances
   instance (Generic g, Rep g a, Rep g Int) => Rep g (T a) where
     rep = repT
   instance (Generic g) => FRep g T where
     frep = frepT
   instance (Generic2 g) => FRep2 g T where
     frep2 = frep2T
   instance (Generic3 g) => FRep3 g T where
     frep3 = frep3T
   -- In this case, no instances for BiFRep2 is generated, because T is not
   -- a bifunctor type; however, the bifrep2T value is always generated in
   -- case T is used in a bifunctor type.
   -- (5) Generic function-specific instances
   instance Rep (Collect (T a)) (T a) where
     rep = Collect (\x -> [x])
   instance (Rep (Everywhere (T a)) a, Rep (Everywhere (T a)) Int)
            => Rep (Everywhere (T a)) (T a) where
     rep = Everywhere (\f x ->
       case x of
         C v1 v2 -> f (C (selEverywhere rep f v1) (selEverywhere rep f v2))
   instance Rep (Everywhere' (T a)) (T a) where
     rep = Everywhere' (\f x -> f x)

Note that all the values are top-level. This allows them to be shared between multiple instances. For example, if you have two mutually recursive functor datatypes, you may need to have each other's derived code in scope.

deriveWith :: Modifiers -> Name -> Q [Dec]Source

Same as derive except that you can pass a list of name modifications to the deriving mechanism.

Use deriveWith if:

  1. You want to use the generated constructor descriptions or embedding-projection pairs and one of your constructors or types is an infix symbol. In other words, if you have a constructor :*, you cannot refer to the (invalid) generated name for its description, con:*. It appears that GHC has no problem with that name internally, so this is only if you want access to it.
  2. You want to define your own constructor description. This allows you to give a precise implementation different from the one generated for you.

For option 1, use ChangeTo as in this example:

   data U = Int :* Char
   $(deriveWith [(":*", ChangeTo "Star")] ''U)
   x = ... conStar ...

For option 2, use DefinedAs as in this example:

   data V = (:=) { i :: Int, j :: Char }
   $(deriveWith [(":=", DefinedAs "Equals")] ''V)
   conEquals = ConDescr ":=" 2 [] (Infix 4)

Using the example for option 2 with Generics.EMGM.Functions.Show will print values of V as infix instead of the default record syntax.

Note that only the first pair with its first field matching the type or constructor name in the Modifiers list will be used. Any other matches will be ignored.

data Modifier Source
Modify the action taken for a given name.
Constructors
ChangeTo StringChange the syntactic name (of a type or constructor) to the argument in the generated EP or ConDescr value. This results in a value named epX or conX if the argument is "X".
DefinedAs StringUse this for the name of a user-defined constructor description instead of a generated one. The generated code assumes the existance of conX :: ConDescr (in scope) if the argument is "X".
show/hide Instances
type Modifiers = [(String, Modifier)]Source
List of pairs mapping a (type or constructor) name to a modifier action.
deriveMono :: Name -> Q [Dec]Source

Same as derive except that only the monomorphic Rep representation value and instance are generated. This is a convenience function that can be used instead of the following declarations:

   $(declareConDescrs ''T)
   $(declareEP ''T)
   $(declareMonoRep ''T)
   $(deriveRep ''T)
   $(deriveFRep ''T)
   $(deriveCollect ''T)
deriveMonoWith :: Modifiers -> Name -> Q [Dec]Source
Same as deriveMono except that you can pass a list of name modifications to the deriving mechanism. See deriveWith for an example.
Manual Instance Deriving

Use the functions in this section for more control over the declarations and instances that are generated.

Since each function here generates one component needed for the entire datatype representation, you will most likely need to use multiple TH declarations. To get the equivalent of the resulting code described in derive, you will need the following:

   {-# LANGUAGE TemplateHaskell        #-}
   {-# LANGUAGE MultiParamTypeClasses  #-}
   {-# LANGUAGE FlexibleContexts       #-}
   {-# LANGUAGE FlexibleInstances      #-}
   {-# LANGUAGE OverlappingInstances   #-}
   {-# LANGUAGE UndecidableInstances   #-}
   module Example where
   import Generics.EMGM.Derive
   data T a = C a Int
   $(declareConDescrs ''T)
   $(declareEP ''T)
   $(declareRepValues ''T)
   $(deriveRep ''T)
   $(deriveFRep ''T)
   $(deriveCollect ''T)
   $(deriveEverywhere ''T)
   $(deriveEverywhere' ''T)
Constructor Description Declaration
Use the following to generate only the ConDescr declarations.
declareConDescrs :: Name -> Q [Dec]Source
Generate declarations of ConDescr values for all constructors in a type. See derive for an example.
declareConDescrsWith :: Modifiers -> Name -> Q [Dec]Source
Same as declareConDescrs except that you can pass a list of name modifications to the deriving mechanism. See deriveWith for an example.
Embedding-Project Pair Declaration
Use the following to generate only the EP declarations.
declareEP :: Name -> Q [Dec]Source
Generate declarations of EP values for a type. See derive for an example.
declareEPWith :: Modifiers -> Name -> Q [Dec]Source
Same as declareEP except that you can pass a list of name modifications to the deriving mechanism. See deriveWith for an example.
Representation Value Declaration
Use the following to generate only the representation values that are used in the instances for rep, frep, etc.
declareRepValues :: Name -> Q [Dec]Source
Generate declarations of all representation values for a type. These functions are used in rep, frep, ..., bifrep2.
declareRepValuesWith :: Modifiers -> Name -> Q [Dec]Source
Same as declareRepValues except that you can pass a list of name modifications to the deriving mechanism. See deriveWith for an example.
declareMonoRep :: Name -> Q [Dec]Source
Generate the declaration of a monomorphic representation value for a type. This is the value used for rep in an instance of Rep. The difference with declareRepValues is that declareRepValues generates generates all representation values (including frep, frep2, etc.). See derive for an example.
declareMonoRepWith :: Modifiers -> Name -> Q [Dec]Source
Same as declareMonoRep except that you can pass a list of name modifications to the deriving mechanism. See deriveWith for an example.
Rep Instance Deriving
Use the following to generate only the Rep instances.
deriveRep :: Name -> Q [Dec]Source
Generate Rep instance declarations for a type. See derive for an example.
deriveRepWith :: Modifiers -> Name -> Q [Dec]Source
Same as deriveRep except that you can pass a list of name modifications to the deriving mechanism. See deriveWith for an example.
FRep Instance Deriving
Use the following to generate only the FRep, FRep2, and FRep3 instances.
deriveFRep :: Name -> Q [Dec]Source
Generate FRep, FRep2, and FRep3 instance declarations for a type. See derive for an example.
deriveFRepWith :: Modifiers -> Name -> Q [Dec]Source
Same as deriveFRep except that you can pass a list of name modifications to the deriving mechanism. See deriveWith for an example.
BiFRep Instance Deriving
Use the following to generate only the BiFRep2 instances.
deriveBiFRep :: Name -> Q [Dec]Source
Generate BiFRep2 instance declarations for a type. See derive for an example.
deriveBiFRepWith :: Modifiers -> Name -> Q [Dec]Source
Same as deriveBiFRep except that you can pass a list of name modifications to the deriving mechanism. See deriveWith for an example.
Function-Specific Instance Deriving
Use the following to generate instances specific to certain functions.
deriveCollect :: Name -> Q [Dec]Source
Generate a Rep Collect T instance declaration for a type T. See derive for an example.
deriveEverywhere :: Name -> Q [Dec]Source
Generate a Rep Everywhere T instance declaration for a type T. See derive for an example.
deriveEverywhere' :: Name -> Q [Dec]Source
Generate a Rep Everywhere' T instance declaration for a type T. See derive for an example.
Datatype Representations
This is the collection of representation values for datatypes included with EMGM.
Bool
epBool :: EP Bool (Unit :+: Unit)Source
Embedding-projection pair for Bool.
conFalse :: ConDescrSource
Constructor description for False.
conTrue :: ConDescrSource
Constructor description for True.
repBool :: Generic g => g BoolSource
Representation of Bool for rep.
frepBool :: Generic g => g BoolSource
Representation of Bool for frep.
frep2Bool :: Generic2 g => g Bool BoolSource
Representation of Bool for frep2.
frep3Bool :: Generic3 g => g Bool Bool BoolSource
Representation of Bool for frep3.
bifrep2Bool :: Generic2 g => g Bool BoolSource
Representation of Bool for bifrep2.
Either
epEither :: EP (Either a b) (a :+: b)Source
Embedding-projection pair for Either.
conLeft :: ConDescrSource
Constructor description for Left.
conRight :: ConDescrSource
Constructor description for Right.
repEither :: (Generic g, Rep g a, Rep g b) => g (Either a b)Source
Representation of Either for rep.
frepEither :: Generic g => g a -> g b -> g (Either a b)Source
Representation of Either for frep.
frep2Either :: Generic2 g => g a1 a2 -> g b1 b2 -> g (Either a1 b1) (Either a2 b2)Source
Representation of Either for frep2.
frep3Either :: Generic3 g => g a1 a2 a3 -> g b1 b2 b3 -> g (Either a1 b1) (Either a2 b2) (Either a3 b3)Source
Representation of Either for frep3.
bifrep2Either :: Generic2 g => g a1 a2 -> g b1 b2 -> g (Either a1 b1) (Either a2 b2)Source
Representation of Either for bifrep2.
List
epList :: EP [a] (Unit :+: (a :*: [a]))Source
Embedding-projection pair for lists.
conNil :: ConDescrSource
Constructor description for ''nil'': [].
conCons :: ConDescrSource
Constructor description for ''cons'': (:).
repList :: (Generic g, Rep g a) => g [a]Source
Representation of lists for rep.
frepList :: Generic g => g a -> g [a]Source
Representation of lists for frep.
frep2List :: Generic2 g => g a b -> g [a] [b]Source
Representation of lists for frep2.
frep3List :: Generic3 g => g a b c -> g [a] [b] [c]Source
Representation of lists for frep3.
bifrep2List :: Generic2 g => g a b -> g [a] [b]Source
Representation of lists for bifrep2.
Maybe
epMaybe :: EP (Maybe a) (Unit :+: a)Source
Embedding-projection pair for Maybe.
conNothing :: ConDescrSource
Constructor description for Nothing.
conJust :: ConDescrSource
Constructor description for Just.
repMaybe :: (Generic g, Rep g a) => g (Maybe a)Source
Representation of Maybe for rep.
frepMaybe :: Generic g => g a -> g (Maybe a)Source
Representation of Maybe for frep.
frep2Maybe :: Generic2 g => g a b -> g (Maybe a) (Maybe b)Source
Representation of Maybe for frep2.
frep3Maybe :: Generic3 g => g a b c -> g (Maybe a) (Maybe b) (Maybe c)Source
Representation of Maybe for frep3.
bifrep2Maybe :: Generic2 g => g a b -> g (Maybe a) (Maybe b)Source
Representation of Maybe for bifrep2.
Tuples
Unit: ()
epTuple0 :: EP () UnitSource
Embedding-projection pair for ().
conTuple0 :: ConDescrSource
Constructor description for ().
repTuple0 :: Generic g => g ()Source
Representation of () for rep.
frepTuple0 :: Generic g => g ()Source
Representation of () for frep.
frep2Tuple0 :: Generic2 g => g () ()Source
Representation of () for frep2.
frep3Tuple0 :: Generic3 g => g () () ()Source
Representation of () for frep3.
bifrep2Tuple0 :: Generic2 g => g () ()Source
Representation of () for bifrep2.
Pair: (a,b)
epTuple2 :: EP (a, b) (a :*: b)Source
Embedding-projection pair for (,).
conTuple2 :: ConDescrSource
Constructor description for (,).
repTuple2 :: (Generic g, Rep g a, Rep g b) => g (a, b)Source
Representation of (,) for rep.
frepTuple2 :: Generic g => g a -> g b -> g (a, b)Source
Representation of (,) for frep.
frep2Tuple2 :: Generic2 g => g a1 a2 -> g b1 b2 -> g (a1, b1) (a2, b2)Source
Representation of (,) for frep2.
frep3Tuple2 :: Generic3 g => g a1 a2 a3 -> g b1 b2 b3 -> g (a1, b1) (a2, b2) (a3, b3)Source
Representation of (,) for frep3.
bifrep2Tuple2 :: Generic2 g => g a1 a2 -> g b1 b2 -> g (a1, b1) (a2, b2)Source
Representation of (,) for bifrep2.
Triple: (a,b,c)
epTuple3 :: EP (a, b, c) (a :*: (b :*: c))Source
Embedding-projection pair for (,,).
conTuple3 :: ConDescrSource
Constructor description for (,,).
repTuple3 :: (Generic g, Rep g a, Rep g b, Rep g c) => g (a, b, c)Source
Representation of (,,) for rep.
frepTuple3 :: Generic g => g a -> g b -> g c -> g (a, b, c)Source
Representation of (,,) for frep.
frep2Tuple3 :: Generic2 g => g a1 a2 -> g b1 b2 -> g c1 c2 -> g (a1, b1, c1) (a2, b2, c2)Source
Representation of (,,) for frep2.
frep3Tuple3 :: Generic3 g => g a1 a2 a3 -> g b1 b2 b3 -> g c1 c2 c3 -> g (a1, b1, c1) (a2, b2, c2) (a3, b3, c3)Source
Representation of (,,) for frep3.
bifrep2Tuple3 :: Generic2 g => g a1 a2 -> g b1 b2 -> g c1 c2 -> g (a1, b1, c1) (a2, b2, c2)Source
Representation of (,,) for bifrep2.
Quadruple: (a,b,c,d)
epTuple4 :: EP (a, b, c, d) (a :*: (b :*: (c :*: d)))Source
Embedding-projection pair for (,,,).
conTuple4 :: ConDescrSource
Constructor description for (,,,).
repTuple4 :: (Generic g, Rep g a, Rep g b, Rep g c, Rep g d) => g (a, b, c, d)Source
Representation of (,,,) for rep.
frepTuple4 :: Generic g => g a -> g b -> g c -> g d -> g (a, b, c, d)Source
Representation of (,,,) for frep.
frep2Tuple4 :: Generic2 g => g a1 a2 -> g b1 b2 -> g c1 c2 -> g d1 d2 -> g (a1, b1, c1, d1) (a2, b2, c2, d2)Source
Representation of (,,,) for frep2.
frep3Tuple4 :: Generic3 g => g a1 a2 a3 -> g b1 b2 b3 -> g c1 c2 c3 -> g d1 d2 d3 -> g (a1, b1, c1, d1) (a2, b2, c2, d2) (a3, b3, c3, d3)Source
Representation of (,,,) for frep3.
bifrep2Tuple4 :: Generic2 g => g a1 a2 -> g b1 b2 -> g c1 c2 -> g d1 d2 -> g (a1, b1, c1, d1) (a2, b2, c2, d2)Source
Representation of (,,,) for bifrep2.
Quintuple: (a,b,c,d,e)
epTuple5 :: EP (a, b, c, d, e) (a :*: (b :*: (c :*: (d :*: e))))Source
Embedding-projection pair for (,,,,).
conTuple5 :: ConDescrSource
Constructor description for (,,,,).
repTuple5 :: (Generic g, Rep g a, Rep g b, Rep g c, Rep g d, Rep g e) => g (a, b, c, d, e)Source
Representation of (,,,,) for rep.
frepTuple5 :: Generic g => g a -> g b -> g c -> g d -> g e -> g (a, b, c, d, e)Source
Representation of (,,,,) for frep.
frep2Tuple5 :: Generic2 g => g a1 a2 -> g b1 b2 -> g c1 c2 -> g d1 d2 -> g e1 e2 -> g (a1, b1, c1, d1, e1) (a2, b2, c2, d2, e2)Source
Representation of (,,,,) for frep2.
frep3Tuple5 :: Generic3 g => g a1 a2 a3 -> g b1 b2 b3 -> g c1 c2 c3 -> g d1 d2 d3 -> g e1 e2 e3 -> g (a1, b1, c1, d1, e1) (a2, b2, c2, d2, e2) (a3, b3, c3, d3, e3)Source
Representation of (,,,,) for frep3.
bifrep2Tuple5 :: Generic2 g => g a1 a2 -> g b1 b2 -> g c1 c2 -> g d1 d2 -> g e1 e2 -> g (a1, b1, c1, d1, e1) (a2, b2, c2, d2, e2)Source
Representation of (,,,,) for bfrep2.
Sextuple: (a,b,c,d,e,f)
epTuple6 :: EP (a, b, c, d, e, f) (a :*: (b :*: (c :*: (d :*: (e :*: f)))))Source
Embedding-projection pair for (,,,,,).
conTuple6 :: ConDescrSource
Constructor description for (,,,,,).
repTuple6 :: (Generic g, Rep g a, Rep g b, Rep g c, Rep g d, Rep g e, Rep g f) => g (a, b, c, d, e, f)Source
Representation of (,,,,,) for rep.
frepTuple6 :: Generic g => g a -> g b -> g c -> g d -> g e -> g f -> g (a, b, c, d, e, f)Source
Representation of (,,,,,) for frep.
frep2Tuple6 :: Generic2 g => g a1 a2 -> g b1 b2 -> g c1 c2 -> g d1 d2 -> g e1 e2 -> g f1 f2 -> g (a1, b1, c1, d1, e1, f1) (a2, b2, c2, d2, e2, f2)Source
Representation of (,,,,,) for frep2.
frep3Tuple6 :: Generic3 g => g a1 a2 a3 -> g b1 b2 b3 -> g c1 c2 c3 -> g d1 d2 d3 -> g e1 e2 e3 -> g f1 f2 f3 -> g (a1, b1, c1, d1, e1, f1) (a2, b2, c2, d2, e2, f2) (a3, b3, c3, d3, e3, f3)Source
Representation of (,,,,,) for frep3.
bifrep2Tuple6 :: Generic2 g => g a1 a2 -> g b1 b2 -> g c1 c2 -> g d1 d2 -> g e1 e2 -> g f1 f2 -> g (a1, b1, c1, d1, e1, f1) (a2, b2, c2, d2, e2, f2)Source
Representation of (,,,,,) for bifrep2.
Septuple: (a,b,c,d,e,f,h)
epTuple7 :: EP (a, b, c, d, e, f, h) (a :*: (b :*: (c :*: (d :*: (e :*: (f :*: h))))))Source
Embedding-projection pair for (,,,,,,).
conTuple7 :: ConDescrSource
Constructor description for (,,,,,,).
repTuple7 :: (Generic g, Rep g a, Rep g b, Rep g c, Rep g d, Rep g e, Rep g f, Rep g h) => g (a, b, c, d, e, f, h)Source
Representation of (,,,,,,) for rep.
frepTuple7 :: Generic g => g a -> g b -> g c -> g d -> g e -> g f -> g h -> g (a, b, c, d, e, f, h)Source
Representation of (,,,,,,) for frep.
frep2Tuple7 :: Generic2 g => g a1 a2 -> g b1 b2 -> g c1 c2 -> g d1 d2 -> g e1 e2 -> g f1 f2 -> g h1 h2 -> g (a1, b1, c1, d1, e1, f1, h1) (a2, b2, c2, d2, e2, f2, h2)Source
Representation of (,,,,,,) for frep2.
frep3Tuple7 :: Generic3 g => g a1 a2 a3 -> g b1 b2 b3 -> g c1 c2 c3 -> g d1 d2 d3 -> g e1 e2 e3 -> g f1 f2 f3 -> g h1 h2 h3 -> g (a1, b1, c1, d1, e1, f1, h1) (a2, b2, c2, d2, e2, f2, h2) (a3, b3, c3, d3, e3, f3, h3)Source
Representation of (,,,,,,) for frep3.
bifrep2Tuple7 :: Generic2 g => g a1 a2 -> g b1 b2 -> g c1 c2 -> g d1 d2 -> g e1 e2 -> g f1 f2 -> g h1 h2 -> g (a1, b1, c1, d1, e1, f1, h1) (a2, b2, c2, d2, e2, f2, h2)Source
Representation of (,,,,,,) for bifrep2.
Template Haskell
For using the representation of Template Haskell, import Generics.EMGM.Data.TH. We don't export it here, because it exports names that conflict with EMGM names.
Derived Generic Functions
These newtypes are exported for generating their Rep instances.
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)
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)
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
Exported Modules
Re-export these modules for generated code.
module Generics.EMGM.Common
Produced by Haddock version 2.4.2