Safe Haskell | None |
---|---|
Language | Haskell98 |
Documentation
deriveLift' :: 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.
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
.
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 Lift
Lift Bool | |
Lift Char | |
Lift Double | |
Lift Float | |
Lift Int | |
Lift Int8 | |
Lift Int16 | |
Lift Int32 | |
Lift Int64 | |
Lift Integer | |
Lift Natural | |
Lift Word | |
Lift Word8 | |
Lift Word16 | |
Lift Word32 | |
Lift Word64 | |
Lift () | |
Lift a => Lift [a] | |
Lift a => Lift (Maybe a) | |
Integral a => Lift (Ratio a) | |
(Lift a, Lift b) => Lift (Either a b) | |
(Lift a, Lift b) => Lift (a, b) | |
(Lift a, Lift b, Lift c) => Lift (a, b, c) | |
(Lift a, Lift b, Lift c, Lift d) => Lift (a, b, c, d) | |
(Lift a, Lift b, Lift c, Lift d, Lift e) => Lift (a, b, c, d, e) | |
(Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) => Lift (a, b, c, d, e, f) | |
(Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) => Lift (a, b, c, d, e, f, g) | |