[commit: ghc] master: Test Trac #9090 (8c82563)

git at git.haskell.org git at git.haskell.org
Thu Dec 11 10:44:43 UTC 2014


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/8c825633135e24f6a0bbcc2c4097afada6ad6167/ghc

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

commit 8c825633135e24f6a0bbcc2c4097afada6ad6167
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Thu Dec 11 10:44:32 2014 +0000

    Test Trac #9090


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

8c825633135e24f6a0bbcc2c4097afada6ad6167
 .../tests/indexed-types/should_compile/T9090.hs    | 28 ++++++++++++++++++++++
 testsuite/tests/indexed-types/should_compile/all.T |  1 +
 2 files changed, 29 insertions(+)

diff --git a/testsuite/tests/indexed-types/should_compile/T9090.hs b/testsuite/tests/indexed-types/should_compile/T9090.hs
new file mode 100644
index 0000000..6d2b6ba
--- /dev/null
+++ b/testsuite/tests/indexed-types/should_compile/T9090.hs
@@ -0,0 +1,28 @@
+{-# LANGUAGE RankNTypes, ConstraintKinds, TypeFamilies #-}
+module T9090 where
+
+import GHC.Exts (Constraint)
+
+type family F (c :: Constraint) :: Constraint
+type instance F (Eq a) = Eq a
+
+-- checks
+f :: Eq b => (forall a. F (Eq a) => f a -> Bool) -> f b -> Bool
+f = error "urk" -- g x = g x
+
+-- checks
+f' :: Eq b => (forall a. Eq a => f a -> Bool) -> f b -> Bool
+f' = f
+
+-- checks, so GHC seems to think that both types are interchangeable
+f'' :: Eq b => (forall a. F (Eq a) => f a -> Bool) -> f b -> Bool
+f'' = f'
+
+-- checks
+test' y = f' (\ (Just x) -> x /= x) y
+
+-- fails
+test y = f (\ (Just x) -> x /= x) y
+
+-- fails too, unsurprisingly
+test'' y = f'' (\ (Just x) -> x /= x) y
diff --git a/testsuite/tests/indexed-types/should_compile/all.T b/testsuite/tests/indexed-types/should_compile/all.T
index 4c48d3e..ae15c27 100644
--- a/testsuite/tests/indexed-types/should_compile/all.T
+++ b/testsuite/tests/indexed-types/should_compile/all.T
@@ -250,3 +250,4 @@ test('Sock', normal, compile, [''])
 test('T9211', normal, compile, [''])
 test('T9747', normal, compile, [''])
 test('T9582', normal, compile, [''])
+test('T9090', normal, compile, [''])



More information about the ghc-commits mailing list