th-orphans-0.13.14: Orphan instances for TH datatypes
Copyright(c) Matt Morrow 2008
LicenseBSD3
MaintainerMichael Sloan <mgsloan at gmail>
Stabilityexperimental
Portabilityportable (template-haskell)
Safe HaskellNone
LanguageHaskell2010

Language.Haskell.TH.Instances

Description

It provides the following instances:

More recent versions of template-haskell, particularly 2.10 (GHC 7.10), provide these instances. However, in order to support older versions you should import this module.

Note that the Ord instances are not guaranteed to produce consistent results across template-haskell / GHC versions, as they have different data types, with different constructor orders.

This module also implicitly re-exports the instances defined in Instances.TH.Lift. This is mostly to ensure that there aren't collisions of orphans between th-orphans and th-lift-instances.

Orphan instances

MonadFix Q Source #

If the function passed to mfix inspects its argument, the resulting action will throw a FixIOException (base >=4.11) or a BlockedIndefinitelyOnMVar with older base.

Instance details

Methods

mfix :: (a -> Q a) -> Q a #

Lift Exp Source # 
Instance details

Methods

lift :: Exp -> Q Exp #

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

Lift Match Source # 
Instance details

Methods

lift :: Match -> Q Exp #

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

Lift Clause Source # 
Instance details

Methods

lift :: Clause -> Q Exp #

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

Lift Pat Source # 
Instance details

Methods

lift :: Pat -> Q Exp #

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

Lift Type Source # 
Instance details

Methods

lift :: Type -> Q Exp #

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

Lift Dec Source # 
Instance details

Methods

lift :: Dec -> Q Exp #

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

Lift FunDep Source # 
Instance details

Methods

lift :: FunDep -> Q Exp #

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

Lift InjectivityAnn Source # 
Instance details

Lift Overlap Source # 
Instance details

Methods

lift :: Overlap -> Q Exp #

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

Lift Loc Source # 
Instance details

Methods

lift :: Loc -> Q Exp #

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

Lift Info Source # 
Instance details

Methods

lift :: Info -> Q Exp #

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

Lift Fixity Source # 
Instance details

Methods

lift :: Fixity -> Q Exp #

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

Lift FixityDirection Source # 
Instance details

Lift Lit Source # 
Instance details

Methods

lift :: Lit -> Q Exp #

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

Lift Bytes Source # 
Instance details

Methods

lift :: Bytes -> Q Exp #

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

Lift Body Source # 
Instance details

Methods

lift :: Body -> Q Exp #

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

Lift Guard Source # 
Instance details

Methods

lift :: Guard -> Q Exp #

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

Lift Stmt Source # 
Instance details

Methods

lift :: Stmt -> Q Exp #

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

Lift Range Source # 
Instance details

Methods

lift :: Range -> Q Exp #

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

Lift DerivClause Source # 
Instance details

Lift DerivStrategy Source # 
Instance details

Lift TypeFamilyHead Source # 
Instance details

Lift TySynEqn Source # 
Instance details

Lift Foreign Source # 
Instance details

Methods

lift :: Foreign -> Q Exp #

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

Lift Callconv Source # 
Instance details

Lift Safety Source # 
Instance details

Methods

lift :: Safety -> Q Exp #

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

Lift Pragma Source # 
Instance details

Methods

lift :: Pragma -> Q Exp #

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

Lift Inline Source # 
Instance details

Methods

lift :: Inline -> Q Exp #

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

Lift RuleMatch Source # 
Instance details

Lift Phases Source # 
Instance details

Methods

lift :: Phases -> Q Exp #

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

Lift RuleBndr Source # 
Instance details

Lift AnnTarget Source # 
Instance details

Lift SourceUnpackedness Source # 
Instance details

Lift SourceStrictness Source # 
Instance details

Lift Con Source # 
Instance details

Methods

lift :: Con -> Q Exp #

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

Lift Bang Source # 
Instance details

Methods

lift :: Bang -> Q Exp #

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

Lift PatSynDir Source # 
Instance details

Lift PatSynArgs Source # 
Instance details

Lift TyVarBndr Source # 
Instance details

Lift FamilyResultSig Source # 
Instance details

Lift TyLit Source # 
Instance details

Methods

lift :: TyLit -> Q Exp #

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

Lift Role Source # 
Instance details

Methods

lift :: Role -> Q Exp #

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

Semigroup a => Semigroup (Q a) Source # 
Instance details

Methods

(<>) :: Q a -> Q a -> Q a #

sconcat :: NonEmpty (Q a) -> Q a #

stimes :: Integral b => b -> Q a -> Q a #

Monoid a => Monoid (Q a) Source # 
Instance details

Methods

mempty :: Q a #

mappend :: Q a -> Q a -> Q a #

mconcat :: [Q a] -> Q a #

Quasi m => Quasi (ReaderT r m) Source # 
Instance details

Quasi m => Quasi (StateT s m) Source # 
Instance details

(Quasi m, Monoid w) => Quasi (WriterT w m) Source # 
Instance details

Quote m => Quote (ReaderT r m) Source # 
Instance details

Methods

newName :: String -> ReaderT r m Name #

Quote m => Quote (StateT s m) Source # 
Instance details

Methods

newName :: String -> StateT s m Name #

(Quote m, Monoid w) => Quote (WriterT w m) Source # 
Instance details

Methods

newName :: String -> WriterT w m Name #

(Quasi m, Monoid w) => Quasi (RWST r w s m) Source # 
Instance details

Methods

qNewName :: String -> RWST r w s m Name #

qReport :: Bool -> String -> RWST r w s m () #

qRecover :: RWST r w s m a -> RWST r w s m a -> RWST r w s m a #

qLookupName :: Bool -> String -> RWST r w s m (Maybe Name) #

qReify :: Name -> RWST r w s m Info #

qReifyFixity :: Name -> RWST r w s m (Maybe Fixity) #

qReifyType :: Name -> RWST r w s m Type #

qReifyInstances :: Name -> [Type] -> RWST r w s m [Dec] #

qReifyRoles :: Name -> RWST r w s m [Role] #

qReifyAnnotations :: Data a => AnnLookup -> RWST r w s m [a] #

qReifyModule :: Module -> RWST r w s m ModuleInfo #

qReifyConStrictness :: Name -> RWST r w s m [DecidedStrictness] #

qLocation :: RWST r w s m Loc #

qRunIO :: IO a -> RWST r w s m a #

qAddDependentFile :: FilePath -> RWST r w s m () #

qAddTempFile :: String -> RWST r w s m FilePath #

qAddTopDecls :: [Dec] -> RWST r w s m () #

qAddForeignFilePath :: ForeignSrcLang -> String -> RWST r w s m () #

qAddModFinalizer :: Q () -> RWST r w s m () #

qAddCorePlugin :: String -> RWST r w s m () #

qGetQ :: Typeable a => RWST r w s m (Maybe a) #

qPutQ :: Typeable a => a -> RWST r w s m () #

qIsExtEnabled :: Extension -> RWST r w s m Bool #

qExtsEnabled :: RWST r w s m [Extension] #

(Quote m, Monoid w) => Quote (RWST r w s m) Source # 
Instance details

Methods

newName :: String -> RWST r w s m Name #