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