[commit: testsuite] master: Error message wibbles (688178e)

git at git.haskell.org git at git.haskell.org
Mon Nov 25 16:59:28 UTC 2013


Repository : ssh://git@git.haskell.org/testsuite

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/688178e40e95d82168d706d2ef65f3dd7f5d4bf1/testsuite

>---------------------------------------------------------------

commit 688178e40e95d82168d706d2ef65f3dd7f5d4bf1
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Mon Nov 25 16:59:17 2013 +0000

    Error message wibbles


>---------------------------------------------------------------

688178e40e95d82168d706d2ef65f3dd7f5d4bf1
 tests/th/T2597b.stderr              |    2 +-
 tests/th/T3395.stderr               |    2 +-
 tests/th/T3600.stderr               |    2 +-
 tests/th/T5358.stderr               |    2 +-
 tests/th/T5508.stderr               |    2 +-
 tests/th/T5795.stderr               |    1 -
 tests/th/T5971.stderr               |    2 --
 tests/th/T6114.stderr               |    2 +-
 tests/th/T7276.stderr               |    3 +--
 tests/th/T7276a.stdout              |    4 +---
 tests/th/T7532.stderr               |    4 ----
 tests/th/T7667a.stderr              |    2 +-
 tests/th/T8412.stderr               |    1 -
 tests/th/TH_1tuple.stderr           |    2 +-
 tests/th/TH_runIO.stderr            |    2 +-
 tests/th/TH_unresolvedInfix2.stderr |    6 ------
 16 files changed, 11 insertions(+), 28 deletions(-)

diff --git a/tests/th/T2597b.stderr b/tests/th/T2597b.stderr
index 7d0a207..99ff754 100644
--- a/tests/th/T2597b.stderr
+++ b/tests/th/T2597b.stderr
@@ -2,4 +2,4 @@
 T2597b.hs:8:8:
     Empty stmt list in do-block
     When splicing a TH expression: do
-    In the expression: $mkBug2
+    In the splice: $mkBug2
diff --git a/tests/th/T3395.stderr b/tests/th/T3395.stderr
index 31a0623..b3d9874 100644
--- a/tests/th/T3395.stderr
+++ b/tests/th/T3395.stderr
@@ -4,7 +4,7 @@ T3395.hs:6:9:
       r1 <- undefined
     (It should be an expression.)
     When splicing a TH expression: [r1 <- undefined | undefined]
