From c99d9aab415ad4aef9abdd8dc70a9063c0f6270c Mon Sep 17 00:00:00 2001
From: Ben Gamari <ben@smart-cactus.org>
Date: Wed, 26 Jun 2019 08:09:18 -0400
Subject: [PATCH] testsuite: Fix T16832

The test seems to have been missing the name of its script and didn't
build with HEAD. How it made it through CI is beyond me.
---
 testsuite/tests/typecheck/should_compile/T16832.hs | 9 +++++----
 testsuite/tests/typecheck/should_compile/all.T     | 2 +-
 2 files changed, 6 insertions(+), 5 deletions(-)

diff --git a/testsuite/tests/typecheck/should_compile/T16832.hs b/testsuite/tests/typecheck/should_compile/T16832.hs
index 8dcd40fe68d8..052a821c9b25 100644
--- a/testsuite/tests/typecheck/should_compile/T16832.hs
+++ b/testsuite/tests/typecheck/should_compile/T16832.hs
@@ -9,21 +9,22 @@
 
 module WorkingGenerics where
 import GHC.Generics
+import Data.Kind
 
--- type family DiffT (p :: * -> *) :: * -> *
+-- type family DiffT (p :: Type -> Type) :: Type -> Type
 
 data Void  deriving(Generic)
 
 class Diff a  where
-  type family Patch a :: *
+  type family Patch a :: Type
   type Patch a = GPatch (Rep a) a
 
   diff :: a -> a -> Patch a
   default diff :: (Generic a, GDiff (Rep a), Patch a ~ (GPatch (Rep a)) a) => a -> a -> Patch a
   diff a a' = gdiff (from a) (from a')
 
-class GDiff (gen :: * -> *)  where
-  type family GPatch gen :: * -> *
+class GDiff (gen :: Type -> Type)  where
+  type family GPatch gen :: Type -> Type
   gdiff :: gen a -> gen a -> (GPatch gen) a
 
 instance GDiff V1 where
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index 244aaa2ec471..9f5a976b9654 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -683,4 +683,4 @@ test('UnliftedNewtypesForall', normal, compile, [''])
 test('UnlifNewUnify', normal, compile, [''])
 test('UnliftedNewtypesLPFamily', normal, compile, [''])
 test('UnliftedNewtypesDifficultUnification', normal, compile, [''])
-test('T16832', normal, ghci_script, [''])
+test('T16832', normal, ghci_script, ['T16832.script'])
-- 
GitLab