summaryrefslogtreecommitdiff
path: root/libraries/template-haskell/Language/Haskell
diff options
context:
space:
mode:
authorIavor S. Diatchki <iavor.diatchki@gmail.com>2014-07-19 14:29:57 -0700
committerIavor S. Diatchki <iavor.diatchki@gmail.com>2014-07-19 14:29:57 -0700
commit524634641c61ab42c555452f6f87119b27f6c331 (patch)
treef78d17bb6b09fb3b2e22cb4d93c2a3d45accc2d9 /libraries/template-haskell/Language/Haskell
parent79ad1d20c5500e17ce5daaf93b171131669bddad (diff)
parentc41b716d82b1722f909979d02a76e21e9b68886c (diff)
downloadhaskell-wip/ext-solver.tar.gz
Merge branch 'master' into wip/ext-solverwip/ext-solver
Diffstat (limited to 'libraries/template-haskell/Language/Haskell')
-rw-r--r--libraries/template-haskell/Language/Haskell/TH.hs124
-rw-r--r--libraries/template-haskell/Language/Haskell/TH/Lib.hs16
-rw-r--r--libraries/template-haskell/Language/Haskell/TH/Syntax.hs2
3 files changed, 79 insertions, 63 deletions
diff --git a/libraries/template-haskell/Language/Haskell/TH.hs b/libraries/template-haskell/Language/Haskell/TH.hs
index e9765a9747..29e3787bd0 100644
--- a/libraries/template-haskell/Language/Haskell/TH.hs
+++ b/libraries/template-haskell/Language/Haskell/TH.hs
@@ -5,52 +5,52 @@ For other documentation, refer to:
-}
module Language.Haskell.TH(
- -- * The monad and its operations
- Q,
- runQ,
+ -- * The monad and its operations
+ Q,
+ runQ,
-- ** Administration: errors, locations and IO
- reportError, -- :: String -> Q ()
- reportWarning, -- :: String -> Q ()
- report, -- :: Bool -> String -> Q ()
- recover, -- :: Q a -> Q a -> Q a
- location, -- :: Q Loc
- Loc(..),
- runIO, -- :: IO a -> Q a
- -- ** Querying the compiler
- -- *** Reify
- reify, -- :: Name -> Q Info
- reifyModule,
- thisModule,
- Info(..), ModuleInfo(..),
- InstanceDec,
- ParentName,
- Arity,
- Unlifted,
- -- *** Name lookup
- lookupTypeName, -- :: String -> Q (Maybe Name)
- lookupValueName, -- :: String -> Q (Maybe Name)
- -- *** Instance lookup
- reifyInstances,
- isInstance,
+ reportError, -- :: String -> Q ()
+ reportWarning, -- :: String -> Q ()
+ report, -- :: Bool -> String -> Q ()
+ recover, -- :: Q a -> Q a -> Q a
+ location, -- :: Q Loc
+ Loc(..),
+ runIO, -- :: IO a -> Q a
+ -- ** Querying the compiler
+ -- *** Reify
+ reify, -- :: Name -> Q Info
+ reifyModule,
+ thisModule,
+ Info(..), ModuleInfo(..),
+ InstanceDec,
+ ParentName,
+ Arity,
+ Unlifted,
+ -- *** Name lookup
+ lookupTypeName, -- :: String -> Q (Maybe Name)
+ lookupValueName, -- :: String -> Q (Maybe Name)
+ -- *** Instance lookup
+ reifyInstances,
+ isInstance,
-- *** Roles lookup
reifyRoles,
-- *** Annotation lookup
reifyAnnotations, AnnLookup(..),
- -- * Typed expressions
- TExp, unType,
-
- -- * Names
- Name, NameSpace, -- Abstract
- -- ** Constructing names
- mkName, -- :: String -> Name
- newName, -- :: String -> Q Name
- -- ** Deconstructing names
- nameBase, -- :: Name -> String
- nameModule, -- :: Name -> Maybe String
- -- ** Built-in names
- tupleTypeName, tupleDataName, -- Int -> Name
- unboxedTupleTypeName, unboxedTupleDataName, -- :: Int -> Name
+ -- * Typed expressions
+ TExp, unType,
+
+ -- * Names
+ Name, NameSpace, -- Abstract
+ -- ** Constructing names
+ mkName, -- :: String -> Name
+ newName, -- :: String -> Q Name
+ -- ** Deconstructing names
+ nameBase, -- :: Name -> String
+ nameModule, -- :: Name -> Maybe String
+ -- ** Built-in names
+ tupleTypeName, tupleDataName, -- Int -> Name
+ unboxedTupleTypeName, unboxedTupleDataName, -- :: Int -> Name
-- * The algebraic data types
-- | The lowercase versions (/syntax operators/) of these constructors are
@@ -58,11 +58,11 @@ module Language.Haskell.TH(
-- quotations (@[| |]@) and splices (@$( ... )@)
-- ** Declarations
- Dec(..), Con(..), Clause(..),
- Strict(..), Foreign(..), Callconv(..), Safety(..), Pragma(..),
- Inline(..), RuleMatch(..), Phases(..), RuleBndr(..), AnnTarget(..),
- FunDep(..), FamFlavour(..), TySynEqn(..),
- Fixity(..), FixityDirection(..), defaultFixity, maxPrecedence,
+ Dec(..), Con(..), Clause(..),
+ Strict(..), Foreign(..), Callconv(..), Safety(..), Pragma(..),
+ Inline(..), RuleMatch(..), Phases(..), RuleBndr(..), AnnTarget(..),
+ FunDep(..), FamFlavour(..), TySynEqn(..),
+ Fixity(..), FixityDirection(..), defaultFixity, maxPrecedence,
-- ** Expressions
Exp(..), Match(..), Body(..), Guard(..), Stmt(..), Range(..), Lit(..),
-- ** Patterns
@@ -78,22 +78,22 @@ module Language.Haskell.TH(
-- ** Constructors lifted to 'Q'
-- *** Literals
- intPrimL, wordPrimL, floatPrimL, doublePrimL, integerL, rationalL,
- charL, stringL, stringPrimL,
+ intPrimL, wordPrimL, floatPrimL, doublePrimL, integerL, rationalL,
+ charL, stringL, stringPrimL,
-- *** Patterns
- litP, varP, tupP, conP, uInfixP, parensP, infixP,
- tildeP, bangP, asP, wildP, recP,
- listP, sigP, viewP,
- fieldPat,
+ litP, varP, tupP, conP, uInfixP, parensP, infixP,
+ tildeP, bangP, asP, wildP, recP,
+ listP, sigP, viewP,
+ fieldPat,
-- *** Pattern Guards
- normalB, guardedB, normalG, normalGE, patG, patGE, match, clause,
+ normalB, guardedB, normalG, normalGE, patG, patGE, match, clause,
-- *** Expressions
- dyn, global, varE, conE, litE, appE, uInfixE, parensE,
- infixE, infixApp, sectionL, sectionR,
- lamE, lam1E, lamCaseE, tupE, condE, multiIfE, letE, caseE, appsE,
- listE, sigE, recConE, recUpdE, stringE, fieldExp,
+ dyn, global, varE, conE, litE, appE, uInfixE, parensE,
+ infixE, infixApp, sectionL, sectionR,
+ lamE, lam1E, lamCaseE, tupE, condE, multiIfE, letE, caseE, appsE,
+ listE, sigE, recConE, recUpdE, stringE, fieldExp,
-- **** Ranges
fromE, fromThenE, fromToE, fromThenToE,
@@ -105,24 +105,24 @@ module Language.Haskell.TH(
bindS, letS, noBindS, parS,
-- *** Types
- forallT, varT, conT, appT, arrowT, equalityT, listT, tupleT, sigT, litT,
+ forallT, varT, conT, appT, arrowT, equalityT, listT, tupleT, sigT, litT,
promotedT, promotedTupleT, promotedNilT, promotedConsT,
-- **** Type literals
numTyLit, strTyLit,
-- **** Strictness
- isStrict, notStrict, strictType, varStrictType,
+ isStrict, notStrict, strictType, varStrictType,
-- **** Class Contexts
- cxt, normalC, recC, infixC, forallC,
+ cxt, classP, equalP, normalC, recC, infixC, forallC,
-- *** Kinds
- varK, conK, tupleK, arrowK, listK, appK, starK, constraintK,
+ varK, conK, tupleK, arrowK, listK, appK, starK, constraintK,
-- *** Roles
nominalR, representationalR, phantomR, inferR,
-- *** Top Level Declarations
-- **** Data
- valD, funD, tySynD, dataD, newtypeD,
+ valD, funD, tySynD, dataD, newtypeD,
-- **** Class
classD, instanceD, sigD,
-- **** Role annotations
@@ -138,7 +138,7 @@ module Language.Haskell.TH(
ruleVar, typedRuleVar,
pragInlD, pragSpecD, pragSpecInlD, pragSpecInstD, pragRuleD, pragAnnD,
- -- * Pretty-printer
+ -- * Pretty-printer
Ppr(..), pprint, pprExp, pprLit, pprPat, pprParendType
) where
diff --git a/libraries/template-haskell/Language/Haskell/TH/Lib.hs b/libraries/template-haskell/Language/Haskell/TH/Lib.hs
index 49baa96cde..3ac16d1dba 100644
--- a/libraries/template-haskell/Language/Haskell/TH/Lib.hs
+++ b/libraries/template-haskell/Language/Haskell/TH/Lib.hs
@@ -526,6 +526,22 @@ sigT t k
equalityT :: TypeQ
equalityT = return EqualityT
+{-# DEPRECATED classP "As of template-haskell-2.10, constraint predicates (Pred) are just types (Type), in keeping with ConstraintKinds. Please use 'conT' and 'appT'." #-}
+classP :: Name -> [Q Type] -> Q Pred
+classP cla tys
+ = do
+ tysl <- sequence tys
+ return (foldl AppT (ConT cla) tysl)
+
+{-# DEPRECATED equalP "As of template-haskell-2.10, constraint predicates (Pred) are just types (Type), in keeping with ConstraintKinds. Please see 'equalityT'." #-}
+equalP :: TypeQ -> TypeQ -> PredQ
+equalP tleft tright
+ = do
+ tleft1 <- tleft
+ tright1 <- tright
+ eqT <- equalityT
+ return (foldl AppT eqT [tleft1, tright1])
+
promotedT :: Name -> TypeQ
promotedT = return . PromotedT
diff --git a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs
index 589c66a530..3172cbbced 100644
--- a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs
+++ b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs
@@ -369,7 +369,7 @@ location = Q qLocation
-- a single 'Q' computation, but not about the order in which splices are run.
--
-- Note: for various murky reasons, stdout and stderr handles are not
--- necesarily flushed when the compiler finishes running, so you should
+-- necessarily flushed when the compiler finishes running, so you should
-- flush them yourself.
runIO :: IO a -> Q a
runIO m = Q (qRunIO m)