~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to erts/emulator/sys/win32/erl_poll.c

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
/*
2
2
 * %CopyrightBegin%
3
3
 *
4
 
 * Copyright Ericsson AB 2007-2010. All Rights Reserved.
 
4
 * Copyright Ericsson AB 2007-2011. All Rights Reserved.
5
5
 *
6
6
 * The contents of this file are subject to the Erlang Public License,
7
7
 * Version 1.1, (the "License"); you may not use this file except in
274
274
    Waiter** waiter;
275
275
    int allocated_waiters;  /* Size ow waiter array */ 
276
276
    int num_waiters;        /* Number of waiter threads. */
277
 
    erts_atomic_t sys_io_ready; /* Tells us there is I/O ready (already). */
278
277
    int restore_events;        /* Tells us to restore waiters events 
279
278
                                  next time around */
280
279
    HANDLE event_io_ready;     /* To be used when waiting for io */
282
281
    volatile int standby_wait_counter; /* Number of threads to wait for */
283
282
    CRITICAL_SECTION standby_crit;     /* CS to guard the counter */
284
283
    HANDLE standby_wait_event;         /* Event signalled when counte == 0 */
 
284
    erts_atomic32_t wakeup_state;
285
285
#ifdef ERTS_SMP
286
 
    erts_smp_atomic_t woken;
287
286
    erts_smp_mtx_t mtx;
288
 
    erts_smp_atomic_t interrupt;
289
287
#endif
290
 
    erts_smp_atomic_t timeout;
 
288
    erts_smp_atomic32_t timeout;
291
289
};
292
290
 
293
291
#ifdef ERTS_SMP
296
294
  erts_smp_mtx_lock(&(PS)->mtx)
297
295
#define ERTS_POLLSET_UNLOCK(PS) \
298
296
  erts_smp_mtx_unlock(&(PS)->mtx)
299
 
#define ERTS_POLLSET_SET_POLLED_CHK(PS) \
300
 
  ((int) erts_smp_atomic_xchg(&(PS)->polled, (long) 1))
301
 
#define ERTS_POLLSET_SET_POLLED(PS) \
302
 
  erts_smp_atomic_set(&(PS)->polled, (long) 1)
303
 
#define ERTS_POLLSET_UNSET_POLLED(PS) \
304
 
  erts_smp_atomic_set(&(PS)->polled, (long) 0)
305
 
#define ERTS_POLLSET_IS_POLLED(PS) \
306
 
  ((int) erts_smp_atomic_read(&(PS)->polled))
307
 
 
308
 
#define ERTS_POLLSET_SET_POLLER_WOKEN_CHK(PS) set_poller_woken_chk((PS))
309
 
#define ERTS_POLLSET_SET_POLLER_WOKEN(PS)                               \
310
 
do {                                                                    \
311
 
      ERTS_THR_MEMORY_BARRIER;                                          \
312
 
      erts_smp_atomic_set(&(PS)->woken, (long) 1);                      \
313
 
} while (0)
314
 
#define ERTS_POLLSET_UNSET_POLLER_WOKEN(PS)                             \
315
 
do {                                                                    \
316
 
    erts_smp_atomic_set(&(PS)->woken, (long) 0);                        \
317
 
    ERTS_THR_MEMORY_BARRIER;                                            \
318
 
} while (0)
319
 
#define ERTS_POLLSET_IS_POLLER_WOKEN(PS)                                \
320
 
  ((int) erts_smp_atomic_read(&(PS)->woken))
321
 
 
322
 
#define ERTS_POLLSET_UNSET_INTERRUPTED_CHK(PS) unset_interrupted_chk((PS))
323
 
#define ERTS_POLLSET_UNSET_INTERRUPTED(PS)                              \
324
 
do {                                                                    \
325
 
    erts_smp_atomic_set(&(PS)->interrupt, (long) 0);                    \
326
 
    ERTS_THR_MEMORY_BARRIER;                                            \
327
 
} while (0)
328
 
#define ERTS_POLLSET_SET_INTERRUPTED(PS)                                \
329
 
do {                                                                    \
330
 
      ERTS_THR_MEMORY_BARRIER;                                          \
331
 
      erts_smp_atomic_set(&(PS)->interrupt, (long) 1);                  \
332
 
} while (0)
333
 
