Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
LiftType
Description
Template Haskell has a class Lift
that allows you to promote values
from Haskell-land into the land of metaprogramming - Q
.
classLift
a wherelift
:: a ->Q
Exp
liftTyped
:: a ->Q
(TExp
a)
However, there wasn't a way to promote a *type* into a
.Q
Type
This library provides exactly that function. It requires a Typeable
constraint, but this is automatically satisfied by GHC.
Since: 0.1.0.0
Synopsis
- liftType :: forall t. Typeable t => Type
- liftTypeQ :: forall t. Typeable t => Q Type
- typeRepToType :: SomeTypeRep -> Type
- tyConToName :: TyCon -> TypeOrDataName
- typeToName :: forall t. Typeable t => TypeOrDataName
- data TypeOrDataName
- getTypeOrDataName :: TypeOrDataName -> Name
Documentation
liftType :: forall t. Typeable t => Type Source #
Convert a type argument into a Template Haskell Type
.
Use with TypeApplications
.
Example:
>>> :set -XTypeApplications >>> liftType @Bool ConT GHC.Types.Bool >>> liftType @[Char] AppT (ConT GHC.Types.[]) (ConT GHC.Types.Char)
This works with data kinds, too.
>>> :set -XDataKinds >>> liftType @3 LitT (NumTyLit 3) >>> liftType @"hello" LitT (StrTyLit "hello") >>> liftType @'[Int, Char] AppT (AppT (PromotedT GHC.Types.:) (ConT GHC.Types.Int)) (AppT (AppT (PromotedT GHC.Types.:) (ConT GHC.Types.Char)) (PromotedT GHC.Types.[])) >>> liftType @'(Int, Char) AppT (AppT (PromotedT GHC.Tuple.(,)) (ConT GHC.Types.Int)) (ConT GHC.Types.Char)
Since: 0.1.0.0
typeRepToType :: SomeTypeRep -> Type Source #
Promote a SomeTypeRep
into a Type
.
Since: 0.1.1.0
tyConToName :: TyCon -> TypeOrDataName Source #
Extract the TypeOrDataName
from a TyCon
. You probably want to use
typeToName
instead. See that function for documentation and more
information.
Since: 0.1.2.0
typeToName :: forall t. Typeable t => TypeOrDataName Source #
This function returns the name of the outermost type constructor.
>>>
typeToName @Char
TypeName ''Char>>>
typeToName @Maybe
TypeName ''Maybe>>>
typeToName @(Maybe Char)
TypeName ''Maybe>>>
typeToName @(Int -> Char)
TypeName ''(->)>>>
typeToName @'False
PromotedDataName 'False
Since: 0.1.2.0
data TypeOrDataName Source #
It's possible to use a data constructor with a DataKinds
promotion.
This disambiguates where the name comes from.
Since: 0.1.2.0
Constructors
TypeName Name | |
PromotedDataName Name |
Instances
Show TypeOrDataName Source # | |
Defined in LiftType Methods showsPrec :: Int -> TypeOrDataName -> ShowS # show :: TypeOrDataName -> String # showList :: [TypeOrDataName] -> ShowS # | |
Eq TypeOrDataName Source # | |
Defined in LiftType Methods (==) :: TypeOrDataName -> TypeOrDataName -> Bool # (/=) :: TypeOrDataName -> TypeOrDataName -> Bool # |
getTypeOrDataName :: TypeOrDataName -> Name Source #
Retrieve the Name
from a TypeOrDataName
, forgetting how it was
parsed.
Since: 0.1.2.0