[commit: testsuite] th-new: Fix test wibbles for new Template Haskell. (27c8361)

Geoffrey Mainland gmainlan at microsoft.com
Wed Jun 12 13:52:14 CEST 2013


Repository : ssh://darcs.haskell.org//srv/darcs/testsuite

On branch  : th-new

https://github.com/ghc/testsuite/commit/27c83617ddfbb5876b00b8ccab5e87caed800dc6

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

commit 27c83617ddfbb5876b00b8ccab5e87caed800dc6
Author: Geoffrey Mainland <mainland at apeiron.net>
Date:   Thu May 16 15:08:07 2013 +0100

    Fix test wibbles for new Template Haskell.
    
    Because splices are now run in the renamer, we do not get the same error context
    as we would when running in the type checker. In most cases we get less context,
    and in some cases I have added additional context. Error messages should at
    least tell the user that an error occurred in a splice; dropping context beyond
    that point is not judged a great loss.
    
    Note that we may now report only one error when multiple errors were reported
    before because splices are now run in the renamer.

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

 tests/ghci/scripts/T4127a.stderr    |    6 +++++
 tests/th/T2222.stderr               |    2 +-
 tests/th/T2597b.stderr              |    1 -
 tests/th/T3177a.stderr              |    6 +---
 tests/th/T3395.stderr               |    6 -----
 tests/th/T5358.stderr               |   36 +----------------------------------
 tests/th/T5795.stderr               |    1 -
 tests/th/T5971.stderr               |    1 -
 tests/th/T6114.stderr               |    5 ----
 tests/th/TH_1tuple.stderr           |    1 -
 tests/th/TH_dataD1.stderr           |    2 +
 tests/th/TH_runIO.stderr            |    1 -
 tests/th/TH_unresolvedInfix2.stderr |    8 +------
 13 files changed, 13 insertions(+), 63 deletions(-)

diff --git a/tests/ghci/scripts/T4127a.stderr b/tests/ghci/scripts/T4127a.stderr
index cc118a9..598bdbc 100644
--- a/tests/ghci/scripts/T4127a.stderr
+++ b/tests/ghci/scripts/T4127a.stderr
@@ -3,3 +3,9 @@
     Multiple declarations of ‛f’
     Declared at: <interactive>:3:32
                  <interactive>:3:68
+    In the Template Haskell quotation
+      [d| f = undefined
+          class Foo x where
+            f :: x -> x
+          instance Foo Int where
+            f = id |]
diff --git a/tests/th/T2222.stderr b/tests/th/T2222.stderr
index 7d90eb3..b0a7e9f 100644
--- a/tests/th/T2222.stderr
+++ b/tests/th/T2222.stderr
@@ -1,5 +1,5 @@
-inside d: t_0
 inside b: a_0
+inside d: GHC.Types.Bool
 type of c: GHC.Types.Bool
 inside f: GHC.Types.Bool
 type of e: GHC.Types.Bool
diff --git a/tests/th/T2597b.stderr b/tests/th/T2597b.stderr
index a9295eb..7d0a207 100644
--- a/tests/th/T2597b.stderr
+++ b/tests/th/T2597b.stderr
@@ -3,4 +3,3 @@ T2597b.hs:8:8:
     Empty stmt list in do-block
     When splicing a TH expression: do
     In the expression: $mkBug2
-    In an equation for ‛bug2’: bug2 = $mkBug2
diff --git a/tests/th/T3177a.stderr b/tests/th/T3177a.stderr
index 4e9d4dd..94d4f2e 100644
--- a/tests/th/T3177a.stderr
+++ b/tests/th/T3177a.stderr
@@ -1,9 +1,7 @@
 
-T3177a.hs:8:15:
+T3177a.hs:8:6:
     ‛Int’ is applied to too many type arguments
-    In the type ‛Int Int’
-    In the Template Haskell quotation [t| Int Int |]
-    In the first argument of ‛id’, namely ‛[t| Int Int |]’
+    In the type signature for ‛f’: f :: Int Int
 
 T3177a.hs:11:6:
     ‛Int’ is applied to too many type arguments
diff --git a/tests/th/T3395.stderr b/tests/th/T3395.stderr
index cd25afe..31a0623 100644
--- a/tests/th/T3395.stderr
+++ b/tests/th/T3395.stderr
@@ -9,9 +9,3 @@ T3395.hs:6:9:
         $ CompE
             [NoBindS (VarE $ mkName "undefined"),
              BindS (VarP $ mkName "r1") (VarE $ mkName "undefined")])
-    In an equation for ‛foo’:
-        foo
-          = $(return
-              $ CompE
-                  [NoBindS (VarE $ mkName "undefined"),
-                   BindS (VarP $ mkName "r1") (VarE $ mkName "undefined")])
diff --git a/tests/th/T5358.stderr b/tests/th/T5358.stderr
index bc4138f..cab4b97 100644
--- a/tests/th/T5358.stderr
+++ b/tests/th/T5358.stderr
@@ -1,35 +1,5 @@
 
