th-utilities-0.1.1.1: Collection of useful functions for use with Template Haskell

Safe HaskellNone
LanguageHaskell2010

TH.ReifyDataType

Description

Utilities for reifying simplified datatype info. It omits details that aren't usually relevant to generating instances that work with the datatype. This makes it easier to use TH to derive instances.

Synopsis

Documentation

data DataType Source #

Simplified info about a DataD. Omits deriving, strictness, and kind info.

Constructors

DataType 

Fields

Instances

Eq DataType Source # 
Data DataType Source # 

Methods

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

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

toConstr :: DataType -> Constr #

dataTypeOf :: DataType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DataType Source # 
Show DataType Source # 
Generic DataType Source # 

Associated Types

type Rep DataType :: * -> * #

Methods

from :: DataType -> Rep DataType x #

to :: Rep DataType x -> DataType #

type Rep DataType Source # 

data DataCon Source #

Simplified info about a Con. Omits strictness, and kind info. This is much nicer than consuming Con directly, because it unifies all the constructors into one.

Constructors

DataCon 

Fields

Instances

Eq DataCon Source # 

Methods

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

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

Data DataCon Source # 

Methods

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

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

toConstr :: DataCon -> Constr #

dataTypeOf :: DataCon -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DataCon Source # 
Show DataCon Source # 
Generic DataCon Source # 

Associated Types

type Rep DataCon :: * -> * #

Methods

from :: DataCon -> Rep DataCon x #

to :: Rep DataCon x -> DataCon #

type Rep DataCon Source # 

reifyDataType :: Name -> Q DataType Source #

Reify the given data or newtype declaration, and yields its DataType representation.

conToDataCons :: Con -> [DataCon] Source #

Convert a Con to a list of DataCon. The result is a list because GadtC and RecGadtC can define multiple constructors.

reifyDataTypeSubstituted :: Type -> Q DataType Source #

Like reifyDataType, but takes a Type instead of just the Name of the datatype. It expects a normal datatype argument (see typeToNamedCon).