| Copyright | (C) 2015-2017 Ryan Scott |
|---|---|
| License | BSD-style (see the file LICENSE) |
| Maintainer | Ryan Scott |
| Safe Haskell | None |
| Language | Haskell2010 |
Language.Haskell.TH.Lift.Generics
Contents
Description
GHC.Generics-based approach to implementing lift.
Synopsis
- genericLiftWithPkg :: (Quote m, Generic a, GLift (Rep a)) => String -> a -> m Exp
- genericLiftTypedWithPkg :: (Quote m, Generic a, GLift (Rep a)) => String -> a -> Code m a
- genericLiftTypedTExpWithPkg :: (Quote m, Generic a, GLift (Rep a)) => String -> a -> m (TExp a)
- genericLiftTypedCompatWithPkg :: (Quote m, Generic a, GLift (Rep a)) => String -> a -> Splice m a
- 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 where
Documentation
genericLiftWithPkg :: (Quote m, Generic a, GLift (Rep a)) => String -> a -> m Exp Source #
GHC.Generics-based lift implementation.
API limitations of early versions of GHC (7.10 and earlier) require the user to produce the package name themselves. This isn't as easy to come up with as it sounds, because GHC 7.10 uses a hashed package ID for a 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—the code sample below shows an example of how to
properly use genericLiftWithPkg without shooting yourself in the foot:
{-# LANGUAGE CPP, DeriveGeneric #-}
-- part of package foobar
module Foo where
import GHC.Generics
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
instance Lift Foo where
lift = genericLiftWithPkg pkgName
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"))
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 #
Lift genericLiftWithPkg, 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.
genericLift :: (Quote m, Generic a, GLift (Rep a)) => a -> m Exp Source #
GHC.Generics-based lift implementation. Only available on GHC 8.0 and later
due to API limitations of earlier GHC versions.
Unlike genericLiftWithPkg, this function does 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
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"))
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.
Class of generic representation types which can be converted to Template Haskell expressions. You shouldn't need to use this typeclass directly; it is only exported for educational purposes.
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. You shouldn't need to use this typeclass directly; it is only exported for educational purposes.
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 be converted to a list of Template Haskell expressions (which represent a constructors' arguments). You shouldn't need to use this typeclass directly; it is only exported for educational purposes.
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 # | |
| Lift c => GLiftArgs (K1 i c :: Type -> Type) Source # | |
| (GLiftArgs f, GLiftArgs g) => GLiftArgs (f :*: g) Source # | |
| GLiftArgs f => GLiftArgs (S1 s f) Source # | |
Lift reexport
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.
A Lift instance must satisfy $(lift x) ≡ x for all x, where $(...)
is a Template Haskell splice.
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 LiftMinimal complete definition
Nothing
Methods
Turn a value into a Template Haskell expression, suitable for use in a splice.
Instances
| 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 () | |
Defined in Language.Haskell.TH.Syntax | |
| Lift a => Lift [a] | |
Defined in Language.Haskell.TH.Syntax | |
| 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) | |
Defined in Language.Haskell.TH.Syntax | |
| (Lift a, Lift b, Lift c) => Lift (a, b, c) | |
Defined in Language.Haskell.TH.Syntax | |
| (Lift a, Lift b, Lift c, Lift d) => Lift (a, b, c, d) | |
Defined in Language.Haskell.TH.Syntax | |
| (Lift a, Lift b, Lift c, Lift d, Lift e) => Lift (a, b, c, d, e) | |
Defined in Language.Haskell.TH.Syntax | |
| (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) => Lift (a, b, c, d, e, f) | |
Defined in Language.Haskell.TH.Syntax | |
| (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) => Lift (a, b, c, d, e, f, g) | |
Defined in Language.Haskell.TH.Syntax | |