[project @ 2003-09-05 17:36:40 by ross]
[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 -- The first parameter is used solely to keep the states of different
38 -- invocations of 'runST' separate from each other and from invocations
39 -- of 'Control.Monad.ST.stToIO'.  In the first case the type parameter
40 -- is not instantiated; in the second it is 'RealWorld'.
41 newtype ST s a = ST (STRep s a)
42 type STRep s a = State# s -> (# State# s, a #)
43
44 instance Functor (ST s) where
45     fmap f (ST m) = ST $ \ s ->
46       case (m s) of { (# new_s, r #) ->
47       (# new_s, f r #) }
48
49 instance Monad (ST s) where
50     {-# INLINE return #-}
51     {-# INLINE (>>)   #-}
52     {-# INLINE (>>=)  #-}
53     return x = ST (\ s -> (# s, x #))
54     m >> k   = m >>= \ _ -> k
55
56     (ST m) >>= k
57       = ST (\ s ->
58         case (m s) of { (# new_s, r #) ->
59         case (k r) of { ST k2 ->
60         (k2 new_s) }})
61
62 data STret s a = STret (State# s) a
63
64 -- liftST is useful when we want a lifted result from an ST computation.  See
65 -- fixST below.
66 liftST :: ST s a -> State# s -> STret s a
67 liftST (ST m) = \s -> case m s of (# s', r #) -> STret s' r
68
69 {-# NOINLINE unsafeInterleaveST #-}
70 unsafeInterleaveST :: ST s a -> ST s a
71 unsafeInterleaveST (ST m) = ST ( \ s ->
72     let
73         r = case m s of (# _, res #) -> res
74     in
75     (# s, r #)
76   )
77
78 -- | Allow the result of a state transformer computation to be used (lazily)
79 -- inside the computation.
80 -- Note that if @f@ is strict, @'fixST' f@ will diverge.
81 fixST :: (a -> ST s a) -> ST s a
82 fixST k = ST $ \ s ->
83     let ans       = liftST (k r) s
84         STret _ r = ans
85     in
86     case ans of STret s' x -> (# s', x #)
87
88 instance  Show (ST s a)  where
89     showsPrec _ _  = showString "<<ST action>>"
90     showList       = showList__ (showsPrec 0)
91 \end{code}
92
93 Definition of runST
94 ~~~~~~~~~~~~~~~~~~~
95
96 SLPJ 95/04: Why @runST@ must not have an unfolding; consider:
97 \begin{verbatim}
98 f x =
99   runST ( \ s -> let
100                     (a, s')  = newArray# 100 [] s
101                     (_, s'') = fill_in_array_or_something a x s'
102                   in
103                   freezeArray# a s'' )
104 \end{verbatim}
105 If we inline @runST@, we'll get:
106 \begin{verbatim}
107 f x = let
108         (a, s')  = newArray# 100 [] realWorld#{-NB-}
109         (_, s'') = fill_in_array_or_something a x s'
110       in
111       freezeArray# a s''
112 \end{verbatim}
113 And now the @newArray#@ binding can be floated to become a CAF, which
114 is totally and utterly wrong:
115 \begin{verbatim}
116 f = let
117     (a, s')  = newArray# 100 [] realWorld#{-NB-} -- YIKES!!!
118     in
119     \ x ->
120         let (_, s'') = fill_in_array_or_something a x s' in
121         freezeArray# a s''
122 \end{verbatim}
123 All calls to @f@ will share a {\em single} array!  End SLPJ 95/04.
124
125 \begin{code}
126 {-# INLINE runST #-}
127 -- The INLINE prevents runSTRep getting inlined in *this* module
128 -- so that it is still visible when runST is inlined in an importing
129 -- module.  Regrettably delicate.  runST is behaving like a wrapper.
130
131 -- | Return the value computed by a state transformer computation.
132 -- The @forall@ is a technical device to ensure that the state used
133 -- by the 'ST' computation is inaccessible to the rest of the program.
134 runST :: (forall s. ST s a) -> a
135 runST st = runSTRep (case st of { ST st_rep -> st_rep })
136
137 -- I'm only letting runSTRep be inlined right at the end, in particular *after* full laziness
138 -- That's what the "INLINE [0]" says.
139 --              SLPJ Apr 99
140 {-# INLINE [0] runSTRep #-}
141 runSTRep :: (forall s. STRep s a) -> a
142 runSTRep st_rep = case st_rep realWorld# of
143                         (# _, r #) -> r
144 \end{code}