Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides some Template Haskell functionality to
help out the declaration of Deep
instances.
Note that we chose to not automate the whole process on purpose.
Sometimes the user will need to define standalone Generic
instances for some select types in the family, some other times
the user might want better control over naming, for example.
Consequently, the most adaptable option is to provide
two TH utilities:
- Unfolding a family into a list of types until a fixpoint is reached,
given in
unfoldFamilyInto
- Declaring
Deep
for a list of types, given indeclareDeepFor
The stepts in between unfolding the family and declaring Deep
vary
too much from case to case and hence, must be manually executed.
Let us run through a simple example, which involves mutual
recursion and type synonyms in the AST of a pseudo-language.
data Stmt var = SAssign var (Exp var) | SIf (Exp var) (Stmt var) (Stmt var) | SSeq (Stmt var) (Stmt var) | SReturn (Exp var) | SDecl (Decl var) | SSkip deriving (Show, Generic) data ODecl var = DVar var | DFun var var (Stmt var) deriving (Show, Generic) type Decl x = TDecl x type TDecl x = ODecl x data Exp var = EVar var | ECall var (Exp var) | EAdd (Exp var) (Exp var) | ESub (Exp var) (Exp var) | ELit Int deriving (Show, Generic)
Now say we want to use some code written with generics-simplistic
over these datatypes above. We must declare the Deep
instances for the types in the family and GHC.Generics
takes care of the rest.
The first step is in defining Prim
and Fam
, which
will be type-level lists with the primitive types and the non-primitive,
or compound, types.
An easy way to gather all types involved in the family is with
unfoldFamilyInto
, like:
unfoldFamilyInto "stmtFam" [t| Stmt Int |]
The call above will be expanded into:
stmtFam :: [String] stmtFam = ["Generics.Simplistic.Example.Exp Int" ,"Generics.Simplistic.Example.ODecl Int" ,"Generics.Simplistic.Example.Stmt Int" ,"Int" ]
Which can then be inspected with GHCi and, with some elbow-grease (or test-editting macros!) we can easily generate the necessary type-level lists:
type Fam = '[Generics.Simplistic.Example.Exp Int ,Generics.Simplistic.Example.ODecl Int ,Generics.Simplistic.Example.Stmt Int ] type Prim = '[Int]
Finally, we are ready to call deriveDeepFor
and get
the instances declared.
deriveDeepFor ''Prim ''Fam
The TH code above expands to:
instance Deep Prim Fam (Exp Int) instance Deep Prim Fam (ODecl Int) instance Deep Prim Fam (Stmt Int)
This workflow is crucial to be able to work with large mutually recursive families, and it becomes especially easy if coupled with a text editor with good macro support (read emacs and vim).
Documentation
unfoldFamilyInto :: String -> Q Type -> Q [Dec] Source #
Lists all the necessary types that should
have Generic
and Deep
instances. For example,
data Rose2 a b = Fork (Either a b) [Rose2 a b] unfoldFamilyInto 'rose2tys [t| Rose2 Int Char |]
Will yield the following code:
rose2tys :: String rose2tys = [ "Rose2 Int Char" , "Either Int Char" , "[Rose2 Int Char]" , "Int" , "Char" ]
You should then use some elbow grease or your favorite text editor and its provided macro functionality to produce:
type Rose2Prim = '[Int , Char] type Rose2Fam = '[Rose2 Int Char , Either Int Char , [Rose2 Int Char]] deriving instance Generic (Rose2 Int Char) deriving instance Generic (Either Int Char) instance Deep Rose2Prim Rose2Fam (Rose2 Int Char) instance Deep Rose2Prim Rose2Fam (Either Int Char) instance Deep Rose2Prim Rose2Fam [Rose2 Int Char]
Note that types like Int
will appear fully qualified,
this will need some renaming.
deriveDeepFor :: Name -> Name -> Q [Dec] Source #
Given two type-level lists Prims
and Fam
, will generate
instance Deep Prim Fam f
for every f
in Fam
.
Given a function f
and a type level stored in fam
,
deriveInstacesWith
will generate:
instance f x
for each x
in fam
. This function is mostly internal,
please check deriveDeepFor
and deriveGenericFor
.