1 /* -----------------------------------------------------------------------------
3 * (c) The GHC Team 1995-2002
5 * Support for concurrent non-blocking I/O and thread waiting in the
6 * non-threaded RTS. In the threded RTS, this file is not used at
7 * all, instead we use the IO manager thread implemented in Haskell in
10 * ---------------------------------------------------------------------------*/
12 #include "PosixSource.h"
19 #include "Capability.h"
21 #include "AwaitEvent.h"
25 # ifdef HAVE_SYS_SELECT_H
26 # include <sys/select.h>
29 # ifdef HAVE_SYS_TYPES_H
30 # include <sys/types.h>
38 #if !defined(THREADED_RTS)
40 // The target time for a threadDelay is stored in a one-word quantity
41 // in the TSO (tso->block_info.target). On a 32-bit machine we
42 // therefore can't afford to use nanosecond resolution because it
43 // would overflow too quickly, so instead we use millisecond
46 #if SIZEOF_VOID_P == 4
47 #define LowResTimeToTime(t) (USToTime((t) * 1000))
48 #define TimeToLowResTimeRoundDown(t) (TimeToUS(t) / 1000)
49 #define TimeToLowResTimeRoundUp(t) ((TimeToUS(t) + 1000-1) / 1000)
51 #define LowResTimeToTime(t) (t)
52 #define TimeToLowResTimeRoundDown(t) (t)
53 #define TimeToLowResTimeRoundUp(t) (t)
57 * Return the time since the program started, in LowResTime,
60 static LowResTime
getLowResTimeOfDay(void)
62 return TimeToLowResTimeRoundDown(getProcessElapsedTime());
66 * For a given microsecond delay, return the target time in LowResTime.
68 LowResTime
getDelayTarget (HsInt us
)
70 // round up the target time, because we never want to sleep *less*
71 // than the desired amount.
72 return TimeToLowResTimeRoundUp(getProcessElapsedTime() + USToTime(us
));
75 /* There's a clever trick here to avoid problems when the time wraps
76 * around. Since our maximum delay is smaller than 31 bits of ticks
77 * (it's actually 31 bits of microseconds), we can safely check
78 * whether a timer has expired even if our timer will wrap around
79 * before the target is reached, using the following formula:
81 * (int)((uint)current_time - (uint)target_time) < 0
83 * if this is true, then our time has expired.
84 * (idea due to Andy Gill).
86 static rtsBool
wakeUpSleepingThreads (LowResTime now
)
89 rtsBool flag
= rtsFalse
;
91 while (sleeping_queue
!= END_TSO_QUEUE
) {
93 if (((long)now
- (long)tso
->block_info
.target
) < 0) {
96 sleeping_queue
= tso
->_link
;
97 tso
->why_blocked
= NotBlocked
;
98 tso
->_link
= END_TSO_QUEUE
;
99 IF_DEBUG(scheduler
,debugBelch("Waking up sleeping thread %lu\n", (unsigned long)tso
->id
));
100 // MainCapability: this code is !THREADED_RTS
101 pushOnRunQueue(&MainCapability
,tso
);
107 static void GNUC3_ATTRIBUTE(__noreturn__
)
108 fdOutOfRange (int fd
)
110 errorBelch("file descriptor %d out of range for select (0--%d).\nRecompile with -threaded to work around this.", fd
, (int)FD_SETSIZE
);
111 stg_exit(EXIT_FAILURE
);
114 /* Argument 'wait' says whether to wait for I/O to become available,
115 * or whether to just check and return immediately. If there are
116 * other threads ready to run, we normally do the non-waiting variety,
117 * otherwise we wait (see Schedule.c).
119 * SMP note: must be called with sched_mutex locked.
121 * Windows: select only works on sockets, so this doesn't really work,
122 * though it makes things better than before. MsgWaitForMultipleObjects
123 * should really be used, though it only seems to work for read handles,
128 awaitEvent(rtsBool wait
)
130 StgTSO
*tso
, *prev
, *next
;
135 rtsBool select_succeeded
= rtsTrue
;
136 rtsBool unblock_all
= rtsFalse
;
137 struct timeval tv
, *ptv
;
141 debugBelch("scheduler: checking for threads blocked on I/O");
143 debugBelch(" (waiting)");
148 /* loop until we've woken up some threads. This loop is needed
149 * because the select timing isn't accurate, we sometimes sleep
150 * for a while but not long enough to wake up a thread in
155 now
= getLowResTimeOfDay();
156 if (wakeUpSleepingThreads(now
)) {
161 * Collect all of the fd's that we're interested in
166 for(tso
= blocked_queue_hd
; tso
!= END_TSO_QUEUE
; tso
= next
) {
169 /* On FreeBSD FD_SETSIZE is unsigned. Cast it to signed int
170 * in order to switch off the 'comparison between signed and
171 * unsigned error message
173 switch (tso
->why_blocked
) {
176 int fd
= tso
->block_info
.fd
;
177 if ((fd
>= (int)FD_SETSIZE
) || (fd
< 0)) {
180 maxfd
= (fd
> maxfd
) ? fd
: maxfd
;
187 int fd
= tso
->block_info
.fd
;
188 if ((fd
>= (int)FD_SETSIZE
) || (fd
< 0)) {
191 maxfd
= (fd
> maxfd
) ? fd
: maxfd
;
206 } else if (sleeping_queue
!= END_TSO_QUEUE
) {
207 Time min
= LowResTimeToTime(sleeping_queue
->block_info
.target
- now
);
208 tv
.tv_sec
= TimeToSeconds(min
);
209 tv
.tv_usec
= TimeToUS(min
) % 1000000;
215 while (1) { // repeat the select on EINTR
217 // Disable the timer signal while blocked in
218 // select(), to conserve power. (#1623, #5991)
219 if (wait
) stopTimer();
221 numFound
= select(maxfd
+1, &rfd
, &wfd
, NULL
, ptv
);
223 if (wait
) startTimer();
225 if (numFound
>= 0) break;
227 if (errno
!= EINTR
) {
228 /* Handle bad file descriptors by unblocking all the
229 waiting threads. Why? Because a thread might have been
230 a bit naughty and closed a file descriptor while another
231 was blocked waiting. This is less-than-good programming
232 practice, but having the RTS as a result fall over isn't
233 acceptable, so we simply unblock all the waiting threads
234 should we see a bad file descriptor & give the threads
235 a chance to clean up their act.
237 Note: assume here that threads becoming unblocked
238 will try to read/write the file descriptor before trying
239 to issue a threadWaitRead/threadWaitWrite again (==> an
240 IOError will result for the thread that's got the bad
241 file descriptor.) Hence, there's no danger of a bad
242 file descriptor being repeatedly select()'ed on, so
245 if ( errno
== EBADF
) {
246 unblock_all
= rtsTrue
;
249 sysErrorBelch("select");
250 stg_exit(EXIT_FAILURE
);
254 /* We got a signal; could be one of ours. If so, we need
255 * to start up the signal handler straight away, otherwise
256 * we could block for a long time before the signal is
259 #if defined(RTS_USER_SIGNALS)
260 if (RtsFlags
.MiscFlags
.install_signal_handlers
&& signals_pending()) {
261 startSignalHandlers(&MainCapability
);
262 return; /* still hold the lock */
266 /* we were interrupted, return to the scheduler immediately.
268 if (sched_state
>= SCHED_INTERRUPTING
) {
269 return; /* still hold the lock */
272 /* check for threads that need waking up
274 wakeUpSleepingThreads(getLowResTimeOfDay());
276 /* If new runnable threads have arrived, stop waiting for
279 if (!emptyRunQueue(&MainCapability
)) {
280 return; /* still hold the lock */
284 /* Step through the waiting queue, unblocking every thread that now has
285 * a file descriptor in a ready state.
289 if (select_succeeded
|| unblock_all
) {
290 for(tso
= blocked_queue_hd
; tso
!= END_TSO_QUEUE
; tso
= next
) {
293 switch (tso
->why_blocked
) {
295 ready
= unblock_all
|| FD_ISSET(tso
->block_info
.fd
, &rfd
);
298 ready
= unblock_all
|| FD_ISSET(tso
->block_info
.fd
, &wfd
);
305 IF_DEBUG(scheduler
,debugBelch("Waking up blocked thread %lu\n", (unsigned long)tso
->id
));
306 tso
->why_blocked
= NotBlocked
;
307 tso
->_link
= END_TSO_QUEUE
;
308 pushOnRunQueue(&MainCapability
,tso
);
311 blocked_queue_hd
= tso
;
313 setTSOLink(&MainCapability
, prev
, tso
);
319 blocked_queue_hd
= blocked_queue_tl
= END_TSO_QUEUE
;
321 prev
->_link
= END_TSO_QUEUE
;
322 blocked_queue_tl
= prev
;
326 } while (wait
&& sched_state
== SCHED_RUNNING
327 && emptyRunQueue(&MainCapability
));
330 #endif /* THREADED_RTS */