| Copyright | (C) 2015-2017 Ryan Scott |
|---|---|
| License | BSD-style (see the file LICENSE) |
| Maintainer | Ryan Scott |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Language.Haskell.TH.Lift.Generics
Contents
- GHC.Generics-based
liftimplementations GenericclassesLiftreexport
Description
GHC.Generics-based approach to implementing lift.
Synopsis
- genericLift :: (Quote m, Generic a, GLift (Rep a)) => a -> m Exp
- genericLiftTyped :: (Quote m, Generic a, GLift (Rep a)) => a -> Code m a
- genericLiftTypedTExp :: (Quote m, Generic a, GLift (Rep a)) => a -> m (TExp a)
- genericLiftTypedCompat :: (Quote m, Generic a, GLift (Rep a)) => a -> Splice m a
- class GLift f where
- class GLiftDatatype f where
- class GLiftArgs f where
- class Lift (t :: TYPE r) where
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 usingtemplate-haskell-2.17.0.0or later), or - A
TExp(if using an older version oftemplate-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 of generic representation types which can be converted to Template Haskell expressions.
Methods
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
Instances
| GLiftDatatype (V1 :: Type -> Type) Source # | |
| (GLiftDatatype f, GLiftDatatype g) => GLiftDatatype (f :+: g) Source # | |
| (Constructor c, GLiftArgs f) => GLiftDatatype (C1 c f) 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
| GLiftArgs (U1 :: Type -> Type) Source # | |
| GLiftArgs (UAddr :: Type -> Type) Source # | |
| GLiftArgs (UChar :: Type -> Type) Source # | |
| GLiftArgs (UDouble :: Type -> Type) Source # | |
| GLiftArgs (UFloat :: Type -> Type) Source # | |
| GLiftArgs (UInt :: Type -> Type) Source # | |
| GLiftArgs (UWord :: Type -> Type) Source # | |
| (GLiftArgs f, GLiftArgs g) => GLiftArgs (f :*: g) Source # | |
| Lift c => GLiftArgs (K1 i c :: Type -> Type) Source # | |
| GLiftArgs f => GLiftArgs (S1 s f) 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 LiftRepresentation-polymorphic since template-haskell-2.16.0.0.
Minimal complete definition
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
| Lift Addr# | Produces an Since: template-haskell-2.16.0.0 |
| Lift Double# | Since: template-haskell-2.16.0.0 |
| Lift Float# | Since: template-haskell-2.16.0.0 |
| Lift Int# | Since: template-haskell-2.16.0.0 |
| Lift ByteArray | Since: template-haskell-2.19.0.0 |
| Lift Void | Since: template-haskell-2.15.0.0 |
| Lift Int16 | |
| Lift Int32 | |
| Lift Int64 | |
| Lift Int8 | |
| Lift Word16 | |
| Lift Word32 | |
| Lift Word64 | |
| Lift Word8 | |
| Lift Integer | |
| Lift Natural | |
| Lift () | |
| Lift Bool | |
| Lift Char | |
| Lift Double | |
| Lift Float | |
| Lift Int | |
| Lift Word | |
| Lift Char# | Since: template-haskell-2.16.0.0 |
| Lift Word# | Since: template-haskell-2.16.0.0 |
| Lift (# #) | Since: template-haskell-2.16.0.0 |
| Lift a => Lift (NonEmpty a :: Type) | Since: template-haskell-2.15.0.0 |
| Integral a => Lift (Ratio a :: Type) | |
| Lift a => Lift (Maybe a :: Type) | |
| Lift a => Lift ([a] :: Type) | |
| (Lift a, Lift b) => Lift (Either a b :: Type) | |
| (Lift a, Lift b) => Lift ((a, b) :: Type) | |
| (Lift a, Lift b, Lift c) => Lift ((a, b, c) :: Type) | |
| (Lift a, Lift b, Lift c, Lift d) => Lift ((a, b, c, d) :: Type) | |
| (Lift a, Lift b, Lift c, Lift d, Lift e) => Lift ((a, b, c, d, e) :: Type) | |
| (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) => Lift ((a, b, c, d, e, f) :: Type) | |
| (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) => Lift ((a, b, c, d, e, f, g) :: Type) | |
| Lift a => Lift ((# a #) :: TYPE ('TupleRep '[LiftedRep])) | Since: template-haskell-2.16.0.0 |
| (Lift a, Lift b) => Lift ((# a | b #) :: TYPE ('SumRep '[LiftedRep, LiftedRep])) | Since: template-haskell-2.16.0.0 |
| (Lift a, Lift b) => Lift ((# a, b #) :: TYPE ('TupleRep '[LiftedRep, LiftedRep])) | Since: template-haskell-2.16.0.0 |
| (Lift a, Lift b, Lift c) => Lift ((# a | b | c #) :: TYPE ('SumRep '[LiftedRep, LiftedRep, LiftedRep])) | Since: template-haskell-2.16.0.0 |
| (Lift a, Lift b, Lift c) => Lift ((# a, b, c #) :: TYPE ('TupleRep '[LiftedRep, LiftedRep, LiftedRep])) | Since: template-haskell-2.16.0.0 |
| (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 |
| (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 |
| (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 |
| (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 |
| (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 |
| (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 |
| (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 |
| (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 |