lift-generics-0.3: GHC.Generics-based Language.Haskell.TH.Syntax.lift implementation
Copyright(C) 2015-2017 Ryan Scott
LicenseBSD-style (see the file LICENSE)
MaintainerRyan Scott
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.Haskell.TH.Lift.Generics

Contents

Description

GHC.Generics-based approach to implementing lift.

Synopsis

GHC.Generics-based lift implementations

These functions leverage GHC.Generics to automatically implement lift implementations. These serve as Generic-based alternatives to DeriveLift. Here is an example of how to use them:

{-# LANGUAGE DeriveGeneric #-}
module Foo where

import GHC.Generics
import Language.Haskell.Lift.Generics

data Foo = Foo Int Char String
  deriving Generic

instance Lift Foo where
  lift = genericLift
#if MIN_VERSION_template_haskell(2,9,0)
  liftTyped = genericLiftTypedCompat
#endif

Now you can splice Foo values directly into Haskell source code:

{-# LANGUAGE TemplateHaskell #-}
module Bar where

import Foo
import Language.Haskell.TH.Syntax

foo :: Foo
foo = $(lift (Foo 1 'a' "baz"))

genericLift :: (Quote m, Generic a, GLift (Rep a)) => a -> m Exp Source #

Produce a generic definition of lift.

genericLiftTyped :: (Quote m, Generic a, GLift (Rep a)) => a -> Code m a Source #

Like genericLift, but returns a Code instead of an Exp.

genericLiftTypedTExp :: (Quote m, Generic a, GLift (Rep a)) => a -> m (TExp a) Source #

Like genericLift, but returns a TExp instead of an Exp.

genericLiftTypedCompat :: (Quote m, Generic a, GLift (Rep a)) => a -> Splice m a Source #

Lift genericLift, but returns:

  • A Code (if using template-haskell-2.17.0.0 or later), or
  • A TExp (if using an older version of template-haskell)

This function is ideal for implementing the liftTyped method of Lift directly, as its type changed in template-haskell-2.17.0.0.

Generic classes

You shouldn't need to use any of these classes directly; they are only exported for educational purposes.

class GLift f where Source #

Class of generic representation types which can be converted to Template Haskell expressions.

Methods

glift Source #

Arguments

:: Quote m 
=> f a

The generic value

-> m Exp

The resulting Template Haskell expression

Instances

Instances details
(Datatype d, GLiftDatatype f) => GLift (D1 d f) Source # 
Instance details

Defined in Language.Haskell.TH.Lift.Generics

Methods

glift :: Quote m => D1 d f a -> m Exp Source #

class GLiftDatatype f where Source #

Class of generic representation types which can be converted to Template Haskell expressions, given a package and module name.

Methods

gliftWith Source #

Arguments

:: Quote m 
=> String

The package name

-> String

The module name

-> f a

The generic value

-> m Exp

The resulting Template Haskell expression

Instances

Instances details
GLiftDatatype (V1 :: Type -> Type) Source # 
Instance details

Defined in Language.Haskell.TH.Lift.Generics

Methods

gliftWith :: Quote m => String -> String -> V1 a -> m Exp Source #

(GLiftDatatype f, GLiftDatatype g) => GLiftDatatype (f :+: g) Source # 
Instance details

Defined in Language.Haskell.TH.Lift.Generics

Methods

gliftWith :: Quote m => String -> String -> (f :+: g) a -> m Exp Source #

(Constructor c, GLiftArgs f) => GLiftDatatype (C1 c f) Source # 
Instance details

Defined in Language.Haskell.TH.Lift.Generics

Methods

gliftWith :: Quote m => String -> String -> C1 c f a -> m Exp Source #

class GLiftArgs f where Source #

Class of generic representation types which can conceptually be converted to a list of Template Haskell expressions (which represent a constructors' arguments).

Methods

gliftArgs :: Quote m => f a -> Exp -> m Exp Source #

gliftArgs e f applies f to the zero or more arguments represented by e.

Instances

Instances details
GLiftArgs (U1 :: Type -> Type) Source # 
Instance details

Defined in Language.Haskell.TH.Lift.Generics

Methods

gliftArgs :: Quote m => U1 a -> Exp -> m Exp Source #

GLiftArgs (UAddr :: Type -> Type) Source # 
Instance details

Defined in Language.Haskell.TH.Lift.Generics

Methods

gliftArgs :: Quote m => UAddr a -> Exp -> m Exp Source #

GLiftArgs (UChar :: Type -> Type) Source # 
Instance details

Defined in Language.Haskell.TH.Lift.Generics

Methods

gliftArgs :: Quote m => UChar a -> Exp -> m Exp Source #

GLiftArgs (UDouble :: Type -> Type) Source # 
Instance details

Defined in Language.Haskell.TH.Lift.Generics

Methods

gliftArgs :: Quote m => UDouble a -> Exp -> m Exp Source #

GLiftArgs (UFloat :: Type -> Type) Source # 
Instance details

Defined in Language.Haskell.TH.Lift.Generics

Methods

gliftArgs :: Quote m => UFloat a -> Exp -> m Exp Source #

GLiftArgs (UInt :: Type -> Type) Source # 
Instance details

Defined in Language.Haskell.TH.Lift.Generics

Methods

gliftArgs :: Quote m => UInt a -> Exp -> m Exp Source #

GLiftArgs (UWord :: Type -> Type) Source # 
Instance details

Defined in Language.Haskell.TH.Lift.Generics

Methods

gliftArgs :: Quote m => UWord a -> Exp -> m Exp Source #

(GLiftArgs f, GLiftArgs g) => GLiftArgs (f :*: g) Source # 
Instance details

Defined in Language.Haskell.TH.Lift.Generics

Methods

gliftArgs :: Quote m => (f :*: g) a -> Exp -> m Exp Source #

Lift c => GLiftArgs (K1 i c :: Type -> Type) Source # 
Instance details

Defined in Language.Haskell.TH.Lift.Generics

Methods

gliftArgs :: Quote m => K1 i c a -> Exp -> m Exp Source #

GLiftArgs f => GLiftArgs (S1 s f) Source # 
Instance details

Defined in Language.Haskell.TH.Lift.Generics

Methods

gliftArgs :: Quote m => S1 s f a -> Exp -> m Exp Source #

Lift reexport

class Lift (t :: TYPE r) 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 ([| ... |] or [|| ... ||]) but not at the top level. As an example:

add1 :: Int -> Q (TExp 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 ≡ unTypeQ (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 Lift

Representation-polymorphic since template-haskell-2.16.0.0.

Minimal complete definition

liftTyped

Methods

lift :: Quote m => t -> m Exp #

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 #

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

Since: template-haskell-2.16.0.0

Instances

Instances details
Lift Addr#

Produces an Addr# literal from the NUL-terminated C-string starting at the given memory address.

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Addr# -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Addr# -> Code m Addr# #

Lift Double#

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Double# -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Double# -> Code m Double# #

Lift Float#

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Float# -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Float# -> Code m Float# #

Lift Int#

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Int# -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Int# -> Code m Int# #

Lift ByteArray

Since: template-haskell-2.19.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => ByteArray -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => ByteArray -> Code m ByteArray #

Lift Void

Since: template-haskell-2.15.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Void -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Void -> Code m Void #

Lift Int16 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Int16 -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Int16 -> Code m Int16 #

Lift Int32 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Int32 -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Int32 -> Code m Int32 #

Lift Int64 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Int64 -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Int64 -> Code m Int64 #

Lift Int8 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Int8 -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Int8 -> Code m Int8 #

Lift Word16 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Word16 -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Word16 -> Code m Word16 #

Lift Word32 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Word32 -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Word32 -> Code m Word32 #

Lift Word64 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Word64 -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Word64 -> Code m Word64 #

Lift Word8 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Word8 -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Word8 -> Code m Word8 #

Lift Integer 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Integer -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Integer -> Code m Integer #

Lift Natural 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Natural -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Natural -> Code m Natural #

Lift () 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => () -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => () -> Code m () #

Lift Bool 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Bool -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Bool -> Code m Bool #

Lift Char 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Char -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Char -> Code m Char #

Lift Double 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Double -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Double -> Code m Double #

Lift Float 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Float -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Float -> Code m Float #

Lift Int 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Int -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Int -> Code m Int #

Lift Word 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Word -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Word -> Code m Word #

Lift Char#

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Char# -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Char# -> Code m Char# #

Lift Word#

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Word# -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Word# -> Code m Word# #

Lift (# #)

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => (# #) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (# #) -> Code m (# #) #

Lift a => Lift (NonEmpty a :: Type)

Since: template-haskell-2.15.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => NonEmpty a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => NonEmpty a -> Code m (NonEmpty a) #

Integral a => Lift (Ratio a :: Type) 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Ratio a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Ratio a -> Code m (Ratio a) #

Lift a => Lift (Maybe a :: Type) 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Maybe a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Maybe a -> Code m (Maybe a) #

Lift a => Lift ([a] :: Type) 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => [a] -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => [a] -> Code m [a] #

(Lift a, Lift b) => Lift (Either a b :: Type) 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Either a b -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Either a b -> Code m (Either a b) #

(Lift a, Lift b) => Lift ((a, b) :: Type) 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => (a, b) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (a, b) -> Code m (a, b) #

(Lift a, Lift b, Lift c) => Lift ((a, b, c) :: Type) 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => (a, b, c) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (a, b, c) -> Code m (a, b, c) #

(Lift a, Lift b, Lift c, Lift d) => Lift ((a, b, c, d) :: Type) 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => (a, b, c, d) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (a, b, c, d) -> Code m (a, b, c, d) #

(Lift a, Lift b, Lift c, Lift d, Lift e) => Lift ((a, b, c, d, e) :: Type) 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => (a, b, c, d, e) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (a, b, c, d, e) -> Code m (a, b, c, d, e) #

(Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) => Lift ((a, b, c, d, e, f) :: Type) 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => (a, b, c, d, e, f) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (a, b, c, d, e, f) -> Code m (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) :: Type) 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

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

liftTyped :: forall (m :: Type -> Type). Quote m => (a, b, c, d, e, f, g) -> Code m (a, b, c, d, e, f, g) #

Lift a => Lift ((# a #) :: TYPE ('TupleRep '[LiftedRep]))

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => (# a #) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (# a #) -> Code m (# a #) #

(Lift a, Lift b) => Lift ((# a | b #) :: TYPE ('SumRep '[LiftedRep, LiftedRep]))

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => (# a | b #) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (# a | b #) -> Code m (# a | b #) #

(Lift a, Lift b) => Lift ((# a, b #) :: TYPE ('TupleRep '[LiftedRep, LiftedRep]))

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => (# a, b #) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (# a, b #) -> Code m (# a, b #) #

(Lift a, Lift b, Lift c) => Lift ((# a | b | c #) :: TYPE ('SumRep '[LiftedRep, LiftedRep, LiftedRep]))

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => (# a | b | c #) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (# a | b | c #) -> Code m (# a | b | c #) #

(Lift a, Lift b, Lift c) => Lift ((# a, b, c #) :: TYPE ('TupleRep '[LiftedRep, LiftedRep, LiftedRep]))

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => (# a, b, c #) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (# a, b, c #) -> Code m (# a, b, c #) #

(Lift a, Lift b, Lift c, Lift d) => Lift ((# a | b | c | d #) :: TYPE ('SumRep '[LiftedRep, LiftedRep, LiftedRep, LiftedRep]))

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => (# a | b | c | d #) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (# a | b | c | d #) -> Code m (# a | b | c | d #) #

(Lift a, Lift b, Lift c, Lift d) => Lift ((# a, b, c, d #) :: TYPE ('TupleRep '[LiftedRep, LiftedRep, LiftedRep, LiftedRep]))

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => (# a, b, c, d #) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (# a, b, c, d #) -> Code m (# a, b, c, d #) #

(Lift a, Lift b, Lift c, Lift d, Lift e) => Lift ((# a | b | c | d | e #) :: TYPE ('SumRep '[LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep]))

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => (# a | b | c | d | e #) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (# a | b | c | d | e #) -> Code m (# a | b | c | d | e #) #

(Lift a, Lift b, Lift c, Lift d, Lift e) => Lift ((# a, b, c, d, e #) :: TYPE ('TupleRep '[LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep]))

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => (# a, b, c, d, e #) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (# a, b, c, d, e #) -> Code m (# a, b, c, d, e #) #

(Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) => Lift ((# a | b | c | d | e | f #) :: TYPE ('SumRep '[LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep]))

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => (# a | b | c | d | e | f #) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (# a | b | c | d | e | f #) -> Code m (# a | b | c | d | e | f #) #

(Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) => Lift ((# a, b, c, d, e, f #) :: TYPE ('TupleRep '[LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep]))

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => (# a, b, c, d, e, f #) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (# a, b, c, d, e, f #) -> Code m (# 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 #) :: TYPE ('SumRep '[LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep]))

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => (# a | b | c | d | e | f | g #) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (# a | b | c | d | e | f | g #) -> Code m (# a | b | c | d | e | f | g #) #

(Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) => Lift ((# a, b, c, d, e, f, g #) :: TYPE ('TupleRep '[LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep]))

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

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

liftTyped :: forall (m :: Type -> Type). Quote m => (# a, b, c, d, e, f, g #) -> Code m (# a, b, c, d, e, f, g #) #