Copyright | (c) 2008--2009 Universiteit Utrecht |
---|---|
License | BSD3 |
Maintainer | generics@haskell.org |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe |
Language | Haskell2010 |
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 x = FamilyChar Char data instance Family Bool x = FamilyTrue | FamilyFalse $(deriveAll0
'FamilyChar) -- instance Generic (Family Char b) where ... $(deriveAll1
'FamilyTrue) -- instance Generic1 (Family Bool) where ... -- Alternatively, one could type $(deriveAll1 'FamilyFalse)
Synopsis
- deriveMeta :: Name -> Q [Dec]
- deriveData :: Name -> Q [Dec]
- deriveConstructors :: Name -> Q [Dec]
- deriveSelectors :: Name -> Q [Dec]
- deriveAll :: Name -> Q [Dec]
- deriveAll0 :: Name -> Q [Dec]
- deriveAll1 :: Name -> Q [Dec]
- deriveAll0And1 :: Name -> Q [Dec]
- deriveRepresentable0 :: Name -> Q [Dec]
- deriveRepresentable1 :: Name -> Q [Dec]
- deriveRep0 :: Name -> Q [Dec]
- deriveRep1 :: Name -> Q [Dec]
- makeRep0Inline :: Name -> Q Type -> Q Type
- makeRep0 :: Name -> Q Type
- makeRep0FromType :: Name -> Q Type -> Q Type
- makeFrom :: Name -> Q Exp
- makeFrom0 :: Name -> Q Exp
- makeTo :: Name -> Q Exp
- makeTo0 :: Name -> Q Exp
- makeRep1Inline :: Name -> Q Type -> Q Type
- makeRep1 :: Name -> Q Type
- makeRep1FromType :: Name -> Q Type -> Q Type
- makeFrom1 :: Name -> Q Exp
- makeTo1 :: Name -> Q Exp
- data Options = Options {}
- defaultOptions :: Options
- data RepOptions
- defaultRepOptions :: RepOptions
- type KindSigOptions = Bool
- defaultKindSigOptions :: KindSigOptions
- type EmptyCaseOptions = Bool
- defaultEmptyCaseOptions :: EmptyCaseOptions
- deriveAll0Options :: Options -> Name -> Q [Dec]
- deriveAll1Options :: Options -> Name -> Q [Dec]
- deriveAll0And1Options :: Options -> Name -> Q [Dec]
- deriveRepresentable0Options :: Options -> Name -> Q [Dec]
- deriveRepresentable1Options :: Options -> Name -> Q [Dec]
- deriveRep0Options :: KindSigOptions -> Name -> Q [Dec]
- deriveRep1Options :: KindSigOptions -> Name -> Q [Dec]
- makeFrom0Options :: EmptyCaseOptions -> Name -> Q Exp
- makeTo0Options :: EmptyCaseOptions -> Name -> Q Exp
- makeFrom1Options :: EmptyCaseOptions -> Name -> Q Exp
- makeTo1Options :: EmptyCaseOptions -> Name -> Q Exp
derive
- functions
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.
On GHC 7.11 and up, this functionality is no longer used in GHC generics, so this function generates no declarations.
deriveData :: Name -> Q [Dec] Source #
Given a datatype name, derive a datatype and instance of class Datatype
.
On GHC 7.11 and up, this functionality is no longer used in GHC generics, so this function generates no declarations.
deriveConstructors :: Name -> Q [Dec] Source #
Given a datatype name, derive datatypes and
instances of class Constructor
.
On GHC 7.11 and up, this functionality is no longer used in GHC generics, so this function generates no declarations.
deriveSelectors :: Name -> Q [Dec] Source #
Given a datatype name, derive datatypes and instances of class Selector
.
On GHC 7.11 and up, this functionality is no longer used in GHC generics, so this function generates no declarations.
deriveAll0 :: 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.
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:
newtype 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) = $(makeRep1Inline
''Fix [t| Fix f |]) from1 = $(makeFrom1
''Fix) to1 = $(makeTo1
''Fix)
Note that due to the lack of type-level lambdas in Haskell, one must manually
apply
to the type makeRep1Inline
''FixFix f
.
Be aware that there is a bug on GHC 7.0, 7.2, and 7.4 which might prevent you from
using makeRep0Inline
and makeRep1Inline
. In the Fix
example above, you
would experience the following error:
Kinded thing f
used as a type
In the Template Haskell quotation [t| Fix f |]
Then a workaround is to use makeRep1
instead, which requires you to:
- Invoke
deriveRep1
beforehand - Pass as arguments the type variables that occur in the instance, in order
from left to right, topologically sorted, excluding duplicates. (Normally,
makeRep1Inline
would figure this out for you.)
Using the above 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)
On GHC 7.4, you might encounter more complicated examples involving data families. For instance:
data family Fix a b c d newtype instance Fix b (f c) (g b) a = Fix (f (Fix b (f c) (g b) a)) $(deriveMeta
''Fix) $(deriveRep1
''Fix) instance Functor f => Generic1 (Fix b (f c) (g b)) where type Rep1 (Fix b (f c) (g b)) = $(makeRep1
'Fix) b f c g from1 = $(makeFrom1
'Fix) to1 = $(makeTo1
'Fix)
Note that you don't pass b
twice, only once.
makeRep0Inline :: Name -> Q Type -> Q Type Source #
Generates the full Rep
type inline. Since this type can be quite
large, it is recommended you only use this to define Rep
, e.g.,
type Rep (Foo (a :: k) b) = $(makeRep0Inline
''Foo [t| Foo (a :: k) b |])
You can then simply refer to Rep (Foo a b)
elsewhere.
Note that the type passed as an argument to makeRep0Inline
must match the
type argument of Rep
exactly, even up to including the explicit kind
signature on a
. This is due to a limitation of Template Haskell—without
the kind signature, makeRep0Inline
has no way of figuring out the kind of
a
, and the generated type might be completely wrong as a result!
makeRep0 :: Name -> Q Type Source #
Generates the Rep
type synonym constructor (as opposed to deriveRep0
,
which generates the type synonym declaration). After splicing it into
Haskell source, it expects types as arguments. For example:
type Rep (Foo a b) = $(makeRep0
''Foo) a b
The use of makeRep0
is generally discouraged, as it can sometimes be
difficult to predict the order in which you are expected to pass type
variables. As a result, makeRep0Inline
is recommended instead. However,
makeRep0Inline
is not usable on GHC 7.0, 7.2, or 7.4 due to a GHC bug,
so makeRep0
still exists for GHC 7.0, 7.2, and 7.4 users.
makeRep0FromType :: Name -> Q Type -> Q Type Source #
Generates the Rep
type synonym constructor (as opposed to deriveRep0
,
which generates the type synonym declaration) applied to its type arguments.
Unlike makeRep0
, this also takes a quoted Type
as an argument, e.g.,
type Rep (Foo (a :: k) b) = $(makeRep0FromType
''Foo [t| Foo (a :: k) b |])
Note that the type passed as an argument to makeRep0FromType
must match the
type argument of Rep
exactly, even up to including the explicit kind
signature on a
. This is due to a limitation of Template Haskell—without
the kind signature, makeRep0FromType
has no way of figuring out the kind of
a
, and the generated type might be completely wrong as a result!
The use of makeRep0FromType
is generally discouraged, since makeRep0Inline
does exactly the same thing but without having to go through an intermediate
type synonym, and as a result, makeRep0Inline
tends to be less buggy.
makeRep1Inline :: Name -> Q Type -> Q Type Source #
Generates the full Rep1
type inline. Since this type can be quite
large, it is recommended you only use this to define Rep1
, e.g.,
type Rep1 (Foo (a :: k)) = $(makeRep0Inline
''Foo [t| Foo (a :: k) |])
You can then simply refer to Rep1 (Foo a)
elsewhere.
Note that the type passed as an argument to makeRep1Inline
must match the
type argument of Rep1
exactly, even up to including the explicit kind
signature on a
. This is due to a limitation of Template Haskell—without
the kind signature, makeRep1Inline
has no way of figuring out the kind of
a
, and the generated type might be completely wrong as a result!
makeRep1 :: Name -> Q Type Source #
Generates the Rep1
type synonym constructor (as opposed to deriveRep1
,
which generates the type synonym declaration). After splicing it into
Haskell source, it expects types as arguments. For example:
type Rep1 (Foo a) = $(makeRep1
''Foo) a
The use of makeRep1
is generally discouraged, as it can sometimes be
difficult to predict the order in which you are expected to pass type
variables. As a result, makeRep1Inline
is recommended instead. However,
makeRep1Inline
is not usable on GHC 7.0, 7.2, or 7.4 due to a GHC bug,
so makeRep1
still exists for GHC 7.0, 7.2, and 7.4 users.
makeRep1FromType :: Name -> Q Type -> Q Type Source #
Generates the Rep1
type synonym constructor (as opposed to deriveRep1
,
which generates the type synonym declaration) applied to its type arguments.
Unlike makeRep1
, this also takes a quoted Type
as an argument, e.g.,
type Rep1 (Foo (a :: k)) = $(makeRep1FromType
''Foo [t| Foo (a :: k) |])
Note that the type passed as an argument to makeRep1FromType
must match the
type argument of Rep
exactly, even up to including the explicit kind
signature on a
. This is due to a limitation of Template Haskell—without
the kind signature, makeRep1FromType
has no way of figuring out the kind of
a
, and the generated type might be completely wrong as a result!
The use of makeRep1FromType
is generally discouraged, since makeRep1Inline
does exactly the same thing but without having to go through an intermediate
type synonym, and as a result, makeRep1Inline
tends to be less buggy.
Options
Options
gives you a way to further tweak derived Generic
and Generic1
instances:
RepOptions
: By default, all derivedRep
andRep1
type instances emit the code directly (theInlineRep
option). One can also choose to emit a separate type synonym for theRep
type (this is the functionality ofderiveRep0
andderiveRep1
) and define aRep
instance in terms of that type synonym (theTypeSynonymRep
option).KindSigOptions
: By default, all derived instances will use explicit kind signatures (when theKindSigOptions
isTrue
). You might wish to set theKindSigOptions
toFalse
if you want a 'Generic'/'Generic1' instance at a particular kind that GHC will infer correctly, but the functions in this module won't guess correctly. For example, the following example will only compile withKindSigOptions
set toFalse
:
newtype Compose (f :: k2 -> *) (g :: k1 -> k2) (a :: k1) = Compose (f (g a))
$(deriveAll1Options
False ''Compose)
EmptyCaseOptions
: By default, all derived instances for empty data types (i.e., data types with no constructors) useerror
infrom(1)
/to(1)
. For instance,data Empty
would have this derivedGeneric
instance:
instance Generic Empty where type Rep Empty = D1 ('MetaData ...) V1 from _ = M1 (error "No generic representation for empty datatype Empty") to (M1 _) = error "No generic representation for empty datatype Empty"
This matches the behavior of GHC up until 8.4, when derived Generic(1)
instances began to use the EmptyCase
extension. In GHC 8.4, the derived
Generic
instance for Empty
would instead be:
instance Generic Empty where type Rep Empty = D1 ('MetaData ...) V1 from x = M1 (case x of {}) to (M1 x) = case x of {}
This is a slightly better encoding since, for example, any divergent
computations passed to from
will actually diverge (as opposed to before,
where the result would always be a call to error
). On the other hand, using
this encoding in generic-deriving
has one large drawback: it requires
enabling EmptyCase
, an extension which was only introduced in GHC 7.8
(and only received reliable pattern-match coverage checking in 8.2).
The EmptyCaseOptions
field controls whether code should be emitted that
uses EmptyCase
(i.e., EmptyCaseOptions
set to True
) or not (False
).
The default value is False
. Note that even if set to True
, this option
has no effect on GHCs before 7.8, as EmptyCase
did not exist then.
Additional options for configuring derived 'Generic'/'Generic1' instances using Template Haskell.
defaultOptions :: Options Source #
Sensible default Options
.
data RepOptions Source #
Configures whether 'Rep'/'Rep1' type instances should be defined inline in a
derived 'Generic'/'Generic1' instance (InlineRep
) or defined in terms of a
type synonym (TypeSynonymRep
).
Instances
Eq RepOptions Source # | |
Defined in Generics.Deriving.TH (==) :: RepOptions -> RepOptions -> Bool # (/=) :: RepOptions -> RepOptions -> Bool # | |
Ord RepOptions Source # | |
Defined in Generics.Deriving.TH compare :: RepOptions -> RepOptions -> Ordering # (<) :: RepOptions -> RepOptions -> Bool # (<=) :: RepOptions -> RepOptions -> Bool # (>) :: RepOptions -> RepOptions -> Bool # (>=) :: RepOptions -> RepOptions -> Bool # max :: RepOptions -> RepOptions -> RepOptions # min :: RepOptions -> RepOptions -> RepOptions # | |
Read RepOptions Source # | |
Defined in Generics.Deriving.TH readsPrec :: Int -> ReadS RepOptions # readList :: ReadS [RepOptions] # readPrec :: ReadPrec RepOptions # readListPrec :: ReadPrec [RepOptions] # | |
Show RepOptions Source # | |
Defined in Generics.Deriving.TH showsPrec :: Int -> RepOptions -> ShowS # show :: RepOptions -> String # showList :: [RepOptions] -> ShowS # |
defaultRepOptions :: RepOptions Source #
InlineRep
, a sensible default RepOptions
.
type KindSigOptions = Bool Source #
defaultKindSigOptions :: KindSigOptions Source #
True
, a sensible default KindSigOptions
.
type EmptyCaseOptions = Bool Source #
defaultEmptyCaseOptions :: EmptyCaseOptions Source #
Sensible default EmptyCaseOptions
.
Functions with optional arguments
deriveAll0Options :: Options -> Name -> Q [Dec] Source #
Like deriveAll0
, but takes an Options
argument.
deriveAll1Options :: Options -> Name -> Q [Dec] Source #
Like deriveAll1
, but takes an Options
argument.
deriveAll0And1Options :: Options -> Name -> Q [Dec] Source #
Like deriveAll0And1
, but takes an Options
argument.
deriveRepresentable0Options :: Options -> Name -> Q [Dec] Source #
Like deriveRepresentable0
, but takes an Options
argument.
deriveRepresentable1Options :: Options -> Name -> Q [Dec] Source #
Like deriveRepresentable1
, but takes an Options
argument.
deriveRep0Options :: KindSigOptions -> Name -> Q [Dec] Source #
Like deriveRep0
, but takes an KindSigOptions
argument.
deriveRep1Options :: KindSigOptions -> Name -> Q [Dec] Source #
Like deriveRep1
, but takes an KindSigOptions
argument.
makeFrom0Options :: EmptyCaseOptions -> Name -> Q Exp Source #
Like makeFrom0Options
, but takes an EmptyCaseOptions
argument.
makeTo0Options :: EmptyCaseOptions -> Name -> Q Exp Source #
Like makeTo0Options
, but takes an EmptyCaseOptions
argument.
makeFrom1Options :: EmptyCaseOptions -> Name -> Q Exp Source #
Like makeFrom1Options
, but takes an EmptyCaseOptions
argument.
makeTo1Options :: EmptyCaseOptions -> Name -> Q Exp Source #
Like makeTo1Options
, but takes an EmptyCaseOptions
argument.