[Haskell-cafe] unsafeSTToIO and stToIO

Ryan Ingram ryani.spam at gmail.com
Wed Apr 29 18:26:59 EDT 2009


The main difference is that the state thread reference can leak out of
the unsafe version:

question :: forall s. IO (STRef s Int)
question = unsafeSTToIO (newSTRef 1)

I was trying to use this to inject the reference into a later ST
computation, but I couldn't figure out how to build an object of type
(IO (forall s. STRef s Int)) which is what you need.  I think there's
still probably a way to break this using a CPS transformation and the
internals of IO, but I gave up.

If you can inject the reference somehow, you can do this:

> {-# LANGUAGE RankNTypes #-}
> module STTest where
> import Data.STRef
> import Control.Monad.ST
> import Unsafe.Coerce (unsafeCoerce)

> newtype Holder = Holder (forall s. STRef s Int)

> mkRef :: IO Holder
> mkRef = do
>    v <- stToIO (newSTRef 0)
>    return (Holder (unsafeCoerce v)) -- is there a way to fill this in using unsafeSTToIO?

> update :: forall s a. STRef s a -> a -> ST s a
> update r v = do
>    res <- readSTRef r
>    writeSTRef r v
>    return res

> tester :: (forall s. STRef s Int) -> Int
> tester r = runST (update r 0) + runST (update r 1)

> non_referentially_transparent = do
>    Holder r <- mkRef
>    return $ case (tester r) of
>        0 -> "Left"
>        1 -> "Right"

This code snippet will let you know which argument + for Int evaluates first.

The "safe" version just lets you treat STRefs as IORefs; IORef a ~=
STRef RealWorld a

  -- ryan

On Wed, Apr 29, 2009 at 2:26 PM, Xiao-Yong Jin <xj2106 at columbia.edu> wrote:
> Hi,
>
> Between the following two functions
>
> stToIO        :: ST RealWorld a -> IO a
> stToIO (ST m) = IO m
>
> unsafeSTToIO :: ST s a -> IO a
> unsafeSTToIO (ST m) = IO (unsafeCoerce# m)
>
> All I can see is that the safe one uses RealWorld instead of
> an arbitrary thread s used in the unsafe one.  I really
> don't understand the difference between these two.  Why is
> the one without RealWorld unsafe?
>
> I tried google, but couldn't find anything helpful.
> --
>    c/*    __o/*
>    <\     * (__
>    */\      <
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list