[GHC] #10000: Derived DataKinds Typeable instance collision leads to SafeHaskell violation
GHC
ghc-devs at haskell.org
Fri Jan 16 17:28:53 UTC 2015
#10000: Derived DataKinds Typeable instance collision leads to SafeHaskell
violation
-------------------------------------+-------------------------------------
Reporter: shachaf | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.8.4
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple | Blocked By:
Test Case: | Related Tickets:
Blocking: |
Differential Revisions: |
-------------------------------------+-------------------------------------
The derived `Typeable` instances for a kind (with `DataKinds`) is equal to
the
instance of a type with the same name:
{{{
λ> data T = T
λ> typeRep (Proxy :: Proxy T) == typeRep (Proxy :: Proxy 'T)
True
}}}
This can be used to violate `SafeHaskell` easily:
{{{#!hs
{-# LANGUAGE AutoDeriveTypeable, DataKinds, TypeFamilies, RankNTypes #-}
module Unsafe where
import Data.Typeable
data T = T
data family F p
newtype instance F (Proxy T) = ID (forall a. a -> a)
newtype instance F (Proxy 'T) = UC (forall a b. a -> b)
uc :: a -> b
uc = case cast (ID id) of Just (UC f) -> f
}}}
{{{
$ ghc -XSafe Unsafe.hs -e "uc 'a' :: Int"
97
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10000>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list