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