Skip to content
Snippets Groups Projects
Commit b050a63d authored by sof's avatar sof
Browse files

[project @ 1999-01-23 17:46:01 by sof]

Move ST <--> IO coercion functions from IOExts to (Lazy)?ST
parent 99b153d6
No related merge requests found
......@@ -48,8 +48,6 @@ module IOExts
#endif
, unsafePtrEq
, unsafeIOToST
, stToIO
) where
......@@ -161,18 +159,6 @@ trace string expr = unsafePerformIO $ do
#endif
\end{code}
\begin{code}
unsafeIOToST :: IO a -> ST s a
#ifdef __HUGS__
unsafeIOToST = primUnsafeCoerce
#else
unsafeIOToST (IO io) = ST $ \ s ->
case ((unsafeCoerce# io) s) of
(# new_s, a #) -> unsafeCoerce# (STret new_s a)
-- IOfail new_s e -> error ("I/O Error (unsafeIOToST): " ++ showsPrec 0 e "\n")
#endif
\end{code}
Not something you want to call normally, but useful
in the cases where you do want to flush stuff out of
the heap or make sure you've got room enough
......
......@@ -26,6 +26,8 @@ module LazyST (
thawSTArray, freezeSTArray, unsafeFreezeSTArray,
Ix,
ST.unsafeIOToST, ST.stToIO,
strictToLazyST, lazyToStrictST
) where
......@@ -80,6 +82,7 @@ writeSTRef :: ST.STRef s a -> a -> ST s ()
newSTRef = strictToLazyST . ST.newSTRef
readSTRef = strictToLazyST . ST.readSTRef
writeSTRef r a = strictToLazyST (ST.writeSTRef r a)
\end{code}
%*********************************************************
......
......@@ -21,6 +21,8 @@ module ST (
STRef,
newSTRef, readSTRef, writeSTRef,
unsafeIOToST, stToIO,
STArray,
newSTArray, readSTArray, writeSTArray, boundsSTArray,
thawSTArray, freezeSTArray, unsafeFreezeSTArray,
......@@ -37,7 +39,8 @@ import PreludeBuiltin
#else
import PrelArr
import PrelST
import PrelBase ( Eq(..), Int, Bool, ($), ()(..) )
import PrelBase ( Eq(..), Int, Bool, ($), ()(..), unsafeCoerce# )
import PrelIOBase ( IO(..), stToIO )
#endif
import Monad
import Ix
......@@ -149,3 +152,15 @@ unsafeFreezeSTArray (STArray arr) = unsafeFreezeArray arr
#endif
\end{code}
\begin{code}
unsafeIOToST :: IO a -> ST s a
#ifdef __HUGS__
unsafeIOToST = primUnsafeCoerce
#else
unsafeIOToST (IO io) = ST $ \ s ->
case ((unsafeCoerce# io) s) of
(# new_s, a #) -> unsafeCoerce# (STret new_s a)
-- IOfail new_s e -> error ("I/O Error (unsafeIOToST): " ++ showsPrec 0 e "\n")
#endif
\end{code}
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment