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