th-typegraph-0.35.1: Graph of the subtype relation

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.TH.TypeGraph.Vertex

Synopsis

Documentation

class TypeGraphVertex v where Source #

Minimal complete definition

typeNames, bestType

Methods

typeNames :: v -> Set Name Source #

Return the set of Name of a type's synonyms, plus the name (if any) used in its data declaration. Note that this might return the empty set.

bestType :: v -> Type Source #

data TGV' Source #

A vertex of the type graph. Includes a type and (optionally) what field of a parent type holds that type. This allows special treatment of a type depending on the type that contains it.

Constructors

TGV' 

Fields

Instances

Eq TGV' Source # 

Methods

(==) :: TGV' -> TGV' -> Bool #

(/=) :: TGV' -> TGV' -> Bool #

Data TGV' Source # 

Methods

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

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

toConstr :: TGV' -> Constr #

dataTypeOf :: TGV' -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TGV' Source # 

Methods

compare :: TGV' -> TGV' -> Ordering #

(<) :: TGV' -> TGV' -> Bool #

(<=) :: TGV' -> TGV' -> Bool #

(>) :: TGV' -> TGV' -> Bool #

(>=) :: TGV' -> TGV' -> Bool #

max :: TGV' -> TGV' -> TGV' #

min :: TGV' -> TGV' -> TGV' #

Show TGV' Source # 

Methods

showsPrec :: Int -> TGV' -> ShowS #

show :: TGV' -> String #

showList :: [TGV'] -> ShowS #

Lift TGV' Source # 

Methods

lift :: TGV' -> Q Exp #

Ppr TGV Source # 

Methods

ppr :: TGV -> Doc #

ppr_list :: [TGV] -> Doc #

Ppr TGV' Source # 

Methods

ppr :: TGV' -> Doc #

ppr_list :: [TGV'] -> Doc #

TypeGraphVertex TGV Source # 
TypeGraphVertex TGV' Source # 
HasTGV TGV Source # 

Methods

asTGV :: TGV -> TGV' Source #

Ppr (Map TGV' (Set TGV')) Source # 

Methods

ppr :: Map TGV' (Set TGV') -> Doc #

ppr_list :: [Map TGV' (Set TGV')] -> Doc #

Ppr ((), TGV', [TGV']) Source # 

Methods

ppr :: ((), TGV', [TGV']) -> Doc #

ppr_list :: [((), TGV', [TGV'])] -> Doc #

type TGV = (Vertex, TGV') Source #

data TGVSimple' Source #

For simple type graphs where no parent field information is required.

Constructors

TGVSimple' 

Fields

Instances

Eq TGVSimple' Source # 
Data TGVSimple' Source # 

Methods

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

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

toConstr :: TGVSimple' -> Constr #

dataTypeOf :: TGVSimple' -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TGVSimple' Source # 
Show TGVSimple' Source # 
Lift TGVSimple' Source # 

Methods

lift :: TGVSimple' -> Q Exp #

Ppr TGVSimple Source # 

Methods

ppr :: TGVSimple -> Doc #

ppr_list :: [TGVSimple] -> Doc #

Ppr TGVSimple' Source # 

Methods

ppr :: TGVSimple' -> Doc #

ppr_list :: [TGVSimple'] -> Doc #

TypeGraphVertex TGVSimple Source # 
TypeGraphVertex TGVSimple' Source # 
HasTGVSimple TGVSimple Source # 
Ppr (Map TGVSimple' (Set TGVSimple')) Source # 
Ppr ((), TGVSimple', [TGVSimple']) Source # 

Methods

ppr :: ((), TGVSimple', [TGVSimple']) -> Doc #

ppr_list :: [((), TGVSimple', [TGVSimple'])] -> Doc #