[commit: ghc] master: Remove "Safe mode" check for Coercible instances (5972229)

git at git.haskell.org git at git.haskell.org
Fri Mar 14 03:35:51 UTC 2014


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

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

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

commit 59722295bb8da8f01d37356fbed6aef7321a8195
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date:   Thu Mar 13 14:16:37 2014 -0400

    Remove "Safe mode" check for Coercible instances
    
    We assume that library authors supply correct role annotations
    for their types, and therefore we do not need to check for
    the availability of data constructors in Safe mode. See
    discussion in #8725. This effectively fixes #8827 and #8826.


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

59722295bb8da8f01d37356fbed6aef7321a8195
 compiler/typecheck/TcInteract.lhs                  |   21 +++++---------------
 .../typecheck/should_fail/TcCoercibleFailSafe.hs   |   11 ----------
 .../should_fail/TcCoercibleFailSafe.stderr         |    8 --------
 testsuite/tests/typecheck/should_fail/all.T        |    1 -
 4 files changed, 5 insertions(+), 36 deletions(-)

diff --git a/compiler/typecheck/TcInteract.lhs b/compiler/typecheck/TcInteract.lhs
index 377cd2d..75835ad 100644
--- a/compiler/typecheck/TcInteract.lhs
+++ b/compiler/typecheck/TcInteract.lhs
@@ -1922,11 +1922,10 @@ getCoercibleInst loc ty1 ty2 = do
       -- Get some global stuff in scope, for nice pattern-guard based code in `go`
       rdr_env <- getGlobalRdrEnvTcS
       famenv <- getFamInstEnvs
-      safeMode <- safeLanguageOn `fmap` getDynFlags
-      go safeMode famenv rdr_env
+      go famenv rdr_env
   where
-  go :: Bool -> FamInstEnvs -> GlobalRdrEnv -> TcS LookupInstResult
-  go safeMode famenv rdr_env
+  go :: FamInstEnvs -> GlobalRdrEnv -> TcS LookupInstResult
+  go famenv rdr_env
     -- Coercible a a                             (see case 1 in [Coercible Instances])
     | ty1 `tcEqType` ty2
     = do return $ GenInst []
@@ -1946,11 +1945,8 @@ getCoercibleInst loc ty1 ty2 = do
     | Just (tc1,tyArgs1) <- splitTyConApp_maybe ty1,
       Just (tc2,tyArgs2) <- splitTyConApp_maybe ty2,
       tc1 == tc2,
-      nominalArgsAgree tc1 tyArgs1 tyArgs2,
-      not safeMode || all (dataConsInScope rdr_env) (tyConsOfTyCon tc1)
-    = do -- Mark all used data constructors as used
-         when safeMode $ mapM_ (markDataConsAsUsed rdr_env) (tyConsOfTyCon tc1)
-         -- We want evidence for all type arguments of role R
+      nominalArgsAgree tc1 tyArgs1 tyArgs2
+    = do -- We want evidence for all type arguments of role R
          arg_stuff <- forM (zip3 (tyConRoles tc1) tyArgs1 tyArgs2) $ \(r,ta1,ta2) ->
            case r of Nominal -> do
                           return
@@ -2060,13 +2056,6 @@ air, in getCoercibleInst. The following “instances” are present:
     The type constructor can be used undersaturated; then the Coercible
     instance is at a higher kind. This does not cause problems.
 
-    Furthermore in Safe Haskell code, we check that
-     * the data constructors of C are in scope and
-     * the data constructors of all type constructors used in the definition of
-     * C are in scope.
-       This is required as otherwise the previous check can be circumvented by
-       just adding a local data type around C.
-
  4. instance Coercible r b => Coercible (NT t1 t2 ...) b
     instance Coercible a r => Coercible a (NT t1 t2 ...)
     for a newtype constructor NT (or data family instance that resolves to a
diff --git a/testsuite/tests/typecheck/should_fail/TcCoercibleFailSafe.hs b/testsuite/tests/typecheck/should_fail/TcCoercibleFailSafe.hs
deleted file mode 100644
index 85f86b6..0000000
--- a/testsuite/tests/typecheck/should_fail/TcCoercibleFailSafe.hs
+++ /dev/null
@@ -1,11 +0,0 @@
-{-# LANGUAGE RoleAnnotations, RankNTypes, ScopedTypeVariables, Safe #-}
-
-import GHC.Prim (coerce, Coercible)
-import Data.Ord (Down)
-
-newtype Age = Age Int deriving Show
-
-foo1 :: (Down Age -> Down Int)
-foo1 = coerce 
-
-main = return ()
diff --git a/testsuite/tests/typecheck/should_fail/TcCoercibleFailSafe.stderr b/testsuite/tests/typecheck/should_fail/TcCoercibleFailSafe.stderr
deleted file mode 100644
index 2d7bf19..0000000
--- a/testsuite/tests/typecheck/should_fail/TcCoercibleFailSafe.stderr
+++ /dev/null
@@ -1,8 +0,0 @@
-
-TcCoercibleFailSafe.hs:9:8:
-    Could not coerce from ‘Down Age’ to ‘Down Int’
-      because the constructor of ‘Down’ is not imported
-      as required in SafeHaskell mode
-      arising from a use of ‘coerce’
-    In the expression: coerce
-    In an equation for ‘foo1’: foo1 = coerce
diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T
index 9f5af09..9367aed 100644
--- a/testsuite/tests/typecheck/should_fail/all.T
+++ b/testsuite/tests/typecheck/should_fail/all.T
@@ -317,7 +317,6 @@ test('T7989', normal, compile_fail, [''])
 test('T8142', normal, compile_fail, [''])
 test('T8262', normal, compile_fail, [''])
 test('TcCoercibleFail', when(compiler_lt('ghc', '7.7'), skip), compile_fail, [''])
-test('TcCoercibleFailSafe', when(compiler_lt('ghc', '7.7'), skip), compile_fail, [''])
 test('TcCoercibleFail2', when(compiler_lt('ghc', '7.7'), skip), compile_fail, [''])
 test('TcCoercibleFail3', when(compiler_lt('ghc', '7.7'), skip), compile_fail, [''])
 test('T8306', normal, compile_fail, [''])



More information about the ghc-commits mailing list