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

« back to all changes in this revision

Viewing changes to erts/emulator/sys/common/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 2006-2010. All Rights Reserved.
 
4
 * Copyright Ericsson AB 2006-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
68
68
#    endif
69
69
#  endif
70
70
#endif
 
71
#include "erl_thr_progress.h"
71
72
#include "erl_driver.h"
72
73
#include "erl_alloc.h"
73
74
 
114
115
#endif
115
116
 
116
117
#define ERTS_POLL_USE_WAKEUP_PIPE \
117
 
   (ERTS_POLL_ASYNC_INTERRUPT_SUPPORT || defined(ERTS_SMP))
 
118
   (ERTS_POLL_ASYNC_INTERRUPT_SUPPORT || defined(USE_THREADS))
118
119
 
119
120
#ifdef ERTS_SMP
120
121
 
124
125
  erts_smp_mtx_unlock(&(PS)->mtx)
125
126
 
126
127
#define ERTS_POLLSET_SET_POLLED_CHK(PS) \
127
 
  ((int) erts_smp_atomic_xchg(&(PS)->polled, (long) 1))
 
128
  ((int) erts_atomic32_xchg_nob(&(PS)->polled, (erts_aint32_t) 1))
128
129
#define ERTS_POLLSET_UNSET_POLLED(PS) \
129
 
  erts_smp_atomic_set(&(PS)->polled, (long) 0)
 
130
  erts_atomic32_set_nob(&(PS)->polled, (erts_aint32_t) 0)
130
131
#define ERTS_POLLSET_IS_POLLED(PS) \
131
 
  ((int) erts_smp_atomic_read(&(PS)->polled))
132
 
 
133
 
#define ERTS_POLLSET_SET_POLLER_WOKEN_CHK(PS) set_poller_woken_chk((PS))
134
 
#define ERTS_POLLSET_SET_POLLER_WOKEN(PS)                               \
135
 
do {                                                                    \
136
 
      ERTS_THR_MEMORY_BARRIER;                                          \
137
 
      erts_smp_atomic_set(&(PS)->woken, (long) 1);                      \
138
 
} while (0)
139
 
#define ERTS_POLLSET_UNSET_POLLER_WOKEN(PS)                             \
140
 
do {                                                                    \
141
 
    erts_smp_atomic_set(&(PS)->woken, (long) 0);                        \
142
 
    ERTS_THR_MEMORY_BARRIER;                                            \
143
 
} while (0)
144
 
#define ERTS_POLLSET_IS_POLLER_WOKEN(PS)                                \
145
 
  ((int) erts_smp_atomic_read(&(PS)->woken))
 
132
  ((int) erts_atomic32_read_nob(&(PS)->polled))
146
133
 
147
134
#else
148
135
 
152
139
#define ERTS_POLLSET_UNSET_POLLED(PS)
153
140
#define ERTS_POLLSET_IS_POLLED(PS) 0
154
141
 
155
 
#if ERTS_POLL_ASYNC_INTERRUPT_SUPPORT
156
 
 
157
 
/*
158
 
 * Ideally, the ERTS_POLLSET_SET_POLLER_WOKEN_CHK(PS) operation would
159
 
 * be atomic. This operation isn't, but we will do okay anyway. The
160
 
 * "woken check" is only an optimization. The only requirement we have:
161
 
 * If (PS)->woken is set to a value != 0 when interrupting, we have to
162
 
 * write on the the wakeup pipe at least once. Multiple writes are okay.
163
 
 */
164
 
#define ERTS_POLLSET_SET_POLLER_WOKEN_CHK(PS) ((PS)->woken++)
165
 
#define ERTS_POLLSET_SET_POLLER_WOKEN(PS) ((PS)->woken = 1, (void) 0)
166
 
#define ERTS_POLLSET_UNSET_POLLER_WOKEN(PS) ((PS)->woken = 0, (void) 0)
167
 
#define ERTS_POLLSET_IS_POLLER_WOKEN(PS) ((PS)->woken)
168
 
 
169
 
#else
170
 
 
171
 
#define ERTS_POLLSET_SET_POLLER_WOKEN_CHK(PS) 1
172
 
#define ERTS_POLLSET_SET_POLLER_WOKEN(PS)
173
 
#define ERTS_POLLSET_UNSET_POLLER_WOKEN(PS)
174
 
#define ERTS_POLLSET_IS_POLLER_WOKEN(PS) 1
175
 
 
176
 
#endif
177
 
 
178
142
#endif
179
143
 
180
144
#if ERTS_POLL_USE_UPDATE_REQUESTS_QUEUE
181
145
#define ERTS_POLLSET_SET_HAVE_UPDATE_REQUESTS(PS) \
182
 
  erts_smp_atomic_set(&(PS)->have_update_requests, (long) 1)
 
146
  erts_smp_atomic32_set_nob(&(PS)->have_update_requests, (erts_aint32_t) 1)
183
147
#define ERTS_POLLSET_UNSET_HAVE_UPDATE_REQUESTS(PS) \
184
 
  erts_smp_atomic_set(&(PS)->have_update_requests, (long) 0)
 
148
  erts_smp_atomic32_set_nob(&(PS)->have_update_requests, (erts_aint32_t) 0)
185
149
#define ERTS_POLLSET_HAVE_UPDATE_REQUESTS(PS) \
186
 
  ((int) erts_smp_atomic_read(&(PS)->have_update_requests))
 
150
  ((int) erts_smp_atomic32_read_nob(&(PS)->have_update_requests))
187
151
#else
188
152
#define ERTS_POLLSET_SET_HAVE_UPDATE_REQUESTS(PS)
189
153
#define ERTS_POLLSET_UNSET_HAVE_UPDATE_REQUESTS(PS)
190
154
#define ERTS_POLLSET_HAVE_UPDATE_REQUESTS(PS) 0
191
155
#endif
192
156
 
193
 
#if ERTS_POLL_ASYNC_INTERRUPT_SUPPORT && !defined(ERTS_SMP)
194
 
 
195
 
#define ERTS_POLLSET_UNSET_INTERRUPTED_CHK(PS) unset_interrupted_chk((PS))
196
 
