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

Language.Haskell.TH.Lift.Generics

Description

GHC.Generics-based approach to implementing lift. Different sets of functions are available for use with different GHC and template-haskell versions.

General recommendations

  • If you only need to support GHC 8.0 (base 4.9.0) and later, then you may either use the "friendly" functions here or skip this package entirely and use the built-in DeriveLift mechanism, which has the advantage of working for GADTs and existential types.
  • If you only need to support GHC 7.4 (base 4.5) and later, and you have Typeable instances for the relevant type constructors (or can derive them), then you should use the "friendly" functions here.
  • If you must support GHC versions before 7.4 (base 4.5), or types in other packages without Typeable instances, then you should seriously consider using the th-lift package to derive Lift instances. If you choose to continue with this package:

    • If you have Typeable instances, then you should use the "less friendly" functions here. These take an argument for the package name, but they ignore it (acting just like the friendly ones) for GHC 7.4 (base 4.5) and later.
    • If you lack a Typeable instance for a type constructor, then you'll need to use the "unfriendly" functions. These rely solely on the user-provided package name. On GHC 7.10, it is extremely difficult to obtain the correct package name for an external package.

A note on Typeable constraints

For relevant versions, the "friendly" and "less friendly" functions require the type to satisfy an OuterTypeable constraint. A type is OuterTypable if its type constructor (applied to any kind arguments) is Typeable. For example, Maybe a is only Typeable if a is Typeable, but it is always OuterTypeable. For Const a b to be OuterTypeable, the kinds of a and b must be Typeable.

Before GHC 7.8, Typeable can only be derived for types with seven or fewer parameters, all of kind *. Types with more parameters that manually instantiate the now-defunct Typeable7 class should work, but there may be some loss of polymorphism in the first arguments. Types whose Typeable instances can't be derived because of kind issues will not work with these GHC versions.

Synopsis

Friendly GHC.Generics-based lift implementations

The functions in this section are nice and simple, but are only available on GHC 7.4.1 (base 4.5) and later due to API limitations of earlier GHC versions. The types of these functions depend slightly on the GHC version. In particular, before GHC 8.0 (base 4.9), these functions have Typeable constraints in addition to Generic ones.

These functions do all of the work for you:

