74a1d7ac6da940972cde2902ac4b6ca7d09dfb07
[ghc-hetmet.git] / ghc / lib / std / PrelConc.lhs
1 %
2 % (c) The AQUA Project, Glasgow University, 1994-1996
3 %
4
5 \section[PrelConc]{Module @PrelConc@}
6
7 Basic concurrency stuff
8
9 \begin{code}
10 {-# OPTIONS -fno-implicit-prelude #-}
11
12 module PrelConc
13         ( ThreadId(..)
14
15         -- Forking and suchlike
16         , myThreadId    -- :: IO ThreadId
17         , killThread    -- :: ThreadId -> IO ()
18         , raiseInThread -- :: ThreadId -> Exception -> IO ()
19         , par           -- :: a -> b -> b
20         , seq           -- :: a -> b -> b
21         , yield         -- :: IO ()
22
23         -- Waiting
24         , threadDelay           -- :: Int -> IO ()
25         , threadWaitRead        -- :: Int -> IO ()
26         , threadWaitWrite       -- :: Int -> IO ()
27
28         -- MVars
29         , MVar          -- abstract
30         , newMVar       -- :: a -> IO (MVar a)
31         , newEmptyMVar  -- :: IO (MVar a)
32         , takeMVar      -- :: MVar a -> IO a
33         , putMVar       -- :: MVar a -> a -> IO ()
34         , readMVar      -- :: MVar a -> IO a
35         , swapMVar      -- :: MVar a -> a -> IO a
36         , tryTakeMVar   -- :: MVar a -> IO (Maybe a)
37         , isEmptyMVar   -- :: MVar a -> IO Bool
38
39     ) where
40
41 import PrelBase
42 import PrelMaybe
43 import PrelErr ( parError, seqError )
44 import PrelST           ( liftST )
45 import PrelIOBase       ( IO(..), MVar(..), unsafePerformIO )
46 import PrelBase         ( Int(..) )
47 import PrelException    ( Exception(..), AsyncException(..) )
48
49 infixr 0 `par`, `seq`
50 \end{code}
51
52 %************************************************************************
53 %*                                                                      *
54 \subsection{@ThreadId@, @par@, and @fork@}
55 %*                                                                      *
56 %************************************************************************
57
58 \begin{code}
59 data ThreadId = ThreadId ThreadId#
60 -- ToDo: data ThreadId = ThreadId (Weak ThreadId#)
61 -- But since ThreadId# is unlifted, the Weak type must use open
62 -- type variables.
63
64 --forkIO has now been hoisted out into the Concurrent library.
65
66 killThread :: ThreadId -> IO ()
67 killThread (ThreadId id) = IO $ \ s ->
68    case (killThread# id (AsyncException ThreadKilled) s) of s1 -> (# s1, () #)
69
70 raiseInThread :: ThreadId -> Exception -> IO ()
71 raiseInThread (ThreadId id) ex = IO $ \ s ->
72    case (killThread# id ex s) of s1 -> (# s1, () #)
73
74 myThreadId :: IO ThreadId
75 myThreadId = IO $ \s ->
76    case (myThreadId# s) of (# s1, id #) -> (# s1, ThreadId id #)
77
78 yield :: IO ()
79 yield = IO $ \s -> 
80    case (yield# s) of s1 -> (# s1, () #)
81
82 -- "seq" is defined a bit wierdly (see below)
83 --
84 -- The reason for the strange "0# -> parError" case is that
85 -- it fools the compiler into thinking that seq is non-strict in
86 -- its second argument (even if it inlines seq at the call site).
87 -- If it thinks seq is strict in "y", then it often evaluates
88 -- "y" before "x", which is totally wrong.  
89 --
90 -- Just before converting from Core to STG there's a bit of magic
91 -- that recognises the seq# and eliminates the duff case.
92
93 {-# INLINE seq  #-}
94 seq :: a -> b -> b
95 seq  x y = case (seq#  x) of { 0# -> seqError; _ -> y }
96
97 {-# INLINE par  #-}
98 par :: a -> b -> b
99 par  x y = case (par# x) of { 0# -> parError; _ -> y }
100 \end{code}
101
102 %************************************************************************
103 %*                                                                      *
104 \subsection[mvars]{M-Structures}
105 %*                                                                      *
106 %************************************************************************
107
108 M-Vars are rendezvous points for concurrent threads.  They begin
109 empty, and any attempt to read an empty M-Var blocks.  When an M-Var
110 is written, a single blocked thread may be freed.  Reading an M-Var
111 toggles its state from full back to empty.  Therefore, any value
112 written to an M-Var may only be read once.  Multiple reads and writes
113 are allowed, but there must be at least one read between any two
114 writes.
115
116 \begin{code}
117 --Defined in IOBase to avoid cycle: data MVar a = MVar (SynchVar# RealWorld a)
118
119 newEmptyMVar  :: IO (MVar a)
120 newEmptyMVar = IO $ \ s# ->
121     case newMVar# s# of
122          (# s2#, svar# #) -> (# s2#, MVar svar# #)
123
124 takeMVar :: MVar a -> IO a
125 takeMVar (MVar mvar#) = IO $ \ s# -> takeMVar# mvar# s#
126
127 putMVar  :: MVar a -> a -> IO ()
128 putMVar (MVar mvar#) x = IO $ \ s# ->
129     case putMVar# mvar# x s# of
130         s2# -> (# s2#, () #)
131
132 newMVar :: a -> IO (MVar a)
133 newMVar value =
134     newEmptyMVar        >>= \ mvar ->
135     putMVar mvar value  >>
136     return mvar
137
138 readMVar :: MVar a -> IO a
139 readMVar mvar =
140     takeMVar mvar       >>= \ value ->
141     putMVar mvar value  >>
142     return value
143
144 swapMVar :: MVar a -> a -> IO a
145 swapMVar mvar new =
146     takeMVar mvar       >>= \ old ->
147     putMVar mvar new    >>
148     return old
149
150 -- tryTakeMVar is a non-blocking takeMVar
151 tryTakeMVar :: MVar a -> IO (Maybe a)
152 tryTakeMVar (MVar m) = IO $ \ s ->
153     case tryTakeMVar# m s of
154         (# s, 0#, _ #) -> (# s, Nothing #)      -- MVar is empty
155         (# s, _,  a #) -> (# s, Just a  #)      -- MVar is full
156
157 {- 
158  Low-level op. for checking whether an MVar is filled-in or not.
159  Notice that the boolean value returned  is just a snapshot of
160  the state of the MVar. By the time you get to react on its result,
161  the MVar may have been filled (or emptied) - so be extremely
162  careful when using this operation.  
163
164  Use tryTakeMVar instead if possible.
165
166  If you can re-work your abstractions to avoid having to
167  depend on isEmptyMVar, then you're encouraged to do so,
168  i.e., consider yourself warned about the imprecision in
169  general of isEmptyMVar :-)
170 -}
171 isEmptyMVar :: MVar a -> IO Bool
172 isEmptyMVar (MVar mv#) = IO $ \ s# -> 
173     case isEmptyMVar# mv# s# of
174         (# s2#, flg #) -> (# s2#, not (flg ==# 0#) #)
175 \end{code}
176
177
178 %************************************************************************
179 %*                                                                      *
180 \subsection{Thread waiting}
181 %*                                                                      *
182 %************************************************************************
183
184 @threadDelay@ delays rescheduling of a thread until the indicated
185 number of microseconds have elapsed.  Generally, the microseconds are
186 counted by the context switch timer, which ticks in virtual time;
187 however, when there are no runnable threads, we don't accumulate any
188 virtual time, so we start ticking in real time.  (The granularity is
189 the effective resolution of the context switch timer, so it is
190 affected by the RTS -C option.)
191
192 @threadWaitRead@ delays rescheduling of a thread until input on the
193 specified file descriptor is available for reading (just like select).
194 @threadWaitWrite@ is similar, but for writing on a file descriptor.
195
196 \begin{code}
197 threadDelay, threadWaitRead, threadWaitWrite :: Int -> IO ()
198
199 threadDelay     (I# ms) = IO $ \s -> case delay# ms s     of s -> (# s, () #)
200 threadWaitRead  (I# fd) = IO $ \s -> case waitRead# fd s  of s -> (# s, () #)
201 threadWaitWrite (I# fd) = IO $ \s -> case waitWrite# fd s of s -> (# s, () #)
202 \end{code}