th-lift-instances-0.1.18: Lift instances for template-haskell for common data types.
Safe HaskellNone
LanguageHaskell2010

Instances.TH.Lift

Synopsis

    Documentation

    This module provides orphan instances for the Lift class from template-haskell. Following is a list of the provided instances.

    Lift instances are useful to precompute values at compile time using template haskell. For example, if you write the following code, you can make sure that 3 * 10 is really computed at compile time:

    {-# LANGUAGE TemplateHaskell #-}
    
    import Language.Haskell.TH.Syntax
    
    expensiveComputation :: Word32
    expensiveComputation = $(lift $ 3 * 10) -- This will computed at compile time

    This uses the Lift instance for Word32.

    The following instances are provided by this package:

    Base

    • Word8, Word16, Word32, Word64
    • Int8, Int16, Int32, Int64
    • NonEmpty and Void, until provided by template-haskell-2.15

    Containers (both strict/lazy)

    ByteString (both strict/lazy)

    Text (both strict/lazy)

    Vector (Boxed, Unboxed, Storable, Primitive)

    Orphan instances

    Lift ByteString Source # 
    Instance details

    Lift ByteString Source # 
    Instance details

    Lift IntSet Source # 
    Instance details

    Methods

    lift :: IntSet -> Q Exp #

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

    Lift Text Source # 
    Instance details

    Methods

    lift :: Text -> Q Exp #

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

    Lift Text Source # 
    Instance details

    Methods

    lift :: Text -> Q Exp #

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

    Lift a => Lift (Identity a :: Type) Source # 
    Instance details

    Methods

    lift :: Identity a -> Q Exp #

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

    Lift v => Lift (IntMap v :: Type) Source # 
    Instance details

    Methods

    lift :: IntMap v -> Q Exp #

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

    Lift a => Lift (Tree a :: Type) Source # 
    Instance details

    Methods

    lift :: Tree a -> Q Exp #

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

    Lift a => Lift (Seq a :: Type) Source # 
    Instance details

    Methods

    lift :: Seq a -> Q Exp #

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

    Lift a => Lift (Set a :: Type) Source # 
    Instance details

    Methods

    lift :: Set a -> Q Exp #

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

    (Unbox a, Lift a) => Lift (Vector a :: Type) Source # 
    Instance details

    Methods

    lift :: Vector a -> Q Exp #

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

    (Storable a, Lift a) => Lift (Vector a :: Type) Source # 
    Instance details

    Methods

    lift :: Vector a -> Q Exp #

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

    (Prim a, Lift a) => Lift (Vector a :: Type) Source # 
    Instance details

    Methods

    lift :: Vector a -> Q Exp #

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

    Lift a => Lift (Vector a :: Type) Source # 
    Instance details

    Methods

    lift :: Vector a -> Q Exp #

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

    (Lift k, Lift v) => Lift (Map k v :: Type) Source # 
    Instance details

    Methods

    lift :: Map k v -> Q Exp #

    liftTyped :: Map k v -> Q (TExp (Map k v)) #

    Lift a => Lift (Const a b :: Type) Source # 
    Instance details

    Methods

    lift :: Const a b -> Q Exp #

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