{-# 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.

Note

A Typeable a instance is required for GHC < 8.0 (base < 4.9).

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.

Less friendly and unfriendly GHC.Generics-based lift

API limitations of early versions of GHC (7.2 and earlier) require the user to produce the package name themselves. This is also occasionally necessary for later versions of GHC when dealing with types from other packages that lack Typeable instances. The package name isn't always as easy to come up with as it sounds, especially because GHC 7.10 uses a hashed package ID for that name. To make things worse, if you produce the wrong package name, you might get bizarre compilation errors!

There's no need to fear, though—in most cases it's possible to obtain the correct package name anyway, at least for types defined in the current package. When compiling a library with Cabal, the current package name is obtained using the CPP macro CURRENT_PACKAGE_KEY. When compiling an application, or compiling without Cabal, it takes a bit more work to get the name. The code sample below shows an example of how to properly use genericLiftWithPkgFallback or genericLiftWithPkg without shooting yourself in the foot:

{-# LANGUAGE CPP, DeriveGeneric, DeriveDataTypeable #-}
-- part of package foobar
module Foo where

import GHC.Generics
import Data.Typeable
import Language.Haskell.Lift.Generics

#ifndef CURRENT_PACKAGE_KEY
import Data.Version (showVersion)
import Paths_foobar (version)
#endif

pkgName :: String
#ifdef CURRENT_PACKAGE_KEY
pkgName = CURRENT_PACKAGE_KEY
#else
pkgName = "foobar-" ++ showVersion version
#endif

data Foo = Foo Int Char String
  deriving (Generic, Typeable)

instance Lift Foo where
  lift = genericLiftWithPkgFallback pkgName
#if MIN_VERSION_template_haskell(2,9,0)
  liftTyped = genericLiftTypedCompatWithPkgFallback pkgName
#endif

As you can see, this trick only works if (1) the current package key is known (i.e., the Lift instance is defined in the same package as the datatype), or (2) you're dealing with a package that has a fixed package name (e.g., base, ghc-prim, template-haskell, etc.).

Once the Lift Foo instance is defined, 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"))

Less friendly implementations

These implementations should be used when support for versions before GHC 7.4 (base 4.5) is required, but a Typeable instance is available. The Typeable instance will be used to get the package name for GHC 7.4 and later.

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

Generically produce an implementation of lift, given a user-provided (but correct!) package name. The provided package name is ignored for GHC 7.4 (base 4.5) and later.

Note

A Typeable a instance is required for 7.4 <= GHC < 8.0 (4.5 <= base < 4.9).

Since: 0.2.1

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

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

Since: 0.2.1

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

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

Since: 0.2.1

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

Like genericLiftWithPkg, 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.

Since: 0.2.1

Unfriendly implementations

These implementations should be used when support for versions before GHC 8.0 (base 4.9) is required and a Typeable instance is not available. These functions are termed "unfriendly" because they're extremely hard to use under GHC 7.10 when working with types defined in other packages. The only way to do so is to use a Typeable type in the same package to get the "package name", which will be a hash value.

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

Generically produce an implementation of lift, given a user-provided (but correct!) package name. The provided package name is ignored for GHC 8.0 (base 4.9) and later.

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

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

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

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

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

Like genericLiftWithPkg, 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 
=> String

The package name (not used on GHC 8.0 and later)

-> 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 => String -> 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 #

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 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 #

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

Levity-polymorphic since template-haskell-2.16.0.0.

Minimal complete definition

liftTyped

Methods

lift :: t -> Q Exp #

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

liftTyped :: t -> Q (TExp 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 Bool 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Bool -> Q Exp #

liftTyped :: Bool -> Q (TExp Bool) #

Lift Char 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Char -> Q Exp #

liftTyped :: Char -> Q (TExp Char) #

Lift Double 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Double -> Q Exp #

liftTyped :: Double -> Q (TExp Double) #

Lift Float 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Float -> Q Exp #

liftTyped :: Float -> Q (TExp Float) #

Lift Int 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int -> Q Exp #

liftTyped :: Int -> Q (TExp Int) #

Lift Int8 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int8 -> Q Exp #

liftTyped :: Int8 -> Q (TExp Int8) #

Lift Int16 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int16 -> Q Exp #

liftTyped :: Int16 -> Q (TExp Int16) #

Lift Int32 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int32 -> Q Exp #

liftTyped :: Int32 -> Q (TExp Int32) #

Lift Int64 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int64 -> Q Exp #

liftTyped :: Int64 -> Q (TExp Int64) #

Lift Integer 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Integer -> Q Exp #

liftTyped :: Integer -> Q (TExp Integer) #

Lift Natural 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Natural -> Q Exp #

liftTyped :: Natural -> Q (TExp Natural) #

Lift Word 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word -> Q Exp #

liftTyped :: Word -> Q (TExp Word) #

Lift Word8 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word8 -> Q Exp #

liftTyped :: Word8 -> Q (TExp Word8) #

Lift Word16 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word16 -> Q Exp #

liftTyped :: Word16 -> Q (TExp Word16) #

Lift Word32 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word32 -> Q Exp #

liftTyped :: Word32 -> Q (TExp Word32) #

Lift Word64 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word64 -> Q Exp #

liftTyped :: Word64 -> Q (TExp Word64) #

Lift () 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: () -> Q Exp #

liftTyped :: () -> Q (TExp ()) #

Lift Void

Since: template-haskell-2.15.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Void -> Q Exp #

liftTyped :: Void -> Q (TExp Void) #

Lift Int#

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int# -> Q Exp #

liftTyped :: Int# -> Q (TExp Int#) #

Lift Char#

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Char# -> Q Exp #

liftTyped :: Char# -> Q (TExp Char#) #

Lift Word#

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word# -> Q Exp #

liftTyped :: Word# -> Q (TExp Word#) #

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 :: Addr# -> Q Exp #

liftTyped :: Addr# -> Q (TExp Addr#) #

Lift Float#

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Float# -> Q Exp #

liftTyped :: Float# -> Q (TExp Float#) #

Lift Double#

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Double# -> Q Exp #

liftTyped :: Double# -> Q (TExp Double#) #

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

Defined in Language.Haskell.TH.Syntax

Methods

lift :: [a] -> Q Exp #

liftTyped :: [a] -> Q (TExp [a]) #

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

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Maybe a -> Q Exp #

liftTyped :: Maybe a -> Q (TExp (Maybe a)) #

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

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Ratio a -> Q Exp #

liftTyped :: Ratio a -> Q (TExp (Ratio a)) #

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

Since: template-haskell-2.15.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: NonEmpty a -> Q Exp #

liftTyped :: NonEmpty a -> Q (TExp (NonEmpty a)) #

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

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Either a b -> Q Exp #

liftTyped :: Either a b -> Q (TExp (Either a b)) #

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

Defined in Language.Haskell.TH.Syntax

Methods

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

liftTyped :: (a, b) -> Q (TExp (a, b)) #

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

Defined in Language.Haskell.TH.Syntax

Methods

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

liftTyped :: (a, b, c) -> Q (TExp (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 :: (a, b, c, d) -> Q Exp #

liftTyped :: (a, b, c, d) -> Q (TExp (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 :: (a, b, c, d, e) -> Q Exp #

liftTyped :: (a, b, c, d, e) -> Q (TExp (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 :: (a, b, c, d, e, f) -> Q Exp #

liftTyped :: (a, b, c, d, e, f) -> Q (TExp (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 :: (a, b, c, d, e, f, g) -> Q Exp #

liftTyped :: (a, b, c, d, e, f, g) -> Q (TExp (a, b, c, d, e, f, g)) #

Lift (# #)

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: (# #) -> Q Exp #

liftTyped :: (# #) -> Q (TExp (# #)) #

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

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

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

liftTyped :: (# a #) -> Q (TExp (# a #)) #

(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 :: (# a, b #) -> Q Exp #

liftTyped :: (# a, b #) -> Q (TExp (# a, b #)) #

(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 :: (# a | b #) -> Q Exp #

liftTyped :: (# a | b #) -> Q (TExp (# a | b #)) #

(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 :: (# a, b, c #) -> Q Exp #

liftTyped :: (# a, b, c #) -> Q (TExp (# a, b, c #)) #

(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 :: (# a | b | c #) -> Q Exp #

liftTyped :: (# a | b | c #) -> Q (TExp (# a | b | c #)) #

(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 :: (# a, b, c, d #) -> Q Exp #

liftTyped :: (# a, b, c, d #) -> Q (TExp (# a, b, c, d #)) #

(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 :: (# a | b | c | d #) -> Q Exp #

liftTyped :: (# a | b | c | d #) -> Q (TExp (# a | b | c | d #)) #

(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 :: (# a, b, c, d, e #) -> Q Exp #

liftTyped :: (# a, b, c, d, e #) -> Q (TExp (# a, b, c, d, e #)) #

(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 :: (# a | b | c | d | e #) -> Q Exp #

liftTyped :: (# a | b | c | d | e #) -> Q (TExp (# 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 ('TupleRep '['LiftedRep, 'LiftedRep, 'LiftedRep, 'LiftedRep, 'LiftedRep, 'LiftedRep]))

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

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

liftTyped :: (# a, b, c, d, e, f #) -> Q (TExp (# 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 ('SumRep '['LiftedRep, 'LiftedRep, 'LiftedRep, 'LiftedRep, 'LiftedRep, 'LiftedRep]))

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

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

liftTyped :: (# a | b | c | d | e | f #) -> Q (TExp (# 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 ('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 :: (# a, b, c, d, e, f, g #) -> Q Exp #

liftTyped :: (# a, b, c, d, e, f, g #) -> Q (TExp (# 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 ('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 :: (# a | b | c | d | e | f | g #) -> Q Exp #

liftTyped :: (# a | b | c | d | e | f | g #) -> Q (TExp (# a | b | c | d | e | f | g #)) #