f98b33d73da3e169f4345db1ad9638ef705496e1
[ghc-base.git] / GHC / ST.lhs
1 % ------------------------------------------------------------------------------
2 % $Id: ST.lhs,v 1.1 2001/06/28 14:15:03 simonmar Exp $
3 %
4 % (c) The University of Glasgow, 1992-2000
5 %
6
7 \section[GHC.ST]{The @ST@ monad}
8
9 \begin{code}
10 {-# OPTIONS -fno-implicit-prelude #-}
11
12 module GHC.ST where
13
14 import GHC.Base
15 import GHC.Show
16 import GHC.Num
17
18 default ()
19 \end{code}
20
21 %*********************************************************
22 %*                                                      *
23 \subsection{The @ST@ monad}
24 %*                                                      *
25 %*********************************************************
26
27 The state-transformer monad proper.  By default the monad is strict;
28 too many people got bitten by space leaks when it was lazy.
29
30 \begin{code}
31 newtype ST s a = ST (STRep s a)
32 type STRep s a = State# s -> (# State# s, a #)
33
34 instance Functor (ST s) where
35     fmap f (ST m) = ST $ \ s ->
36       case (m s) of { (# new_s, r #) ->
37       (# new_s, f r #) }
38
39 instance Monad (ST s) where
40     {-# INLINE return #-}
41     {-# INLINE (>>)   #-}
42     {-# INLINE (>>=)  #-}
43     return x = ST $ \ s -> (# s, x #)
44     m >> k   =  m >>= \ _ -> k
45
46     (ST m) >>= k
47       = ST $ \ s ->
48         case (m s) of { (# new_s, r #) ->
49         case (k r) of { ST k2 ->
50         (k2 new_s) }}
51
52 data STret s a = STret (State# s) a
53
54 -- liftST is useful when we want a lifted result from an ST computation.  See
55 -- fixST below.
56 liftST :: ST s a -> State# s -> STret s a
57 liftST (ST m) = \s -> case m s of (# s', r #) -> STret s' r
58
59 {-# NOINLINE unsafeInterleaveST #-}
60 unsafeInterleaveST :: ST s a -> ST s a
61 unsafeInterleaveST (ST m) = ST ( \ s ->
62     let
63         r = case m s of (# _, res #) -> res
64     in
65     (# s, r #)
66   )
67
68 fixST :: (a -> ST s a) -> ST s a
69 fixST k = ST $ \ s ->
70     let ans       = liftST (k r) s
71         STret _ r = ans
72     in
73     case ans of STret s' x -> (# s', x #)
74
75 instance  Show (ST s a)  where
76     showsPrec _ _  = showString "<<ST action>>"
77     showList       = showList__ (showsPrec 0)
78 \end{code}
79
80 Definition of runST
81 ~~~~~~~~~~~~~~~~~~~
82
83 SLPJ 95/04: Why @runST@ must not have an unfolding; consider:
84 \begin{verbatim}
85 f x =
86   runST ( \ s -> let
87                     (a, s')  = newArray# 100 [] s
88                     (_, s'') = fill_in_array_or_something a x s'
89                   in
90                   freezeArray# a s'' )
91 \end{verbatim}
92 If we inline @runST@, we'll get:
93 \begin{verbatim}
94 f x = let
95         (a, s')  = newArray# 100 [] realWorld#{-NB-}
96         (_, s'') = fill_in_array_or_something a x s'
97       in
98       freezeArray# a s''
99 \end{verbatim}
100 And now the @newArray#@ binding can be floated to become a CAF, which
101 is totally and utterly wrong:
102 \begin{verbatim}
103 f = let
104     (a, s')  = newArray# 100 [] realWorld#{-NB-} -- YIKES!!!
105     in
106     \ x ->
107         let (_, s'') = fill_in_array_or_something a x s' in
108         freezeArray# a s''
109 \end{verbatim}
110 All calls to @f@ will share a {\em single} array!  End SLPJ 95/04.
111
112 \begin{code}
113 {-# INLINE runST #-}
114 -- The INLINE prevents runSTRep getting inlined in *this* module
115 -- so that it is still visible when runST is inlined in an importing
116 -- module.  Regrettably delicate.  runST is behaving like a wrapper.
117 runST :: (forall s. ST s a) -> a
118 runST st = runSTRep (case st of { ST st_rep -> st_rep })
119
120 -- I'm only letting runSTRep be inlined right at the end, in particular *after* full laziness
121 -- That's what the "INLINE 100" says.
122 --              SLPJ Apr 99
123 {-# INLINE 100 runSTRep #-}
124 runSTRep :: (forall s. STRep s a) -> a
125 runSTRep st_rep = case st_rep realWorld# of
126                         (# _, r #) -> r
127 \end{code}