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