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

Language.Haskell.TH.Instances

Description

It provides the following instances:

More recent versions of template-haskell provide these instances. However, in order to support older versions you should import this module.

Orphan instances

Lift AnnTarget Source # 
Instance details

Methods

lift :: Quote m => AnnTarget -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => AnnTarget -> Code m AnnTarget #

Lift Bang Source # 
Instance details

Methods

lift :: Quote m => Bang -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Bang -> Code m Bang #

Lift Body Source # 
Instance details

Methods

lift :: Quote m => Body -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Body -> Code m Body #

Lift Bytes Source # 
Instance details

Methods

lift :: Quote m => Bytes -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Bytes -> Code m Bytes #

Lift Callconv Source # 
Instance details

Methods

lift :: Quote m => Callconv -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Callconv -> Code m Callconv #

Lift Clause Source # 
Instance details

Methods

lift :: Quote m => Clause -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Clause -> Code m Clause #

Lift Con Source # 
Instance details

Methods

lift :: Quote m => Con -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Con -> Code m Con #

Lift Dec Source # 
Instance details

Methods

lift :: Quote m => Dec -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Dec -> Code m Dec #

Lift DerivClause Source # 
Instance details

Methods

lift :: Quote m => DerivClause -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => DerivClause -> Code m DerivClause #

Lift DerivStrategy Source # 
Instance details

Methods

lift :: Quote m => DerivStrategy -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => DerivStrategy -> Code m DerivStrategy #

Lift Exp Source # 
Instance details

Methods

lift :: Quote m => Exp -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Exp -> Code m Exp #

Lift FamilyResultSig Source # 
Instance details

Methods

lift :: Quote m => FamilyResultSig -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => FamilyResultSig -> Code m FamilyResultSig #

Lift Fixity Source # 
Instance details

Methods

lift :: Quote m => Fixity -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Fixity -> Code m Fixity #

Lift FixityDirection Source # 
Instance details

Methods

lift :: Quote m => FixityDirection -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => FixityDirection -> Code m FixityDirection #

Lift Foreign Source # 
Instance details

Methods

lift :: Quote m => Foreign -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Foreign -> Code m Foreign #

Lift FunDep Source # 
Instance details

Methods

lift :: Quote m => FunDep -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => FunDep -> Code m FunDep #

Lift Guard Source # 
Instance details

Methods

lift :: Quote m => Guard -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Guard -> Code m Guard #

Lift Info Source # 
Instance details

Methods

lift :: Quote m => Info -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Info -> Code m Info #

Lift InjectivityAnn Source # 
Instance details

Methods

lift :: Quote m => InjectivityAnn -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => InjectivityAnn -> Code m InjectivityAnn #

Lift Inline Source # 
Instance details

Methods

lift :: Quote m => Inline -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Inline -> Code m Inline #

Lift Lit Source # 
Instance details

Methods

lift :: Quote m => Lit -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Lit -> Code m Lit #

Lift Loc Source # 
Instance details

Methods

lift :: Quote m => Loc -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Loc -> Code m Loc #

Lift Match Source # 
Instance details

Methods

lift :: Quote m => Match -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Match -> Code m Match #

Lift Overlap Source # 
Instance details

Methods

lift :: Quote m => Overlap -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Overlap -> Code m Overlap #

Lift Pat Source # 
Instance details

Methods

lift :: Quote m => Pat -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Pat -> Code m Pat #

Lift PatSynArgs Source # 
Instance details

Methods

lift :: Quote m => PatSynArgs -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => PatSynArgs -> Code m PatSynArgs #

Lift PatSynDir Source # 
Instance details

Methods

lift :: Quote m => PatSynDir -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => PatSynDir -> Code m PatSynDir #

Lift Phases Source # 
Instance details

Methods

lift :: Quote m => Phases -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Phases -> Code m Phases #

Lift Pragma Source # 
Instance details

Methods

lift :: Quote m => Pragma -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Pragma -> Code m Pragma #

Lift Range Source # 
Instance details

Methods

lift :: Quote m => Range -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Range -> Code m Range #

Lift Role Source # 
Instance details

Methods

lift :: Quote m => Role -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Role -> Code m Role #

Lift RuleBndr Source # 
Instance details

Methods

lift :: Quote m => RuleBndr -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => RuleBndr -> Code m RuleBndr #

Lift RuleMatch Source # 
Instance details

Methods

lift :: Quote m => RuleMatch -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => RuleMatch -> Code m RuleMatch #

Lift Safety Source # 
Instance details

Methods

lift :: Quote m => Safety -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Safety -> Code m Safety #

Lift SourceStrictness Source # 
Instance details

Methods

lift :: Quote m => SourceStrictness -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => SourceStrictness -> Code m SourceStrictness #

Lift SourceUnpackedness Source # 
Instance details

Lift Specificity Source # 
Instance details

Methods

lift :: Quote m => Specificity -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Specificity -> Code m Specificity #

Lift Stmt Source # 
Instance details

Methods

lift :: Quote m => Stmt -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Stmt -> Code m Stmt #

Lift TyLit Source # 
Instance details

Methods

lift :: Quote m => TyLit -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => TyLit -> Code m TyLit #

Lift TySynEqn Source # 
Instance details

Methods

lift :: Quote m => TySynEqn -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => TySynEqn -> Code m TySynEqn #

Lift Type Source # 
Instance details

Methods

lift :: Quote m => Type -> m Exp #

liftTyped :: forall (m :: Type0 -> Type0). Quote m => Type -> Code m Type #

Lift TypeFamilyHead Source # 
Instance details

Methods

lift :: Quote m => TypeFamilyHead -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => TypeFamilyHead -> Code m TypeFamilyHead #

Lift flag => Lift (TyVarBndr flag :: Type) Source # 
Instance details

Methods

lift :: Quote m => TyVarBndr flag -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => TyVarBndr flag -> Code m (TyVarBndr flag) #

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 #

qGetPackageRoot :: RWST r w s m FilePath #

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] #

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

qGetDoc :: DocLoc -> RWST r w s m (Maybe String) #

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

Methods

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