[commit: ghc] master: Add missing T11408.hs (3b6a490)

git at git.haskell.org git at git.haskell.org
Sat Jan 16 23:52:00 UTC 2016


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/3b6a4909ff579507a7f9527264e0cb8464fbe555/ghc

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

commit 3b6a4909ff579507a7f9527264e0cb8464fbe555
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Sat Jan 16 23:51:42 2016 +0000

    Add missing T11408.hs


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

3b6a4909ff579507a7f9527264e0cb8464fbe555
 .../tests/indexed-types/should_compile/T11408.hs   | 23 ++++++++++++++++++++++
 1 file changed, 23 insertions(+)

diff --git a/testsuite/tests/indexed-types/should_compile/T11408.hs b/testsuite/tests/indexed-types/should_compile/T11408.hs
new file mode 100644
index 0000000..df63c67
--- /dev/null
+++ b/testsuite/tests/indexed-types/should_compile/T11408.hs
@@ -0,0 +1,23 @@
+{-# LANGUAGE TypeFamilies #-}
+module T11408 where
+
+type family UL a
+type family UR a
+type family MT a b
+
+mkMerge :: a -> UL a -> UR a -> Int
+mkMerge = undefined
+
+merger :: a -> b -> MT a b
+merger = undefined
+
+{-
+merge ::
+ forall a b. (UL (MT a b) ~ a, UR (MT a b) ~ b) => a -> b -> Int
+or
+ forall t. (MT (UL t) (UR t) ~ t) => UL t -> UR t -> Int
+
+These types are equivalent, and in fact neither is ambiguous,
+but the solver has to work quite hard to prove that.
+-}
+merge x y = mkMerge (merger x y) x y



More information about the ghc-commits mailing list