emgm-0.2: Extensible and Modular Generics for the MassesSource codeContentsIndex
Generics.EMGM.Common.Derive
Portabilitynon-portable
Stabilityexperimental
Maintainergenerics@haskell.org
Contents
Automatic Instance Deriving
Manual Instance Deriving
Constructor Description Declaration
Embedding-Project Pair Declaration
Rep Instance Deriving
FRep Instance Deriving
BiFRep Instance Deriving
Function-Specific Instance Deriving
Description

Summary: Functions for generating support for using a datatype with EMGM.

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 described here.

Synopsis
derive :: Name -> Q [Dec]
deriveWith :: Modifiers -> Name -> Q [Dec]
data Modifier
= ChangeTo String
| DefinedAs String
type Modifiers = [(String, Modifier)]
declareConDescrs :: Name -> Q [Dec]
declareConDescrsWith :: Modifiers -> Name -> Q [Dec]
declareEP :: Name -> Q [Dec]
declareEPWith :: 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]
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
   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 (1 per constructor)
   conC :: ConDescr
   conC = ConDescr "C" 2 [] Nonfix
   -- (2) Embedding-projection pair declarations (1 per type)
   epT :: EP (T a) (a :*: Int)
   epT = EP fromT toT
     where fromT (C v1 v2) = v1 :*: v2
           toT (v1 :*: v2) = C v1 v2
   -- (3) Rep instance (1 per type)
   instance (Generic g, Rep g a, Rep g Int) => Rep g (T a) where
     rep = rtype epT (rcon conC (rprod rep rep))
   -- (4) Higher arity instances if applicable (either FRep, FRep2, and
   -- FRep3 together, or BiFRep2)
   instance (Generic g) => FRep g T where
     frep ra = rtype epT (rcon conC (rprod ra rint))
   -- In this case, similar instances would be generated for FRep2 and FRep3.
   -- (5) Function-specific instances (1 per type)
   instance Rep (Collect Char) Char where
     rep = Collect (:[])

Note that the constructor description conC and embedding-project pair epT are top-level values. This allows them to be shared between multiple instances. If these names conflict with your own, you may want to put the $(derive ...) declaration in its own module and restrict the export list.

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.
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.Common.Derive
   data T a = C a Int
   $(declareConDescrs ''T)
   $(declareEP ''T)
   $(deriveRep ''T)
   $(deriveFRep ''T)
   $(deriveCollect ''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.
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.
Produced by Haddock version 2.4.2