typeable-th-0.1: Automatic deriving of TypeableN instances with Template Haskell

Safe HaskellNone

Data.Typeable.TH

Contents

Synopsis

Intro

This module provides Template Haskell functions that derive TypeableN instances. They are smart in that they try define the best possible TypeableN instance, where a higher N is better. The best N is given by the number of parameters before the first parameter not of kind *, reading backwards.

Maybe an example can explain this better:

First, you need to enable some extensions and import Data.Typeable.TH to use this package:

 {-# LANGUAGE EmptyDataDecls       #-}
 {-# LANGUAGE KindSignatures       #-}
 {-# LANGUAGE ScopedTypeVariables  #-}
 {-# LANGUAGE TemplateHaskell      #-}
 {-# LANGUAGE UndecidableInstances #-}
 
 import Data.Typeable
 import Data.Typeable.TH

Now, we have some weird data type:

 data Weird (a :: *) (b :: (* -> *)) (c :: *) (d :: *) (e :: *)

which has the kind * -> (* -> *) -> * -> * -> * -> *, then the best N we can pick for our TypeableN instance is 3, because there are 3 parameters of kind * (from the back) until we hit a parameter that isn't of kind *. Remember that the last * is not a kind of a parameter, but instead the kind of the data type when it has been applied to all parameters it needs.

To derive a Typeable3 instance for this data type, we can use the following code:

 makeTypeable ''Weird

This also gives use Typeable2, Typeable1 and Typeable, because those have default instances in terms of Typeable3.

We can also test our instance:

>>> typeOf3 (undefined :: Weird Int Maybe [Char] Int Float)
Weird Int Maybe
>>> typeOf2 (undefined :: Weird Int Maybe [Char] Int Float)
Weird Int Maybe [Char]

No more manual writing of TypeableN instances!

User interface

makeTypeable :: Name -> Q [Dec]Source

Derive the best typeable instance for a given data type.

makeTypeableN :: Name -> Int -> Q [Dec]Source

Derive the given TypeableN instance for a data type. Using N=0 generates a plain Typeable instance. Note that this function may fail if it's not possible to derive the requested TypeableN instance.

Utility and internal functions

dropEnd :: Int -> [a] -> [a]Source

dropEnd n l drops n items from the end of the list l. This function is implemented the naive way, it might not be the fastest.

bestTypeable :: Kind -> IntSource

Calculate the maximum N for which a TypeableN instance is generatable for a given kind. How this works is explained in the description at the top of this module.

typeableBody :: Name -> Kind -> Int -> [Name] -> WriterT ([Dec], [Pred]) (StateT Integer Q) ExpSource

Generate the typeOfN function of TypeableN, tell'ing all instance context predicates and declarations we need. We also update a state to have a counter for generating unique names for data types we declare.

typeRepOf :: Name -> Kind -> WriterT ([Dec], [Pred]) (StateT Integer Q) ExpSource

Returns the expression to get the TypeRep of a given type variable with a given kind.

splitKind :: Kind -> (Kind, Maybe Kind)Source

Split the part in front of the arrow from a kind, and return the rest (if there is any rest). Example: splitKind (* -> *) -> * -> * will return ((* -> *),Just * -> *). This is used to implement params.

params :: Kind -> [Kind]Source

Split a kind into a list of kinds, where each list element is a kind of the parameter of the orginal kind. The list is ordered, a parameter which comes first comes first in the list too.

typeOfKind :: Kind -> StateT Integer Q (Name, [Dec])Source

Generate a data type with the given kind that has no constructor and return the name of it. The state is used for generating unqiue names for the data type.

expectTyCon :: String -> Info -> Q DecSource

A helper function that makes sure the info is a TyConI, and throws an error otherwise.

Error messages

If you get an error like this,

   test3.hs:6:1:
    The exact Name p_a2t1 is not in scope
      Probable cause: you used a unique Template Haskell name (NameU), 
      perhaps via newName, but did not bind it
      If that's it, then -ddump-splices might be useful

check if you have enabled all extensions that are needed (a list is in the intro), in particular ScopedTypeVariables.

If you get a different error, it should tell you which extension you need to enable. If it doesn't, please file a bug report.

Reexports