| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Language.Haskell.TH.Lift
Contents
Documentation
deriveLift' :: [Role] -> Info -> Q [Dec] Source #
Obtain Info values through a custom reification function. This is useful
when generating instances for datatypes that have not yet been declared.
makeLift :: Name -> Q Exp Source #
Generates a lambda expresson which behaves like lift (without requiring
a Lift instance). Example:
newtype Fix f = In { out :: f (Fix f) }
instance Lift (f (Fix f)) => Lift (Fix f) where
lift = $(makeLift ''Fix)
This can be useful when deriveLift is not clever enough to infer the
correct instance context, such as in the example above.
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 ([| ... |]) but not
at the top level. As an example:
add1 :: Int -> Q Exp 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 for all x, where $(...)
is a Template Haskell splice.
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 LiftMinimal complete definition
Nothing
Methods
Turn a value into a Template Haskell expression, suitable for use in a splice.