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