
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/* <\ * (__ */\ <

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
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Wednesday 29 April 2009 5:26:46 pm Xiao-Yong Jin 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?
Behold! ---- snip ---- {-# LANGUAGE FlexibleContexts, ScopedTypeVariables #-} import Control.Monad.ST import Data.Array import Data.Array.ST import Data.Maybe import Data.Dynamic bad :: forall s. MArray (STArray s) Dynamic (ST s) => ST s (STArray s Int Dynamic) bad = do arr <- newArray (0,1) (toDyn (0 :: Int)) let evil :: IO () evil = unsafeSTToIO (writeArray arr 1 (toDyn (1 :: Int)) :: ST s ()) writeArray arr 0 (toDyn evil) return arr main = let arr :: Array Int Dynamic arr = runSTArray bad io :: IO () io = fromJust . fromDynamic $ (arr ! 0) i :: Int i = fromJust . fromDynamic $ (arr ! 1) j :: Int j = fromJust . fromDynamic $ (arr ! 1) in do print i io print j ---- snip ---- Output: *Main> main 0 1 This is, admittedly, only possible because runSTArray uses unsafeFreeze. However, unsafeSTToIO is partially to blame, because it allows us to produce both IO actions that manipulate references/arrays in a particular region *and* pure values using runST over said region. Perhaps someone can come up with a more insidious example, but that's the best I could do after puzzling for a bit. -- Dan

On Wed, Apr 29, 2009 at 05:26:46PM -0400, Xiao-Yong Jin wrote:
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?
Here's an example: http://www.mail-archive.com/glasgow-haskell-bugs@haskell.org/msg03555.html

I gather that "...making it possible to use ST code directly on IORef's." is what we have today? -- Jason Dusek |...making it possible to use ST code directly on IORef's.| http://www.mail-archive.com/glasgow-haskell-bugs@haskell.org/msg03568.html

On Thu, Apr 30, 2009 at 12:44:49PM -0700, Jason Dusek wrote:
I gather that "...making it possible to use ST code directly on IORef's." is what we have today?
No, we have stToIO :: ST RealWorld a -> IO a, but STRef and IORef are still incompatible types. (I now think that's a good thing, because STRefs have more equations than IORefs.)
participants (5)
-
Dan Doel
-
Jason Dusek
-
Ross Paterson
-
Ryan Ingram
-
Xiao-Yong Jin