1 /*
2  * (c) The GRASP/AQUA Project, Glasgow University, 1994-2002
3  *
4  * hWaitForInput Runtime Support
5  */
6 
7 /* FD_SETSIZE defaults to 64 on Windows, which makes even the most basic
8  * programs break that use select() on a socket FD.
9  * Thus we raise it here (before any #include of network-related headers)
10  * to 1024 so that at least those programs would work that would work on
11  * Linux if that used select() (luckily it uses poll() by now).
12  * See https://gitlab.haskell.org/ghc/ghc/issues/13497#note_140304
13  * The real solution would be to remove all uses of select()
14  * on Windows, too, and use IO Completion Ports instead.
15  * Note that on Windows, one can simply define FD_SETSIZE to the desired
16  * size before including Winsock2.h, as described here:
17  *   https://msdn.microsoft.com/en-us/library/windows/desktop/ms740141(v=vs.85).aspx
18  */
19 #if defined(_WIN32)
20 #define FD_SETSIZE 1024
21 #endif
22 
23 /* select and supporting types is not Posix */
24 /* #include "PosixSource.h" */
25 #include "Rts.h"
26 #include <limits.h>
27 #include <stdbool.h>
28 #include "HsBase.h"
29 #if !defined(_WIN32)
30 #include <poll.h>
31 #endif
32 
33 /*
34  * Returns a timeout suitable to be passed into poll().
35  *
36  * If `remaining` contains a fractional milliseconds part that cannot be passed
37  * to poll(), this function will return the next larger value that can, so
38  * that the timeout passed to poll() would always be `>= remaining`.
39  *
40  * If `infinite`, `remaining` is ignored.
41  */
42 static inline
43 int
compute_poll_timeout(bool infinite,Time remaining)44 compute_poll_timeout(bool infinite, Time remaining)
45 {
46     if (infinite) return -1;
47 
48     if (remaining < 0) return 0;
49 
50     if (remaining > MSToTime(INT_MAX)) return INT_MAX;
51 
52     int remaining_ms = TimeToMS(remaining);
53 
54     if (remaining != MSToTime(remaining_ms)) return remaining_ms + 1;
55 
56     return remaining_ms;
57 }
58 
59 #if defined(_WIN32)
60 /*
61  * Returns a timeout suitable to be passed into select() on Windows.
62  *
63  * The given `remaining_tv` serves as a storage for the timeout
64  * when needed, but callers should use the returned value instead
65  * as it will not be filled in all cases.
66  *
67  * If `infinite`, `remaining` is ignored and `remaining_tv` not touched
68  * (and may be passed as NULL in that case).
69  */
70 static inline
71 struct timeval *
compute_windows_select_timeout(bool infinite,Time remaining,struct timeval * remaining_tv)72 compute_windows_select_timeout(bool infinite, Time remaining,
73                                /* out */ struct timeval * remaining_tv)
74 {
75     if (infinite) {
76         return NULL;
77     }
78 
79     ASSERT(remaining_tv);
80 
81     if (remaining < 0) {
82         remaining_tv->tv_sec = 0;
83         remaining_tv->tv_usec = 0;
84     } else if (remaining > MSToTime(LONG_MAX)) {
85         remaining_tv->tv_sec = LONG_MAX;
86         remaining_tv->tv_usec = LONG_MAX;
87     } else {
88         remaining_tv->tv_sec  = TimeToMS(remaining) / 1000;
89         remaining_tv->tv_usec = TimeToUS(remaining) % 1000000;
90     }
91 
92     return remaining_tv;
93 }
94 
95 /*
96  * Returns a timeout suitable to be passed into WaitForSingleObject() on
97  * Windows.
98  *
99  * If `remaining` contains a fractional milliseconds part that cannot be passed
100  * to WaitForSingleObject(), this function will return the next larger value
101  * that can, so that the timeout passed to WaitForSingleObject() would
102  * always be `>= remaining`.
103  *
104  * If `infinite`, `remaining` is ignored.
105  */
106 static inline
107 DWORD
compute_WaitForSingleObject_timeout(bool infinite,Time remaining)108 compute_WaitForSingleObject_timeout(bool infinite, Time remaining)
109 {
110     // WaitForSingleObject() has the fascinating delicacy behaviour
111     // that it waits indefinitely if the `DWORD dwMilliseconds`
112     // is set to 0xFFFFFFFF (the maximum DWORD value), which is
113     // 4294967295 seconds == ~49.71 days
114     // (the Windows API calls this constant INFINITE...).
115     //   https://msdn.microsoft.com/en-us/library/windows/desktop/ms687032(v=vs.85).aspx
116     //
117     // We ensure that if accidentally `remaining == 4294967295`, it does
118     // NOT wait forever, by never passing that value to
119     // WaitForSingleObject() (so, never returning it from this function),
120     // unless `infinite`.
121 
122     if (infinite) return INFINITE;
123 
124     if (remaining < 0) return 0;
125 
126     if (remaining >= MSToTime(INFINITE)) return INFINITE - 1;
127 
128     DWORD remaining_ms = TimeToMS(remaining);
129 
130     if (remaining != MSToTime(remaining_ms)) return remaining_ms + 1;
131 
132     return remaining_ms;
133 }
134 #endif
135 
136 /*
137  * inputReady(fd) checks to see whether input is available on the file
138  * descriptor 'fd' within 'msecs' milliseconds (or indefinitely if 'msecs' is
139  * negative). "Input is available" is defined as 'can I safely read at least a
140  * *character* from this file object without blocking?' (this does not work
141  * reliably on Linux when the fd is a not-O_NONBLOCK socket, so if you pass
142  * socket fds to this function, ensure they have O_NONBLOCK;
143  * see `man 2 poll` and `man 2 select`, and
144  * https://gitlab.haskell.org/ghc/ghc/issues/13497#note_140309).
145  *
146  * This function blocks until either `msecs` have passed, or input is
147  * available.
148  *
149  * Returns:
150  *   1 => Input ready, 0 => not ready, -1 => error
151  * On error, sets `errno`.
152  */
153 int
fdReady(int fd,bool write,int64_t msecs,bool isSock)154 fdReady(int fd, bool write, int64_t msecs, bool isSock)
155 {
156     bool infinite = msecs < 0;
157 
158     // if we need to track the time then record the end time in case we are
159     // interrupted.
160     Time endTime = 0;
161     if (msecs > 0) {
162         endTime = getProcessElapsedTime() + MSToTime(msecs);
163     }
164 
165     // Invariant of all code below:
166     // If `infinite`, then `remaining` and `endTime` are never used.
167 
168     Time remaining = MSToTime(msecs);
169 
170     // Note [Guaranteed syscall time spent]
171     //
172     // The implementation ensures that if fdReady() is called with N `msecs`,
173     // it will not return before an FD-polling syscall *returns*
174     // with `endTime` having passed.
175     //
176     // Consider the following scenario:
177     //
178     //     1 int ready = poll(..., msecs);
179     //     2 if (EINTR happened) {
180     //     3   Time now = getProcessElapsedTime();
181     //     4   if (now >= endTime) return 0;
182     //     5   remaining = endTime - now;
183     //     6 }
184     //
185     // If `msecs` is 5 seconds, but in line 1 poll() returns with EINTR after
186     // only 10 ms due to a signal, and if at line 2 the machine starts
187     // swapping for 10 seconds, then line 4 will return that there's no
188     // data ready, even though by now there may be data ready now, and we have
189     // not actually checked after up to `msecs` = 5 seconds whether there's
190     // data ready as promised.
191     //
192     // Why is this important?
193     // Assume you call the pizza man to bring you a pizza.
194     // You arrange that you won't pay if he doesn't ring your doorbell
195     // in under 10 minutes delivery time.
196     // At 9:58 fdReady() gets woken by EINTR and then your computer swaps
197     // for 3 seconds.
198     // At 9:59 the pizza man rings.
199     // At 10:01 fdReady() will incorrectly tell you that the pizza man hasn't
200     // rung within 10 minutes, when in fact he has.
201     //
202     // If the pizza man is some watchdog service or dead man's switch program,
203     // this is problematic.
204     //
205     // To avoid it, we ensure that in the timeline diagram:
206     //
207     //                      endTime
208     //                         |
209     //     time ----+----------+-------+---->
210     //              |                  |
211     //       syscall starts     syscall returns
212     //
213     // the "syscall returns" event is always >= the "endTime" time.
214     //
215     // In the code this means that we never check whether to `return 0`
216     // after a `Time now = getProcessElapsedTime();`, and instead always
217     // let the branch marked [we waited the full msecs] handle that case.
218 
219 #if !defined(_WIN32)
220     struct pollfd fds[1];
221 
222     fds[0].fd = fd;
223     fds[0].events = write ? POLLOUT : POLLIN;
224     fds[0].revents = 0;
225 
226     // The code below tries to make as few syscalls as possible;
227     // in particular, it eschews getProcessElapsedTime() calls
228     // when `infinite` or `msecs == 0`.
229 
230     // We need to wait in a loop because poll() accepts `int` but `msecs` is
231     // `int64_t`, and because signals can interrupt it.
232 
233     while (true) {
234         int res = poll(fds, 1, compute_poll_timeout(infinite, remaining));
235 
236         if (res < 0 && errno != EINTR)
237             return (-1); // real error; errno is preserved
238 
239         if (res > 0)
240             return 1; // FD has new data
241 
242         if (res == 0 && !infinite && remaining <= MSToTime(INT_MAX))
243             return 0; // FD has no new data and [we waited the full msecs]
244 
245         // Non-exit cases
246         CHECK( ( res < 0 && errno == EINTR ) || // EINTR happened
247                // need to wait more
248                ( res == 0 && (infinite ||
249                               remaining > MSToTime(INT_MAX)) ) );
250 
251         if (!infinite) {
252             Time now = getProcessElapsedTime();
253             remaining = endTime - now;
254         }
255     }
256 
257 #else
258 
259     if (isSock) {
260         int maxfd;
261         fd_set rfd, wfd;
262         struct timeval remaining_tv;
263 
264         if ((fd >= (int)FD_SETSIZE) || (fd < 0)) {
265             barf("fdReady: fd is too big: %d but FD_SETSIZE is %d", fd, (int)FD_SETSIZE);
266         }
267         FD_ZERO(&rfd);
268         FD_ZERO(&wfd);
269         if (write) {
270             FD_SET(fd, &wfd);
271         } else {
272             FD_SET(fd, &rfd);
273         }
274 
275         /* select() will consider the descriptor set in the range of 0 to
276          * (maxfd-1)
277          */
278         maxfd = fd + 1;
279 
280         // We need to wait in a loop because the `timeval` `tv_*` members
281         // passed into select() accept are `long` (which is 32 bits on 32-bit
282         // and 64-bit Windows), but `msecs` is `int64_t`, and because signals
283         // can interrupt it.
284         //   https://msdn.microsoft.com/en-us/library/windows/desktop/ms740560(v=vs.85).aspx
285         //   https://stackoverflow.com/questions/384502/what-is-the-bit-size-of-long-on-64-bit-windows#384672
286 
287         while (true) {
288             int res = select(maxfd, &rfd, &wfd, NULL,
289                              compute_windows_select_timeout(infinite, remaining,
290                                                             &remaining_tv));
291 
292             if (res < 0 && errno != EINTR)
293                 return (-1); // real error; errno is preserved
294 
295             if (res > 0)
296                 return 1; // FD has new data
297 
298             if (res == 0 && !infinite && remaining <= MSToTime(INT_MAX))
299                 return 0; // FD has no new data and [we waited the full msecs]
300 
301             // Non-exit cases
302             CHECK( ( res < 0 && errno == EINTR ) || // EINTR happened
303                    // need to wait more
304                    ( res == 0 && (infinite ||
305                                   remaining > MSToTime(INT_MAX)) ) );
306 
307             if (!infinite) {
308                 Time now = getProcessElapsedTime();
309                 remaining = endTime - now;
310             }
311         }
312 
313     } else {
314         DWORD rc;
315         HANDLE hFile = (HANDLE)_get_osfhandle(fd);
316         DWORD avail = 0;
317 
318         switch (GetFileType(hFile)) {
319 
320             case FILE_TYPE_CHAR:
321                 {
322                     INPUT_RECORD buf[1];
323                     DWORD count;
324 
325                     // nightmare.  A Console Handle will appear to be ready
326                     // (WaitForSingleObject() returned WAIT_OBJECT_0) when
327                     // it has events in its input buffer, but these events might
328                     // not be keyboard events, so when we read from the Handle the
329                     // read() will block.  So here we try to discard non-keyboard
330                     // events from a console handle's input buffer and then try
331                     // the WaitForSingleObject() again.
332 
333                     while (1) // keep trying until we find a real key event
334                     {
335                         rc = WaitForSingleObject(
336                             hFile,
337                             compute_WaitForSingleObject_timeout(infinite, remaining));
338                         switch (rc) {
339                             case WAIT_TIMEOUT:
340                                 // We need to use < here because if remaining
341                                 // was INFINITE, we'll have waited for
342                                 // `INFINITE - 1` as per
343                                 // compute_WaitForSingleObject_timeout(),
344                                 // so that's 1 ms too little. Wait again then.
345                                 if (!infinite && remaining < MSToTime(INFINITE))
346                                     return 0; // real complete or [we waited the full msecs]
347                                 goto waitAgain;
348                             case WAIT_OBJECT_0: break;
349                             default: /* WAIT_FAILED */ maperrno(); return -1;
350                         }
351 
352                         while (1) // discard non-key events
353                         {
354                             BOOL success = PeekConsoleInput(hFile, buf, 1, &count);
355                             // printf("peek, rc=%d, count=%d, type=%d\n", rc, count, buf[0].EventType);
356                             if (!success) {
357                                 rc = GetLastError();
358                                 if (rc == ERROR_INVALID_HANDLE || rc == ERROR_INVALID_FUNCTION) {
359                                     return 1;
360                                 } else {
361                                     maperrno();
362                                     return -1;
363                                 }
364                             }
365 
366                             if (count == 0) break; // no more events => wait again
367 
368                             // discard console events that are not "key down", because
369                             // these will also be discarded by ReadFile().
370                             if (buf[0].EventType == KEY_EVENT &&
371                                 buf[0].Event.KeyEvent.bKeyDown &&
372                                 buf[0].Event.KeyEvent.uChar.AsciiChar != '\0')
373                             {
374                                 // it's a proper keypress:
375                                 return 1;
376                             }
377                             else
378                             {
379                                 // it's a non-key event, a key up event, or a
380                                 // non-character key (e.g. shift).  discard it.
381                                 BOOL success = ReadConsoleInput(hFile, buf, 1, &count);
382                                 if (!success) {
383                                     rc = GetLastError();
384                                     if (rc == ERROR_INVALID_HANDLE || rc == ERROR_INVALID_FUNCTION) {
385                                         return 1;
386                                     } else {
387                                         maperrno();
388                                         return -1;
389                                     }
390                                 }
391                             }
392                         }
393 
394                         Time now;
395                     waitAgain:
396                         now = getProcessElapsedTime();
397                         remaining = endTime - now;
398                     }
399                 }
400 
401             case FILE_TYPE_DISK:
402                 // assume that disk files are always ready:
403                 return 1;
404 
405             case FILE_TYPE_PIPE: {
406                 // WaitForMultipleObjects() doesn't work for pipes (it
407                 // always returns WAIT_OBJECT_0 even when no data is
408                 // available).  If the HANDLE is a pipe, therefore, we try
409                 // PeekNamedPipe():
410                 //
411                 // PeekNamedPipe() does not block, so if it returns that
412                 // there is no new data, we have to sleep and try again.
413 
414                 // Because PeekNamedPipe() doesn't block, we have to track
415                 // manually whether we've called it one more time after `endTime`
416                 // to fulfill Note [Guaranteed syscall time spent].
417                 bool endTimeReached = false;
418                 while (avail == 0) {
419                     BOOL success = PeekNamedPipe( hFile, NULL, 0, NULL, &avail, NULL );
420                     if (success) {
421                         if (avail != 0) {
422                             return 1;
423                         } else { // no new data
424                             if (infinite) {
425                                 Sleep(1); // 1 millisecond (smallest possible time on Windows)
426                                 continue;
427                             } else if (msecs == 0) {
428                                 return 0;
429                             } else {
430                                 if (endTimeReached) return 0; // [we waited the full msecs]
431                                 Time now = getProcessElapsedTime();
432                                 if (now >= endTime) endTimeReached = true;
433                                 Sleep(1); // 1 millisecond (smallest possible time on Windows)
434                                 continue;
435                             }
436                         }
437                     } else {
438                         rc = GetLastError();
439                         if (rc == ERROR_BROKEN_PIPE) {
440                             return 1; // this is probably what we want
441                         }
442                         if (rc != ERROR_INVALID_HANDLE && rc != ERROR_INVALID_FUNCTION) {
443                             maperrno();
444                             return -1;
445                         }
446                     }
447                 }
448             }
449             /* PeekNamedPipe didn't work - fall through to the general case */
450 
451             default:
452                 while (true) {
453                     rc = WaitForSingleObject(
454                         hFile,
455                         compute_WaitForSingleObject_timeout(infinite, remaining));
456 
457                     switch (rc) {
458                         case WAIT_TIMEOUT:
459                             // We need to use < here because if remaining
460                             // was INFINITE, we'll have waited for
461                             // `INFINITE - 1` as per
462                             // compute_WaitForSingleObject_timeout(),
463                             // so that's 1 ms too little. Wait again then.
464                             if (!infinite && remaining < MSToTime(INFINITE))
465                                 return 0; // real complete or [we waited the full msecs]
466                             break;
467                         case WAIT_OBJECT_0: return 1;
468                         default: /* WAIT_FAILED */ maperrno(); return -1;
469                     }
470 
471                     // EINTR or a >(INFINITE - 1) timeout completed
472                     if (!infinite) {
473                         Time now = getProcessElapsedTime();
474                         remaining = endTime - now;
475                     }
476                 }
477         }
478     }
479 #endif
480 }
481