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