[project @ 1997-03-14 05:27:40 by sof]
[ghc-hetmet.git] / ghc / lib / ghc / STBase.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1996
3 %
4 \section[STBase]{The @ST@ and @PrimIO@ monads}
5
6 \begin{code}
7 {-# OPTIONS -fno-implicit-prelude #-}
8
9 module STBase where
10
11 import Monad
12 import PrelBase
13 import GHC
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 data State a   = S# (State# a)
27 newtype ST s a = ST (State s -> (a, State s))
28
29 runST (ST m)
30   = case m (S# realWorld#) of
31       (r,_) -> r
32
33 instance Monad (ST s) where
34     {-# INLINE return #-}
35     {-# INLINE (>>)   #-}
36     {-# INLINE (>>=)  #-}
37     return x = ST $ \ s@(S# _) -> (x, s)
38     m >> k   =  m >>= \ _ -> k
39
40     (ST m) >>= k
41       = ST $ \ s ->
42         case (m s) of {(r, new_s) ->
43         case (k r) of { ST k2 ->
44         (k2 new_s) }}
45
46 {-# INLINE returnST #-}
47
48 -- here for backward compatibility:
49 returnST :: a -> ST s a
50 thenST   :: ST s a -> (a -> ST s b) -> ST s b
51 seqST    :: ST s a -> ST s b -> ST s b
52
53 returnST = return
54 thenST   = (>>=)
55 seqST    = (>>)
56
57 unsafeInterleaveST :: ST s a -> ST s a    -- ToDo: put in state-interface.tex
58 unsafeInterleaveST (ST m) = ST $ \ s ->
59     let
60         (r, new_s) = m s
61     in
62     (r, s)
63
64 fixST :: (a -> ST s a) -> ST s a
65 fixST k = ST $ \ s ->
66     let (ST k_r)  = k r
67         ans       = k_r s
68         (r,new_s) = ans
69     in
70     ans
71
72 -- more backward compatibility stuff:
73 listST          :: [ST s a] -> ST s [a]
74 mapST           :: (a -> ST s b) -> [a] -> ST s [b]
75 mapAndUnzipST   :: (a -> ST s (b,c)) -> [a] -> ST s ([b],[c])
76
77 listST          = accumulate
78 mapST           = mapM
79 mapAndUnzipST   = mapAndUnzipM
80
81 \end{code}
82
83
84 %*********************************************************
85 %*                                                      *
86 \subsection{The @PrimIO@ monad}
87 %*                                                      *
88 %*********************************************************
89
90 \begin{code}
91 type PrimIO a = ST RealWorld a
92
93 fixPrimIO :: (a -> PrimIO a) -> PrimIO a
94 fixPrimIO = fixST
95
96 {-# GENERATE_SPECS unsafePerformPrimIO a #-}
97 unsafePerformPrimIO     :: PrimIO a -> a
98 unsafeInterleavePrimIO  :: PrimIO a -> PrimIO a
99
100 unsafePerformPrimIO     = runST
101 unsafeInterleavePrimIO  = unsafeInterleaveST
102
103 -- the following functions are now there for backward compatibility mostly:
104
105 {-# GENERATE_SPECS returnPrimIO a #-}
106 returnPrimIO    :: a -> PrimIO a
107
108 {-# GENERATE_SPECS thenPrimIO b #-}
109 thenPrimIO      :: PrimIO a -> (a -> PrimIO b) -> PrimIO b
110
111 {-# GENERATE_SPECS seqPrimIO b #-}
112 seqPrimIO       :: PrimIO a -> PrimIO b -> PrimIO b
113
114 listPrimIO      :: [PrimIO a] -> PrimIO [a]
115 mapPrimIO       :: (a -> PrimIO b) -> [a] -> PrimIO [b]
116 mapAndUnzipPrimIO :: (a -> PrimIO (b,c)) -> [a] -> PrimIO ([b],[c])
117
118 {-# INLINE returnPrimIO #-}
119 {-# INLINE thenPrimIO   #-}
120 {-# INLINE seqPrimIO  #-}
121
122 returnPrimIO      = return
123 thenPrimIO        = (>>=)
124 seqPrimIO         = (>>)
125 listPrimIO        = accumulate
126 mapPrimIO         = mapM
127 mapAndUnzipPrimIO = mapAndUnzipM
128 \end{code}
129
130
131 %*********************************************************
132 %*                                                      *
133 \subsection{Ghastly return types}
134 %*                                                      *
135 %*********************************************************
136
137 \begin{code}
138 data StateAndPtr#    s elt = StateAndPtr#    (State# s) elt 
139
140 data StateAndChar#   s     = StateAndChar#   (State# s) Char# 
141 data StateAndInt#    s     = StateAndInt#    (State# s) Int# 
142 data StateAndWord#   s     = StateAndWord#   (State# s) Word#
143 data StateAndFloat#  s     = StateAndFloat#  (State# s) Float# 
144 data StateAndDouble# s     = StateAndDouble# (State# s) Double#  
145 data StateAndAddr#   s     = StateAndAddr#   (State# s) Addr#
146 \end{code}