[project @ 1999-12-03 16:17:42 by simonmar]
[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 {-# NOINLINE unsafeInterleaveST #-}
57 unsafeInterleaveST :: ST s a -> ST s a
58 unsafeInterleaveST (ST m) = ST ( \ s ->
59     let
60         r = case m s of (# _, res #) -> res
61     in
62     (# s, r #)
63   )
64
65 instance  Show (ST s a)  where
66     showsPrec _ _  = showString "<<ST action>>"
67     showList       = showList__ (showsPrec 0)
68 \end{code}
69
70 Definition of runST
71 ~~~~~~~~~~~~~~~~~~~
72
73 SLPJ 95/04: Why @runST@ must not have an unfolding; consider:
74 \begin{verbatim}
75 f x =
76   runST ( \ s -> let
77                     (a, s')  = newArray# 100 [] s
78                     (_, s'') = fill_in_array_or_something a x s'
79                   in
80                   freezeArray# a s'' )
81 \end{verbatim}
82 If we inline @runST@, we'll get:
83 \begin{verbatim}
84 f x = let
85         (a, s')  = newArray# 100 [] realWorld#{-NB-}
86         (_, s'') = fill_in_array_or_something a x s'
87       in
88       freezeArray# a s''
89 \end{verbatim}
90 And now the @newArray#@ binding can be floated to become a CAF, which
91 is totally and utterly wrong:
92 \begin{verbatim}
93 f = let
94     (a, s')  = newArray# 100 [] realWorld#{-NB-} -- YIKES!!!
95     in
96     \ x ->
97         let (_, s'') = fill_in_array_or_something a x s' in
98         freezeArray# a s''
99 \end{verbatim}
100 All calls to @f@ will share a {\em single} array!  End SLPJ 95/04.
101
102 \begin{code}
103 {-# INLINE runST #-}
104 -- The INLINE prevents runSTRep getting inlined in *this* module
105 -- so that it is still visible when runST is inlined in an importing
106 -- module.  Regrettably delicate.  runST is behaving like a wrapper.
107 runST :: (forall s. ST s a) -> a
108 runST st = runSTRep (case st of { ST st_rep -> st_rep })
109
110 -- I'm only letting runSTRep be inlined right at the end, in particular *after* full laziness
111 -- That's what the "INLINE 100" says.
112 --              SLPJ Apr 99
113 {-# INLINE 100 runSTRep #-}
114 runSTRep :: (forall s. STRep s a) -> a
115 runSTRep st_rep = case st_rep realWorld# of
116                         (# _, r #) -> r
117 \end{code}