[commit: ghc] master: Add test for #11473 (89bdac7)

git at git.haskell.org git at git.haskell.org
Sat Jan 23 21:48:49 UTC 2016


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/89bdac7635e6ed08927d760aa885d3e7ef3edb81/ghc

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

commit 89bdac7635e6ed08927d760aa885d3e7ef3edb81
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Fri Jan 22 13:33:36 2016 +0100

    Add test for #11473


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

89bdac7635e6ed08927d760aa885d3e7ef3edb81
 testsuite/tests/typecheck/should_fail/T11473.hs | 20 ++++++++++++++++++++
 testsuite/tests/typecheck/should_fail/all.T     |  1 +
 2 files changed, 21 insertions(+)

diff --git a/testsuite/tests/typecheck/should_fail/T11473.hs b/testsuite/tests/typecheck/should_fail/T11473.hs
new file mode 100644
index 0000000..cb9f791
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T11473.hs
@@ -0,0 +1,20 @@
+{-# LANGUAGE PolyKinds, TypeFamilies, MagicHash, DataKinds, TypeInType, RankNTypes #-}
+
+module T11473 where
+import GHC.Exts
+import GHC.Types
+
+type family Boxed (a :: k) :: *
+type instance Boxed Char# = Char
+type instance Boxed Char  = Char
+
+class BoxIt (a :: TYPE lev) where
+    boxed :: a -> Boxed a
+
+instance BoxIt Char# where boxed x = C# x
+instance BoxIt Char  where boxed = id
+
+-- This should be an error: there is no way we can produce code for both Lifted
+-- and Unlifted levities
+hello :: forall (lev :: Levity). forall (a :: TYPE lev). BoxIt a => a -> Boxed a
+hello x = boxed x
diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T
index 1c4e86e..3b090f7 100644
--- a/testsuite/tests/typecheck/should_fail/all.T
+++ b/testsuite/tests/typecheck/should_fail/all.T
@@ -404,3 +404,4 @@ test('T11347', normal, compile_fail, [''])
 test('T11356', normal, compile_fail, [''])
 test('T11355', normal, compile_fail, [''])
 test('T11464', normal, compile_fail, [''])
+test('T11473', expect_broken(11473), compile_fail, [''])



More information about the ghc-commits mailing list