unsafeCoerce and type aliases under type applications

Joachim Breitner mail at joachim-breitner.de
Sun Dec 4 11:17:25 CET 2011


Hi,

Am Sonntag, den 04.12.2011, 00:50 -0500 schrieb wren ng thornton:
> On 12/3/11 9:07 PM, Felipe Almeida Lessa wrote:
> > On Sat, Dec 3, 2011 at 5:39 PM, Joachim Breitner
> > <mail at joachim-breitner.de>  wrote:
> >> have used unsafeCoerce to change the type inside a container to a "type"
> >> alias in real code, but your post makes me wonder: Under what
> >> circumstances is that safe? Is that documented somehow? Can a tool or
> >> the compiler decide for us whether it is safe?
> >
> > AFAIK, newtypes are safe, and for everything else you're on your own.  =)
> 
> N.B., newtypes are safe in the sense of congruent rewriting; i.e., if X 
> is a newtype of Y, then we can rewrite X to Y (or Y to X) in any subterm 
> of the type term (just like if X = Y or X ~ Y). It's not just at the 
> top-level of the type term.

that is what I would expect at first glance, but at least some type
features break this behavior:

$ cat brokenNewtype.hs 
{-# LANGUAGE TypeFamilies #-}

import Unsafe.Coerce

newtype Int' = Int' Int

type family Break a
type instance Break Int = Int
type instance Break Int' = Int -> IO Int

list :: [Break Int]
list = [1..10]

list' :: [Break Int']
list' = unsafeCoerce list

main = do
    print list
    head list' 1 >>= print
$ ghc --make brokenNewtype.hs 
[1 of 1] Compiling Main             ( brokenNewtype.hs, brokenNewtype.o )
Linking brokenNewtype ...
$ ./brokenNewtype
[1,2,3,4,5,6,7,8,9,10]
brokenNewtype: internal error: stg_ap_v_ret
    (GHC version 7.0.4 for x86_64_unknown_linux)
    Please report this as a GHC bug:
http://www.haskell.org/ghc/reportabug
Abgebrochen

So the question remains: Under which circumstances is newtypes coercing
within a type term using unsafeCoerce safe?

And I find this not a purely academic question: If I have a huge data
structure of “[Tagged SomePhantomType Int]” and I need to run some
library function on it that only provides me with an operation of type
“[Int] -> [Int]”, I do not want to re-create the list twice even when I
_know_ the representation is the same.

Greetings,
Joachim

-- 
Joachim "nomeata" Breitner
  mail at joachim-breitner.de  |  nomeata at debian.org  |  GPG: 0x4743206C
  xmpp: nomeata at joachim-breitner.de | http://www.joachim-breitner.de/

-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 198 bytes
Desc: This is a digitally signed message part
URL: <http://www.haskell.org/pipermail/libraries/attachments/20111204/1b3b906a/attachment.pgp>


More information about the Libraries mailing list