-    In the expression:
+    In the splice:
       $(return
         $ CompE
             [NoBindS (VarE $ mkName "undefined"),
diff --git a/tests/th/T3600.stderr b/tests/th/T3600.stderr
index 8ab357d..2cd8332 100644
--- a/tests/th/T3600.stderr
+++ b/tests/th/T3600.stderr
@@ -2,4 +2,4 @@ T3600.hs:1:1: Splicing declarations
     test
   ======>
     T3600.hs:5:3-6
-    myFunction = (testFun1 [], testFun2 "", testFun2 "x")
+    myFunction = (testFun1 [], testFun2 [], testFun2 "x")
diff --git a/tests/th/T5358.stderr b/tests/th/T5358.stderr
index cab4b97..fd7e32c 100644
--- a/tests/th/T5358.stderr
+++ b/tests/th/T5358.stderr
@@ -4,6 +4,6 @@ T5358.hs:14:15:
       runTest called error: forall t_0 . t_0 -> GHC.Types.Bool
     Code: do { VarI _ t _ _ <- reify (mkName "prop_x1");
                ($) error ((++) "runTest called error: " pprint t) }
-    In the expression:
+    In the splice:
       $(do { VarI _ t _ _ <- reify (mkName "prop_x1");
              error $ ("runTest called error: " ++ pprint t) })
diff --git a/tests/th/T5508.stderr b/tests/th/T5508.stderr
index f1a553a..3cd9bf2 100644
--- a/tests/th/T5508.stderr
+++ b/tests/th/T5508.stderr
@@ -2,6 +2,6 @@ T5508.hs:(7,9)-(9,28): Splicing expression
     do { let x = mkName "x"
              v = return (LamE [VarP x] $ VarE x);
          [| $v . id |]
-         pending(rn) [(splice, v)] }
+         pending(rn) [<splice, v>] }
   ======>
     ((\ x -> x) . id)
diff --git a/tests/th/T5795.stderr b/tests/th/T5795.stderr
index 7093492..757ba72 100644
--- a/tests/th/T5795.stderr
+++ b/tests/th/T5795.stderr
@@ -4,4 +4,3 @@ T5795.hs:9:6:
       ‛ty’ is used in a top-level splice or annotation,
       and must be imported, not defined locally
     In the splice: $ty
-    To see what the splice expanded to, use -ddump-splices
diff --git a/tests/th/T5971.stderr b/tests/th/T5971.stderr
index e6538c0..9d647d1 100644
--- a/tests/th/T5971.stderr
+++ b/tests/th/T5971.stderr
@@ -5,5 +5,3 @@ T5971.hs:6:7:
       perhaps via newName, but did not bind it
       If that's it, then -ddump-splices might be useful
     In the splice: $(newName "x" >>= varE)
-    To see what the splice expanded to, use -ddump-splices
-    In the expression: $(newName "x" >>= varE)
diff --git a/tests/th/T6114.stderr b/tests/th/T6114.stderr
index ff93cb2..6267aa6 100644
--- a/tests/th/T6114.stderr
+++ b/tests/th/T6114.stderr
@@ -5,7 +5,7 @@ T6114.hs:6:17:
       perhaps via newName, but did not bind it
       If that's it, then -ddump-splices might be useful
     In the argument of reifyInstances: GHC.Classes.Eq x_0
-    In the expression:
+    In the splice:
       $(do { xName <- newName "x";
              instanceType <- [t| $(varT xName) |];
              _ <- reifyInstances ''Eq [instanceType];
diff --git a/tests/th/T7276.stderr b/tests/th/T7276.stderr
index d1bb7c7..7b76966 100644
--- a/tests/th/T7276.stderr
+++ b/tests/th/T7276.stderr
@@ -4,6 +4,5 @@ T7276.hs:6:8:
                   with ‛Language.Haskell.TH.Syntax.Exp’
     Expected type: Language.Haskell.TH.Lib.ExpQ
       Actual type: Language.Haskell.TH.Lib.DecsQ
-    In the Template Haskell quotation [d| y = 3 |]
     In the expression: [d| y = 3 |]
-    In the expression: $([d| y = 3 |])
+    In the splice: $([d| y = 3 |])
diff --git a/tests/th/T7276a.stdout b/tests/th/T7276a.stdout
index 15ece93..2edeaae 100644
--- a/tests/th/T7276a.stdout
+++ b/tests/th/T7276a.stdout
@@ -3,7 +3,6 @@
     Couldn't match type ‛[Dec]’ with ‛Exp’
     Expected type: Q Exp
       Actual type: DecsQ
-    In the Template Haskell quotation [d| a = () |]
     In the expression: [d| a = () |] :: Q Exp
     In an equation for ‛x’: x = [d| a = () |] :: Q Exp
 
@@ -13,9 +12,8 @@
     Couldn't match type ‛[Dec]’ with ‛Exp’
     Expected type: Q Exp
       Actual type: DecsQ
-    In the Template Haskell quotation [d| a = () |]
     In the expression: [d| a = () |] :: Q Exp
     In an equation for ‛x’: x = [d| a = () |] :: Q Exp
 (deferred type error)
     Code: x
-    In the expression: $x
+    In the splice: $x
diff --git a/tests/th/T7532.stderr b/tests/th/T7532.stderr
index 840be3a..0890ae2 100644
--- a/tests/th/T7532.stderr
+++ b/tests/th/T7532.stderr
@@ -3,10 +3,6 @@
 instance C Bool where
   data D Bool = T7532.MkD
 
-
-==================== Renamer ====================
-$bang
-
 T7532.hs:1:1: Splicing declarations
     bang
   ======>
diff --git a/tests/th/T7667a.stderr b/tests/th/T7667a.stderr
index b8258cb..7e85d06 100644
--- a/tests/th/T7667a.stderr
+++ b/tests/th/T7667a.stderr
@@ -2,4 +2,4 @@
 T7667a.hs:8:12:
     Illegal variable name: ‛False’
     When splicing a TH expression: False
-    In the expression: $(return $ VarE (mkName "False"))
+    In the splice: $(return $ VarE (mkName "False"))
diff --git a/tests/th/T8412.stderr b/tests/th/T8412.stderr
index 8def784..64e2d41 100644
--- a/tests/th/T8412.stderr
+++ b/tests/th/T8412.stderr
@@ -2,4 +2,3 @@
 T8412.hs:5:12:
     Illegal literal in type (type literals must not be negative): -1
     In the splice: $(return $ LitT $ NumTyLit (- 1))
-    To see what the splice expanded to, use -ddump-splices
diff --git a/tests/th/TH_1tuple.stderr b/tests/th/TH_1tuple.stderr
index cd6aaca..4e1d38b 100644
--- a/tests/th/TH_1tuple.stderr
+++ b/tests/th/TH_1tuple.stderr
@@ -2,4 +2,4 @@
 TH_1tuple.hs:11:7:
     Illegal 1-tuple type constructor
     When splicing a TH expression: 1 :: ()
-    In the expression: $(sigE [| 1 |] (tupleT 1))
+    In the splice: $(sigE [| 1 |] (tupleT 1))
diff --git a/tests/th/TH_runIO.stderr b/tests/th/TH_runIO.stderr
index 14c3ec8..8173e83 100644
--- a/tests/th/TH_runIO.stderr
+++ b/tests/th/TH_runIO.stderr
@@ -3,4 +3,4 @@ TH_runIO.hs:12:9:
     Exception when trying to run compile-time code:
       user error (hi)
     Code: runIO (fail "hi")
-    In the expression: $(runIO (fail "hi"))
+    In the splice: $(runIO (fail "hi"))
diff --git a/tests/th/TH_unresolvedInfix2.stderr b/tests/th/TH_unresolvedInfix2.stderr
index 30b1aa4..4baa35a 100644
--- a/tests/th/TH_unresolvedInfix2.stderr
+++ b/tests/th/TH_unresolvedInfix2.stderr
@@ -6,12 +6,6 @@ TH_unresolvedInfix2.hs:14:11:
         in the section: ‛:+ N :+ N’
     In the splice:
       $(let
-          plus = conE ':+
-          n = conE 'N
-        in infixE Nothing plus (Just $ uInfixE n plus n))
-    To see what the splice expanded to, use -ddump-splices
-    In the expression:
-      $(let
           plus = conE ...
           n = conE ...
         in infixE Nothing plus (Just $ uInfixE n plus n))



More information about the ghc-commits mailing list