[project @ 1998-12-02 13:17:09 by simonm]
[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 PrelBase
13 import PrelGHC
14 \end{code}
15
16 %*********************************************************
17 %*                                                      *
18 \subsection{The @ST@ monad}
19 %*                                                      *
20 %*********************************************************
21
22 The state-transformer monad proper.  By default the monad is strict;
23 too many people got bitten by space leaks when it was lazy.
24
25 \begin{code}
26 newtype ST s a = ST (State# s -> (# State# s, a #))
27
28 instance Functor (ST s) where
29     map f (ST m) = ST $ \ s ->
30       case (m s) of { (# new_s, r #) ->
31       (# new_s, f r #) }
32
33 instance Monad (ST s) where
34     {-# INLINE return #-}
35     {-# INLINE (>>)   #-}
36     {-# INLINE (>>=)  #-}
37     return x = ST $ \ s -> (# s, x #)
38     m >> k   =  m >>= \ _ -> k
39
40     (ST m) >>= k
41       = ST $ \ s ->
42         case (m s) of { (# new_s, r #) ->
43         case (k r) of { ST k2 ->
44         (k2 new_s) }}
45
46 data STret s a = STret (State# s) a
47
48 -- liftST is useful when we want a lifted result from an ST computation.  See
49 -- fixST below.
50 liftST :: ST s a -> State# s -> STret s a
51 liftST (ST m) = \s -> case m s of (# s', r #) -> STret s' r
52
53 fixST :: (a -> ST s a) -> ST s a
54 fixST k = ST $ \ s ->
55     let ans       = liftST (k r) s
56         STret _ r = ans
57     in
58     case ans of STret s' r -> (# 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 p f  = 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 {-# NOINLINE runST #-}
108 runST :: (forall s. ST s a) -> a
109 runST st = 
110   case st of
111         ST m -> case m realWorld# of
112                         (# _, r #) -> r
113 \end{code}
114
115 %*********************************************************
116 %*                                                      *
117 \subsection{Ghastly return types}
118 %*                                                      *
119 %*********************************************************
120
121 The @State@ type is the return type of a _ccall_ with no result.  It
122 never actually exists, since it's always deconstructed straight away;
123 the desugarer ensures this.
124
125 \begin{code}
126 data State           s     = S#              (State# s)
127 \end{code}