[commit: ghc] master: Testsuite wibbles from fixing #8953 (99882ba)

git at git.haskell.org git at git.haskell.org
Sun Nov 2 03:53:28 UTC 2014


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/99882babf9bb2d73b972330b1cfa9495a029855b/ghc

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

commit 99882babf9bb2d73b972330b1cfa9495a029855b
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date:   Tue Oct 28 10:42:32 2014 -0400

    Testsuite wibbles from fixing #8953


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

99882babf9bb2d73b972330b1cfa9495a029855b
 testsuite/tests/th/T1835.stdout         |  2 +-
 testsuite/tests/th/T4188.stderr         | 15 ++++++++-----
 testsuite/tests/th/T8499.hs             |  2 +-
 testsuite/tests/th/T8884.stderr         |  2 +-
 testsuite/tests/th/T9692.stderr         |  2 +-
 testsuite/tests/th/TH_reifyDecl1.stderr | 39 +++++++++++++++++----------------
 testsuite/tests/th/TH_reifyDecl2.stderr |  3 ++-
 7 files changed, 35 insertions(+), 30 deletions(-)

diff --git a/testsuite/tests/th/T1835.stdout b/testsuite/tests/th/T1835.stdout
index ba8e65f..5b21c03 100644
--- a/testsuite/tests/th/T1835.stdout
+++ b/testsuite/tests/th/T1835.stdout
@@ -1,4 +1,4 @@
-class GHC.Classes.Eq a_0 => Main.MyClass a_0
+class GHC.Classes.Eq a_0 => Main.MyClass (a_0 :: *)
 instance Main.MyClass Main.Foo
 instance Main.MyClass Main.Baz
 instance GHC.Classes.Eq a_1 => Main.MyClass (Main.Quux a_1)
diff --git a/testsuite/tests/th/T4188.stderr b/testsuite/tests/th/T4188.stderr
index 02b9977..bea2e80 100644
--- a/testsuite/tests/th/T4188.stderr
+++ b/testsuite/tests/th/T4188.stderr
@@ -1,6 +1,9 @@
-data T4188.T1 a_0 = forall b_1 . T4188.MkT1 a_0 b_1
-data T4188.T2 a_0
-    = forall b_1 . (T4188.C a_0, T4188.C b_1) => T4188.MkT2 a_0 b_1
-data T4188.T3 x_0
-    = forall x_1 y_2 . (x_0 ~ (x_1, y_2), T4188.C x_1, T4188.C y_2) =>
-                       T4188.MkT3 x_1 y_2
+data T4188.T1 (a_0 :: *) = forall (b_1 :: *) . T4188.MkT1 a_0 b_1
+data T4188.T2 (a_0 :: *)
+    = forall (b_1 :: *) . (T4188.C a_0, T4188.C b_1) =>
+                          T4188.MkT2 a_0 b_1
+data T4188.T3 (x_0 :: *)
+    = forall (x_1 :: *) (y_2 :: *) . (x_0 ~ (x_1, y_2),
+                                      T4188.C x_1,
+                                      T4188.C y_2) =>
+                                     T4188.MkT3 x_1 y_2
diff --git a/testsuite/tests/th/T8499.hs b/testsuite/tests/th/T8499.hs
index 353bb9f..7829e99 100644
--- a/testsuite/tests/th/T8499.hs
+++ b/testsuite/tests/th/T8499.hs
@@ -5,7 +5,7 @@ module T8499 where
 
 import Language.Haskell.TH
 
