[commit: ghc] master: Some stress tests for the empty case linter (6cf0c79)
git at git.haskell.org
git at git.haskell.org
Tue Mar 24 10:31:14 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/6cf0c7962c582eefb84cdf2735504d034fb16314/ghc
>---------------------------------------------------------------
commit 6cf0c7962c582eefb84cdf2735504d034fb16314
Author: Joachim Breitner <mail at joachim-breitner.de>
Date: Tue Mar 24 11:28:55 2015 +0100
Some stress tests for the empty case linter
This is a variation of T2431 where the emptyness of the type is hidden
behind a newtype, a type family and a closed type family. In all cases,
it would be sound for the compiler to determine that the equality type
is empty and the case alternatives may be dropped.
At the moment, GHC does _not_ determine that. But if it ever does, this
test ensures that we do not forget to make the lint from #10180 smarter
as well.
>---------------------------------------------------------------
6cf0c7962c582eefb84cdf2735504d034fb16314
testsuite/tests/simplCore/should_compile/T10180.hs | 27 ++++++++++++++++++++++
testsuite/tests/simplCore/should_compile/all.T | 1 +
2 files changed, 28 insertions(+)
diff --git a/testsuite/tests/simplCore/should_compile/T10180.hs b/testsuite/tests/simplCore/should_compile/T10180.hs
new file mode 100644
index 0000000..55c52f0
--- /dev/null
+++ b/testsuite/tests/simplCore/should_compile/T10180.hs
@@ -0,0 +1,27 @@
+{-# LANGUAGE TypeOperators, TypeFamilies, GADTs, EmptyCase #-}
+module T10180 where
+
+newtype Foo = Foo Int
+
+type family Bar a
+type instance Bar Int = Int
+
+type family Baz a where
+ Baz Int = Int
+ Baz Char = Int
+
+data a :~: b where
+ Refl :: a :~: a
+
+absurd0 :: Int :~: Bool -> a
+absurd0 x = case x of {}
+
+absurd1 :: Foo :~: Bool -> a
+absurd1 x = case x of {}
+
+absurd2 :: Bar Int :~: Bool -> a
+absurd2 x = case x of {}
+
+absurd3 :: Baz a :~: Bool -> a
+absurd3 x = case x of {}
+
diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T
index 6c000d3..daf038a 100644
--- a/testsuite/tests/simplCore/should_compile/all.T
+++ b/testsuite/tests/simplCore/should_compile/all.T
@@ -212,3 +212,4 @@ test('T9583', only_ways(['optasm']), compile, [''])
test('T9565', only_ways(['optasm']), compile, [''])
test('T5821', only_ways(['optasm']), compile, [''])
test('T10176', only_ways(['optasm']), compile, [''])
+test('T10180', only_ways(['optasm']), compile, [''])
More information about the ghc-commits
mailing list