[commit: ghc] master: Add in (disabled for now) test of a Safe Haskell bug. (ab90bf2)

git at git.haskell.org git at git.haskell.org
Sat Aug 2 02:05:40 UTC 2014


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

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

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

commit ab90bf214bac86890b3533ff77272780828004e2
Author: David Terei <code at davidterei.com>
Date:   Fri Aug 1 18:50:45 2014 -0700

    Add in (disabled for now) test of a Safe Haskell bug.


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

ab90bf214bac86890b3533ff77272780828004e2
 .../tests/safeHaskell/safeInfered/SafeInfered05.hs | 32 ++++++++++++++++++++++
 .../safeHaskell/safeInfered/SafeInfered05_A.hs     |  9 ++++++
 testsuite/tests/safeHaskell/safeInfered/all.T      |  5 ++++
 3 files changed, 46 insertions(+)

diff --git a/testsuite/tests/safeHaskell/safeInfered/SafeInfered05.hs b/testsuite/tests/safeHaskell/safeInfered/SafeInfered05.hs
new file mode 100644
index 0000000..0b42002
--- /dev/null
+++ b/testsuite/tests/safeHaskell/safeInfered/SafeInfered05.hs
@@ -0,0 +1,32 @@
+{-# LANGUAGE Unsafe #-}
+{-# LANGUAGE OverlappingInstances #-}
+{-# LANGUAGE FlexibleInstances #-}
+
+-- |
+-- This module should actually fail to compile since we have the instances C
+-- [Int] from the -XSafe module SafeInfered05_A overlapping as the most
+-- specific instance the other instance C [a] from this module. This is in
+-- violation of our single-origin-policy.
+--
+-- Right now though, the above actually compiles fine but *this is a bug*.
+-- Compiling module SafeInfered05_A with -XSafe has the right affect of causing
+-- the compilation of module SafeInfered05 to then subsequently fail. So we
+-- have a discrepancy between a safe-inferred module and a -XSafe module, which
+-- there should not be.
+--
+-- It does raise a question of if this bug should be fixed. Right now we've
+-- designed Safe Haskell to be completely opt-in, even with safe-inference.
+-- Fixing this of course changes this, causing safe-inference to alter the
+-- compilation success of some cases. How common it is to have overlapping
+-- declarations without -XOverlappingInstances specified needs to be tested.
+--
+module SafeInfered05 where
+
+import safe SafeInfered05_A
+
+instance C [a] where
+  f _ = "[a]"
+
+test2 :: String
+test2 = f ([1,2,3,4] :: [Int])
+
diff --git a/testsuite/tests/safeHaskell/safeInfered/SafeInfered05_A.hs b/testsuite/tests/safeHaskell/safeInfered/SafeInfered05_A.hs
new file mode 100644
index 0000000..a1e12a6
--- /dev/null
+++ b/testsuite/tests/safeHaskell/safeInfered/SafeInfered05_A.hs
@@ -0,0 +1,9 @@
+{-# LANGUAGE FlexibleInstances #-}
+module SafeInfered05_A where
+
+class C a where
+  f :: a -> String
+
+instance C [Int] where
+  f _ = "[Int]"
+
diff --git a/testsuite/tests/safeHaskell/safeInfered/all.T b/testsuite/tests/safeHaskell/safeInfered/all.T
index 9fb587b..a995c76 100644
--- a/testsuite/tests/safeHaskell/safeInfered/all.T
+++ b/testsuite/tests/safeHaskell/safeInfered/all.T
@@ -21,6 +21,11 @@ test('SafeInfered04',
      [ extra_clean(['SafeInfered04_A.hi', 'SafeInfered04_A.o']) ],
      multimod_compile, ['SafeInfered04', ''])
 
+# Test should fail, tests an earlier bug in 7.8
+# test('SafeInfered05',
+#      [ extra_clean(['SafeInfered05_A.hi', 'SafeInfered05_A.o']) ],
+#      multimod_compile_fail, ['SafeInfered05', ''])
+
 # Tests that should fail to compile as they should be infered unsafe
 test('UnsafeInfered01',
      [ extra_clean(['UnsafeInfered01_A.hi', 'UnsafeInfered01_A.o']) ],



More information about the ghc-commits mailing list