#define ERTS_POLLSET_IS_INTERRUPTED(PS)                                 \
334
 
  ((int) erts_smp_atomic_read(&(PS)->interrupt))
335
 
 
336
 
static ERTS_INLINE int
337
 
unset_interrupted_chk(ErtsPollSet ps)
338
 
{
339
 
    int res = (int) erts_smp_atomic_xchg(&ps->interrupt, (long) 0);
340
 
    ERTS_THR_MEMORY_BARRIER;
341
 
    return res;
342
 
 
343
 
}
344
 
 
345
 
static ERTS_INLINE int
346
 
set_poller_woken_chk(ErtsPollSet ps)
347
 
{
348
 
    ERTS_THR_MEMORY_BARRIER;
349
 
    return (int) erts_smp_atomic_xchg(&ps->woken, (long) 1);
350
 
}
351
297
 
352
298
#else
353
299
 
354
300
#define ERTS_POLLSET_LOCK(PS)
355
301
#define ERTS_POLLSET_UNLOCK(PS)
356
 
#define ERTS_POLLSET_SET_POLLED_CHK(PS) 0
357
 
#define ERTS_POLLSET_UNSET_POLLED(PS)
358
 
#define ERTS_POLLSET_IS_POLLED(PS) 0
359
 
#define ERTS_POLLSET_SET_POLLER_WOKEN_CHK(PS) 1
360
 
#define ERTS_POLLSET_SET_POLLER_WOKEN(PS)
361
 
#define ERTS_POLLSET_UNSET_POLLER_WOKEN(PS)
362
 
#define ERTS_POLLSET_IS_POLLER_WOKEN(PS) 1
363
 
 
364
 
 
365
 
#endif
366
 
 
367
 
/*
368
 
 * While atomics are not yet implemented for windows in the common library...
369
 
 *
370
 
 * MSDN doc states that SMP machines and old compilers require
371
 
 * InterLockedExchange to properly read and write interlocked
372
 
 * variables, otherwise the processors might reschedule
373
 
 * the access and order of atomics access is destroyed... 
374
 
 * While they only mention it in white-papers, the problem
375
 
 * in VS2003 is due to the IA64 arch, so we can still count
376
 
 * on the CPU not rescheduling the access to volatile in X86 arch using 
377
 
 * even the slightly older compiler...
378
 
 *
379
 
 * So here's (hopefully) a subset of the generally working atomic 
380
 
 * variable access...
381
 
 */
382
 
 
383
 
#if defined(__GNUC__)
384
 
#  if defined(__i386__) || defined(__x86_64__)
385
 
#    define VOLATILE_IN_SEQUENCE 1
386
 
#  else
387
 
#    define VOLATILE_IN_SEQUENCE 0
388
 
#  endif 
389
 
#elif defined(_MSC_VER)
390
 
#  if _MSC_VER < 1300
391
 
#    define VOLATILE_IN_SEQUENCE 0 /* Dont trust really old compilers */
392
 
#  else
393
 
#    if defined(_M_IX86)
394
 
#      define VOLATILE_IN_SEQUENCE 1
395
 
#    else /* I.e. IA64 */
396
 
#      if _MSC_VER >= 1400 
397
 
#        define VOLATILE_IN_SEQUENCE 1
398
 
#      else
399
 
#        define VOLATILE_IN_SEQUENCE 0
400
 
#      endif
401
 
#    endif
402
 
#  endif
403
 
#else
404
 
# define VOLATILE_IN_SEQUENCE 0
405
 
#endif
406
 
 
407
 
 
 
302
 
 
303
#endif
408
304
 
409
305
/*
410
306
 * Communication with sys_interrupt
411
307
 */
412
308
 
413
309
#ifdef ERTS_SMP
414
 
extern erts_smp_atomic_t erts_break_requested;
 
310
extern erts_smp_atomic32_t erts_break_requested;
415
311
#define ERTS_SET_BREAK_REQUESTED \
416
 
  erts_smp_atomic_set(&erts_break_requested, (long) 1)
 
312
  erts_smp_atomic32_set_nob(&erts_break_requested, (erts_aint32_t) 1)
417
313
#define ERTS_UNSET_BREAK_REQUESTED \
418
 
  erts_smp_atomic_set(&erts_break_requested, (long) 0)
 
314
  erts_smp_atomic32_set_nob(&erts_break_requested, (erts_aint32_t) 0)