#define ERTS_POLLSET_UNSET_INTERRUPTED(PS) ((PS)->interrupt = 0, (void) 0)
197
 
#define ERTS_POLLSET_SET_INTERRUPTED(PS) ((PS)->interrupt = 1, (void) 0)
198
 
#define ERTS_POLLSET_IS_INTERRUPTED(PS) ((PS)->interrupt)
199
 
 
200
 
#else
201
 
 
202
 
#define ERTS_POLLSET_UNSET_INTERRUPTED_CHK(PS) unset_interrupted_chk((PS))
203
 
#define ERTS_POLLSET_UNSET_INTERRUPTED(PS)                              \
204
 
do {                                                                    \
205
 
    erts_smp_atomic_set(&(PS)->interrupt, (long) 0);                    \
206
 
    ERTS_THR_MEMORY_BARRIER;                                            \
207
 
} while (0)
208
 
#define ERTS_POLLSET_SET_INTERRUPTED(PS)                                \
209
 
do {                                                                    \
210
 
      ERTS_THR_MEMORY_BARRIER;                                          \
211
 
      erts_smp_atomic_set(&(PS)->interrupt, (long) 1);                  \
212
 
} while (0)
213
 
#define ERTS_POLLSET_IS_INTERRUPTED(PS)                                 \
214
 
  ((int) erts_smp_atomic_read(&(PS)->interrupt))
215
 
 
216
 
#endif
217
 
 
218
157
#if ERTS_POLL_USE_FALLBACK
219
158
#  if ERTS_POLL_USE_POLL
220
159
#    define ERTS_POLL_NEED_FALLBACK(PS) ((PS)->no_poll_fds > 1)
318
257
#if ERTS_POLL_USE_UPDATE_REQUESTS_QUEUE
319
258
    ErtsPollSetUpdateRequestsBlock update_requests;
320
259
    ErtsPollSetUpdateRequestsBlock *curr_upd_req_block;
321
 
    erts_smp_atomic_t have_update_requests;
 
260
    erts_smp_atomic32_t have_update_requests;
322
261
#endif
323
262
#ifdef ERTS_SMP
324
 
    erts_smp_atomic_t polled;
325
 
    erts_smp_atomic_t woken;
 
263
    erts_atomic32_t polled;
326
264
    erts_smp_mtx_t mtx;
327
 
#elif ERTS_POLL_ASYNC_INTERRUPT_SUPPORT
328
 
    volatile int woken;
329
265
#endif
330
266
#if ERTS_POLL_USE_WAKEUP_PIPE
331
267
    int wake_fds[2];
333
269
#if ERTS_POLL_USE_FALLBACK
334
270
    int fallback_used;
335
271
#endif
336
 
#if ERTS_POLL_ASYNC_INTERRUPT_SUPPORT && !defined(ERTS_SMP)
337
 
    volatile int interrupt;
338
 
#else
339
 
    erts_smp_atomic_t interrupt;
 
272
#if defined(USE_THREADS) || ERTS_POLL_ASYNC_INTERRUPT_SUPPORT
 
273
    erts_atomic32_t wakeup_state;
340
274
#endif
341
 
    erts_smp_atomic_t timeout;
 
275
    erts_smp_atomic32_t timeout;
342
276
#ifdef ERTS_POLL_COUNT_AVOIDED_WAKEUPS
343
277
    erts_smp_atomic_t no_avoided_wakeups;
344
278
    erts_smp_atomic_t no_avoided_interrupts;
346
280
#endif
347
281
};
348
282
 
349
 
static ERTS_INLINE int
350
 
unset_interrupted_chk(ErtsPollSet ps)
351
 
{
352
 
    int res;
353
 
#if ERTS_POLL_ASYNC_INTERRUPT_SUPPORT && !defined(ERTS_SMP)
354
 
    /* This operation isn't atomic, but we have no need at all for an
355
 
       atomic operation here... */
356
 
    res = ps->interrupt;
357
 
    ps->interrupt = 0;
358
 
#else
359
 
    res = (int) erts_smp_atomic_xchg(&ps->interrupt, (long) 0);
360
 
    ERTS_THR_MEMORY_BARRIER;
361
 
#endif
362
 
    return res;
363
 
 
364
 
}
365
 
 
366
 
#ifdef ERTS_SMP
367
 
 
368
 
static ERTS_INLINE int
369
 
set_poller_woken_chk(ErtsPollSet ps)
370
 
{
371
 
    ERTS_THR_MEMORY_BARRIER;
372
 
    return (int) erts_smp_atomic_xchg(&ps->woken, (long) 1);
373
 
}
374
 
 
375
 
#endif
376
 
 
377
283
void erts_silence_warn_unused_result(long unused);
378
284
static void fatal_error(char *format, ...);
379
285
static void fatal_error_async_signal_safe(char *error_str);
430
336
static void print_misc_debug_info(void);
431
337
#endif
432
338
 
 
339
#define ERTS_POLL_NOT_WOKEN     0
 
340
#define ERTS_POLL_WOKEN         -1
 
341
#define ERTS_POLL_WOKEN_INTR    1
 
342
 
 
343
static ERTS_INLINE void
 
344
reset_wakeup_state(ErtsPollSet ps)
 
345
{
 
346
#if defined(USE_THREADS) || ERTS_POLL_ASYNC_INTERRUPT_SUPPORT
 
347
    erts_atomic32_set_mb(&ps->wakeup_state, ERTS_POLL_NOT_WOKEN);
 
348
#endif
 
349
}
 
350
 
 
351
static ERTS_INLINE int
 
352
is_woken(ErtsPollSet ps)
 
353
{
 
354
#if defined(USE_THREADS) || ERTS_POLL_ASYNC_INTERRUPT_SUPPORT
 
355
    return erts_atomic32_read_acqb(&ps->wakeup_state) != ERTS_POLL_NOT_WOKEN;
 
356
#else
 
357
    return 0;
 
358
#endif
 
359
}
 
360
 
 
361
static ERTS_INLINE int
 
