Safe Haskell | None |
---|---|
Language | Haskell2010 |
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.
The "Simple" in the module name refers to the simplicity of the datatypes, not the module itself, which exports quite a few things which are useful in some circumstance or another. I anticipate that the most common uses of this will be the following APIs:
- Getting info about a
data
ornewtype
declaration, viaDataType
,reifyDataType
, andDataCon
. This is useful for writing something which generates declarations based on a datatype, one of the most common uses of Template Haskell. - Getting nicely structured info about a named type. See
TypeInfo
andreifyType
. This does not yet support reifying typeclasses, primitive type constructors, or type variables (TyVarI
).
Currently, this module supports reifying simplified versions of the
following Info
constructors:
TyConI
withDataD
andNewtypeD
(becomes aDataType
value)FamilyI
becomes aDataFamily
orTypeFamily
value.DataConI
becomes aDataCon
value.
In the future it will hopefully also have support for the remaining
Info
constructors, ClassI
, ClassOpI
, PrimTyConI
, VarI
, and
TyVarI
.
Synopsis
- data TypeInfo
- reifyType :: Name -> Q TypeInfo
- infoToType :: Info -> Q (Maybe TypeInfo)
- reifyTypeNoDataKinds :: Name -> Q (Maybe TypeInfo)
- infoToTypeNoDataKinds :: Info -> Maybe TypeInfo
- data DataType = DataType {}
- reifyDataType :: Name -> Q DataType
- infoToDataType :: Info -> Maybe DataType
- data DataCon = DataCon {}
- reifyDataCon :: Name -> Q DataCon
- infoToDataCon :: Info -> Maybe DataCon
- typeToDataCon :: Name -> Type -> DataCon
- data DataFamily = DataFamily {}
- data DataInst = DataInst {}
- reifyDataFamily :: Name -> Q DataFamily
- infoToDataFamily :: Info -> Maybe DataFamily
- data TypeFamily = TypeFamily {}
- data TypeInst = TypeInst {}
- reifyTypeFamily :: Name -> Q TypeFamily
- infoToTypeFamily :: Info -> Maybe TypeFamily
- conToDataCons :: Con -> [DataCon]
- reifyDataTypeSubstituted :: Type -> Q DataType
Reifying simplified type info
reifyTypeNoDataKinds :: Name -> Q (Maybe TypeInfo) Source #
Reifies type info, but instead of yielding a LiftedDataConInfo
,
will instead yield Nothing
.
Reifying simplified info for specific declaration varieties
Datatype info
Simplified info about a DataD
. Omits deriving, strictness,
kind info, and whether it's data
or newtype
.
Instances
Eq DataType Source # | |
Data DataType Source # | |
Defined in TH.ReifySimple 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 -> DataType0 # 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 # | |
Defined in TH.ReifySimple | |
Show DataType Source # | |
Generic DataType Source # | |
type Rep DataType Source # | |
Defined in TH.ReifySimple type Rep DataType = D1 (MetaData "DataType" "TH.ReifySimple" "th-utilities-0.2.4.0-6lJFZoHl3Jv4IrMAsgWvtt" False) (C1 (MetaCons "DataType" PrefixI True) ((S1 (MetaSel (Just "dtName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name) :*: S1 (MetaSel (Just "dtTvs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Name])) :*: (S1 (MetaSel (Just "dtCxt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Cxt) :*: S1 (MetaSel (Just "dtCons") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [DataCon])))) |
reifyDataType :: Name -> Q DataType Source #
Reify the given data or newtype declaration, and yields its
DataType
representation.
Data constructor info
Simplified info about a Con
. Omits deriving, strictness, and kind
info. This is much nicer than consuming Con
directly, because it
unifies all the constructors into one.
Instances
Eq DataCon Source # | |
Data DataCon Source # | |
Defined in TH.ReifySimple 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 # | |
type Rep DataCon Source # | |
Defined in TH.ReifySimple type Rep DataCon = D1 (MetaData "DataCon" "TH.ReifySimple" "th-utilities-0.2.4.0-6lJFZoHl3Jv4IrMAsgWvtt" False) (C1 (MetaCons "DataCon" PrefixI True) ((S1 (MetaSel (Just "dcName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name) :*: S1 (MetaSel (Just "dcTvs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Name])) :*: (S1 (MetaSel (Just "dcCxt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Cxt) :*: S1 (MetaSel (Just "dcFields") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(Maybe Name, Type)])))) |
Data family info
data DataFamily Source #
Simplified info about a data family. Omits deriving, strictness, and kind info.
Instances
Simplified info about a data family instance. Omits deriving, strictness, and kind info.
Instances
Eq DataInst Source # | |
Data DataInst Source # | |
Defined in TH.ReifySimple gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataInst -> c DataInst # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DataInst # toConstr :: DataInst -> Constr # dataTypeOf :: DataInst -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DataInst) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DataInst) # gmapT :: (forall b. Data b => b -> b) -> DataInst -> DataInst # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataInst -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataInst -> r # gmapQ :: (forall d. Data d => d -> u) -> DataInst -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DataInst -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataInst -> m DataInst # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataInst -> m DataInst # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataInst -> m DataInst # | |
Ord DataInst Source # | |
Defined in TH.ReifySimple | |
Show DataInst Source # | |
Generic DataInst Source # | |
type Rep DataInst Source # | |
Defined in TH.ReifySimple type Rep DataInst = D1 (MetaData "DataInst" "TH.ReifySimple" "th-utilities-0.2.4.0-6lJFZoHl3Jv4IrMAsgWvtt" False) (C1 (MetaCons "DataInst" PrefixI True) ((S1 (MetaSel (Just "diName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name) :*: S1 (MetaSel (Just "diCxt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Cxt)) :*: (S1 (MetaSel (Just "diParams") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Type]) :*: S1 (MetaSel (Just "diCons") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [DataCon])))) |
reifyDataFamily :: Name -> Q DataFamily Source #
Reify the given data family, and yield its DataFamily
representation.
infoToDataFamily :: Info -> Maybe DataFamily Source #
Type family info
data TypeFamily Source #
Simplified info about a type family. Omits kind info and injectivity info.
Instances
Simplified info about a type family instance. Omits nothing.
Instances
Eq TypeInst Source # | |
Data TypeInst Source # | |
Defined in TH.ReifySimple gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TypeInst -> c TypeInst # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TypeInst # toConstr :: TypeInst -> Constr # dataTypeOf :: TypeInst -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TypeInst) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TypeInst) # gmapT :: (forall b. Data b => b -> b) -> TypeInst -> TypeInst # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TypeInst -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TypeInst -> r # gmapQ :: (forall d. Data d => d -> u) -> TypeInst -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TypeInst -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypeInst -> m TypeInst # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeInst -> m TypeInst # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeInst -> m TypeInst # | |
Ord TypeInst Source # | |
Defined in TH.ReifySimple | |
Show TypeInst Source # | |
Generic TypeInst Source # | |
type Rep TypeInst Source # | |
Defined in TH.ReifySimple type Rep TypeInst = D1 (MetaData "TypeInst" "TH.ReifySimple" "th-utilities-0.2.4.0-6lJFZoHl3Jv4IrMAsgWvtt" False) (C1 (MetaCons "TypeInst" PrefixI True) (S1 (MetaSel (Just "tiName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name) :*: (S1 (MetaSel (Just "tiParams") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Type]) :*: S1 (MetaSel (Just "tiType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)))) |
reifyTypeFamily :: Name -> Q TypeFamily Source #
Reify the given type family instance declaration, and yields its
TypeInst
representation.
infoToTypeFamily :: Info -> Maybe TypeFamily Source #
Other utilities
conToDataCons :: Con -> [DataCon] Source #
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
).