[project @ 2001-02-13 10:12:45 by sewardj]
[ghc-hetmet.git] / ghc / lib / std / PrelST.lhs
index a45c8b2..735426d 100644 (file)
@@ -1,6 +1,9 @@
+% ------------------------------------------------------------------------------
+% $Id: PrelST.lhs,v 1.17 2000/09/25 12:58:39 simonpj Exp $
 %
-% (c) The GRASP/AQUA Project, Glasgow University, 1992-1996
+% (c) The University of Glasgow, 1992-2000
 %
+
 \section[PrelST]{The @ST@ monad}
 
 \begin{code}
 
 module PrelST where
 
-import Monad
+import PrelNum ( fromInteger )         -- For integer literals
 import PrelShow
 import PrelBase
-import PrelGHC
 import PrelNum ()      -- So that we get the .hi file for system imports
+
+default ()
 \end{code}
 
 %*********************************************************
@@ -53,13 +57,6 @@ data STret s a = STret (State# s) a
 liftST :: ST s a -> State# s -> STret s a
 liftST (ST m) = \s -> case m s of (# s', r #) -> STret s' r
 
-fixST :: (a -> ST s a) -> ST s a
-fixST k = ST $ \ s ->
-    let ans       = liftST (k r) s
-       STret _ r = ans
-    in
-    case ans of STret s' x -> (# s', x #)
-
 {-# NOINLINE unsafeInterleaveST #-}
 unsafeInterleaveST :: ST s a -> ST s a
 unsafeInterleaveST (ST m) = ST ( \ s ->
@@ -114,8 +111,10 @@ All calls to @f@ will share a {\em single} array!  End SLPJ 95/04.
 runST :: (forall s. ST s a) -> a
 runST st = runSTRep (case st of { ST st_rep -> st_rep })
 
--- I'm letting runSTRep be inlined *after* full laziness
+-- I'm only letting runSTRep be inlined right at the end, in particular *after* full laziness
+-- That's what the "INLINE 100" says.
 --             SLPJ Apr 99
+{-# INLINE 100 runSTRep #-}
 runSTRep :: (forall s. STRep s a) -> a
 runSTRep st_rep = case st_rep realWorld# of
                        (# _, r #) -> r