[Haskell-cafe] Dynamic types through unsafeCoerce

Alfonso Acosta alfonso.acosta at gmail.com
Tue Dec 12 12:46:36 EST 2006


On 12/10/06, Taral <taralx at gmail.com> wrote:
> On 12/10/06, Alfonso Acosta <alfonso.acosta at gmail.com> wrote:
> > On 12/10/06, Taral <taralx at gmail.com> wrote:
> > > Sure it is. The type you gave (MyType Int Char -> MyType a b) can
> > > easily crash your program.
> >
> > Ok I see. Why would that happen? I'm (maybe wrongly) taking as granted
> > that the compiler/interpreter uses the same internal representation
> > for both types. But that makes me think it shouldn't be that dangerous
> > if nothing is later assumed about the type parameters "a" and "b".


> 1. The Haskell Report does not guarantee that these things have the
> same representation.

Well, to be honest the idea of using unsafeCoerce came after browing
the sources of the Lava (http://www.md.chalmers.se/~koen/Lava/ )
library. Now I have explicit permission to reuse them so I guess  I'm
allowed to paste a few snippets here as well.

Here they approach the same problem I have by using unsafe Coerce

-- This code implements Observable sharing references for circuits

-- Some Comments made by Koen describing the problem:

-- "The disadvantage is that, since the types of the
-- Tables vary, the Ref has no idea what type of
-- values it is supposed to store. So we use dynamic
-- types."

toDyn :: a -> Dyn
toDyn = unsafeCoerce

fromDyn :: Dyn -> a
fromDyn = unsafeCoerce

-- If  GHC is used
unsafeCoerce :: a -> b
unsafeCoerce a = unsafePerformIO $
  do writeIORef ref a
     readIORef ref
 where
  ref = unsafePerformIO $
    do newIORef undefined

-- If Hugs is used
primitive unsafeCoerce "primUnsafeCoerce" :: a -> b

-- Pieces of code where toDyn/fromDyn is used
data Ref a
  = Ref (IORef [(TableTag, Dyn)]) a

type TableTag
  = IORef ()

newtype TableIO a b
  = TableIO TableTag
 deriving Eq

extendIO :: TableIO a b -> Ref a -> b -> IO ()
extendIO (TableIO t) (Ref r _) b =
  do list <- readIORef r
     writeIORef r ((t,toDyn b) : filter ((/= t) . fst) list)

findIO :: TableIO a b -> Ref a -> IO (Maybe b)
findIO (TableIO t) (Ref r _) =
  do list <- readIORef r
     return (fromDyn `fmap` lookup t list)


> 2. Assuming that a polymorphic type will never be made monomorphic is
> like running without a safety net. The typecheck will not save you,
> and it'll be a pain to debug if it goes wrong. If you're not using
> those type parameters, then wrap it up so they can't be used.

The problem is that, even if not mandatory, the binding would look
more intuitive and similar to the original library with the (internal
and user-hidden) use of those type parameters.

I already tried to hide them through an existential and actually
that's how the last version of the binding is implemented.

As I already said. The user is only able to transform to dynamic but
not back to a polymorphic type so I have control over those
parameters.

> Why not post some code snippets so we can see what you're doing?

If this mail doesn't clarify the problem I will try paste some
snippets  of my code (it's a real pain to try to simplify it)

Thanks for your help Taral :)


More information about the Haskell-Cafe mailing list