linear-generics-0.2.1: Generic programming library for generalised deriving.
Copyright(c) 2008--2009 Universiteit Utrecht
LicenseBSD3
MaintainerDavid.Feuer@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Generics.Linear.TH

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
$(deriveGeneric     ''Example) -- Derives Generic instance
$(deriveGeneric1     ''Example) -- Derives Generic1 instance
$(deriveGenericAnd1 ''Example) -- Derives Generic and Generic1 instances

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 x = FamilyChar Char
data    instance Family Bool x = FamilyTrue | FamilyFalse

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

General usage notes

Template Haskell imposes some fairly harsh limitations on ordering and visibility within a module. In most cases, classes derived generically will need to be derived using StandaloneDeriving after the deriveGeneric* invocation. For example, if Generically is a class that uses a Generic constraint for its instances, then you cannot write

data Fish = Fish
  deriving Show via (Generically Fish)

$(deriveGeneric 'Fish)

You must instead write

data Fish = Fish

$(deriveGeneric 'Fish)

deriving via Generically Fish
  instance Show Fish

Furthermore, types defined after a deriveGeneric* invocation are not visible before that invocation. This may require some careful ordering, especially in the case of mutually recursive types. For example, the following will not compile:

data Foo = Foo | Bar Baz
$(deriveGeneric 'Foo)

data Baz = Baz Int Foo
$(deriveGeneric 'Baz)

Instead, you must write

data Foo = Foo | Bar Baz
data Baz = Baz Int Foo

$(deriveGeneric 'Foo)
$(deriveGeneric 'Baz)
Synopsis

Documentation

deriveGeneric :: Name -> Q [Dec] Source #

Given the name of a type or data family constructor, derive a Generic instance.

deriveGeneric1 :: Name -> Q [Dec] Source #

Given the name of a type or data family constructor, derive a Generic1 instance.

deriveGenericAnd1 :: Name -> Q [Dec] Source #

Given the name of a type or data family constructor, derive a Generic instance and a Generic1 instance.