type-tree-0.2.0.1: Tree representations of datatypes

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.TypeTree

Contents

Synopsis

GHCi setup

>>> :set -XTemplateHaskell -XGADTs -XTypeFamilies

Usage

type-tree provides a way to build tree structures from datatypes.

Basic usage

>>> data Foo a = Foo { field1 :: a, field2 :: Either String Int }
>>> putStr $(ttDescribe ''Foo)
Foo :: * -> *
|
+- Either :: * -> * -> *
|
+- [] :: * -> *
|  |
|  `- ...[] :: * -> *
|
+- Char :: *
|
`- Int :: *

ttReify passes through type synonyms by default:

>>> putStr $(ttDescribe ''FilePath) -- FilePath --> String --> [Char]
[] :: * -> *
|
`- ...[] :: * -> *

Char :: *

but this behavior can be disabled:

>>> putStr $(ttDescribeOpts defaultOpts { synonyms = True } ''FilePath)
FilePath :: *
|
`- String :: *
   |
   +- [] :: * -> *
   |  |
   |  `- ...[] :: * -> *
   |
   `- Char :: *

data ReifyOpts Source #

Constructors

ReifyOpts 

Fields

  • stop :: Set Name

    If a name in this set is encountered, stop recursing.

  • prim :: Bool

    Expand primitive type constructors (i.e. IntInt#)?

  • synonyms :: Bool

    If True, type synonyms are present in the resulting Forest; if False, a synonym will be expanded and its RHS will appear in the out-list instead.

defaultOpts :: ReifyOpts Source #

defaultOpts = ReifyOpts
  { stop = S.fromList []
  , prim = False
  , synonyms = False
  }

Building trees

ttReifyOpts :: IsDatatype a => ReifyOpts -> a -> Q (Forest Leaf) Source #

Build a Forest of constructor names contained in the given type.

ttReify :: IsDatatype a => a -> Q (Forest Leaf) Source #

ttReifyOpts with default options.

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

Embed the produced Forest as an expression.

ttLit :: IsDatatype a => a -> ExpQ Source #

ttLitOpts with default options.

ttDescribeOpts :: IsDatatype a => ReifyOpts -> a -> ExpQ Source #

Produce a string representation of the forest generated by $(ttReifyOpts opts ''SomeName). Useful for debugging purposes.

ttDescribe :: IsDatatype a => a -> ExpQ Source #

ttDescribeOpts with default options.

Graph utilities

ttConnCompOpts :: IsDatatype a => ReifyOpts -> a -> ExpQ Source #

ttConnCompOpts is useful for the usecase which I had in mind when I originally wrote this package, namely:

Given some datatype, I need a topologically sorted list of all types contained in that datatype for which an instance of some class must be defined if I wish to define an instance for that datatype (and likewise for each subtype, etc.)

Here's an example using CondTree, which is a useful datatype for an example, as it's both mutually recursive and refers to other recursive types.

>>> :m +Language.Haskell.TypeTree.ExampleDatatypes
>>> mapM_ print $(ttConnComp ''CondTree)
AcyclicSCC ([] :: * -> *,[])
AcyclicSCC (Bool :: *,[])
AcyclicSCC (Condition :: * -> *,[Bool :: *])
AcyclicSCC (Maybe :: * -> *,[])
CyclicSCC [(CondBranch :: * -> * -> * -> *,[Condition :: * -> *,CondTree :: * -> * -> * -> *,Maybe :: * -> *]),(CondTree :: * -> * -> * -> *,[[] :: * -> *,CondBranch :: * -> * -> * -> *])]

ttConnComp :: IsDatatype a => a -> ExpQ Source #

ttConnCompOpts with default opts

Datatypes

data Leaf Source #

Constructors

TypeL Name Arity

TypeL name arr represents the type constructor name, which has arity arr.

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 #

class IsDatatype a where Source #

Minimal complete definition

asDatatype

Methods

asDatatype :: a -> Q [Name] Source #

Produce a list of constructor names