th-reify-many-0.1.6: Recurseively reify template haskell datatype info

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.TH.ReifyMany

Description

th-reify-many provides functions for recursively reifying top level declarations. The main intended use case is for enumerating the names of datatypes reachable from an initial datatype, and passing these names to some function which generates instances.

For example, in order to define Lift instances for two mutually recursive datatypes, I could write something like:

{-# LANGUAGE TemplateHaskell #-}
import Language.Haskell.TH.ReifyMany (reifyManyWithoutInstances)
import Language.Haskell.TH.Lift (Lift(..), deriveLiftMany)

data A = A B

data B = B Int

$(reifyManyWithoutInstances ''Lift [''A] (const True) >>= deriveLiftMany)

One interesting feature of this is that it attempts to omit the types which already have an instance defined. For example, if $(deriveLift ''B) is used before deriveLiftMany, it will omit the instance for B.

Of course, the intended usecase for this involves many more datatypes - for example, syntax trees such as those found in TH.

Note that reifyManyWithoutInstances is rather imperfect in its testing of whether an instance exists, and whether an instance should exist. See this function's docs for details.

Synopsis

Documentation

reifyManyWithoutInstances :: Name -> [Name] -> (Name -> Bool) -> Q [Name]

Recursively enumerates type constructor declarations, halting when datatypes appear to already have an instance for the typeclass specified by the first Name parameter. It guesses that an instance exists for a given datatype if it's used in the top constructor of any of its parameters (see instanceMatches).

This function is useful for bulk defining typeclass instances like Binary, Lift, Data, Typeable, etc. It isn't very clever, though - in particular it has the following limitations:

  • It only works well when type constructors mentioned in fields should all have instances defined for them.
  • It ignores data type / constructor constraints.
  • It ignores data / type families.

It also takes a user-defined predicate, which is useful in situations where this attempts to descend into datatypes which do not need instances defined for them.

Note that this will always initially yield the Names of the initial types, regardless of whether they are instances or not.

reifyManyTyCons :: ((Name, Dec) -> Q (Bool, [Name])) -> [Name] -> Q [(Name, Info)]

Like reifyMany, but specialized for recursively enumerating type constructor declarations, omitting PrimTyConI.

In order to have this behave like reifyManyWithoutInstances, but not do any instance filtering, use it with the isDataDec and decConcreteNames internal utilities. For example:

{-# LANGUAGE TemplateHaskell #-}
import Language.Haskell.TH
import Language.Haskell.TH.ReifyMany
import Language.Haskell.TH.ReifyMany.Internal

$(do results <- reifyManyTyCons
         (\(_, dec) -> return (isDataDec dec, decConcreteNames dec))
         [''Exp]
     -- Display the results
     reportError (show (map fst results))
     -- This TH splice doesn't generate any code.
     return []
 )

reifyMany :: ((Name, Info) -> Q (Bool, [Name])) -> [Name] -> Q [(Name, Info)]

Starting from a set of initial top level declarations, specified by [Name], recursively enumerate other related declarations. The provided function determines whether the current info be included in the list of results, and which Names to lookup next. This function handles keeping track of which Names have already been visited.