lift-generics-0.1: GHC.Generics-based Language.Haskell.TH.Syntax.lift implementation

Copyright(C) 2015 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"))

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

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

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

Lift reexport

class Lift t where

Methods

lift :: t -> Q Exp

Instances

Lift Bool 
Lift Char 
Lift Double 
Lift Float 
Lift Int 
Lift Int8 
Lift Int16 
Lift Int32 
Lift Int64 
Lift Integer 
Lift Word 
Lift Word8 
Lift Word16 
Lift Word32 
Lift Word64 
Lift () 
Lift Natural 
Lift a => Lift [a] 
Integral a => Lift (Ratio a) 
Lift a => Lift (Maybe a) 
(Lift a, Lift b) => Lift (Either a b) 
(Lift a, Lift b) => Lift (a, b) 
(Lift a, Lift b, Lift c) => Lift (a, b, c) 
(Lift a, Lift b, Lift c, Lift d) => Lift (a, b, c, d) 
(Lift a, Lift b, Lift c, Lift d, Lift e) => Lift (a, b, c, d, e) 
(Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) => Lift (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)