[GHC] #8827: Inferring Safe mode with GeneralizedNewtypeDeriving is wrong
GHC
ghc-devs at haskell.org
Mon Feb 8 02:48:58 UTC 2016
#8827: Inferring Safe mode with GeneralizedNewtypeDeriving is wrong
-------------------------------------+-------------------------------------
Reporter: goldfire | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.9
Resolution: | Keywords: SafeHaskell
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #8226, #8745 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Description changed by dterei:
@@ -1,2 +1,1 @@
- See a detailed write up here [wiki:SafeRoles/RolesOverview Safe Haskell,
- GND and Roles]
+ See a detailed write up here [wiki:SafeRoles Safe Haskell, GND and Roles]
New description:
See a detailed write up here [wiki:SafeRoles Safe Haskell, GND and Roles]
Consider the following modules:
{{{
module A (List, ints) where
data List a = Nil | Cons a (List a)
infixr 4 `Cons`
ints :: List Int
ints = 1 `Cons` 2 `Cons` 3 `Cons` Nil
}}}
{{{
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module B where
import A
newtype Age = MkAge Int
deriving C
class C a where
cList :: List a
instance C Int where
cList = ints
}}}
{{{
{-# LANGUAGE Safe #-}
module C (ages) where
import A
import B
ages :: List Age
ages = cList
}}}
Module C compiles without a hiccup. But, it shouldn't: the coercion
between `ages` and `ints` (performed by !GeneralizedNewtypeDeriving in
module B) isn't Safe, as it breaks through `List`'s abstraction. (Note
that the constructors of `List` are ''not'' exported from module A!)
If module B includes `{-# LANGUAGE Safe #-}`, it duly doesn't compile,
because of the stringent "constructors-must-be-in-scope" check done by the
`Coercible` mechanism. The problem is that safety can be ''inferred''
without this check taking place.
You may also want to read the commentary on #8745 for related discussion.
--
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8827#comment:53>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list