summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--compiler/typecheck/TcSimplify.hs4
-rw-r--r--compiler/typecheck/TcTyClsDecls.hs2
-rw-r--r--testsuite/tests/dependent/should_compile/T14991.hs34
-rw-r--r--testsuite/tests/dependent/should_compile/all.T1
4 files changed, 39 insertions, 2 deletions
diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs
index 7307f74396..ccb7ef5056 100644
--- a/compiler/typecheck/TcSimplify.hs
+++ b/compiler/typecheck/TcSimplify.hs
@@ -165,7 +165,9 @@ solveEqualities thing_inside
= checkNoErrs $ -- See Note [Fail fast on kind errors]
do { (result, wanted) <- captureConstraints thing_inside
; traceTc "solveEqualities {" $ text "wanted = " <+> ppr wanted
- ; final_wc <- runTcSEqualities $ solveWanteds wanted
+ ; final_wc <- runTcSEqualities $ simpl_top wanted
+ -- NB: Use simpl_top here so that we potentially default RuntimeRep
+ -- vars to LiftedRep. This is needed to avoid #14991.
; traceTc "End solveEqualities }" empty
; traceTc "reportAllUnsolved {" empty
diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs
index 6598942533..cdcc3bda01 100644
--- a/compiler/typecheck/TcTyClsDecls.hs
+++ b/compiler/typecheck/TcTyClsDecls.hs
@@ -1485,7 +1485,7 @@ So, the kind-checker must return both the new args (that is, Type
Because we don't need this information in the kind-checking phase of
checking closed type families, we don't require these extra pieces of
-information in tc_fam_ty_pats. See also Note [tc_fam_ty_pats vs tcFamTyPats].
+information in tc_fam_ty_pats.
Note [Failing early in kcDataDefn]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
diff --git a/testsuite/tests/dependent/should_compile/T14991.hs b/testsuite/tests/dependent/should_compile/T14991.hs
new file mode 100644
index 0000000000..f435c37690
--- /dev/null
+++ b/testsuite/tests/dependent/should_compile/T14991.hs
@@ -0,0 +1,34 @@
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE TypeOperators #-}
+{-# LANGUAGE UndecidableInstances #-}
+module T14991 where
+
+import Data.Kind
+
+type family Promote (k :: Type) :: Type
+type family PromoteX (a :: k) :: Promote k
+
+type family Demote (k :: Type) :: Type
+type family DemoteX (a :: k) :: Demote k
+
+-----
+-- Type
+-----
+
+type instance Demote Type = Type
+type instance Promote Type = Type
+
+type instance DemoteX (a :: Type) = Demote a
+type instance PromoteX (a :: Type) = Promote a
+
+-----
+-- Arrows
+-----
+
+data TyFun :: Type -> Type -> Type
+type a ~> b = TyFun a b -> Type
+infixr 0 ~>
+
+type instance Demote (a ~> b) = DemoteX a -> DemoteX b
+type instance Promote (a -> b) = PromoteX a ~> PromoteX b
diff --git a/testsuite/tests/dependent/should_compile/all.T b/testsuite/tests/dependent/should_compile/all.T
index 070e1203f8..701e187b36 100644
--- a/testsuite/tests/dependent/should_compile/all.T
+++ b/testsuite/tests/dependent/should_compile/all.T
@@ -34,3 +34,4 @@ test('T14556', normal, compile, [''])
test('T14720', normal, compile, [''])
test('T14066a', normal, compile, [''])
test('T14749', normal, compile, [''])
+test('T14991', normal, compile, [''])