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