lift-generics-0.1.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 HaskellNone
LanguageHaskell2010

Language.Haskell.TH.Lift.Generics

Contents

Description

GHC.Generics-based approach to implementing lift.

Synopsis

Documentation

genericLiftWithPkg :: (Generic a, GLift (Rep a)) => String -> a -> Q 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 :: (Generic a, GLift (Rep a)) => String -> a -> Q (TExp a) Source #

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

genericLift :: (Generic a, GLift (Rep a)) => a -> Q 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 :: (Generic a, GLift (Rep a)) => a -> Q (TExp a) Source #

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

class GLift f where Source #

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

glift Source #

Arguments

:: String

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

-> f a

The generic value

-> Q Exp

The resulting Template Haskell expression

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

Defined in Language.Haskell.TH.Lift.Generics

Methods

glift :: String -> D1 d f a -> Q 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. You shouldn't need to use this typeclass directly; it is only exported for educational purposes.

Methods

gliftWith Source #

Arguments

:: String

The package name

-> String

The module name

-> f a

The generic value

-> Q Exp

The resulting Template Haskell expression

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

Defined in Language.Haskell.TH.Lift.Generics

Methods

gliftWith :: String -> String -> (f :+: g) a -> Q Exp Source #

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

Defined in Language.Haskell.TH.Lift.Generics

Methods

gliftWith :: String -> String -> C1 c f a -> Q Exp 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.

Methods

gliftArgs :: f a -> [Q Exp] Source #

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

Defined in Language.Haskell.TH.Lift.Generics

Methods

gliftArgs :: V1 a -> [Q Exp] Source #

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

Defined in Language.Haskell.TH.Lift.Generics

Methods

gliftArgs :: U1 a -> [Q Exp] Source #

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

Defined in Language.Haskell.TH.Lift.Generics

Methods

gliftArgs :: UAddr a -> [Q Exp] Source #

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

Defined in Language.Haskell.TH.Lift.Generics

Methods

gliftArgs :: UChar a -> [Q Exp] Source #

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

Defined in Language.Haskell.TH.Lift.Generics

Methods

gliftArgs :: UDouble a -> [Q Exp] Source #

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

Defined in Language.Haskell.TH.Lift.Generics

Methods

gliftArgs :: UFloat a -> [Q Exp] Source #

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

Defined in Language.Haskell.TH.Lift.Generics

Methods

gliftArgs :: UInt a -> [Q Exp] Source #

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

Defined in Language.Haskell.TH.Lift.Generics

Methods

gliftArgs :: UWord a -> [Q Exp] Source #

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

Defined in Language.Haskell.TH.Lift.Generics

Methods

gliftArgs :: K1 i c a -> [Q Exp] Source #

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

Defined in Language.Haskell.TH.Lift.Generics

Methods

gliftArgs :: (f :*: g) a -> [Q Exp] Source #

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

Defined in Language.Haskell.TH.Lift.Generics

Methods

gliftArgs :: S1 s f a -> [Q Exp] Source #

Lift reexport

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.

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 Lift

Minimal complete definition

Nothing

Methods

lift :: t -> Q Exp #

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

Instances
Lift Bool 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Bool -> Q Exp #

Lift Char 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Char -> Q Exp #

Lift Double 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Double -> Q Exp #

Lift Float 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Float -> Q Exp #

Lift Int 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int -> Q Exp #

Lift Int8 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int8 -> Q Exp #

Lift Int16 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int16 -> Q Exp #

Lift Int32 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int32 -> Q Exp #

Lift Int64 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int64 -> Q Exp #

Lift Integer 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Integer -> Q Exp #

Lift Natural 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Natural -> Q Exp #

Lift Word 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word -> Q Exp #

Lift Word8 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word8 -> Q Exp #

Lift Word16 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word16 -> Q Exp #

Lift Word32 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word32 -> Q Exp #

Lift Word64 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word64 -> Q Exp #

Lift () 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: () -> Q Exp #

Lift a => Lift [a] 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: [a] -> Q Exp #

Lift a => Lift (Maybe a) 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Maybe a -> Q Exp #

Integral a => Lift (Ratio a) 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Ratio a -> Q Exp #

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

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Either a b -> Q Exp #

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

Defined in Language.Haskell.TH.Syntax

Methods

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

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

Defined in Language.Haskell.TH.Syntax

Methods

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

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

Defined in Language.Haskell.TH.Syntax

Methods

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

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

Defined in Language.Haskell.TH.Syntax

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) 
Instance details

Defined in Language.Haskell.TH.Syntax

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) 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

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