wolfgang.thaller:
> >g (F# f) =
> >        let w     = W32# (unsafeCoerce# f)
> 
> Why does GHC even accept this code?
> I think unsafeCoerce# is not intended to be able to coerce unboxed 
> values.
> 
> Prelude GHC.Base> :t unsafeCoerce#
> unsafeCoerce# :: forall b a. a -> b
> 
> The type variables a and b are supposed to be of kind *, and f is of 
> kind #.

How do you know the tyvars have kind * ?  Anyway, it's even used like
this in the libraries :)

    GHC.Conc:
    mkWeak key val Nothing = IO $ \s ->
       case mkWeak# key val (unsafeCoerce# 0#) s of 
            { (# s1, w #) -> (# s1, Weak w #) }

So those tyvars must really be ? kind (I think). I.e. 
    forall b:? a:? . a -> b
or
    forall b:?? a:?? . a -> b

There's a description of this stuff in types/Kind.lhs.
Also, I see in basicTypes/MkId.lhs:

    unsafeCoerce# isn't so much a PrimOp as a phantom identifier, that
    just gets expanded into a type coercion wherever it occurs.  Hence we
    add it as a built-in Id with an unfolding here.

    The type variables we use here are "open" type variables: this means
    they can unify with both unlifted and lifted types.  Hence we provide
    another gun with which to shoot yourself in the foot.

open == ??, I think, and the above comment explains the unsafeCoerce# behaviour
I'm using/shooting myself with. Further down:

    ty  = mkForAllTys [openAlphaTyVar,openBetaTyVar]
                  (mkFunTy openAlphaTy openBetaTy)

which looks like: a:?? -> b:?? to me. In prelude/TysPrim.lhs:

    -- openAlphaTyVar is prepared to be instantiated
    -- to a lifted or unlifted type variable.  It's used for the 
    -- result type for "error", so that we can have (error Int# "Help")
    openAlphaTy = mkTyVarTy openAlphaTyVar

So I think this all implies that unsafeCoerce# x# is legal, though not polite.

Cheers,
   Don

_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to