th-lift-0.7.6: Derive Template Haskell's Lift class for datatypes.

Safe HaskellNone
LanguageHaskell98

Language.Haskell.TH.Lift

Contents

Synopsis

Documentation

deriveLift :: Name -> Q [Dec] #

Derive Lift instances for the given datatype.

deriveLiftMany :: [Name] -> Q [Dec] #

Derive Lift instances for many datatypes.

deriveLift' :: Info -> Q [Dec] #

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 #

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)

makeLift' :: Info -> Q Exp #

Like makeLift, but using a custom reification function.

class Lift t where #

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

Methods

lift :: t -> Q Exp #

Turn a value into a Template Haskell expression, suitable for use in a splice.

Instances

Lift Bool 

Methods

lift :: Bool -> Q Exp #

Lift Char 

Methods

lift :: Char -> Q Exp #

Lift Double 

Methods

lift :: Double -> Q Exp #

Lift Float 

Methods

lift :: Float -> Q Exp #

Lift Int 

Methods

lift :: Int -> Q Exp #

Lift Int8 

Methods

lift :: Int8 -> Q Exp #

Lift Int16 

Methods

lift :: Int16 -> Q Exp #

Lift Int32 

Methods

lift :: Int32 -> Q Exp #

Lift Int64 

Methods

lift :: Int64 -> Q Exp #

Lift Integer 

Methods

lift :: Integer -> Q Exp #

Lift Word 

Methods

lift :: Word -> Q Exp #

Lift Word8 

Methods

lift :: Word8 -> Q Exp #

Lift Word16 

Methods

lift :: Word16 -> Q Exp #

Lift Word32 

Methods

lift :: Word32 -> Q Exp #

Lift Word64 

Methods

lift :: Word64 -> Q Exp #

Lift () 

Methods

lift :: () -> Q Exp #

Lift Natural 

Methods

lift :: Natural -> Q Exp #

Lift a => Lift [a] 

Methods

lift :: [a] -> Q Exp #

Lift a => Lift (Maybe a) 

Methods

lift :: Maybe a -> Q Exp #

Integral a => Lift (Ratio a) 

Methods

lift :: Ratio a -> Q Exp #

(Lift a, Lift b) => Lift (Either a b) 

Methods

lift :: Either a b -> Q Exp #

(Lift a, Lift b) => Lift (a, b) 

Methods

lift :: (a, b) -> Q Exp #

(Lift a, Lift b, Lift c) => Lift (a, b, c) 

Methods

lift :: (a, b, c) -> Q Exp #

(Lift a, Lift b, Lift c, Lift d) => Lift (a, b, c, d) 

Methods

lift :: (a, b, c, d) -> Q Exp #

(Lift a, Lift b, Lift c, Lift d, Lift e) => Lift (a, b, c, d, e) 

Methods

lift :: (a, b, c, d, e) -> Q Exp #

(Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) => Lift (a, b, c, d, e, f) 

Methods

lift :: (a, b, c, d, e, f) -> Q Exp #

(Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) => Lift (a, b, c, d, e, f, g) 

Methods

lift :: (a, b, c, d, e, f, g) -> Q Exp #

Orphan instances

Lift Name # 

Methods

lift :: Name -> Q Exp #

Lift ModName # 

Methods

lift :: ModName -> Q Exp #

Lift PkgName # 

Methods

lift :: PkgName -> Q Exp #

Lift OccName # 

Methods

lift :: OccName -> Q Exp #

Lift NameFlavour # 

Methods

lift :: NameFlavour -> Q Exp #

Lift NameSpace # 

Methods

lift :: NameSpace -> Q Exp #