generic-deriving-1.9.0: Generic programming library for generalised deriving.

Copyright(c) 2008--2009 Universiteit Utrecht
LicenseBSD3
Maintainergenerics@haskell.org
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell98

Generics.Deriving.TH

Contents

Description

This module contains Template Haskell code that can be used to automatically generate the boilerplate code for the generic deriving library.

To use these functions, pass the name of a data type as an argument:

{-# LANGUAGE TemplateHaskell #-}

data Example a = Example Int Char a
$(deriveAll0     ''Example) -- Derives Generic instance
$(deriveAll1     ''Example) -- Derives Generic1 instance
$(deriveAll0And1 ''Example) -- Derives Generic and Generic1 instances

On GHC 7.4 or later, this code can also be used with data families. To derive for a data family instance, pass the name of one of the instance's constructors:

{-# LANGUAGE FlexibleInstances, TemplateHaskell, TypeFamilies #-}

data family Family a b
newtype instance Family Char b = FamilyChar Char
data    instance Family Bool b = FamilyTrue | FamilyFalse

$(deriveAll0 'FamilyChar) -- instance Generic (Family Char b) where ...
$(deriveAll1 'FamilyTrue) -- instance Generic1 (Family Bool) where ...
-- Alternatively, one could type $(deriveAll1 'FamilyFalse)

If you are deriving for data family instances, be aware of a bug on GHC 7.8 (Trac #9692) which can cause incorrectly derived Generic1 instances if a data family declaration and one of its instances use different type variables:

data family Foo a b c
data instance Foo Int y z = Foo Int y z
$(deriveAll1 'Foo)

To avoid this issue, it is recommened that you use the same type variables in the same positions in which they appeared in the data family declaration:

data family Foo a b c
data instance Foo Int b c = Foo Int b c
$(deriveAll1 'Foo)

Synopsis

Documentation

deriveMeta :: Name -> Q [Dec] Source

Given the type and the name (as string) for the type to derive, generate the Data instance, the Constructor instances, and the Selector instances.

deriveData :: Name -> Q [Dec] Source

Given a datatype name, derive a datatype and instance of class Datatype.

deriveConstructors :: Name -> Q [Dec] Source

Given a datatype name, derive datatypes and instances of class Constructor.

deriveSelectors :: Name -> Q [Dec] Source

Given a datatype name, derive datatypes and instances of class Selector.

deriveAll :: Name -> Q [Dec] Source

Given the type and the name (as string) for the type to derive, generate the Data instance, the Constructor instances, the Selector instances, and the Representable0 instance.

deriveAll1 :: Name -> Q [Dec] Source

Given the type and the name (as string) for the type to derive, generate the Data instance, the Constructor instances, the Selector instances, and the Representable1 instance.

deriveAll0And1 :: Name -> Q [Dec] Source

Given the type and the name (as string) for the type to derive, generate the Data instance, the Constructor instances, the Selector instances, the Representable0 instance, and the Representable1 instance.

deriveRepresentable0 :: Name -> Q [Dec] Source

Given the type and the name (as string) for the Representable0 type synonym to derive, generate the Representable0 instance.

deriveRepresentable1 :: Name -> Q [Dec] Source

Given the type and the name (as string) for the Representable1 type synonym to derive, generate the Representable1 instance.

deriveRep0 :: Name -> Q [Dec] Source

Derive only the Rep0 type synonym. Not needed if deriveRepresentable0 is used.

deriveRep1 :: Name -> Q [Dec] Source

Derive only the Rep1 type synonym. Not needed if deriveRepresentable1 is used.

simplInstance :: Name -> Name -> Name -> Name -> Q [Dec] Source

Given the names of a generic class, a type to instantiate, a function in the class and the default implementation, generates the code for a basic generic instance.

make- functions

There are some data types for which the Template Haskell deriver functions in this module are not sophisticated enough to infer the correct Generic or Generic1 instances. As an example, consider this data type:

data Fix f a = Fix (f (Fix f a))

A proper Generic1 instance would look like this:

instance Functor f => Generic1 (Fix f) where ...

Unfortunately, deriveRepresentable1 cannot infer the Functor f constraint. One can still define a Generic1 instance for Fix, however, by using the functions in this module that are prefixed with make-. For example:

$(deriveMeta ''Fix)
$(deriveRep1 ''Fix)
instance Functor f => Generic1 (Fix f) where
  type Rep1 (Fix f) = $(makeRep1 ''Fix) f
  from1 = $(makeFrom1 ''Fix)
  to1   = $(makeTo1   ''Fix)

Note that due to the lack of type-level lambdas in Haskell, one must manually apply $(makeRep1 ''Fix) to the type parameters of Fix (f in the above example).

makeRep0 :: Name -> Q Type Source

Generates the Rep0 type synonym constructor (as opposed to deriveRep0, which generates the type synonym declaration).

makeFrom :: Name -> Q Exp Source

Generates a lambda expression which behaves like from.

makeTo :: Name -> Q Exp Source

Generates a lambda expression which behaves like to.

makeRep1 :: Name -> Q Type Source

Generates the Rep1 type synonym constructor (as opposed to deriveRep1, which generates the type synonym declaration).

makeFrom1 :: Name -> Q Exp Source

Generates a lambda expression which behaves like from1.

makeTo1 :: Name -> Q Exp Source

Generates a lambda expression which behaves like to1.