type-tree-0.1.0.1: Tree representations of datatypes

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.TypeTree

Contents

Synopsis

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 expandPrim = False, as otherwise you would never be able to get useful information out of a field with a function type.

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

asDatatype

Methods

asDatatype :: a -> Q (Binding, [Type]) Source #

Produce binding info and a list of type arguments

data Binding Source #

More ergonomic representation of bound and unbound names of things.

Constructors

Bound

We know this name refers to a specific thing (i.e. it's a constructor)

Fields

Unbound

We don't know what this is (i.e. a type variable)

Fields

Instances

Eq Binding Source # 

Methods

(==) :: Binding -> Binding -> Bool #

(/=) :: Binding -> Binding -> Bool #

Data Binding Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Binding -> c Binding #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Binding #

toConstr :: Binding -> Constr #

dataTypeOf :: Binding -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Binding) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Binding) #

gmapT :: (forall b. Data b => b -> b) -> Binding -> Binding #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Binding -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Binding -> r #

gmapQ :: (forall d. Data d => d -> u) -> Binding -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Binding -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Binding -> m Binding #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Binding -> m Binding #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Binding -> m Binding #

Ord Binding Source # 
Show Binding Source # 

guess :: Name -> Binding Source #

Convenience function.

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.

ttLitOpts :: IsDatatype t => ReifyOpts -> t -> ExpQ Source #

ttLit with provided opts.

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

type Key = (Name, [Type]) Source #

Some type and its arguments, as representable in a graph.

type Arity = Int Source #

Type constructor arity.

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 #

$(ttConnComp ''Foo) :: [SCC (Name, Arity)]

$(ttConnComp ''Foo) produces a topologically sorted list of the strongly connected components of the graph representing Foo.

Customizing trees

data Leaf Source #

Constructors

TypeL (Binding, [Type])

TypeL (name, xs) is a field with type name applied to types xs.

Recursive Leaf

Recursive field.

Instances

Eq Leaf Source # 

Methods

(==) :: Leaf -> Leaf -> Bool #

(/=) :: Leaf -> Leaf -> Bool #

Data Leaf Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Leaf -> c Leaf #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Leaf #

toConstr :: Leaf -> Constr #

dataTypeOf :: Leaf -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Leaf) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Leaf) #

gmapT :: (forall b. Data b => b -> b) -> Leaf -> Leaf #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Leaf -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Leaf -> r #

gmapQ :: (forall d. Data d => d -> u) -> Leaf -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Leaf -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Leaf -> m Leaf #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Leaf -> m Leaf #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Leaf -> m Leaf #

Ord Leaf Source # 

Methods

compare :: Leaf -> Leaf -> Ordering #

(<) :: Leaf -> Leaf -> Bool #

(<=) :: Leaf -> Leaf -> Bool #

(>) :: Leaf -> Leaf -> Bool #

(>=) :: Leaf -> Leaf -> Bool #

max :: Leaf -> Leaf -> Leaf #

min :: Leaf -> Leaf -> Leaf #

Show Leaf Source # 

Methods

showsPrec :: Int -> Leaf -> ShowS #

show :: Leaf -> String #

showList :: [Leaf] -> ShowS #

Lift Leaf Source # 

Methods

lift :: Leaf -> Q Exp #

data ReifyOpts Source #

Constructors

ReifyOpts 

Fields

defaultOpts :: ReifyOpts Source #

Default reify options.

defaultOpts = ReifyOpts
  { expandPrim = False
  , terminals = mempty
  }