From 7514865a205ff8eff568d0f6e9e05c2b95418260 Mon Sep 17 00:00:00 2001
From: "Dr. ERDI Gergo" <gergo@erdi.hu>
Date: Wed, 19 Mar 2014 21:44:38 +0800
Subject: [PATCH] Update expected test outputs to match new format of
 pretty-printing interface contents

---
 .../indexed-types/should_compile/T3017.stderr |  2 +-
 .../tests/roles/should_compile/Roles1.stderr  | 70 +++++++++----------
 .../tests/roles/should_compile/Roles2.stderr  | 20 +++---
 testsuite/tests/roles/should_compile/all.T    |  6 +-
 .../typecheck/should_compile/tc231.stderr     |  7 +-
 5 files changed, 52 insertions(+), 53 deletions(-)

diff --git a/testsuite/tests/indexed-types/should_compile/T3017.stderr b/testsuite/tests/indexed-types/should_compile/T3017.stderr
index d11fad837711..20190471ae52 100644
--- a/testsuite/tests/indexed-types/should_compile/T3017.stderr
+++ b/testsuite/tests/indexed-types/should_compile/T3017.stderr
@@ -14,7 +14,7 @@ TYPE CONSTRUCTORS
     No C type associated
     Roles: [representational]
     RecFlag NonRecursive, Promotable
-    = L :: forall a. [a] -> ListColl a Stricts: _
+    = L :: [a] -> ListColl a Stricts: _
     FamilyInstance: none
 COERCION AXIOMS
   axiom Foo.TFCo:R:ElemListColl :: Elem (ListColl a) = a
diff --git a/testsuite/tests/roles/should_compile/Roles1.stderr b/testsuite/tests/roles/should_compile/Roles1.stderr
index e1808e8b2b1c..cd027f13f2c7 100644
--- a/testsuite/tests/roles/should_compile/Roles1.stderr
+++ b/testsuite/tests/roles/should_compile/Roles1.stderr
@@ -2,53 +2,53 @@ TYPE SIGNATURES
 TYPE CONSTRUCTORS
   T1 :: * -> *
   data T1 a
-      No C type associated
-      Roles: [nominal]
-      RecFlag NonRecursive, Promotable
-      = K1 :: forall a. a -> T1 a Stricts: _
-      FamilyInstance: none
+    No C type associated
+    Roles: [nominal]
+    RecFlag NonRecursive, Promotable
+    = K1 :: forall a. a -> T1 a Stricts: _
+    FamilyInstance: none
   T2 :: * -> *
   data T2 a
-      No C type associated
-      Roles: [representational]
-      RecFlag NonRecursive, Promotable
-      = K2 :: forall a. a -> T2 a Stricts: _
-      FamilyInstance: none
+    No C type associated
+    Roles: [representational]
+    RecFlag NonRecursive, Promotable
+    = K2 :: forall a. a -> T2 a Stricts: _
+    FamilyInstance: none
   T3 :: k -> *
   data T3 (k::BOX) (a::k)
-      No C type associated
-      Roles: [nominal, phantom]
-      RecFlag NonRecursive, Not promotable
-      = K3 :: forall (k::BOX) (a::k). T3 k a
-      FamilyInstance: none
+    No C type associated
+    Roles: [nominal, phantom]
+    RecFlag NonRecursive, Not promotable
+    = K3 :: forall (k::BOX) (a::k). T3 k a
+    FamilyInstance: none
   T4 :: (* -> *) -> * -> *
   data T4 (a::* -> *) b
-      No C type associated
-      Roles: [nominal, nominal]
-      RecFlag NonRecursive, Not promotable
-      = K4 :: forall (a::* -> *) b. (a b) -> T4 a b Stricts: _
-      FamilyInstance: none
+    No C type associated
+    Roles: [nominal, nominal]
+    RecFlag NonRecursive, Not promotable
+    = K4 :: forall (a::* -> *) b. (a b) -> T4 a b Stricts: _
+    FamilyInstance: none
   T5 :: * -> *
   data T5 a
-      No C type associated
-      Roles: [representational]
-      RecFlag NonRecursive, Promotable
-      = K5 :: forall a. a -> T5 a Stricts: _
-      FamilyInstance: none
+    No C type associated
+    Roles: [representational]
+    RecFlag NonRecursive, Promotable
+    = K5 :: forall a. a -> T5 a Stricts: _
+    FamilyInstance: none
   T6 :: k -> *
   data T6 (k::BOX) (a::k)
-      No C type associated
-      Roles: [nominal, phantom]
-      RecFlag NonRecursive, Not promotable
-      = K6 :: forall (k::BOX) (a::k). T6 k a
-      FamilyInstance: none
+    No C type associated
+    Roles: [nominal, phantom]
+    RecFlag NonRecursive, Not promotable
+    = K6 :: forall (k::BOX) (a::k). T6 k a
+    FamilyInstance: none
   T7 :: k -> * -> *
   data T7 (k::BOX) (a::k) b
