| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
TH.Derive
Description
This module implements a system for registering and using typeclass
derivers and instantiators. This allows you to derive instances for
typeclasses beyond GHC's ability to generate instances in deriving
clauses.
For exmaple, TH.Derive.Storable defines a Deriver for Storable.
This allows us to use derive to generate an instance for Storable:
data X = X Int Float
$($(derive [d|
instance Deriving (Storable X)
|]))
In particular, note the use of double splicing, $($(derive [d| ...
|])). The inner $(derive [d| ... |]) expression generates code
which invokes the runDeriver method with appropriate arguments. The
outer $( ... $) then runs that code in order to generate the
resulting instances. This is how it does dispatch at compile time.
There are a number of advantages of re-using instance syntax in this way:
- It allows the user to specify constraints. Similarly to GHC's need for standalone deriving, it is sometimes very difficult for TH to figure out appropriate superclass constraints.
- The instance gets thoroughly checked by GHC (syntax, kind, and type checking). This means that you get reasonably nice error messages when you misuse these.
- It allows the user to specify methods. With
Instantiators, the user can provide values which can be used in the definition of the generated instance. This is a bit like having Instance Templates. We don't have pretty ways of writing these quite yet, but I have worked on something similar in the past. - Using compile-time dispatch allows for concise specification of a multiple of instances you'd like derived.
- In the case of use of a
Derivers, the user doesn't need to know about anything butderiveand the name of the class they want. (and theDeriverinstance must be in scope one way or another)
Documentation
derive :: DecsQ -> ExpQ Source
This is the primary function for users of TH.Derive. See the module documentation for usage info.
This class has no instances. Its only purpose is usage within the
[d| ... |] quote provided to derive. Usage such as instance
Deriving (Foo X) indicates that you would like to use the Deriver
registered for Foo a.
class Instantiator inst where Source
Instances of Instantiator are similar in purpose to instance of
Deriver. The difference is that instead of using the Deriving
class, each instantiator has its own new typeclass. This means that
you can have multiple instantiators that all produce instances for
the same typeclass, using different approaches.
Having a new class also allows the instantiator to have methods and
data / type family declarations. This allows the user to provide
definitions which specify how the generated instances behave. For
example, lets say we want to be able to directly define Eq and
Ord instances via a conversion function to the type to compare.
Here's what this currently looks like:
class Ord o => InstEqOrdVia o a where
_toOrd :: a -> o
instance Instantiator (InstEqOrdVia o a) where
runInstantiator _ preds (AppT (AppT (ConT ((== ''InstEqOrdVia) -> True)) _oTy) aTy) decls =
dequalifyMethods ''InstEqOrdVia =<<
sequence
[instanceD (return preds) [t| Eq $(return aTy) |] $
[valD (varP '(==))
(normalB [| l r -> _toOrd l == _toOrd r |])
(map return decls)]
, instanceD (return preds) [t| Ord $(return aTy) |] $
[valD (varP 'compare)
(normalB [| l r -> compare (_toOrd l) (_toOrd r) |])
(map return decls)
]
]
runInstantiator _ _ _ _ =
fail "Theoretically impossible case in InstEqOrdVia instantiator"
Why the underscore prefixing of _toOrd? It's to suppress name
shadowing warnings which otherwise occur. In the future, this library
will likely provide pretty ways to define instantiators. For now it's
a bit ugly.
Here's what usage of this looks like:
data T = Y | Z
$($(derive [d|
instance InstEqOrdVia Bool T where
_toOrd Y = True
_toOrd Z = False
|]))
main = when (Y > Z) (putStrLn "It worked!!")
dequalifyMethods :: Data a => Name -> a -> Q a Source
Useful function for defining Instantiator instances. It uses
Data to generically replace references to the methods with plain
Names. This is handy when you are putting the definitions passed to
the instantiator in a where clause. It is also useful so that you can
reference the class methods from AST quotes involved in the
definition of the instantiator.