419
315
#else
420
316
extern volatile int erts_break_requested;
421
317
#define ERTS_SET_BREAK_REQUESTED (erts_break_requested = 1)
424
320
 
425
321
static erts_mtx_t break_waiter_lock;
426
322
static HANDLE break_happened_event;
427
 
static erts_atomic_t break_waiter_state;
 
323
static erts_atomic32_t break_waiter_state;
428
324
#define BREAK_WAITER_GOT_BREAK 1
429
325
#define BREAK_WAITER_GOT_HALT 2
430
326
 
467
363
    wait_standby(PS); \
468
364
 } while(0)
469
365
 
470
 
#if ERTS_POLL_ASYNC_INTERRUPT_SUPPORT && !defined(ERTS_SMP)
471
 
 
472
 
static ERTS_INLINE int
473
 
unset_interrupted_chk(ErtsPollSet ps)
474
 
{
475
 
    /* This operation isn't atomic, but we have no need at all for an
476
 
       atomic operation here... */
477
 
    int res = ps->interrupt;
478
 
    ps->interrupt = 0;
 
366
#define ERTS_POLL_NOT_WOKEN             ((erts_aint32_t) 0)
 
367
#define ERTS_POLL_WOKEN_IO_READY        ((erts_aint32_t) 1)
 
368
#define ERTS_POLL_WOKEN_INTR            ((erts_aint32_t) 2)
 
369
#define ERTS_POLL_WOKEN_TIMEDOUT        ((erts_aint32_t) 3)
 
370
 
 
371
static ERTS_INLINE int
 
372
is_io_ready(ErtsPollSet ps)
 
373
{
 
374
    return erts_atomic32_read_nob(&ps->wakeup_state) == ERTS_POLL_WOKEN_IO_READY;
 
375
}
 
376
 
 
377
static ERTS_INLINE void
 
378
woke_up(ErtsPollSet ps)
 
379
{
 
380
    if (erts_atomic32_read_nob(&ps->wakeup_state) == ERTS_POLL_NOT_WOKEN)
 
381
        erts_atomic32_cmpxchg_nob(&ps->wakeup_state,
 
382
                                  ERTS_POLL_WOKEN_TIMEDOUT,
 
383
                                  ERTS_POLL_NOT_WOKEN);
 
384
#ifdef DEBUG
 
385
    {
 
386
        erts_aint32_t wakeup_state = erts_atomic32_read_nob(&ps->wakeup_state);
 
387
        switch (wakeup_state) {
 
388
        case ERTS_POLL_WOKEN_IO_READY:
 
389
        case ERTS_POLL_WOKEN_INTR:
 
390
        case ERTS_POLL_WOKEN_TIMEDOUT:
 
391
            break;
 
392
        default:
 
393
            ASSERT(0);
 
394
            break;
 
395
        }
 
396
    }
 
397
#endif
 
398
}
 
399
 
 
400
static ERTS_INLINE int
 
401
wakeup_cause(ErtsPollSet ps)
 
402
{
 
403
    int res;
 
404
    erts_aint32_t wakeup_state = erts_atomic32_read_nob(&ps->wakeup_state);
 
405
    switch (wakeup_state) {
 
406
    case ERTS_POLL_WOKEN_IO_READY:
 
407
        res = 0;
 
408
        break;
 
409
    case ERTS_POLL_WOKEN_INTR:
 
410
        res = EINTR;
 
411
        break;
 
412
    case ERTS_POLL_WOKEN_TIMEDOUT:
 
413
        res = ETIMEDOUT;
 
414
        break;
 
415
    default:
 
416
        res = 0;
 
417
        erl_exit(ERTS_ABORT_EXIT,
 
418
                 "%s:%d: Internal error: Invalid wakeup_state=%d\n",
 
419
                 __FILE__, __LINE__, (int) wakeup_state);
 
420
    }
479
421
    return res;
480
422
}
481
423
 
482
 
#endif
483
 
 
484
 
#ifdef ERTS_SMP
 
424
static ERTS_INLINE DWORD
 
425
poll_wait_timeout(ErtsPollSet ps, SysTimeval *tvp)
 
426
{
 
427
    time_t timeout = tvp->tv_sec * 1000 + tvp->tv_usec / 1000;
 
428
 
 
429
    if (timeout <= 0) {
 
430
        woke_up(ps);
 
431
        return (DWORD) 0;
 
432
    }
 
433
 
 
434
    ResetEvent(ps->event_io_ready);
 
435
    /*
 
436
     * Since we don't know the internals of ResetEvent() we issue
 
437
     * a memory barrier as a safety precaution ensuring that
 
438
     * the load of wakeup_state wont be reordered with stores made
 
439
     * by ResetEvent().
 
440
     */
 
441
    ERTS_THR_MEMORY_BARRIER;
 
442
    if (erts_atomic32_read_nob(&ps->wakeup_state) != ERTS_POLL_NOT_WOKEN)
 
443
        return (DWORD) 0;
 
444
 
 
445
    if (timeout > ((time_t) ERTS_AINT32_T_MAX))
 
446
        timeout = ERTS_AINT32_T_MAX; /* Also prevents DWORD overflow */
 
447
 
 
448
    erts_smp_atomic32_set_relb(&ps->timeout, (erts_aint32_t) timeout);
 
449
    return (DWORD) timeout;
 
450
}
 
451
 
485
452
static ERTS_INLINE void
486
 
wake_poller(ErtsPollSet ps)
 
453
wake_poller(ErtsPollSet ps, int io_ready)
487
454
{
488
 
    if (!ERTS_POLLSET_SET_POLLER_WOKEN_CHK(ps)) {
 
455
    erts_aint32_t wakeup_state;
 
456
    if (io_ready) {
 
457
        /* We may set the event multiple times. This is, however, harmless. */
 
458
        wakeup_state = erts_atomic32_read_nob(&ps->wakeup_state);
 
459
        erts_atomic32_set_relb(&ps->wakeup_state, ERTS_POLL_WOKEN_IO_READY);
 
460
    }
 
461
    else {
 
462
        ERTS_THR_MEMORY_BARRIER;
 
463
        wakeup_state = erts_atomic32_read_nob(&ps->wakeup_state);
 
464
        while (wakeup_state != ERTS_POLL_WOKEN_IO_READY
 
465
               && wakeup_state != ERTS_POLL_WOKEN_INTR) {
 
466
            erts_aint32_t act = erts_atomic32_cmpxchg_nob(&ps->wakeup_state,
 
467
                                                          ERTS_POLL_WOKEN_INTR,
 
468
                                                          wakeup_state);
 
469
            if (act == wakeup_state) {
 
470
                wakeup_state = act;
 
471
                break;
 
472
            }
 
473
            wakeup_state = act;
 
474
        }
 
475
    }
 
476
    if (wakeup_state == ERTS_POLL_NOT_WOKEN) {
 
477
        /*
 
478
         * Since we don't know the internals of SetEvent() we issue
 
479
         * a memory barrier as a safety precaution ensuring that
 
480
         * the store we just made to wakeup_state wont be reordered
 
481
         * with loads in SetEvent().
 
482
         */
 
483
        ERTS_THR_MEMORY_BARRIER;
489
484
        SetEvent(ps->event_io_ready);
490
485
    }
491
486
}
492
 
#endif
 
487
 
 
488
static ERTS_INLINE void
 
489
reset_io_ready(ErtsPollSet ps)
 
490
{
 
491
    erts_atomic32_set_nob(&ps->wakeup_state, ERTS_POLL_NOT_WOKEN);
 
492
}
 
493
 
 
494
static ERTS_INLINE void
 
495
restore_io_ready(ErtsPollSet ps)
 
496
{
 
497
    erts_atomic32_set_nob(&ps->wakeup_state, ERTS_POLL_WOKEN_IO_READY);
 
498
}
 
499
 
 
500
/*
 
501
 * notify_io_ready() is used by threads waiting for events, when
 
502
 * notifying a poller thread about I/O ready.
 
503
 */
 
504
static ERTS_INLINE void
 
505
notify_io_ready(ErtsPollSet ps)
 
506
{
 
507
    wake_poller(ps, 1);
 
508
}
 
509
 
 
510
static ERTS_INLINE void
 
511
reset_interrupt(ErtsPollSet ps)
 
512
{
 
513
    /* We need to keep io-ready if set */
 
514
    erts_aint32_t wakeup_state = erts_atomic32_read_nob(&ps->wakeup_state);
 
515
    while (wakeup_state != ERTS_POLL_WOKEN_IO_READY
 
516
           && wakeup_state != ERTS_POLL_NOT_WOKEN) {
 
517
        erts_aint32_t act = erts_atomic32_cmpxchg_nob(&ps->wakeup_state,
 
518
                                                      ERTS_POLL_NOT_WOKEN,
 
519
                                                      wakeup_state);
 
520
        if (wakeup_state == act)
 
521
            break;
 
522
        wakeup_state = act;
 
523
    }
 
524
    ERTS_THR_MEMORY_BARRIER;
 
525
}
 
526
 
 
527
static ERTS_INLINE void
 
528
set_interrupt(ErtsPollSet ps)
 
529
{
 
530
    wake_poller(ps, 0);
 
531
}
493
532
 
494
533
static void setup_standby_wait(ErtsPollSet ps, int num_threads)
495
534
{
653
692
        case WAIT_OBJECT_0:
654
693
            ResetEvent(harr[0]);
655
694
            erts_mtx_lock(&break_waiter_lock);
656
 
            erts_atomic_set(&break_waiter_state,BREAK_WAITER_GOT_BREAK);
 
695
            erts_atomic32_set_nob(&break_waiter_state,BREAK_WAITER_GOT_BREAK);
 
696
            ERTS_THR_MEMORY_BARRIER;
657
697
            SetEvent(break_happened_event);
658
698
            erts_mtx_unlock(&break_waiter_lock);
659
699
            break;
660
700
        case (WAIT_OBJECT_0+1):
661
701
            ResetEvent(harr[1]);
662
702
            erts_mtx_lock(&break_waiter_lock);
663
 
            erts_atomic_set(&break_waiter_state,BREAK_WAITER_GOT_HALT);
 
703
            erts_atomic32_set_nob(&break_waiter_state,BREAK_WAITER_GOT_HALT);
 
704
            ERTS_THR_MEMORY_BARRIER;
664
705
            SetEvent(break_happened_event);
665
706
            erts_mtx_unlock(&break_waiter_lock);
666
707
            break;
767
808
            consistency_check(w);
768
809
#endif
769
810
            ASSERT(WAIT_OBJECT_0 < i && i < WAIT_OBJECT_0+w->active_events);
770
 
            if (!erts_atomic_xchg(&ps->sys_io_ready,1)) { 
771
 
                HARDDEBUGF(("SET EventIoReady (%d)",erts_atomic_read(&ps->sys_io_ready)));
772
 
                SetEvent(ps->event_io_ready);
773
 
            } else {
774
 
                HARDDEBUGF(("DONT SET EventIoReady"));
775
 
            }
 
811
            notify_io_ready(ps);
776
812
 
777
813
            /* 
778
814
             * The main thread wont start working on our arrays untill we're
967
1003
void  erts_poll_interrupt(ErtsPollSet ps, int set /* bool */)
968
1004
{
969
1005
    HARDTRACEF(("In erts_poll_interrupt(%d)",set));
970
 
#ifdef ERTS_SMP
971
 
    if (set) {
972
 
        ERTS_POLLSET_SET_INTERRUPTED(ps);
973
 
        wake_poller(ps);
974
 
    }
975
 
    else {
976
 
        ERTS_POLLSET_UNSET_INTERRUPTED(ps);
977
 
    }
978
 
#endif
 
1006
    if (!set)
 
1007
        reset_interrupt(ps);
 
1008
    else
 
1009
        set_interrupt(ps);
979
1010
    HARDTRACEF(("Out erts_poll_interrupt(%d)",set));
980
1011
}
981
1012
 
982
1013
void erts_poll_interrupt_timed(ErtsPollSet ps,
983
1014
                               int set /* bool */,
984
 
                               long msec)
 
1015
                               erts_short_time_t msec)
985
1016
{
986
1017
    HARDTRACEF(("In erts_poll_interrupt_timed(%d,%ld)",set,msec));
987
 
#ifdef ERTS_SMP
988
 
    if (set) {
989
 
        if (erts_smp_atomic_read(&ps->timeout) > msec) {
990
 
            ERTS_POLLSET_SET_INTERRUPTED(ps);
991
 
            wake_poller(ps);
992
 
        }
993
 
    }
994
 
    else {
995
 
        ERTS_POLLSET_UNSET_INTERRUPTED(ps);
996
 
    }
997
 
#endif
 
1018
    if (!set)
 
1019
        reset_interrupt(ps);
 
1020
    else if (erts_smp_atomic32_read_acqb(&ps->timeout) > (erts_aint32_t) msec)
 
1021
        set_interrupt(ps);
998
1022
    HARDTRACEF(("Out erts_poll_interrupt_timed"));
999
1023
}
1000
1024
 
1068
1092
int erts_poll_wait(ErtsPollSet ps,
1069
1093
                   ErtsPollResFd pr[],
1070
1094
                   int *len,
1071
 
                   SysTimeval *utvp)
 
1095
                   SysTimeval *tvp)