-T5358.hs:7:1:
-    Couldn't match expected type ‛t1 -> t1’ with actual type ‛Int’
-    The equation(s) for ‛t1’ have one argument,
-    but its type ‛Int’ has none
-
-T5358.hs:8:1:
-    Couldn't match expected type ‛t0 -> t0’ with actual type ‛Int’
-    The equation(s) for ‛t2’ have one argument,
-    but its type ‛Int’ has none
-
-T5358.hs:10:13:
-    Couldn't match expected type ‛t -> a0’ with actual type ‛Int’
-    Relevant bindings include
-      prop_x1 :: t -> Bool (bound at T5358.hs:10:1)
-      x :: t (bound at T5358.hs:10:9)
-    The function ‛t1’ is applied to one argument,
-    but its type ‛Int’ has none
-    In the first argument of ‛(==)’, namely ‛t1 x’
-    In the expression: t1 x == t2 x
-
-T5358.hs:10:21:
-    Couldn't match expected type ‛t -> a0’ with actual type ‛Int’
-    Relevant bindings include
-      prop_x1 :: t -> Bool (bound at T5358.hs:10:1)
-      x :: t (bound at T5358.hs:10:9)
-    The function ‛t2’ is applied to one argument,
-    but its type ‛Int’ has none
-    In the second argument of ‛(==)’, namely ‛t2 x’
-    In the expression: t1 x == t2 x
-
-T5358.hs:12:15:
+T5358.hs:14:15:
     Exception when trying to run compile-time code:
       runTest called error: forall t_0 . t_0 -> GHC.Types.Bool
     Code: do { VarI _ t _ _ <- reify (mkName "prop_x1");
@@ -37,7 +7,3 @@ T5358.hs:12:15:
     In the expression:
       $(do { VarI _ t _ _ <- reify (mkName "prop_x1");
              error $ ("runTest called error: " ++ pprint t) })
-    In an equation for ‛runTests’:
-        runTests
-          = $(do { VarI _ t _ _ <- reify (mkName "prop_x1");
-                   error $ ("runTest called error: " ++ pprint t) })
diff --git a/tests/th/T5795.stderr b/tests/th/T5795.stderr
index 74d6c34..dd909f1 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 expression: ty
-    In the type signature for ‛f’: f :: $ty
diff --git a/tests/th/T5971.stderr b/tests/th/T5971.stderr
index 9f3f993..16eb00a 100644
--- a/tests/th/T5971.stderr
+++ b/tests/th/T5971.stderr
@@ -8,4 +8,3 @@ T5971.hs:6:7:
       $(newName "x" >>= varE)
     To see what the splice expanded to, use -ddump-splices
     In the expression: $(newName "x" >>= varE)
-    In a pattern binding: _ = $(newName "x" >>= varE)
diff --git a/tests/th/T6114.stderr b/tests/th/T6114.stderr
index e588ada..ff93cb2 100644
--- a/tests/th/T6114.stderr
+++ b/tests/th/T6114.stderr
@@ -10,8 +10,3 @@ T6114.hs:6:17:
              instanceType <- [t| $(varT xName) |];
              _ <- reifyInstances ''Eq [instanceType];
              .... })
-    In an equation for ‛instanceVar’:
-        instanceVar
-          = $(do { xName <- newName "x";
-                   instanceType <- [t| $(varT xName) |];
-                   .... })
diff --git a/tests/th/TH_1tuple.stderr b/tests/th/TH_1tuple.stderr
index 309bde5..cd6aaca 100644
--- a/tests/th/TH_1tuple.stderr
+++ b/tests/th/TH_1tuple.stderr
@@ -3,4 +3,3 @@ TH_1tuple.hs:11:7:
     Illegal 1-tuple type constructor
     When splicing a TH expression: 1 :: ()
     In the expression: $(sigE [| 1 |] (tupleT 1))
-    In an equation for ‛y’: y = $(sigE [| 1 |] (tupleT 1))
diff --git a/tests/th/TH_dataD1.stderr b/tests/th/TH_dataD1.stderr
index ddabee7..6c1ea38 100644
--- a/tests/th/TH_dataD1.stderr
+++ b/tests/th/TH_dataD1.stderr
@@ -1,3 +1,5 @@
 
 TH_dataD1.hs:8:13:
     Declaration splices are not permitted inside declaration brackets
+    In the Template Haskell quotation
+      [d| $(dataD [] (mkName "D") [] [normalC "K" []] []) |]
diff --git a/tests/th/TH_runIO.stderr b/tests/th/TH_runIO.stderr
index 6d7499a..14c3ec8 100644
--- a/tests/th/TH_runIO.stderr
+++ b/tests/th/TH_runIO.stderr
@@ -4,4 +4,3 @@ TH_runIO.hs:12:9:
       user error (hi)
     Code: runIO (fail "hi")
     In the expression: $(runIO (fail "hi"))
-    In an equation for ‛foo’: foo = $(runIO (fail "hi"))
diff --git a/tests/th/TH_unresolvedInfix2.stderr b/tests/th/TH_unresolvedInfix2.stderr
index fab508a..31f0605 100644
--- a/tests/th/TH_unresolvedInfix2.stderr
+++ b/tests/th/TH_unresolvedInfix2.stderr
@@ -1,5 +1,5 @@
 
-TH_unresolvedInfix2.hs:12:11:
+TH_unresolvedInfix2.hs:14:11:
     The operator ‛:+’ [infixl 6] of a section
         must have lower precedence than that of the operand,
           namely ‛:+’ [infixl 6]
@@ -15,9 +15,3 @@ TH_unresolvedInfix2.hs:12:11:
           plus = conE ...
           n = conE ...
         in infixE Nothing plus (Just $ uInfixE n plus n))
-    In an equation for ‛expr’:
-        expr
-          = $(let
-                plus = ...
-                ....
-              in infixE Nothing plus (Just $ uInfixE n plus n))





More information about the ghc-commits mailing list