[project @ 2005-02-03 10:32:11 by ross]
[ghc-base.git] / GHC / ST.lhs
1 \begin{code}
2 {-# OPTIONS_GHC -fno-implicit-prelude #-}
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  GHC.ST
6 -- Copyright   :  (c) The University of Glasgow, 1992-2002
7 -- License     :  see libraries/base/LICENSE
8 -- 
9 -- Maintainer  :  cvs-ghc@haskell.org
10 -- Stability   :  internal
11 -- Portability :  non-portable (GHC Extensions)
12 --
13 -- The 'ST' Monad.
14 --
15 -----------------------------------------------------------------------------
16
17 -- #hide
18 module GHC.ST where
19
20 import GHC.Base
21 import GHC.Show
22 import GHC.Num
23
24 default ()
25 \end{code}
26
27 %*********************************************************
28 %*                                                      *
29 \subsection{The @ST@ monad}
30 %*                                                      *
31 %*********************************************************
32
33 The state-transformer monad proper.  By default the monad is strict;
34 too many people got bitten by space leaks when it was lazy.
35
36 \begin{code}
37 -- | The strict state-transformer monad.
38 -- A computation of type @'ST' s a@ transforms an internal state indexed
39 -- by @s@, and returns a value of type @a@.
40 -- The @s@ parameter is either
41 --
42 -- * an unstantiated type variable (inside invocations of 'runST'), or
43 --
44 -- * 'RealWorld' (inside invocations of 'Control.Monad.ST.stToIO').
45 --
46 -- It serves to keep the internal states of different invocations
47 -- of 'runST' separate from each other and from invocations of
48 -- 'Control.Monad.ST.stToIO'.
49 newtype ST s a = ST (STRep s a)
50 type STRep s a = State# s -> (# State# s, a #)
51
52 instance Functor (ST s) where
53     fmap f (ST m) = ST $ \ s ->
54       case (m s) of { (# new_s, r #) ->
55       (# new_s, f r #) }
56
57 instance Monad (ST s) where
58     {-# INLINE return #-}
59     {-# INLINE (>>)   #-}
60     {-# INLINE (>>=)  #-}
61     return x = ST (\ s -> (# s, x #))
62     m >> k   = m >>= \ _ -> k
63
64     (ST m) >>= k
65       = ST (\ s ->
66         case (m s) of { (# new_s, r #) ->
67         case (k r) of { ST k2 ->
68         (k2 new_s) }})
69
70 data STret s a = STret (State# s) a
71
72 -- liftST is useful when we want a lifted result from an ST computation.  See
73 -- fixST below.
74 liftST :: ST s a -> State# s -> STret s a
75 liftST (ST m) = \s -> case m s of (# s', r #) -> STret s' r
76
77 {-# NOINLINE unsafeInterleaveST #-}
78 unsafeInterleaveST :: ST s a -> ST s a
79 unsafeInterleaveST (ST m) = ST ( \ s ->
80     let
81         r = case m s of (# _, res #) -> res
82     in
83     (# s, r #)
84   )
85
86 -- | Allow the result of a state transformer computation to be used (lazily)
87 -- inside the computation.
88 -- Note that if @f@ is strict, @'fixST' f = _|_@.
89 fixST :: (a -> ST s a) -> ST s a
90 fixST k = ST $ \ s ->
91     let ans       = liftST (k r) s
92         STret _ r = ans
93     in
94     case ans of STret s' x -> (# s', x #)
95
96 instance  Show (ST s a)  where
97     showsPrec _ _  = showString "<<ST action>>"
98     showList       = showList__ (showsPrec 0)
99 \end{code}
100
101 Definition of runST
102 ~~~~~~~~~~~~~~~~~~~
103
104 SLPJ 95/04: Why @runST@ must not have an unfolding; consider:
105 \begin{verbatim}
106 f x =
107   runST ( \ s -> let
108                     (a, s')  = newArray# 100 [] s
109                     (_, s'') = fill_in_array_or_something a x s'
110                   in
111                   freezeArray# a s'' )
112 \end{verbatim}
113 If we inline @runST@, we'll get:
114 \begin{verbatim}
115 f x = let
116         (a, s')  = newArray# 100 [] realWorld#{-NB-}
117         (_, s'') = fill_in_array_or_something a x s'
118       in
119       freezeArray# a s''
120 \end{verbatim}
121 And now the @newArray#@ binding can be floated to become a CAF, which
122 is totally and utterly wrong:
123 \begin{verbatim}
124 f = let
125     (a, s')  = newArray# 100 [] realWorld#{-NB-} -- YIKES!!!
126     in
127     \ x ->
128         let (_, s'') = fill_in_array_or_something a x s' in
129         freezeArray# a s''
130 \end{verbatim}
131 All calls to @f@ will share a {\em single} array!  End SLPJ 95/04.
132
133 \begin{code}
134 {-# INLINE runST #-}
135 -- The INLINE prevents runSTRep getting inlined in *this* module
136 -- so that it is still visible when runST is inlined in an importing
137 -- module.  Regrettably delicate.  runST is behaving like a wrapper.
138
139 -- | Return the value computed by a state transformer computation.
140 -- The @forall@ ensures that the internal state used by the 'ST'
141 -- computation is inaccessible to the rest of the program.
142 runST :: (forall s. ST s a) -> a
143 runST st = runSTRep (case st of { ST st_rep -> st_rep })
144
145 -- I'm only letting runSTRep be inlined right at the end, in particular *after* full laziness
146 -- That's what the "INLINE [0]" says.
147 --              SLPJ Apr 99
148 {-# INLINE [0] runSTRep #-}
149 runSTRep :: (forall s. STRep s a) -> a
150 runSTRep st_rep = case st_rep realWorld# of
151                         (# _, r #) -> r
152 \end{code}