362
is_interrupted_reset(ErtsPollSet ps)
 
363
{
 
364
#if defined(USE_THREADS) || ERTS_POLL_ASYNC_INTERRUPT_SUPPORT
 
365
    return (erts_atomic32_xchg_nob(&ps->wakeup_state, ERTS_POLL_NOT_WOKEN)
 
366
            == ERTS_POLL_WOKEN_INTR);
 
367
#else
 
368
    return 0;
 
369
#endif
 
370
}
 
371
 
 
372
static ERTS_INLINE void
 
373
woke_up(ErtsPollSet ps)
 
374
{
 
375
#if defined(USE_THREADS) || ERTS_POLL_ASYNC_INTERRUPT_SUPPORT
 
376
    erts_aint32_t wakeup_state = erts_atomic32_read_nob(&ps->wakeup_state);
 
377
    if (wakeup_state == ERTS_POLL_NOT_WOKEN)
 
378
        (void) erts_atomic32_cmpxchg_nob(&ps->wakeup_state,
 
379
                                         ERTS_POLL_WOKEN,
 
380
                                         ERTS_POLL_NOT_WOKEN);
 
381
    ASSERT(erts_atomic32_read_nob(&ps->wakeup_state) != ERTS_POLL_NOT_WOKEN);
 
382
#endif
 
383
}
 
384
 
433
385
/*
434
386
 * --- Wakeup pipe -----------------------------------------------------------
435
387
 */
437
389
#if ERTS_POLL_USE_WAKEUP_PIPE
438
390
 
439
391
static ERTS_INLINE void
440
 
wake_poller(ErtsPollSet ps)
 
392
wake_poller(ErtsPollSet ps, int interrupted, int async_signal_safe)
441
393
{
 
394
    int wake;
 
395
    if (async_signal_safe)
 
396
        wake = 1;
 
397
    else {
 
398
        erts_aint32_t wakeup_state;
 
399
        if (!interrupted)
 
400
            wakeup_state = erts_atomic32_cmpxchg_relb(&ps->wakeup_state,
 
401
                                                      ERTS_POLL_WOKEN,
 
402
                                                      ERTS_POLL_NOT_WOKEN);
 
403
        else {
 
404
            /*
 
405
             * We might unnecessarily write to the pipe, however,
 
406
             * that isn't problematic.
 
407
             */
 
408
            wakeup_state = erts_atomic32_read_nob(&ps->wakeup_state);
 
409
            erts_atomic32_set_relb(&ps->wakeup_state, ERTS_POLL_WOKEN_INTR);
 
410
        }
 
411
        wake = wakeup_state == ERTS_POLL_NOT_WOKEN;
 
412
    }
442
413
    /*
443
414
     * NOTE: This function might be called from signal handlers in the
444
415
     *       non-smp case; therefore, it has to be async-signal safe in
445
416
     *       the non-smp case.
446
417
     */
447
 
    if (!ERTS_POLLSET_SET_POLLER_WOKEN_CHK(ps)) {
 
418
    if (wake) {
448
419
        ssize_t res;
449
420
        if (ps->wake_fds[1] < 0)
450
421
            return; /* Not initialized yet */
453
424
            res = write(ps->wake_fds[1], "!", 1);
454
425
        } while (res < 0 && errno == EINTR);
455
426
        if (res <= 0 && errno != ERRNO_BLOCK) {
456
 
            fatal_error_async_signal_safe(__FILE__
457
 
                                          ":XXX:wake_poller(): "
458
 
                                          "Failed to write on wakeup pipe\n");
 
427
            if (async_signal_safe)
 
428
                fatal_error_async_signal_safe(__FILE__
 
429
                                              ":XXX:wake_poller(): "
 
430
                                              "Failed to write on wakeup pipe\n");
 
431
            else
 
432
                fatal_error("%s:%d:wake_poller(): "
 
433
                            "Failed to write to wakeup pipe fd=%d: "
 
434
                            "%s (%d)\n",
 
435
                            __FILE__, __LINE__,
 
436
                            ps->wake_fds[1],
 
437
                            erl_errno_id(errno), errno);
459
438
        }
460
439
    }
461
440
}
463
442
static ERTS_INLINE void
464
443
cleanup_wakeup_pipe(ErtsPollSet ps)
465
444
{
 
445
#if ERTS_POLL_ASYNC_INTERRUPT_SUPPORT
 
446
    int intr = 0;
 
447
#endif
466
448
    int fd = ps->wake_fds[0];
467
449
    int res;
468
450
    do {
469
451
        char buf[32];
470
452
        res = read(fd, buf, sizeof(buf));
 
453
#if ERTS_POLL_ASYNC_INTERRUPT_SUPPORT
 
454
        if (res > 0)
 
455
            intr = 1;
 
456
#endif
471
457
    } while (res > 0 || (res < 0 && errno == EINTR));
472
458
    if (res < 0 && errno != ERRNO_BLOCK) {
473
459
        fatal_error("%s:%d:cleanup_wakeup_pipe(): "
477
463
                    fd,
478
464
                    erl_errno_id(errno), errno);
479
465
    }
 
466
#if ERTS_POLL_ASYNC_INTERRUPT_SUPPORT
 
467
    if (intr)
 
468
        erts_atomic32_set_nob(&ps->wakeup_state, ERTS_POLL_WOKEN_INTR);
 
469
#endif
480
470
}
481
471
 
482
472
static void
780
770
                short filter;
781
771
                int fd = (int) ebuf[i].ident;
782
772
 