-$( do TyConI (DataD _ _ [PlainTV tvb_a] _ _) <- reify ''Maybe
+$( do TyConI (DataD _ _ [KindedTV tvb_a _] _ _) <- reify ''Maybe
       my_a <- newName "a"
       return [TySynD (mkName "SMaybe")
                      [KindedTV my_a (AppT (ConT ''Maybe) (VarT tvb_a))]
diff --git a/testsuite/tests/th/T8884.stderr b/testsuite/tests/th/T8884.stderr
index 3c45d0e..24fc15a 100644
--- a/testsuite/tests/th/T8884.stderr
+++ b/testsuite/tests/th/T8884.stderr
@@ -1,3 +1,3 @@
 type family T8884.Foo (a_0 :: k_1) :: k_1 where T8884.Foo x_2 = x_2
 type family T8884.Baz (a_0 :: k_1) :: *
-type instance T8884.Baz x_0 = x_0
+type instance T8884.Baz (x_0 :: *) = x_0
diff --git a/testsuite/tests/th/T9692.stderr b/testsuite/tests/th/T9692.stderr
index e62c8c5..ffa5536 100644
--- a/testsuite/tests/th/T9692.stderr
+++ b/testsuite/tests/th/T9692.stderr
@@ -1,2 +1,2 @@
 data family T9692.F (a_0 :: k_1) (b_2 :: k_3) :: *
-data instance T9692.F GHC.Types.Int x_4 = T9692.FInt x_4
+data instance T9692.F GHC.Types.Int (x_4 :: *) = T9692.FInt x_4
diff --git a/testsuite/tests/th/TH_reifyDecl1.stderr b/testsuite/tests/th/TH_reifyDecl1.stderr
index 9c3b6da..bf5a819 100644
--- a/testsuite/tests/th/TH_reifyDecl1.stderr
+++ b/testsuite/tests/th/TH_reifyDecl1.stderr
@@ -1,35 +1,36 @@
 data TH_reifyDecl1.T = TH_reifyDecl1.A | TH_reifyDecl1.B
-data TH_reifyDecl1.R a_0 = TH_reifyDecl1.C a_0 | TH_reifyDecl1.D
-data TH_reifyDecl1.List a_0
+data TH_reifyDecl1.R (a_0 :: *)
+    = TH_reifyDecl1.C a_0 | TH_reifyDecl1.D
+data TH_reifyDecl1.List (a_0 :: *)
     = TH_reifyDecl1.Nil
     | TH_reifyDecl1.Cons a_0 (TH_reifyDecl1.List a_0)
-data TH_reifyDecl1.Tree a_0
+data TH_reifyDecl1.Tree (a_0 :: *)
     = TH_reifyDecl1.Leaf
     | (TH_reifyDecl1.Tree a_0) TH_reifyDecl1.:+: (TH_reifyDecl1.Tree a_0)
 type TH_reifyDecl1.IntList = [GHC.Types.Int]
 newtype TH_reifyDecl1.Length = TH_reifyDecl1.Length GHC.Types.Int
-Constructor from TH_reifyDecl1.Tree: TH_reifyDecl1.Leaf :: forall a_0 . TH_reifyDecl1.Tree a_0
-Class op from TH_reifyDecl1.C1: TH_reifyDecl1.m1 :: forall a_0 . TH_reifyDecl1.C1 a_0 =>
-                                                                 a_0 -> GHC.Types.Int
+Constructor from TH_reifyDecl1.Tree: TH_reifyDecl1.Leaf :: forall (a_0 :: *) . TH_reifyDecl1.Tree a_0
+Class op from TH_reifyDecl1.C1: TH_reifyDecl1.m1 :: forall (a_0 :: *) . TH_reifyDecl1.C1 a_0 =>
+                                                                        a_0 -> GHC.Types.Int
                                 infixl 3 TH_reifyDecl1.m1
-class TH_reifyDecl1.C1 a_0
-    where TH_reifyDecl1.m1 :: forall a_0 . TH_reifyDecl1.C1 a_0 =>
-                                           a_0 -> GHC.Types.Int
-class TH_reifyDecl1.C2 a_0
-    where TH_reifyDecl1.m2 :: forall a_0 . TH_reifyDecl1.C2 a_0 =>
-                                           a_0 -> GHC.Types.Int
+class TH_reifyDecl1.C1 (a_0 :: *)
+    where TH_reifyDecl1.m1 :: forall (a_0 :: *) . TH_reifyDecl1.C1 a_0 =>
+                                                  a_0 -> GHC.Types.Int
+class TH_reifyDecl1.C2 (a_0 :: *)
+    where TH_reifyDecl1.m2 :: forall (a_0 :: *) . TH_reifyDecl1.C2 a_0 =>
+                                                  a_0 -> GHC.Types.Int
 instance TH_reifyDecl1.C2 GHC.Types.Int
-class TH_reifyDecl1.C3 a_0
+class TH_reifyDecl1.C3 (a_0 :: *)
 instance TH_reifyDecl1.C3 GHC.Types.Int
-type family TH_reifyDecl1.AT1 a_0 :: *
+type family TH_reifyDecl1.AT1 (a_0 :: *) :: *
 type instance TH_reifyDecl1.AT1 GHC.Types.Int = GHC.Types.Bool
-data family TH_reifyDecl1.AT2 a_0 :: *
+data family TH_reifyDecl1.AT2 (a_0 :: *) :: *
 data instance TH_reifyDecl1.AT2 GHC.Types.Int
     = TH_reifyDecl1.AT2Int
-type family TH_reifyDecl1.TF1 a_0 :: *
-type family TH_reifyDecl1.TF2 a_0 :: *
+type family TH_reifyDecl1.TF1 (a_0 :: *) :: *
+type family TH_reifyDecl1.TF2 (a_0 :: *) :: *
 type instance TH_reifyDecl1.TF2 GHC.Types.Bool = GHC.Types.Bool
-data family TH_reifyDecl1.DF1 a_0 :: *
-data family TH_reifyDecl1.DF2 a_0 :: *
+data family TH_reifyDecl1.DF1 (a_0 :: *) :: *
+data family TH_reifyDecl1.DF2 (a_0 :: *) :: *
 data instance TH_reifyDecl1.DF2 GHC.Types.Bool
     = TH_reifyDecl1.DBool
diff --git a/testsuite/tests/th/TH_reifyDecl2.stderr b/testsuite/tests/th/TH_reifyDecl2.stderr
index 3711f8e..64436f8 100644
--- a/testsuite/tests/th/TH_reifyDecl2.stderr
+++ b/testsuite/tests/th/TH_reifyDecl2.stderr
@@ -1 +1,2 @@
-data GHC.Base.Maybe a_0 = GHC.Base.Nothing | GHC.Base.Just a_0
+data GHC.Base.Maybe (a_0 :: *)
+    = GHC.Base.Nothing | GHC.Base.Just a_0



More information about the ghc-commits mailing list