Copyright | (C) 2015-2017 Ryan Scott |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Ryan Scott |
Portability | Template Haskell |
Safe Haskell | None |
Language | Haskell2010 |
This module reexports all of the functionality of the other modules in this library
(with the exception of Data.Deriving.Via, which is only available on GHC 8.2 or
later). This module also provides a high-level tutorial on deriving-compat
's
naming conventions and best practices. Typeclass-specific information can be found
in their respective modules.
Backported changes
The following changes have been backported:
- In GHC 7.2, deriving
Read
was changed so that constructors that useMagicHash
now parse correctly. - In GHC 7.8, deriving standalone
Read
instances was fixed to avoid crashing on datatypes with no constructors. DerivedRead
instances were also changed so as to compile more quickly. - In GHC 7.10, deriving standalone
Read
andShow
instances were fixed to ensure that they use the correct fixity information for a particular datatype. - In GHC 8.0,
DeriveFoldable
was changed to allow folding over data types with existential constraints. - In GHC 8.0,
DeriveFoldable
andDeriveTraversable
were changed so as not to generate superfluousmempty
orpure
expressions in generated code. As a result, this allows derivingTraversable
instances for datatypes with unlifted argument types. - In GHC 8.0, deriving
Ix
was changed to use(
instead of&&
)if
, as the latter interacts poorly withRebindableSyntax
. A bug was also fixed so that standalone-derivedIx
instances for single-constructor GADTs do not crash GHC. - In GHC 8.0, deriving
Show
was changed so that constructor fields with unlifted types are no longer shown with parentheses, and the output of showing an unlifted type is suffixed with the same number of hash signs as the corresponding primitive literals. - In GHC 8.2, deriving
Ord
was changed so that it generates concreteif
-expressions that are not subject toRebindableSyntax
. It was also changed so that derived(
,<=
)(
, and>
)(
methods are expressed through>=
)(
, which avoids generating a substantial amount of code.<
) - In GHC 8.2, deriving
Traversable
was changed so that it usesliftA2
to implementtraverse
whenever possible. This was done sinceliftA2
was also made a class method ofApplicative
, so sometimes usingliftA2
produces more efficient code. - In GHC 8.2, deriving
Show
was changed so that it uses an explicitshowCommaSpace
method, instead of repeating the codeshowString ", "
in several places. - In GHC 8.4, deriving
Functor
andTraverable
was changed so that it usescoerce
for efficiency when the last parameter of the data type is at phantom role. In GHC 8.4, the
EmptyDataDeriving
proposal brought forth a slew of changes related to how instances for empty data types (i.e., no constructors) were derived. These changes include:- For derived
Eq
andOrd
instances for empty data types, simply returnTrue
andEQ
, respectively, without inspecting the arguments. - For derived
Read
instances for empty data types, simply returnpfail
(withoutparens
). - For derived
Show
instances for empty data types, inspect the argument (instead oferror
ing). - For derived
Functor
andTraversable
instances for empty data types, makefmap
andtraverse
strict in its argument. - For derived
Foldable
instances, do not error on empty data types. Instead, simply return the folded state (forfoldr
) ormempty
(forfoldMap
), without inspecting the arguments.
- For derived
derive
- functions
Functions with the derive
- prefix can be used to automatically generate an instance
of a typeclass for a given datatype Name
. Some examples:
{-# LANGUAGE TemplateHaskell #-} import Data.Deriving data Pair a = Pair a a $(deriveFunctor
''Pair) -- instance Functor Pair where ... data Product f g a = Product (f a) (g a) $(deriveFoldable
''Product) -- instance (Foldable f, Foldable g) => Foldable (Pair f g) where ...
If you are using template-haskell-2.7.0.0
or later (i.e., GHC 7.4 or later),
then derive
-functions can be used with data family instances (which requires the
-XTypeFamilies
extension). To do so, pass the Name
of a data or newtype instance
constructor (NOT a data family name!) to deriveFoldable
. Note that the
generated code may require the -XFlexibleInstances
extension. Example:
{-# LANGUAGE FlexibleInstances, TemplateHaskell, TypeFamilies #-}
import Data.Deriving
class AssocClass a b where
data AssocData a b
instance AssocClass Int b where
data AssocData Int b = AssocDataInt1 Int
| AssocDataInt2 b
$(deriveFunctor
'AssocDataInt1) -- instance Functor (AssocData Int) where ...
-- Alternatively, one could use $(deriveFunctor 'AssocDataInt2)
derive
-functions in deriving-compat
fall into one of three categories:
- Category 0: Typeclasses with an argument of kind
*
. (deriveBounded
,deriveEnum
,deriveEq
,deriveIx
,deriveOrd
,deriveRead
,deriveShow
) - Category 1: Typeclasses with an argument of kind
* -> *
, That is, a datatype with such an instance must have at least one type variable, and the last type variable must be of kind*
. (deriveEq1
,deriveFoldable
,deriveFunctor
,deriveOrd1
,deriveRead1
,deriveShow1
,deriveTraversable
) - Category 2: Typeclasses with an argument of kind
* -> * -> *
. That is, a datatype with such an instance must have at least two type variables, and the last two type variables must be of kind*
. (deriveEq2
,deriveOrd2
,deriveRead2
,deriveShow2
)
Note that there are some limitations to derive
-functions:
- The
Name
argument must not be of a type synonym. - Type variables (other than the last ones) are assumed to require typeclass
constraints. The constraints are different depending on the category. For example,
for Category 0 functions, other type variables of kind
*
are assumed to be constrained by that typeclass. As an example:
data Foo a = Foo a $(deriveEq ''Foo)
will result in a generated instance of:
instance Eq a => Eq (Foo a) where ...
If you do not want this behavior, use a make
- function instead.
- For Category 1 and 2 functions, if you are using the
-XDatatypeContexts
extension, a constraint cannot mention the last type variables. For example,data Illegal a where I :: Ord a => a -> Illegal a
cannot have a derivedFunctor
instance. - For Category 1 and 2 functions, if one of the last type variables is used within a
constructor field's type, it must only be used in the last type arguments. For
example,
data Legal a = Legal (Either Int a)
can have a derivedFunctor
instance, butdata Illegal a = Illegal (Either a Int)
cannot. - For Category 1 and 2 functions, data family instances must be able to eta-reduce the last type variables. In other words, if you have a instance of the form:
data family Family a1 ... an t1 ... tn data instance Family e1 ... e2 v1 ... vn = ...
where t1
, ..., tn
are the last type variables, then the following conditions
must hold:
v1
, ...,vn
must be type variables.v1
, ...,vn
must not be mentioned in any ofe1
, ...,e2
.
make
- functions
Functions prefixed with make
- are similar to derive
-functions in that they also
generate code, but make
-functions in particular generate the expression for a
particular typeclass method. For example:
{-# LANGUAGE TemplateHaskell #-}
import Data.Deriving
data Pair a = Pair a a
instance Functor Pair where
fmap = $(makeFmap
''Pair)
In this example, makeFmap
will splice in the appropriate lambda expression which
implements fmap
for Pair
.
make
-functions are subject to all the restrictions of derive
-functions listed
above save for one exception: the datatype need not be an instance of a particular
typeclass. There are some scenarios where this might be preferred over using a
derive
-function. For example, you might want to map over a Pair
value
without explicitly having to make it an instance of Functor
.
Another use case for make
-functions is sophisticated data types—that is, an
expression for which a derive
-function would infer the wrong instance context.
Consider the following example:
data Proxy a = Proxy
$(deriveEq
''Proxy)
This would result in a generated instance of:
instance Eq a => Eq (Proxy a) where ...
This compiles, but is not what we want, since the Eq a
constraint is completely
unnecessary. Another scenario in which derive
-functions fail is when you
have something like this:
newtype HigherKinded f a b = HigherKinded (f a b)
$(deriveFunctor
''HigherKinded)
Ideally, this would produce HigherKinded (f a)
as its instance context, but sadly,
the Template Haskell type inference machinery used in deriving-compat
is not smart
enough to figure that out. Nevertheless, make
-functions provide a valuable
backdoor for these sorts of scenarios:
{-# LANGUAGE FlexibleContexts, TemplateHaskell #-} import Data.Foldable.Deriving data Proxy a = Proxy newtype HigherKinded f a b = HigherKinded (f a b) instance Eq (Proxy a) where (==) = $(makeEq
''Proxy) instance Functor (f a) => Functor (HigherKinded f a) where fmap = $(makeFmap
''HigherKinded)