[project @ 1999-11-26 16:26:32 by simonmar]
[ghc-hetmet.git] / ghc / lib / exts / LazyST.lhs
index ee3925e..9b9baab 100644 (file)
@@ -15,16 +15,13 @@ module LazyST (
        runST,
        unsafeInterleaveST,
 
-        -- ST is one, so you'll likely need some Monad bits
-        module Monad,
-
        ST.STRef,
        newSTRef, readSTRef, writeSTRef,
 
        STArray,
        newSTArray, readSTArray, writeSTArray, boundsSTArray, 
        thawSTArray, freezeSTArray, unsafeFreezeSTArray, 
-       Ix,
+       unsafeThawSTArray,
 
        ST.unsafeIOToST, ST.stToIO,
 
@@ -39,7 +36,9 @@ import Monad
 import Ix
 import PrelGHC
 
-newtype ST s a = ST (PrelST.State s -> (a,PrelST.State s))
+newtype ST s a = ST (State s -> (a, State s))
+
+data State s = S# (State# s)
 
 instance Functor (ST s) where
     fmap f m = ST $ \ s ->
@@ -65,7 +64,7 @@ instance Monad (ST s) where
 
 {-# NOINLINE runST #-}
 runST :: (forall s. ST s a) -> a
-runST st = case st of ST the_st -> let (r,_) = the_st (PrelST.S# realWorld#) in r
+runST st = case st of ST the_st -> let (r,_) = the_st (S# realWorld#) in r
 \end{code}
 
 %*********************************************************
@@ -115,19 +114,22 @@ thawSTArray arr   =
 
 freezeSTArray (STArray arr) = strictToLazyST (freezeArray arr)
 unsafeFreezeSTArray (STArray arr) = strictToLazyST (unsafeFreezeArray arr)
+unsafeThawSTArray arr =
+           strictToLazyST (unsafeThawArray arr) >>= \ marr -> 
+           return (STArray marr)
 
 strictToLazyST :: PrelST.ST s a -> ST s a
 strictToLazyST m = ST $ \s ->
         let 
-          pr = case s of { PrelST.S# s# -> PrelST.liftST m s# }
+          pr = case s of { S# s# -> PrelST.liftST m s# }
           r  = case pr of { PrelST.STret _ v -> v }
-          s' = case pr of { PrelST.STret s2# _ -> PrelST.S# s2# }
+          s' = case pr of { PrelST.STret s2# _ -> S# s2# }
        in
        (r, s')
 
 lazyToStrictST :: ST s a -> PrelST.ST s a
 lazyToStrictST (ST m) = PrelST.ST $ \s ->
-        case (m (PrelST.S# s)) of (a, PrelST.S# s') -> (# s', a #)
+        case (m (S# s)) of (a, S# s') -> (# s', a #)
 
 unsafeInterleaveST :: ST s a -> ST s a
 unsafeInterleaveST = strictToLazyST . ST.unsafeInterleaveST . lazyToStrictST