Remove Control.Parallel*, now in package parallel
[haskell-directory.git] / GHC / ST.lhs
index 137debc..909a8da 100644 (file)
@@ -1,5 +1,5 @@
 \begin{code}
-{-# OPTIONS -fno-implicit-prelude #-}
+{-# OPTIONS_GHC -fno-implicit-prelude #-}
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  GHC.ST
@@ -14,6 +14,7 @@
 --
 -----------------------------------------------------------------------------
 
+-- #hide
 module GHC.ST where
 
 import GHC.Base
@@ -34,10 +35,22 @@ too many people got bitten by space leaks when it was lazy.
 
 \begin{code}
 -- | The strict state-transformer monad.
--- The first parameter is used solely to keep the states of different
--- invocations of 'runST' separate from each other and from invocations
--- of 'Control.Monad.ST.stToIO'.  In the first case the type parameter
--- is not instantiated; in the second it is 'RealWorld'.
+-- A computation of type @'ST' s a@ transforms an internal state indexed
+-- by @s@, and returns a value of type @a@.
+-- The @s@ parameter is either
+--
+-- * an uninstantiated type variable (inside invocations of 'runST'), or
+--
+-- * 'RealWorld' (inside invocations of 'Control.Monad.ST.stToIO').
+--
+-- It serves to keep the internal states of different invocations
+-- of 'runST' separate from each other and from invocations of
+-- 'Control.Monad.ST.stToIO'.
+--
+-- The '>>=' and '>>' operations are strict in the state (though not in
+-- values stored in the state).  For example,
+--
+-- @'runST' (writeSTRef _|_ v >>= f) = _|_@
 newtype ST s a = ST (STRep s a)
 type STRep s a = State# s -> (# State# s, a #)
 
@@ -77,7 +90,7 @@ unsafeInterleaveST (ST m) = ST ( \ s ->
 
 -- | Allow the result of a state transformer computation to be used (lazily)
 -- inside the computation.
--- Note that if @f@ is strict, @'fixST' f@ will diverge.
+-- Note that if @f@ is strict, @'fixST' f = _|_@.
 fixST :: (a -> ST s a) -> ST s a
 fixST k = ST $ \ s ->
     let ans       = liftST (k r) s
@@ -129,15 +142,22 @@ All calls to @f@ will share a {\em single} array!  End SLPJ 95/04.
 -- module.  Regrettably delicate.  runST is behaving like a wrapper.
 
 -- | Return the value computed by a state transformer computation.
--- The @forall@ is a technical device to ensure that the state used
--- by the 'ST' computation is inaccessible to the rest of the program.
+-- The @forall@ ensures that the internal state used by the 'ST'
+-- computation is inaccessible to the rest of the program.
 runST :: (forall s. ST s a) -> a
 runST st = runSTRep (case st of { ST st_rep -> st_rep })
 
 -- I'm only letting runSTRep be inlined right at the end, in particular *after* full laziness
 -- That's what the "INLINE [0]" says.
 --             SLPJ Apr 99
-{-# INLINE [0] runSTRep #-}
+-- {-# INLINE [0] runSTRep #-}
+
+-- SDM: further to the above, inline phase 0 is run *before*
+-- full-laziness at the moment, which means that the above comment is
+-- invalid.  Inlining runSTRep doesn't make a huge amount of
+-- difference, anyway.  Hence:
+
+{-# NOINLINE runSTRep #-}
 runSTRep :: (forall s. STRep s a) -> a
 runSTRep st_rep = case st_rep realWorld# of
                        (# _, r #) -> r