-      No C type associated
-      Roles: [nominal, phantom, representational]
-      RecFlag NonRecursive, Not promotable
-      = K7 :: forall (k::BOX) (a::k) b. b -> T7 k a b Stricts: _
-      FamilyInstance: none
+    No C type associated
+    Roles: [nominal, phantom, representational]
+    RecFlag NonRecursive, Not promotable
+    = K7 :: forall (k::BOX) (a::k) b. b -> T7 k a b Stricts: _
+    FamilyInstance: none
 COERCION AXIOMS
 Dependent modules: []
 Dependent packages: [base, ghc-prim, integer-gmp]
diff --git a/testsuite/tests/roles/should_compile/Roles2.stderr b/testsuite/tests/roles/should_compile/Roles2.stderr
index ac7a94bbfa21..f5bcbe682951 100644
--- a/testsuite/tests/roles/should_compile/Roles2.stderr
+++ b/testsuite/tests/roles/should_compile/Roles2.stderr
@@ -2,18 +2,18 @@ TYPE SIGNATURES
 TYPE CONSTRUCTORS
   T1 :: * -> *
   data T1 a
-      No C type associated
-      Roles: [representational]
-      RecFlag NonRecursive, Not promotable
-      = K1 :: forall a. (IO a) -> T1 a Stricts: _
-      FamilyInstance: none
+    No C type associated
+    Roles: [representational]
+    RecFlag NonRecursive, Not promotable
+    = K1 :: forall a. (IO a) -> T1 a Stricts: _
+    FamilyInstance: none
   T2 :: * -> *
   data T2 a
-      No C type associated
-      Roles: [representational]
-      RecFlag NonRecursive, Not promotable
-      = K2 :: forall a. (FunPtr a) -> T2 a Stricts: _
-      FamilyInstance: none
+    No C type associated
+    Roles: [representational]
+    RecFlag NonRecursive, Not promotable
+    = K2 :: forall a. (FunPtr a) -> T2 a Stricts: _
+    FamilyInstance: none
 COERCION AXIOMS
 Dependent modules: []
 Dependent packages: [base, ghc-prim, integer-gmp]
diff --git a/testsuite/tests/roles/should_compile/all.T b/testsuite/tests/roles/should_compile/all.T
index a016de319dca..f77e61f55d20 100644
--- a/testsuite/tests/roles/should_compile/all.T
+++ b/testsuite/tests/roles/should_compile/all.T
@@ -1,7 +1,7 @@
-test('Roles1', only_ways('normal'), compile, ['-ddump-tc'])
-test('Roles2', only_ways('normal'), compile, ['-ddump-tc'])
+test('Roles1', only_ways('normal'), compile, ['-ddump-tc -fprint-explicit-foralls'])
+test('Roles2', only_ways('normal'), compile, ['-ddump-tc -fprint-explicit-foralls'])
 test('Roles3', only_ways('normal'), compile, ['-ddump-tc'])
 test('Roles4', only_ways('normal'), compile, ['-ddump-tc'])
 test('Roles13', only_ways('normal'), compile, ['-ddump-simpl -dsuppress-uniques'])
 test('Roles14', only_ways('normal'), compile, ['-ddump-tc'])
-test('RolesIArray', only_ways('normal'), compile, [''])
\ No newline at end of file
+test('RolesIArray', only_ways('normal'), compile, [''])
diff --git a/testsuite/tests/typecheck/should_compile/tc231.stderr b/testsuite/tests/typecheck/should_compile/tc231.stderr
index 4334d62a42e2..16ddddac09f5 100644
--- a/testsuite/tests/typecheck/should_compile/tc231.stderr
+++ b/testsuite/tests/typecheck/should_compile/tc231.stderr
@@ -10,21 +10,20 @@ TYPE CONSTRUCTORS
     No C type associated
     Roles: [representational, representational, representational]
     RecFlag NonRecursive, Promotable
-    = Node :: forall s a chain. s -> a -> chain -> Q s a chain
-        Stricts: _ _ _
+    = Node :: s -> a -> chain -> Q s a chain Stricts: _ _ _
     FamilyInstance: none
   Z :: * -> *
   data Z a
     No C type associated
     Roles: [representational]
     RecFlag NonRecursive, Promotable
-    = Z :: forall a. a -> Z a Stricts: _
+    = Z :: a -> Z a Stricts: _
     FamilyInstance: none
   Zork :: * -> * -> * -> Constraint
   class Zork s a b | a -> b
     Roles: [nominal, nominal, nominal]
     RecFlag NonRecursive
-    huh :: forall chain. Q s a chain -> ST s ()
+    huh :: Q s a chain -> ST s ()
 COERCION AXIOMS
   axiom ShouldCompile.NTCo:Zork ::
       Zork s a b = forall chain. Q s a chain -> ST s ()
-- 
GitLab