summaryrefslogtreecommitdiff
path: root/testsuite/tests/dependent
diff options
context:
space:
mode:
authorRichard Eisenberg <rae@cs.brynmawr.edu>2018-04-02 15:32:04 -0400
committerRichard Eisenberg <rae@cs.brynmawr.edu>2018-04-02 17:24:29 -0400
commitd8d4266bf73790f65b223ec16f645763eaed8be3 (patch)
treed43a1607c057f2d56b862ced3ca4f0012d0f4986 /testsuite/tests/dependent
parentddf895577173106646cfc6f6d21be3d5651067bc (diff)
downloadhaskell-d8d4266bf73790f65b223ec16f645763eaed8be3.tar.gz
Fix #14991.
It turns out that solveEqualities really does need to use simpl_top. I thought that solveWanteds would be enough, and no existing test case showed up the different. #14991 shows that we need simpl_top. Easy enough to fix. test case: dependent/should_compile/T14991
Diffstat (limited to 'testsuite/tests/dependent')
-rw-r--r--testsuite/tests/dependent/should_compile/T14991.hs34
-rw-r--r--testsuite/tests/dependent/should_compile/all.T1
2 files changed, 35 insertions, 0 deletions
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, [''])