783
 
                switch ((int) ebuf[i].udata) {
 
773
                switch ((int) (long) ebuf[i].udata) {
784
774
 
785
775
                    /*
786
776
                     * Since we use a lazy update approach EV_DELETE will
819
809
                        if (fd == (int) ebuf[j].ident) {
820
810
                            ebuf[j].udata = (void *) ERTS_POLL_KQ_OP_HANDLED;
821
811
                            if (!(ebuf[j].flags & EV_ERROR)) {
822
 
                                switch ((int) ebuf[j].udata) {
 
812
                                switch ((int) (long) ebuf[j].udata) {
823
813
                                case ERTS_POLL_KQ_OP_ADD2_W:
824
814
                                    filter = EVFILT_WRITE;
825
815
                                    goto rm_add_fb;
837
827
                        }
838
828
                    }
839
829
                    /* The other add succeded... */
840
 
                    filter = (((int) ebuf[i].udata == ERTS_POLL_KQ_OP_ADD2_W)
 
830
                    filter = ((((int) (long) ebuf[i].udata)
 
831
                               == ERTS_POLL_KQ_OP_ADD2_W)
841
832
                              ? EVFILT_READ
842
833
                              : EVFILT_WRITE);
843
834
                rm_add_fb:
852
843
                    ps->fds_status[fd].flags |= ERTS_POLL_FD_FLG_USEFLBCK;
853
844
                    ASSERT(ps->fds_status[fd].used_events);
854
845
                    ps->fds_status[fd].used_events = 0;
855
 
                    erts_smp_atomic_dec(&ps->no_of_user_fds);
 
846
                    erts_smp_atomic_dec_nob(&ps->no_of_user_fds);
856
847
                    update_fallback_pollset(ps, fd);
857
848
                    ASSERT(ps->fds_status[fd].flags & ERTS_POLL_FD_FLG_INFLBCK);
858
849
                    break;
902
893
    events = ERTS_POLL_EV_E2N(ps->fds_status[fd].events);
903
894
    if (!events) {
904
895
        buf[buf_len].events = POLLREMOVE;
905
 
        erts_smp_atomic_dec(&ps->no_of_user_fds);
 
896
        erts_smp_atomic_dec_nob(&ps->no_of_user_fds);
906
897
    }
907
898
    else if (!ps->fds_status[fd].used_events) {
908
899
        buf[buf_len].events = events;
909
 
        erts_smp_atomic_inc(&ps->no_of_user_fds);
 
900
        erts_smp_atomic_inc_nob(&ps->no_of_user_fds);
910
901
    }
911
902
    else {
912
903
        if ((ps->fds_status[fd].flags & ERTS_POLL_FD_FLG_RST)
996
987
        }
997
988
        if (used_events) {
998
989
            if (!events) {
999
 
                erts_smp_atomic_dec(&ps->no_of_user_fds);
 
990
                erts_smp_atomic_dec_nob(&ps->no_of_user_fds);
1000
991
            }
1001
992
        }
1002
993
        else {
1003
994
            if (events)
1004
 
                erts_smp_atomic_inc(&ps->no_of_user_fds);
 
995
                erts_smp_atomic_inc_nob(&ps->no_of_user_fds);
1005
996
        }
1006
997
        ASSERT((events & ~(ERTS_POLL_EV_IN|ERTS_POLL_EV_OUT)) == 0);
1007
998
        ASSERT((used_events & ~(ERTS_POLL_EV_IN|ERTS_POLL_EV_OUT)) == 0);
1075
1066
            epe.data.fd = epe_templ.data.fd;
1076
1067
            res = epoll_ctl(ps->kp_fd, EPOLL_CTL_DEL, fd, &epe);
1077
1068
        } while (res != 0 && errno == EINTR);
1078
 
        erts_smp_atomic_dec(&ps->no_of_user_fds);
 
1069
        erts_smp_atomic_dec_nob(&ps->no_of_user_fds);
1079
1070
        ps->fds_status[fd].used_events = 0;
1080
1071
    }
1081
1072
 
1083
1074
        /* A note on EPOLL_CTL_DEL: linux kernel versions before 2.6.9
1084
1075
           need a non-NULL event pointer even though it is ignored... */
1085
1076
        op = EPOLL_CTL_DEL;
1086
 
        erts_smp_atomic_dec(&ps->no_of_user_fds);
 
1077
        erts_smp_atomic_dec_nob(&ps->no_of_user_fds);
1087
1078
    }
1088
1079
    else if (!ps->fds_status[fd].used_events) {
1089
1080
        op = EPOLL_CTL_ADD;
1090
 
        erts_smp_atomic_inc(&ps->no_of_user_fds);
 
1081
        erts_smp_atomic_inc_nob(&ps->no_of_user_fds);
1091
1082
    }
1092
1083
    else {
1093
1084
        op = EPOLL_CTL_MOD;
1137
1128
        /* Fall through ... */
1138
1129
        case EPOLL_CTL_ADD: {
1139
1130
            ps->fds_status[fd].flags |= ERTS_POLL_FD_FLG_USEFLBCK;
1140
 
            erts_smp_atomic_dec(&ps->no_of_user_fds);
 
1131
            erts_smp_atomic_dec_nob(&ps->no_of_user_fds);
1141
1132
#if ERTS_POLL_USE_CONCURRENT_UPDATE
1142
1133
            if (!*update_fallback) {
1143
1134
                *update_fallback = 1;
1225
1216
#if ERTS_POLL_USE_FALLBACK
1226
1217
        ASSERT(ps->fds_status[fd].flags & ERTS_POLL_FD_FLG_INFLBCK);
1227
1218
#endif
1228
 
        erts_smp_atomic_dec(&ps->no_of_user_fds);
 
1219
        erts_smp_atomic_dec_nob(&ps->no_of_user_fds);
1229
1220
        last_pix = --ps->no_poll_fds;
1230
1221
        if (pix != last_pix) {
1231
1222
        /* Move last pix to this pix */
1252
1243
            ASSERT(!(ps->fds_status[fd].flags & ERTS_POLL_FD_FLG_INFLBCK)
1253
1244
                    || fd == ps->kp_fd);
1254
1245
#endif
1255
 
            erts_smp_atomic_inc(&ps->no_of_user_fds);
 
1246
            erts_smp_atomic_inc_nob(&ps->no_of_user_fds);
1256
1247
            ps->fds_status[fd].pix = pix = ps->no_poll_fds++;
1257
1248
            if (pix >= ps->poll_fds_len)
1258
1249
                grow_poll_fds(ps, pix);
1303
1294
 
1304
1295
        if (!ps->fds_status[fd].used_events) {
1305
1296
            ASSERT(events);
1306
 
            erts_smp_atomic_inc(&ps->no_of_user_fds);
 
1297
            erts_smp_atomic_inc_nob(&ps->no_of_user_fds);
1307
1298
#if ERTS_POLL_USE_FALLBACK
1308
1299
            ps->no_select_fds++;
1309
1300
            ps->fds_status[fd].flags |= ERTS_POLL_FD_FLG_INFLBCK;
1311
1302
        }
1312
1303
        else if (!events) {
1313
1304
            ASSERT(ps->fds_status[fd].used_events);
1314
 
            erts_smp_atomic_dec(&ps->no_of_user_fds);
 
1305
            erts_smp_atomic_dec_nob(&ps->no_of_user_fds);
1315
1306
            ps->fds_status[fd].events = events;
1316
1307
#if ERTS_POLL_USE_FALLBACK
1317
1308
            ps->no_select_fds--;
1387
1378
#endif /* ERTS_POLL_USE_UPDATE_REQUESTS_QUEUE */
1388
1379
 
1389
1380
static ERTS_INLINE ErtsPollEvents
1390
 
poll_control(ErtsPollSet ps, int fd, ErtsPollEvents events, int on,
1391
 
             int *have_set_have_update_requests,
1392
 
             int *do_wake)
 
1381
poll_control(ErtsPollSet ps, int fd, ErtsPollEvents events, int on, int *do_wake)
1393
1382
{
1394
1383
    ErtsPollEvents new_events;
1395
1384
 
1493
1482
                                     int len)
1494
1483
{
1495
1484
    int i;
1496
 
    int hshur = 0;
1497
1485
    int do_wake;
1498
1486
    int final_do_wake = 0;
1499
1487
 
1505
1493
                                      pcev[i].fd,
1506
1494
                                      pcev[i].events,
1507
1495
                                      pcev[i].on,
1508
 
                                      &hshur,
1509
1496
                                      &do_wake);
1510
1497
        final_do_wake |= do_wake;
1511
1498
    }
1512
1499
 
 
1500
    ERTS_POLLSET_UNLOCK(ps);
 
1501
 
1513
1502
#ifdef ERTS_SMP
1514
1503
    if (final_do_wake)
1515
 
        wake_poller(ps);
 
1504
        wake_poller(ps, 0, 0);
1516
1505
#endif /* ERTS_SMP */
1517
1506
 
1518
 
    ERTS_POLLSET_UNLOCK(ps);
1519
1507
}
1520
1508
 
1521
1509
ErtsPollEvents
1526
1514
                                    int* do_wake) /* In: Wake up polling thread */
1527
1515
                                                  /* Out: Poller is woken */
1528
1516
{
1529
 
    int hshur = 0;
1530
1517
    ErtsPollEvents res;
1531
1518
 
1532
1519
    ERTS_POLLSET_LOCK(ps);
1533
1520
 
1534
 
    res = poll_control(ps, fd, events, on, &hshur, do_wake);
 
1521
    res = poll_control(ps, fd, events, on, do_wake);
 
1522
 
 
1523
    ERTS_POLLSET_UNLOCK(ps);
1535
1524
 
1536
1525
#ifdef ERTS_SMP
1537
1526
    if (*do_wake) {
1538
 
        wake_poller(ps);
 
1527
        wake_poller(ps, 0, 0);
1539
1528
    }
1540
1529
#endif /* ERTS_SMP */
1541
1530
 
1542
 
    ERTS_POLLSET_UNLOCK(ps);
1543
1531
    return res;
1544
1532
}
1545
1533
 
1909
1897
}
1910
1898
 
1911
1899
static ERTS_INLINE int
1912
 
check_fd_events(ErtsPollSet ps, SysTimeval *tv, int max_res, int *ps_locked)
 
1900
check_fd_events(ErtsPollSet ps, SysTimeval *tv, int max_res)
1913
1901
{
1914
 
    ASSERT(!*ps_locked);
1915
 
    if (erts_smp_atomic_read(&ps->no_of_user_fds) == 0
 
1902
    int res;
 
1903
    if (erts_smp_atomic_read_nob(&ps->no_of_user_fds) == 0
1916
1904
        && tv->tv_usec == 0 && tv->tv_sec == 0) {
1917
1905
        /* Nothing to poll and zero timeout; done... */
1918
1906
        return 0;
1919
1907
    }
1920
1908
    else {
1921
1909
        long timeout = tv->tv_sec*1000 + tv->tv_usec/1000;
 
1910
        if (timeout > ERTS_AINT32_T_MAX)
 
1911
            timeout = ERTS_AINT32_T_MAX;
1922
1912
        ASSERT(timeout >= 0);
1923
 
        erts_smp_atomic_set(&ps->timeout, timeout);
 
1913
        erts_smp_atomic32_set_relb(&ps->timeout, (erts_aint32_t) timeout);
1924
1914
#if ERTS_POLL_USE_FALLBACK
1925
1915
        if (!(ps->fallback_used = ERTS_POLL_NEED_FALLBACK(ps))) {
1926
1916
 
1929
1919
                timeout = INT_MAX;
1930
1920
            if (max_res > ps->res_events_len)
1931
1921
                grow_res_events(ps, max_res);
1932
 
            return epoll_wait(ps->kp_fd, ps->res_events, max_res, (int)timeout);
 
1922
#ifdef ERTS_SMP
 
1923
            if (timeout)
 
1924
                erts_thr_progress_prepare_wait(NULL);
 
1925
#endif
 
1926
            res = epoll_wait(ps->kp_fd, ps->res_events, max_res, (int)timeout);
1933
1927
#elif ERTS_POLL_USE_KQUEUE      /* --- kqueue ------------------------------ */
1934
1928
            struct timespec ts;
 
1929
            if (max_res > ps->res_events_len)
 
1930
                grow_res_events(ps, max_res);
 
1931
#ifdef ERTS_SMP
 
1932
            if (timeout)
 
1933
                erts_thr_progress_prepare_wait(NULL);
 
1934
#endif
1935
1935
            ts.tv_sec = tv->tv_sec;
1936
1936
            ts.tv_nsec = tv->tv_usec*1000;
1937
 
            if (max_res > ps->res_events_len)
1938
 
                grow_res_events(ps, max_res);
1939
 
            return kevent(ps->kp_fd, NULL, 0, ps->res_events, max_res, &ts);
 
1937
            res = kevent(ps->kp_fd, NULL, 0, ps->res_events, max_res, &ts);
1940
1938
#endif                          /* ----------------------------------------- */
1941
 
 
1942
1939
        }
1943
1940
        else /* use fallback (i.e. poll() or select()) */
1944
1941
#endif /* ERTS_POLL_USE_FALLBACK */
1951
1948
             * the maximum number of file descriptors in the poll set.
1952
1949
             */
1953
1950
            struct dvpoll poll_res;
1954
 
            int nfds = (int) erts_smp_atomic_read(&ps->no_of_user_fds);
 
1951
            int nfds = (int) erts_smp_atomic_read_nob(&ps->no_of_user_fds);
1955
1952
#ifdef ERTS_SMP
1956
1953
            nfds++; /* Wakeup pipe */
1957
1954
#endif
1961
1958
            if (poll_res.dp_nfds > ps->res_events_len)
1962
1959
                grow_res_events(ps, poll_res.dp_nfds);
1963
1960
            poll_res.dp_fds = ps->res_events;
 
1961
#ifdef ERTS_SMP
 
1962
            if (timeout)
 
1963
                erts_thr_progress_prepare_wait(NULL);
 
1964
#endif
1964
1965
            poll_res.dp_timeout = (int) timeout;
1965
 
            return ioctl(ps->kp_fd, DP_POLL, &poll_res);
 
1966
            res = ioctl(ps->kp_fd, DP_POLL, &poll_res);
1966
1967
#elif ERTS_POLL_USE_POLL        /* --- poll -------------------------------- */
1967
1968
            if (timeout > INT_MAX)
1968
1969
                timeout = INT_MAX;
1969
 
            return poll(ps->poll_fds, ps->no_poll_fds, (int) timeout);
 
1970
#ifdef ERTS_SMP
 
1971
            if (timeout)
 
1972
                erts_thr_progress_prepare_wait(NULL);
 
1973
#endif
 
1974
            res = poll(ps->poll_fds, ps->no_poll_fds, (int) timeout);
1970
1975
#elif ERTS_POLL_USE_SELECT      /* --- select ------------------------------ */
1971
 
            int res;
 
1976
            SysTimeval to = *tv;
 
1977
 
1972
1978
            ps->res_input_fds = ps->input_fds;
1973
1979
            ps->res_output_fds = ps->output_fds;
 
1980
 
 
1981
#ifdef ERTS_SMP
 
1982
            if (to.tv_sec || to.tv_usec)
 
1983
                erts_thr_progress_prepare_wait(NULL);
 
1984
#endif
1974
1985
            res = select(ps->max_fd + 1,
1975
1986
                         &ps->res_input_fds,
1976
1987
                         &ps->res_output_fds,
1977
1988
                         NULL,
1978
 
                         tv);
 
1989
                         &to);
1979
1990
#ifdef ERTS_SMP
 
1991
            if (to.tv_sec || to.tv_usec)
 
1992
                erts_thr_progress_finalize_wait(NULL);
1980
1993
            if (res < 0
1981
1994
                && errno == EBADF
1982
1995
                && ERTS_POLLSET_HAVE_UPDATE_REQUESTS(ps)) {
1992
2005
                 * have triggered, we fake an EAGAIN error and let the caller
1993
2006
                 * restart us.
1994
2007
                 */
1995
 
                SysTimeval zero_tv = {0, 0};
1996
 
                *ps_locked = 1;
 
2008
                to.tv_sec = 0;
 
2009
                to.tv_usec = 0;
1997
2010
                ERTS_POLLSET_LOCK(ps);
1998
2011
                handle_update_requests(ps);
 
2012
                ERTS_POLLSET_UNLOCK(ps);
1999
2013
                res = select(ps->max_fd + 1,
2000
2014
                             &ps->res_input_fds,
2001
2015
                             &ps->res_output_fds,
2002
2016
                             NULL,
2003
 
                             &zero_tv);
 
2017
                             &to);
2004
2018
                if (res == 0) {
2005
2019
                    errno = EAGAIN;
2006
2020
                    res = -1;
2010
2024
            return res;
2011
2025
#endif                          /* ----------------------------------------- */
2012
2026
        }
 
2027
#ifdef ERTS_SMP
 
2028
        if (timeout)
 
2029
            erts_thr_progress_finalize_wait(NULL);
 
2030
#endif
 
2031
        return res;
2013
2032
    }
2014
2033
}
2015
2034
 
2021
2040
{
2022
2041
    int res, no_fds;
2023
2042
    int ebadf = 0;
2024
 
    int ps_locked;
 
2043
#ifdef ERTS_SMP
 
2044
    int ps_locked = 0;
 
2045
#endif
2025
2046
    SysTimeval *tvp;
2026
2047
    SysTimeval itv;
2027
2048
 
2042
2063
                 (int) tv->tv_sec*1000 + tv->tv_usec/1000);
2043
2064
#endif
2044
2065
 
2045
 
    ERTS_POLLSET_UNSET_POLLER_WOKEN(ps);
2046
2066
    if (ERTS_POLLSET_SET_POLLED_CHK(ps)) {
2047
2067
        res = EINVAL; /* Another thread is in erts_poll_wait()
2048
2068
                         on this pollset... */
2049
2069
        goto done;
2050
2070
    }
2051
2071
 
2052
 
    if (ERTS_POLLSET_IS_INTERRUPTED(ps)) {
2053
 
        /* Interrupt use zero timeout */
 
2072
    if (is_woken(ps)) {
 
2073
        /* Use zero timeout */
2054
2074
        itv.tv_sec = 0;
2055
2075
        itv.tv_usec = 0;
2056
2076
        tvp = &itv;
2064
2084
    }
2065
2085
#endif
2066
2086
 
2067
 
    ps_locked = 0;
2068
 
    res = check_fd_events(ps, tvp, no_fds, &ps_locked);
 
2087
    res = check_fd_events(ps, tvp, no_fds);
2069
2088
 
2070
 
    ERTS_POLLSET_SET_POLLER_WOKEN(ps);
 
2089
    woke_up(ps);
2071
2090
 
2072
2091
    if (res == 0) {
2073
2092
        res = ETIMEDOUT;
2087
2106
#endif
2088
2107
 
2089
2108
#ifdef ERTS_SMP
2090
 
        if (!ps_locked) {
2091
 
            ps_locked = 1;
2092
 
            ERTS_POLLSET_LOCK(ps);
2093
 
        }
 
2109
        ps_locked = 1;
 
2110
        ERTS_POLLSET_LOCK(ps);
2094
2111
#endif
2095
2112
 
2096
2113
        no_fds = save_poll_result(ps, pr, no_fds, res, ebadf);
2099
2116
        check_poll_result(pr, no_fds);
2100
2117
#endif
2101
2118
 
2102
 
        res = (no_fds == 0
2103
 
               ? (ERTS_POLLSET_UNSET_INTERRUPTED_CHK(ps) ? EINTR : EAGAIN)
2104
 
               : 0);
 
2119
        res = (no_fds == 0 ? (is_interrupted_reset(ps) ? EINTR : EAGAIN) : 0);
2105
2120
        *len = no_fds;
2106
2121
    }
2107
2122
 
2112
2127
#endif
2113
2128
 
2114
2129
 done:
2115
 
    erts_smp_atomic_set(&ps->timeout, LONG_MAX);
 
2130
    erts_smp_atomic32_set_relb(&ps->timeout, ERTS_AINT32_T_MAX);
2116
2131
#ifdef ERTS_POLL_DEBUG_PRINT
2117
2132
    erts_printf("Leaving %s = erts_poll_wait()\n",
2118
2133
                 res == 0 ? "0" : erl_errno_id(res));
2128
2143
void
2129
2144
ERTS_POLL_EXPORT(erts_poll_interrupt)(ErtsPollSet ps, int set)
2130
2145
{
 
2146
#if defined(USE_THREADS)
 
2147
    if (!set)
 
2148
        reset_wakeup_state(ps);
 
2149
    else
 
2150
        wake_poller(ps, 1, 0);
 
2151
#endif
 
2152
}
 
2153
 
 
2154
#if ERTS_POLL_ASYNC_INTERRUPT_SUPPORT
 
2155
void
 
2156
ERTS_POLL_EXPORT(erts_poll_async_sig_interrupt)(ErtsPollSet ps)
 
2157
{
2131
2158
    /*
2132
 
     * NOTE: This function might be called from signal handlers in the
2133
 
     *       non-smp case; therefore, it has to be async-signal safe in
2134
 
     *       the non-smp case.
 
2159
     * NOTE: This function is called from signal handlers, it,
 
2160
     *       therefore, it has to be async-signal safe.
2135
2161
     */
2136
 
    if (set) {
2137
 
        ERTS_POLLSET_SET_INTERRUPTED(ps);
2138
 
#if ERTS_POLL_ASYNC_INTERRUPT_SUPPORT || defined(ERTS_SMP)
2139
 
        wake_poller(ps);
 
2162
    wake_poller(ps, 1, 1);
 
2163
}
2140
2164
#endif
2141
 
    }
2142
 
    else {
2143
 
        ERTS_POLLSET_UNSET_INTERRUPTED(ps);
2144
 
    }
2145
 
}
2146
2165
 
2147
2166
/*
2148
2167
 * erts_poll_interrupt_timed():
2150
2169
 * is not guaranteed that it will timeout before 'msec' milli seconds.
2151
2170
 */
2152
2171
void
2153
 
ERTS_POLL_EXPORT(erts_poll_interrupt_timed)(ErtsPollSet ps, int set, long msec)
 
2172
ERTS_POLL_EXPORT(erts_poll_interrupt_timed)(ErtsPollSet ps,
 
2173
                                            int set,
 
2174
                                            erts_short_time_t msec)
2154
2175
{
2155
 
    if (set) {
2156
 
        if (erts_smp_atomic_read(&ps->timeout) > msec) {
2157
 
            ERTS_POLLSET_SET_INTERRUPTED(ps);
2158
2176
#if ERTS_POLL_ASYNC_INTERRUPT_SUPPORT || defined(ERTS_SMP)
2159
 
            wake_poller(ps);
2160
 
#endif
2161
 
        }
 
2177
    if (!set)
 
2178
        reset_wakeup_state(ps);
 
2179
    else {
 
2180
        if (erts_smp_atomic32_read_acqb(&ps->timeout) > (erts_aint32_t) msec)
 
2181
            wake_poller(ps, 1, 0);
2162
2182
#ifdef ERTS_POLL_COUNT_AVOIDED_WAKEUPS
2163
2183
        else {
2164
2184
            if (ERTS_POLLSET_IS_POLLED(ps))
2165
 
                erts_smp_atomic_inc(&ps->no_avoided_wakeups);
2166
 
            erts_smp_atomic_inc(&ps->no_avoided_interrupts);
 
2185
                erts_smp_atomic_inc_nob(&ps->no_avoided_wakeups);
 
2186
            erts_smp_atomic_inc_nob(&ps->no_avoided_interrupts);
2167
2187
        }
2168
 
        erts_smp_atomic_inc(&ps->no_interrupt_timed);
2169
 
#endif
2170
 
    }
2171
 
    else {
2172
 
        ERTS_POLLSET_UNSET_INTERRUPTED(ps);
2173
 
    }
 
2188
        erts_smp_atomic_inc_nob(&ps->no_interrupt_timed);
 
2189
#endif
 
2190
    }
 
2191
#endif
2174
2192
}
2175
2193
 
2176
2194
int
2229
2247
    ps->internal_fd_limit = 0;
2230
2248
    ps->fds_status = NULL;
2231
2249
    ps->fds_status_len = 0;
2232
 
    erts_smp_atomic_init(&ps->no_of_user_fds, 0);
 
2250
    erts_smp_atomic_init_nob(&ps->no_of_user_fds, 0);
2233
2251
#if ERTS_POLL_USE_KERNEL_POLL
2234
2252
    ps->kp_fd = -1;
2235
2253
#if ERTS_POLL_USE_EPOLL
2281
2299
    ps->update_requests.next = NULL;
2282
2300
    ps->update_requests.len = 0;
2283
2301
    ps->curr_upd_req_block = &ps->update_requests;
2284
 
    erts_smp_atomic_init(&ps->have_update_requests, 0);
 
2302
    erts_smp_atomic32_init_nob(&ps->have_update_requests, 0);
2285
2303
#endif
2286
2304
#ifdef ERTS_SMP
2287
 
    erts_smp_atomic_init(&ps->polled, 0);
2288
 
    erts_smp_atomic_init(&ps->woken, 0);
 
2305
    erts_atomic32_init_nob(&ps->polled, 0);
2289
2306
    erts_smp_mtx_init(&ps->mtx, "pollset");
2290
 
#elif ERTS_POLL_ASYNC_INTERRUPT_SUPPORT
2291
 
    ps->woken = 0;
 
2307
#endif
 
2308
#if defined(USE_THREADS) || ERTS_POLL_ASYNC_INTERRUPT_SUPPORT
 
2309
    erts_atomic32_init_nob(&ps->wakeup_state, (erts_aint32_t) 0);
2292
2310
#endif
2293
2311
#if ERTS_POLL_USE_WAKEUP_PIPE
2294
2312
    create_wakeup_pipe(ps);
2310
2328
        ps->internal_fd_limit = kp_fd + 1;
2311
2329
    ps->kp_fd = kp_fd;
2312
2330
#endif
2313
 
#if ERTS_POLL_ASYNC_INTERRUPT_SUPPORT && !defined(ERTS_SMP)
2314
 
    ps->interrupt = 0;
2315
 
#else
2316
 
    erts_smp_atomic_init(&ps->interrupt, 0);
2317
 
#endif
2318
 
    erts_smp_atomic_init(&ps->timeout, LONG_MAX);
 
2331
    erts_smp_atomic32_init_nob(&ps->timeout, ERTS_AINT32_T_MAX);
2319
2332
#ifdef ERTS_POLL_COUNT_AVOIDED_WAKEUPS
2320
 
    erts_smp_atomic_init(&ps->no_avoided_wakeups, 0);
2321
 
    erts_smp_atomic_init(&ps->no_avoided_interrupts, 0);
2322
 
    erts_smp_atomic_init(&ps->no_interrupt_timed, 0);
 
2333
    erts_smp_atomic_init_nob(&ps->no_avoided_wakeups, 0);
 
2334
    erts_smp_atomic_init_nob(&ps->no_avoided_interrupts, 0);
 
2335
    erts_smp_atomic_init_nob(&ps->no_interrupt_timed, 0);
2323
2336
#endif
2324
2337
#if ERTS_POLL_USE_UPDATE_REQUESTS_QUEUE
2325
2338
    handle_update_requests(ps);
2327
2340
#if ERTS_POLL_USE_FALLBACK
2328
2341
    ps->fallback_used = 0;
2329
2342
#endif
2330
 
    erts_smp_atomic_set(&ps->no_of_user_fds, 0); /* Don't count wakeup pipe and fallback fd */
 
2343
    erts_smp_atomic_set_nob(&ps->no_of_user_fds, 0); /* Don't count wakeup pipe and fallback fd */
2331
2344
 
2332
2345
    erts_smp_spin_lock(&pollsets_lock);
2333
2346
    ps->next = pollsets;
2473
2486
 
2474
2487
    pip->memory_size = size;
2475
2488
 
2476
 
    pip->poll_set_size = (int) erts_smp_atomic_read(&ps->no_of_user_fds);
 
2489
    pip->poll_set_size = (int) erts_smp_atomic_read_nob(&ps->no_of_user_fds);
2477
2490
#ifdef ERTS_SMP
2478
2491
    pip->poll_set_size++; /* Wakeup pipe */
2479
2492
#endif
2531
2544
    pip->max_fds = max_fds;
2532
2545
 
2533
2546
#ifdef ERTS_POLL_COUNT_AVOIDED_WAKEUPS
2534
 
    pip->no_avoided_wakeups = erts_smp_atomic_read(&ps->no_avoided_wakeups);
2535
 
    pip->no_avoided_interrupts = erts_smp_atomic_read(&ps->no_avoided_interrupts);
2536
 
    pip->no_interrupt_timed = erts_smp_atomic_read(&ps->no_interrupt_timed);
 
2547
    pip->no_avoided_wakeups = erts_smp_atomic_read_nob(&ps->no_avoided_wakeups);
 
2548
    pip->no_avoided_interrupts = erts_smp_atomic_read_nob(&ps->no_avoided_interrupts);
 
2549
    pip->no_interrupt_timed = erts_smp_atomic_read_nob(&ps->no_interrupt_timed);
2537
2550
#endif
2538
2551
 
2539
2552
    ERTS_POLLSET_UNLOCK(ps);
2553
2566
{
2554
2567
    va_list ap;
2555
2568
 
2556
 
    if (ERTS_IS_CRASH_DUMPING || ERTS_GOT_SIGUSR1) {
 
2569
    if (ERTS_SOMEONE_IS_CRASH_DUMPING || ERTS_GOT_SIGUSR1) {
2557
2570
        /*
2558
2571
         * Crash dump writing and reception of sigusr1 (which will
2559
2572
         * result in a crash dump) closes all file descriptors. This
2573
2586
static void
2574
2587
fatal_error_async_signal_safe(char *error_str)
2575
2588
{
2576
 
    if (ERTS_IS_CRASH_DUMPING || ERTS_GOT_SIGUSR1) {
 
2589
    if (ERTS_SOMEONE_IS_CRASH_DUMPING || ERTS_GOT_SIGUSR1) {
2577
2590
        /* See comment above in fatal_error() */
2578
2591
        return;
2579
2592
    }