| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Language.Haskell.TypeTree
- class IsDatatype a where
- data Binding
- guess :: Name -> Binding
- ttReify :: IsDatatype t => t -> Q (Tree Leaf)
- ttReifyOpts :: IsDatatype t => ReifyOpts -> t -> Q (Tree Leaf)
- ttLit :: IsDatatype t => t -> ExpQ
- ttLitOpts :: IsDatatype t => ReifyOpts -> t -> ExpQ
- ttDescribe :: IsDatatype t => t -> ExpQ
- ttDescribeOpts :: IsDatatype t => ReifyOpts -> t -> ExpQ
- type Key = (Name, [Type])
- type Arity = Int
- ttEdges :: IsDatatype t => t -> ExpQ
- ttConnComp :: IsDatatype t => t -> ExpQ
- data Leaf
- data ReifyOpts = ReifyOpts {
- expandPrim :: Bool
- terminals :: Set Name
- defaultOpts :: ReifyOpts
GHCi setup
>>>:set -XTemplateHaskell -XTypeFamilies -XGADTs
Usage
Basic usage
ttReify allows you to build a Tree containing type information for
each field of any given datatype, which can then be examined if you want
to, for example, generate class instances for a deeply nested datatype.
(The idea for this package came about when I was trying to figure out the easiest
way to generate several dozen instances for Cabal's GenericPackageDescription.)
Plain constructors
>>>data Foo a = Foo { field1 :: Either a Int }>>>putStr $(ttDescribe ''Foo)Ghci4.Foo a_0 | `- Data.Either.Either a_0 GHC.Types.Int | +- $a_0 | `- GHC.Types.Int
Passing type arguments
ttReify and friends accept any value with an IsDatatype instance.
>>>putStr $(ttDescribe [t|Maybe Int|])GHC.Base.Maybe GHC.Types.Int | `- GHC.Types.Int
GADTs
>>>data MyGADT a where Con1 :: String -> MyGADT String; Con2 :: Int -> MyGADT [Int]>>>putStr $(ttDescribe ''MyGADT)Ghci10.MyGADT | +- GHC.Base.String | | | `- GHC.Types.[] GHC.Types.Char | | | `- GHC.Types.Char | +- GHC.Base.String | | | `- GHC.Types.[] GHC.Types.Char | | | `- GHC.Types.Char | +- GHC.Types.Int | `- GHC.Types.[] GHC.Types.Int | `- GHC.Types.Int
When reifying GADTs, constructors' return types are treated as another field.
Data/type family instances
>>>class Foo a where data Bar a :: * -> *>>>instance Foo Int where data Bar Int a = IntBar { bar :: Maybe (Int, a) }>>>putStr $(ttDescribe [t|Bar Int|])Ghci14.Bar GHC.Types.Int a_0 | `- GHC.Base.Maybe (GHC.Types.Int, a_0) | `- GHC.Tuple.(,) GHC.Types.Int a_0 | +- GHC.Types.Int | `- $a_0
>>>:module +GHC.Exts>>>putStr $(ttDescribe [t|Item [Int]|])GHC.Exts.Item ([GHC.Types.Int]) | `- GHC.Types.Int
Recursive datatypes
>>>data Foo a = Foo { a :: Either Int (Bar a) }; data Bar b = Bar { b :: Either (Foo b) Int }>>>putStr $(ttDescribe ''Foo)Ghci23.Foo a_0 | `- Data.Either.Either GHC.Types.Int (Ghci23.Bar a_0) | +- GHC.Types.Int | `- Ghci23.Bar a_0 | `- Data.Either.Either (Ghci23.Foo a_0) GHC.Types.Int | +- <recursive Ghci23.Foo a_0> | `- GHC.Types.Int
Passing options
If needed, type-tree allows you to specify that primitive type constructors
should be included in its output.
>>>data Baz = Baz { field :: [Int] }>>>putStr $(ttDescribeOpts defaultOpts { expandPrim = True } ''Baz)Ghci27.Baz | `- GHC.Types.[] GHC.Types.Int | `- GHC.Types.Int | `- GHC.Prim.Int#
Note that the function arrow (->), despite being a primitive type constructor,
will always be included even with , as otherwise you
would never be able to get useful information out of a field with a function type.expandPrim = False
You can also specify a set of names where type-tree should stop descending, if,
for example, you have no desire to see String -> [] -> Char ad nauseam in
your tree.
>>>data Bar = Bar (Either String [String])>>>putStr $(ttDescribeOpts defaultOpts { terminals = S.fromList [''String] } ''Bar)Ghci31.Bar | `- Data.Either.Either GHC.Base.String ([GHC.Base.String]) | +- GHC.Base.String | `- GHC.Types.[] GHC.Base.String | `- GHC.Base.String
Reify input
class IsDatatype a where Source #
Minimal complete definition
Methods
asDatatype :: a -> Q (Binding, [Type]) Source #
Produce binding info and a list of type arguments
Instances
More ergonomic representation of bound and unbound names of things.
Producing trees
ttReify :: IsDatatype t => t -> Q (Tree Leaf) Source #
Build a "type tree" of the given datatype.
Occurrences of a given node after the first will be wrapped in
Recursive and have no children.
ttReifyOpts :: IsDatatype t => ReifyOpts -> t -> Q (Tree Leaf) Source #
ttReify with the provided options.
ttLit :: IsDatatype t => t -> ExpQ Source #
Embed the produced tree as an expression.
Debugging trees
ttDescribe :: IsDatatype t => t -> ExpQ Source #
Produces a string literal representing a type tree. Useful for debugging purposes.
ttDescribeOpts :: IsDatatype t => ReifyOpts -> t -> ExpQ Source #
ttDescribe with the given options.
Building graphs
ttEdges :: IsDatatype t => t -> ExpQ Source #
$(ttEdges ''Foo) :: [((Name,Arity),Key, [Key])]
$(ttEdges ''Foo) produces a list suitable for passing to graphFromEdges.
ttConnComp :: IsDatatype t => t -> ExpQ Source #
Customizing trees
defaultOpts :: ReifyOpts Source #
Default reify options.
defaultOpts = ReifyOpts { expandPrim = False , terminals = mempty }