[GHC] #10534: Data families + Coercible = unsafeCoerce
GHC
ghc-devs at haskell.org
Tue Jun 16 01:20:16 UTC 2015
#10534: Data families + Coercible = unsafeCoerce
-------------------------------------+-------------------------------------
Reporter: goldfire | Owner:
Type: bug | Status: new
Priority: highest | Milestone: 7.10.2
Component: Compiler | Version: 7.10.2-rc1
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple | Blocked By:
Test Case: | Related Tickets:
Blocking: |
Differential Revisions: |
-------------------------------------+-------------------------------------
When I say
{{{
{-# LANGUAGE TypeFamilies, FlexibleContexts #-}
module A where
import Data.Coerce
data family DF a
silly :: Coercible (DF a) (DF b) => a -> b
silly = coerce
}}}
{{{
{-# LANGUAGE TypeFamilies #-}
module B where
import A
newtype instance DF a = MkDF ()
unsafeCoerce :: a -> b
unsafeCoerce = silly
}}}
I get
{{{
[1 of 2] Compiling A ( A.hs, interpreted )
[2 of 2] Compiling B ( B.hs, interpreted )
Ok, modules loaded: A, B.
}}}
Eep!
Happily, the fix is very very simple: `TyCon.isDistinctAlgRhs` should
return `False` for `DataFamilyTyCon`s. This fix is already in-flight for
HEAD in Phab:D968, but this ticket serves to correct this problem in
7.10.2 before the release.
Patch coming very shortly.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10534>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list