[Haskell-cafe] unsafeSTToIO and stToIO
Dan Doel
dan.doel at gmail.com
Wed Apr 29 18:28:03 EDT 2009
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
More information about the Haskell-Cafe
mailing list