1072
1096
{
1073
 
    SysTimeval *tvp = utvp;
1074
 
    SysTimeval itv;
1075
1097
    int no_fds;
1076
1098
    DWORD timeout;
1077
1099
    EventData* ev;
1084
1106
    HARDTRACEF(("In erts_poll_wait"));
1085
1107
    ERTS_POLLSET_LOCK(ps);
1086
1108
 
1087
 
    if (!erts_atomic_read(&ps->sys_io_ready) && ps->restore_events) {
 
1109
    if (!is_io_ready(ps) && ps->restore_events) {
1088
1110
        HARDDEBUGF(("Restore events: %d",ps->num_waiters));
1089
1111
        ps->restore_events = 0;
1090
1112
        for (i = 0; i < ps->num_waiters; ++i) {
1102
1124
               if (w->highwater != w->active_events) {
1103
1125
                   HARDDEBUGF(("Oups!"));
1104
1126
                   /* Oups, got signalled before we took the lock, can't reset */
1105
 
                   if(erts_atomic_read(&ps->sys_io_ready) == 0) {
 
1127
                   if(!is_io_ready(ps)) {
1106
1128
                       erl_exit(1,"Internal error: "
1107
1129
                                "Inconsistent io structures in erl_poll.\n");
1108
1130
                   }
1127
1149
        no_fds = ERTS_POLL_MAX_RES;
1128
1150
#endif
1129
1151
 
1130
 
 
1131
 
    ResetEvent(ps->event_io_ready);
1132
 
    ERTS_POLLSET_UNSET_POLLER_WOKEN(ps);
1133
 
 
1134
 
#ifdef ERTS_SMP
1135
 
    if (ERTS_POLLSET_IS_INTERRUPTED(ps)) {
1136
 
        /* Interrupt use zero timeout */
1137
 
        itv.tv_sec = 0;
1138
 
        itv.tv_usec = 0;
1139
 
        tvp = &itv;
1140
 
    }
1141
 
#endif
1142
 
 
1143
 
    timeout = tvp->tv_sec * 1000 + tvp->tv_usec / 1000;
 
1152
    timeout = poll_wait_timeout(ps, tvp);
 
1153
 
1144
1154
    /*HARDDEBUGF(("timeout = %ld",(long) timeout));*/
1145
 
    erts_smp_atomic_set(&ps->timeout, timeout);
1146
1155
 
1147
 
    if (timeout > 0 && ! erts_atomic_read(&ps->sys_io_ready) && ! erts_atomic_read(&break_waiter_state)) {
 
1156
    if (timeout > 0 && !erts_atomic32_read_nob(&break_waiter_state)) {
1148
1157
        HANDLE harr[2] = {ps->event_io_ready, break_happened_event};
1149
1158
        int num_h = 2;
1150
1159
 
1151
 
        HARDDEBUGF(("Start waiting %d [%d]",num_h, (long) timeout));
 
1160
        HARDDEBUGF(("Start waiting %d [%d]",num_h, (int) timeout));
1152
1161
        ERTS_POLLSET_UNLOCK(ps);
 
1162
#ifdef ERTS_SMP
 
1163
        erts_thr_progress_prepare_wait(NULL);
 
1164
#endif
1153
1165
        WaitForMultipleObjects(num_h, harr, FALSE, timeout);
 
1166
#ifdef ERTS_SMP
 
1167
        erts_thr_progress_finalize_wait(NULL);
 
1168
#endif
1154
1169
        ERTS_POLLSET_LOCK(ps);
1155
 
        HARDDEBUGF(("Stop waiting %d [%d]",num_h, (long) timeout));
 
1170
        HARDDEBUGF(("Stop waiting %d [%d]",num_h, (int) timeout));
 
1171
        woke_up(ps);
1156
1172
    }
1157
1173
 
1158
1174
    ERTS_UNSET_BREAK_REQUESTED;
1159
 
    if(erts_atomic_read(&break_waiter_state)) {
 
1175
    if(erts_atomic32_read_nob(&break_waiter_state)) {
1160
1176
        erts_mtx_lock(&break_waiter_lock);
1161
 
        break_state = erts_atomic_read(&break_waiter_state);
1162
 
        erts_atomic_set(&break_waiter_state,0);
 
1177
        break_state = erts_atomic32_read_nob(&break_waiter_state);
 
1178
        erts_atomic32_set_nob(&break_waiter_state,0);
1163
1179
        ResetEvent(break_happened_event);
1164
1180
        erts_mtx_unlock(&break_waiter_lock);
1165
1181
        switch (break_state) {
1174
1190
        }
1175
1191
    }
1176
1192
 
1177
 
    ERTS_POLLSET_SET_POLLER_WOKEN(ps);
1178
 
 
1179
 
    if (!erts_atomic_read(&ps->sys_io_ready)) {
1180
 
        res = EINTR;
1181
 
        HARDDEBUGF(("EINTR!"));
1182
 
        goto done; 
 
1193
    res = wakeup_cause(ps);
 
1194
    if (res != 0) {
 
1195
        HARDDEBUGF(("%s!", res == EINTR ? "EINTR" : "ETIMEDOUT"));
 
1196
        goto done;
1183
1197
    }
1184
1198
 
1185
 
    erts_atomic_set(&ps->sys_io_ready,0);
 
1199
    reset_io_ready(ps);
1186
1200
 
1187
1201
    n = ps->num_waiters;        
1188
1202
 
1204
1218
            if (num >= no_fds) {
1205
1219
                w->highwater=j+1;
1206
1220
                erts_mtx_unlock(&w->mtx);
1207
 
                /* This might mean we still have data to report, set
1208
 
                   back the global flag! */
1209
 
                erts_atomic_set(&ps->sys_io_ready,1);
 
1221
                /* This might mean we still have data to report,
 
1222
                   restore flag indicating I/O ready! */
 
1223
                restore_io_ready(ps);
1210
1224
                HARDDEBUGF(("To many FD's to report!"));
1211
1225
                goto done;
1212
1226
            }
1228
1242
        erts_mtx_unlock(&w->mtx);
1229
1243
    }
1230
1244
 done:
1231
 
    erts_smp_atomic_set(&ps->timeout, LONG_MAX);
 
1245
    erts_smp_atomic32_set_nob(&ps->timeout, ERTS_AINT32_T_MAX);
1232
1246
    *len = num;
1233
1247
    ERTS_POLLSET_UNLOCK(ps);
1234
1248
    HARDTRACEF(("Out erts_poll_wait"));
1306
1320
    ps->standby_wait_counter = 0;
1307
1321
    ps->event_io_ready = CreateManualEvent(FALSE);
1308
1322
    ps->standby_wait_event = CreateManualEvent(FALSE); 
1309
 
    erts_atomic_init(&ps->sys_io_ready,0);
1310
1323
    ps->restore_events = 0;
1311
1324
 
 
1325
    erts_atomic32_init_nob(&ps->wakeup_state, ERTS_POLL_NOT_WOKEN);
1312
1326
#ifdef ERTS_SMP
1313
 
    erts_smp_atomic_init(&ps->woken, 0);
1314
1327
    erts_smp_mtx_init(&ps->mtx, "pollset");
1315
 
    erts_smp_atomic_init(&ps->interrupt, 0);
1316
1328
#endif
1317
 
    erts_smp_atomic_init(&ps->timeout, LONG_MAX);
 
1329
    erts_smp_atomic32_init_nob(&ps->timeout, ERTS_AINT32_T_MAX);
1318
1330
 
1319
1331
    HARDTRACEF(("Out erts_poll_create_pollset"));
1320
1332
    return ps;
1366
1378
 
1367
1379
    erts_mtx_init(&break_waiter_lock,"break_waiter_lock");
1368
1380
    break_happened_event = CreateManualEvent(FALSE);
1369
 
    erts_atomic_init(&break_waiter_state, 0); 
 
1381
    erts_atomic32_init_nob(&break_waiter_state, 0); 
1370
1382
 
1371
1383
    erts_thr_create(&thread, &break_waiter, NULL, NULL);
1372
1384
    ERTS_UNSET_BREAK_REQUESTED;