57559708f774c2a9927f47de52ca3e281439a60a
[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 -> STret s a)
27
28 data STret s a = STret (State# s) a
29
30 instance Functor (ST s) where
31     map f (ST m) = ST $ \ s ->
32       case (m s) of { STret new_s r ->
33       STret new_s (f r) }
34
35 instance Monad (ST s) where
36     {-# INLINE return #-}
37     {-# INLINE (>>)   #-}
38     {-# INLINE (>>=)  #-}
39     return x = ST $ \ s -> STret s x
40     m >> k   =  m >>= \ _ -> k
41
42     (ST m) >>= k
43       = ST $ \ s ->
44         case (m s) of { STret new_s r ->
45         case (k r) of { ST k2 ->
46         (k2 new_s) }}
47
48
49
50 fixST :: (a -> ST s a) -> ST s a
51 fixST k = ST $ \ s ->
52     let (ST k_r)  = k r
53         ans       = k_r s
54         STret _ r = ans
55     in
56     ans
57
58 {-# NOINLINE unsafeInterleaveST #-}
59 unsafeInterleaveST :: ST s a -> ST s a
60 unsafeInterleaveST (ST m) = ST ( \ s ->
61     let
62         STret _ r = m s
63     in
64     STret s r)
65
66 \end{code}
67
68 Definition of runST
69 ~~~~~~~~~~~~~~~~~~~
70
71 SLPJ 95/04: Why @runST@ must not have an unfolding; consider:
72 \begin{verbatim}
73 f x =
74   runST ( \ s -> let
75                     (a, s')  = newArray# 100 [] s
76                     (_, s'') = fill_in_array_or_something a x s'
77                   in
78                   freezeArray# a s'' )
79 \end{verbatim}
80 If we inline @runST@, we'll get:
81 \begin{verbatim}
82 f x = let
83         (a, s')  = newArray# 100 [] realWorld#{-NB-}
84         (_, s'') = fill_in_array_or_something a x s'
85       in
86       freezeArray# a s''
87 \end{verbatim}
88 And now the @newArray#@ binding can be floated to become a CAF, which
89 is totally and utterly wrong:
90 \begin{verbatim}
91 f = let
92     (a, s')  = newArray# 100 [] realWorld#{-NB-} -- YIKES!!!
93     in
94     \ x ->
95         let (_, s'') = fill_in_array_or_something a x s' in
96         freezeArray# a s''
97 \end{verbatim}
98 All calls to @f@ will share a {\em single} array!  End SLPJ 95/04.
99
100 \begin{code}
101 {-# NOINLINE runST #-}
102 runST :: (All s => ST s a) -> a
103 runST st = 
104   case st of
105         ST m -> case m realWorld# of
106                         STret _ r -> r
107 \end{code}
108
109 %*********************************************************
110 %*                                                      *
111 \subsection{Ghastly return types}
112 %*                                                      *
113 %*********************************************************
114
115 The @State@ type is the return type of a _ccall_ with no result.  It
116 never actually exists, since it's always deconstructed straight away;
117 the desugarer ensures this.
118
119 \begin{code}
120 data State           s     = S#              (State# s)
121 data StateAndPtr#    s elt = StateAndPtr#    (State# s) elt 
122
123 data StateAndChar#   s     = StateAndChar#   (State# s) Char# 
124 data StateAndInt#    s     = StateAndInt#    (State# s) Int# 
125 data StateAndWord#   s     = StateAndWord#   (State# s) Word#
126 data StateAndFloat#  s     = StateAndFloat#  (State# s) Float# 
127 data StateAndDouble# s     = StateAndDouble# (State# s) Double#  
128 data StateAndAddr#   s     = StateAndAddr#   (State# s) Addr#
129
130 data StateAndInt64#  s     = StateAndInt64#  (State# s) Int64#
131 data StateAndWord64# s     = StateAndWord64# (State# s) Word64#
132 \end{code}