| Safe Haskell | Trustworthy |
|---|---|
| Language | Haskell2010 |
GHC.Internal.TH.Lift
Contents
Description
This module gives the definition of the Lift class.
This is an internal module. Please import Language.Haskell.TH.Lift, Language.Haskell.TH or Language.Haskell.TH.Syntax instead!
Documentation
class Lift (t :: TYPE r) where Source #
A Lift instance can have any of its values turned into a Template
Haskell expression. This is needed when a value used within a Template
Haskell quotation is bound outside the Oxford brackets ([| ... |] or
[|| ... ||]) but not at the top level. As an example:
add1 :: Int -> Code Q Int add1 x = [|| x + 1 ||]
Template Haskell has no way of knowing what value x will take on at
splice-time, so it requires the type of x to be an instance of Lift.
A Lift instance must satisfy $(lift x) ≡ x and $$(liftTyped x) ≡ x
for all x, where $(...) and $$(...) are Template Haskell splices.
It is additionally expected that .lift x ≡ unTypeCode (liftTyped x)
Lift instances can be derived automatically by use of the -XDeriveLift
GHC language extension:
{-# LANGUAGE DeriveLift #-}
module Foo where
import Language.Haskell.TH.Syntax
data Bar a = Bar1 a (Bar a) | Bar2 String
deriving LiftRepresentation-polymorphic since template-haskell-2.16.0.0.
This is exposed both from the template-haskell-lift and template-haskell packages.
Consider importing it from the more stable template-haskell-lift if you don't need the full breadth of the template-haskell interface.
Minimal complete definition
Methods
lift :: Quote m => t -> m Exp Source #
Turn a value into a Template Haskell expression, suitable for use in a splice.
liftTyped :: forall (m :: Type -> Type). Quote m => t -> Code m t Source #
Turn a value into a Template Haskell typed expression, suitable for use in a typed splice.
Since: template-haskell-2.16.0.0
Instances
| Lift Addr# Source # | Produces an Since: template-haskell-2.16.0.0 |
| Lift Double# Source # | Since: template-haskell-2.16.0.0 |
| Lift Float# Source # | Since: template-haskell-2.16.0.0 |
| Lift Int# Source # | Since: template-haskell-2.16.0.0 |
| Lift Void Source # | Since: template-haskell-2.15.0.0 |
| Lift ForeignSrcLang Source # | Since: template-haskell-2.22.1.0 |
Defined in GHC.Internal.TH.Lift Methods lift :: Quote m => ForeignSrcLang -> m Exp Source # liftTyped :: forall (m :: Type -> Type). Quote m => ForeignSrcLang -> Code m ForeignSrcLang Source # | |
| Lift Int16 Source # | |
| Lift Int32 Source # | |
| Lift Int64 Source # | |
| Lift Int8 Source # | |
| Lift Extension Source # | Since: template-haskell-2.22.1.0 |
| Lift AnnLookup Source # | Since: template-haskell-2.22.1.0 |
| Lift AnnTarget Source # | Since: template-haskell-2.22.1.0 |
| Lift Bang Source # | Since: template-haskell-2.22.1.0 |
| Lift BndrVis Source # | Since: template-haskell-2.22.1.0 |
| Lift Body Source # | Since: template-haskell-2.22.1.0 |
| Lift Bytes Source # | Since: template-haskell-2.22.1.0 |
| Lift Callconv Source # | Since: template-haskell-2.22.1.0 |
| Lift Clause Source # | Since: template-haskell-2.22.1.0 |
| Lift Con Source # | Since: template-haskell-2.22.1.0 |
| Lift Dec Source # | Since: template-haskell-2.22.1.0 |
| Lift DecidedStrictness Source # | Since: template-haskell-2.22.1.0 |
Defined in GHC.Internal.TH.Lift Methods lift :: Quote m => DecidedStrictness -> m Exp Source # liftTyped :: forall (m :: Type -> Type). Quote m => DecidedStrictness -> Code m DecidedStrictness Source # | |
| Lift DerivClause Source # | Since: template-haskell-2.22.1.0 |
Defined in GHC.Internal.TH.Lift Methods lift :: Quote m => DerivClause -> m Exp Source # liftTyped :: forall (m :: Type -> Type). Quote m => DerivClause -> Code m DerivClause Source # | |
| Lift DerivStrategy Source # | Since: template-haskell-2.22.1.0 |
Defined in GHC.Internal.TH.Lift Methods lift :: Quote m => DerivStrategy -> m Exp Source # liftTyped :: forall (m :: Type -> Type). Quote m => DerivStrategy -> Code m DerivStrategy Source # | |
| Lift DocLoc Source # | Since: template-haskell-2.22.1.0 |
| Lift Exp Source # | Since: template-haskell-2.22.1.0 |
| Lift FamilyResultSig Source # | Since: template-haskell-2.22.1.0 |
Defined in GHC.Internal.TH.Lift Methods lift :: Quote m => FamilyResultSig -> m Exp Source # liftTyped :: forall (m :: Type -> Type). Quote m => FamilyResultSig -> Code m FamilyResultSig Source # | |
| Lift Fixity Source # | Since: template-haskell-2.22.1.0 |
| Lift FixityDirection Source # | Since: template-haskell-2.22.1.0 |
Defined in GHC.Internal.TH.Lift Methods lift :: Quote m => FixityDirection -> m Exp Source # liftTyped :: forall (m :: Type -> Type). Quote m => FixityDirection -> Code m FixityDirection Source # | |
| Lift Foreign Source # | Since: template-haskell-2.22.1.0 |
| Lift FunDep Source # | Since: template-haskell-2.22.1.0 |
| Lift Guard Source # | Since: template-haskell-2.22.1.0 |
| Lift Info Source # | Since: template-haskell-2.22.1.0 |
| Lift InjectivityAnn Source # | Since: template-haskell-2.22.1.0 |
Defined in GHC.Internal.TH.Lift Methods lift :: Quote m => InjectivityAnn -> m Exp Source # liftTyped :: forall (m :: Type -> Type). Quote m => InjectivityAnn -> Code m InjectivityAnn Source # | |
| Lift Inline Source # | Since: template-haskell-2.22.1.0 |
| Lift Lit Source # | Since: template-haskell-2.22.1.0 |
| Lift Loc Source # | Since: template-haskell-2.22.1.0 |
| Lift Match Source # | Since: template-haskell-2.22.1.0 |
| Lift ModName Source # | Since: template-haskell-2.22.1.0 |
| Lift Module Source # | Since: template-haskell-2.22.1.0 |
| Lift Name Source # | Since: template-haskell-2.22.1.0 |
| Lift NameFlavour Source # | Since: template-haskell-2.22.1.0 |
Defined in GHC.Internal.TH.Lift Methods lift :: Quote m => NameFlavour -> m Exp Source # liftTyped :: forall (m :: Type -> Type). Quote m => NameFlavour -> Code m NameFlavour Source # | |
| Lift NameIs Source # | Since: template-haskell-2.22.1.0 |
| Lift NameSpace Source # | Since: template-haskell-2.22.1.0 |
| Lift NamespaceSpecifier Source # | Since: template-haskell-2.22.1.0 |
Defined in GHC.Internal.TH.Lift Methods lift :: Quote m => NamespaceSpecifier -> m Exp Source # liftTyped :: forall (m :: Type -> Type). Quote m => NamespaceSpecifier -> Code m NamespaceSpecifier Source # | |
| Lift OccName Source # | Since: template-haskell-2.22.1.0 |
| Lift Overlap Source # | Since: template-haskell-2.22.1.0 |
| Lift Pat Source # | Since: template-haskell-2.22.1.0 |
| Lift PatSynArgs Source # | Since: template-haskell-2.22.1.0 |
Defined in GHC.Internal.TH.Lift Methods lift :: Quote m => PatSynArgs -> m Exp Source # liftTyped :: forall (m :: Type -> Type). Quote m => PatSynArgs -> Code m PatSynArgs Source # | |
| Lift PatSynDir Source # | Since: template-haskell-2.22.1.0 |
| Lift Phases Source # | Since: template-haskell-2.22.1.0 |
| Lift PkgName Source # | Since: template-haskell-2.22.1.0 |
| Lift Pragma Source # | Since: template-haskell-2.22.1.0 |
| Lift Range Source # | Since: template-haskell-2.22.1.0 |
| Lift Role Source # | Since: template-haskell-2.22.1.0 |
| Lift RuleBndr Source # | Since: template-haskell-2.22.1.0 |
| Lift RuleMatch Source # | Since: template-haskell-2.22.1.0 |
| Lift Safety Source # | Since: template-haskell-2.22.1.0 |
| Lift SourceStrictness Source # | Since: template-haskell-2.22.1.0 |
Defined in GHC.Internal.TH.Lift Methods lift :: Quote m => SourceStrictness -> m Exp Source # liftTyped :: forall (m :: Type -> Type). Quote m => SourceStrictness -> Code m SourceStrictness Source # | |
| Lift SourceUnpackedness Source # | Since: template-haskell-2.22.1.0 |
Defined in GHC.Internal.TH.Lift Methods lift :: Quote m => SourceUnpackedness -> m Exp Source # liftTyped :: forall (m :: Type -> Type). Quote m => SourceUnpackedness -> Code m SourceUnpackedness Source # | |
| Lift Specificity Source # | Since: template-haskell-2.22.1.0 |
Defined in GHC.Internal.TH.Lift Methods lift :: Quote m => Specificity -> m Exp Source # liftTyped :: forall (m :: Type -> Type). Quote m => Specificity -> Code m Specificity Source # | |
| Lift Stmt Source # | Since: template-haskell-2.22.1.0 |
| Lift TyLit Source # | Since: template-haskell-2.22.1.0 |
| Lift TySynEqn Source # | Since: template-haskell-2.22.1.0 |
| Lift Type Source # | Since: template-haskell-2.22.1.0 |
| Lift TypeFamilyHead Source # | Since: template-haskell-2.22.1.0 |
Defined in GHC.Internal.TH.Lift Methods lift :: Quote m => TypeFamilyHead -> m Exp Source # liftTyped :: forall (m :: Type -> Type). Quote m => TypeFamilyHead -> Code m TypeFamilyHead Source # | |
| Lift Word16 Source # | |
| Lift Word32 Source # | |
| Lift Word64 Source # | |
| Lift Word8 Source # | |
| Lift Integer Source # | |
| Lift Natural Source # | |
| Lift () Source # | |
| Lift Bool Source # | |
| Lift Char Source # | |
| Lift Double Source # | |
| Lift Float Source # | |
| Lift Int Source # | |
| Lift Word Source # | |
| Lift Char# Source # | Since: template-haskell-2.16.0.0 |
| Lift Word# Source # | Since: template-haskell-2.16.0.0 |
| Lift (# #) Source # | Since: template-haskell-2.16.0.0 |
| Lift a => Lift (NonEmpty a :: Type) Source # | Since: template-haskell-2.15.0.0 |
| Integral a => Lift (Ratio a :: Type) Source # | |
| Lift a => Lift (TyVarBndr a :: Type) Source # | Since: template-haskell-2.22.1.0 |
| Lift a => Lift (Maybe a :: Type) Source # | |
| Lift a => Lift ([a] :: Type) Source # | |
| (Lift a, Lift b) => Lift (Either a b :: Type) Source # | |
| Lift (TExp a :: Type) Source # | Since: template-haskell-2.22.1.0 |
| (Lift a, Lift b) => Lift ((a, b) :: Type) Source # | |
| (Lift a, Lift b, Lift c) => Lift ((a, b, c) :: Type) Source # | |
| (Lift a, Lift b, Lift c, Lift d) => Lift ((a, b, c, d) :: Type) Source # | |
| (Lift a, Lift b, Lift c, Lift d, Lift e) => Lift ((a, b, c, d, e) :: Type) Source # | |
| (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) => Lift ((a, b, c, d, e, f) :: Type) Source # | |
| (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) => Lift ((a, b, c, d, e, f, g) :: Type) Source # | |