~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

Viewing changes to erts/emulator/sys/common/erl_check_io.c

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
34
34
#include "sys.h"
35
35
#include "global.h"
36
36
#include "erl_check_io.h"
37
 
#ifndef ERTS_SYS_CONTINOUS_FD_NUMBERS
38
 
#include "hash.h"
 
37
 
 
38
#ifdef ERTS_SYS_CONTINOUS_FD_NUMBERS
 
39
#  define ERTS_DRV_EV_STATE_EXTRA_SIZE 128
 
40
#else
 
41
#  include "safe_hash.h"
 
42
#  define DRV_EV_STATE_HTAB_SIZE 1024
39
43
#endif
40
44
 
41
 
#define ERTS_EV_FLG_IGNORE              (((short) 1) << 0)
42
 
 
43
45
#define ERTS_EV_TYPE_NONE               ((short) 0)
44
46
#define ERTS_EV_TYPE_DRV_SEL            ((short) 1)
45
47
#define ERTS_EV_TYPE_DRV_EV             ((short) 2)
46
48
 
47
 
#define ERTS_DRV_EV_STATE_EXTRA_SIZE 128
48
 
 
49
49
#if defined(ERTS_KERNEL_POLL_VERSION)
50
50
#  define ERTS_CIO_EXPORT(FUNC) FUNC ## _kp
51
51
#elif defined(ERTS_NO_KERNEL_POLL_VERSION)
67
67
#define ERTS_CIO_POLL_INIT      ERTS_POLL_EXPORT(erts_poll_init)
68
68
#define ERTS_CIO_POLL_INFO      ERTS_POLL_EXPORT(erts_poll_info)
69
69
 
70
 
static ErtsPollSet pollset;
 
70
static struct pollset_info
 
71
{
 
72
    ErtsPollSet ps;
 
73
    erts_smp_atomic_t in_poll_wait;        /* set while doing poll */
 
74
#ifdef ERTS_SMP
 
75
    struct removed_fd* removed_list;       /* list of deselected fd's*/
 
76
    erts_smp_spinlock_t removed_list_lock;
 
77
#endif
 
78
}pollset;
 
79
#define NUM_OF_POLLSETS 1
 
80
 
 
81
#ifdef ERTS_SMP
 
82
struct removed_fd {
 
83
    struct removed_fd *next;
 
84
    ErtsSysFdType fd;
 
85
};
 
86
#endif
71
87
 
72
88
typedef struct {
73
89
#ifndef ERTS_SYS_CONTINOUS_FD_NUMBERS
74
 
    HashBucket hb;
 
90
    SafeHashBucket hb;
75
91
#endif
76
92
    ErtsSysFdType fd;
77
93
    union {
79
95
        ErtsDrvSelectDataState *select;
80
96
    } driver;
81
97
    ErtsPollEvents events;
82
 
    short flags;
 
98
    unsigned short remove_cnt; /* number of removed_fd's referring to this fd */
83
99
    short type;
84
100
} ErtsDrvEventState;
85
101
 
86
 
struct erts_fd_list {
87
 
    struct erts_fd_list *next;
88
 
    ErtsSysFdType fd;
89
 
};
90
 
 
91
102
#ifdef ERTS_SYS_CONTINOUS_FD_NUMBERS
92
103
static int max_fds = -1;
93
104
#endif
94
 
static erts_smp_mtx_t drv_ev_state_mtx;
 
105
#define DRV_EV_STATE_LOCK_CNT 16
 
106
static union {
 
107
    erts_smp_mtx_t lck;
 
108
    byte _cache_line_alignment[64];
 
109
}drv_ev_state_locks[DRV_EV_STATE_LOCK_CNT];
 
110
 
 
111
#ifdef ERTS_SMP
 
112
static ERTS_INLINE erts_smp_mtx_t* fd_mtx(ErtsSysFdType fd)
 
113
{
 
114
    int hash = (int)fd;
 
115
# ifndef ERTS_SYS_CONTINOUS_FD_NUMBERS
 
116
    hash ^= (hash >> 9);
 
117
# endif
 
118
    return &drv_ev_state_locks[hash % DRV_EV_STATE_LOCK_CNT].lck;
 
119
}
 
120
#else
 
121
#  define fd_mtx(fd) NULL
 
122
#endif
95
123
 
96
124
#ifdef ERTS_SYS_CONTINOUS_FD_NUMBERS
97
125
 
98
 
static int drv_ev_state_len;
 
126
static erts_smp_atomic_t drv_ev_state_len;
99
127
static ErtsDrvEventState *drv_ev_state;
 
128
static erts_smp_mtx_t drv_ev_state_grow_lock; /* prevent lock-hogging of racing growers */
100
129
 
101
130
#else
102
 
static Hash drv_ev_state_tab;
 
131
static SafeHash drv_ev_state_tab;
103
132
static int num_state_prealloc;
104
133
static ErtsDrvEventState *state_prealloc_first;
 
134
erts_smp_spinlock_t state_prealloc_lock;
105
135
 
106
136
static ERTS_INLINE ErtsDrvEventState *hash_get_drv_ev_state(ErtsSysFdType fd)
107
137
{
108
138
    ErtsDrvEventState tmpl;
109
139
    tmpl.fd = fd;
110
 
    return  (ErtsDrvEventState *) hash_get(&drv_ev_state_tab, (void *) &tmpl);
 
140
    return  (ErtsDrvEventState *) safe_hash_get(&drv_ev_state_tab, (void *) &tmpl);
111
141
}
112
142
 
113
 
static ERTS_INLINE ErtsDrvEventState *hash_new_drv_ev_state(ErtsSysFdType fd)
 
143
static ERTS_INLINE ErtsDrvEventState* hash_new_drv_ev_state(ErtsSysFdType fd)
114
144
{
115
145
    ErtsDrvEventState tmpl;
116
146
    tmpl.fd = fd;
117
147
    tmpl.driver.select = NULL;
118
148
    tmpl.events = 0;
119
 
    tmpl.flags = 0;
 
149
    tmpl.remove_cnt = 0;
120
150
    tmpl.type = ERTS_EV_TYPE_NONE;
121
 
    return  (ErtsDrvEventState *) hash_put(&drv_ev_state_tab, (void *) &tmpl);
 
151
    return  (ErtsDrvEventState *) safe_hash_put(&drv_ev_state_tab, (void *) &tmpl);
122
152
}
123
153
 
124
154
static ERTS_INLINE void hash_erase_drv_ev_state(ErtsDrvEventState *state)
125
155
{
126
 
    hash_erase(&drv_ev_state_tab, (void *) state);
 
156
    safe_hash_erase(&drv_ev_state_tab, (void *) state);
127
157
}
128
158
 
129
 
#endif
130
 
 
131
 
static erts_smp_atomic_t in_poll_wait;
132
 
 
133
 
struct erts_fd_list *ignored_list;
 
159
#endif /* !ERTS_SYS_CONTINOUS_FD_NUMBERS */
134
160
 
135
161
static void stale_drv_select(Eterm id, ErtsDrvEventState *state, int mode);
136
162
static void select_steal(ErlDrvPort ix, ErtsDrvEventState *state, 
158
184
    }
159
185
}
160
186
 
161
 
ERTS_QUALLOC_IMPL(fd_list, struct erts_fd_list, 64, ERTS_ALC_T_FD_LIST)
 
187
#ifdef ERTS_SMP
 
188
ERTS_SCHED_PREF_QUICK_ALLOC_IMPL(removed_fd, struct removed_fd, 64, ERTS_ALC_T_FD_LIST)
 
189
#endif
 
190
 
162
191
 
163
192
static ERTS_INLINE void
164
 
check_ignore(ErtsDrvEventState *state, ErtsPollEvents new_evs, ErtsPollEvents old_evs)
 
193
remember_removed(ErtsDrvEventState *state, struct pollset_info* psi)
165
194
{
166
 
 
167
 
    if (!new_evs
168
 
        && old_evs
169
 
        && !(state->flags & ERTS_EV_FLG_IGNORE)
170
 
        && erts_smp_atomic_read(&in_poll_wait)) {
171
 
        struct erts_fd_list *fdlp = fd_list_alloc();
 
195
#ifdef ERTS_SMP
 
196
    struct removed_fd *fdlp;
 
197
    ERTS_SMP_LC_ASSERT(erts_smp_lc_mtx_is_locked(fd_mtx(state->fd)));
 
198
    if (erts_smp_atomic_read(&psi->in_poll_wait)) {
 
199
        state->remove_cnt++;
 
200
        ASSERT(state->remove_cnt > 0);
 
201
        fdlp = removed_fd_alloc();
172
202
        fdlp->fd = state->fd;
173
 
        fdlp->next = ignored_list;
174
 
        ignored_list = fdlp;
175
 
        state->flags |= ERTS_EV_FLG_IGNORE;
 
203
        erts_smp_spin_lock(&psi->removed_list_lock);
 
204
        fdlp->next = psi->removed_list;
 
205
        psi->removed_list = fdlp;
 
206
        erts_smp_spin_unlock(&psi->removed_list_lock);
176
207
    }
177
 
 
178
 
}
 
208
#endif
 
209
}
 
210
 
 
211
 
 
212
static ERTS_INLINE int
 
213
is_removed(ErtsDrvEventState *state)
 
214
{
 
215
#ifdef ERTS_SMP
 
216
    /* Note that there is a possible race here, where an fd is removed
 
217
       (increasing remove_cnt) and then added again just before erts_poll_wait
 
218
       is called by erts_check_io. Any polled event on the re-added fd will then
 
219
       be falsely ignored. But that does not matter, as the event will trigger
 
220
       again next time erl_check_io is called. */
 
221
    return state->remove_cnt > 0;
 
222
#else
 
223
    return 0;
 
224
#endif
 
225
}
 
226
 
179
227
 
180
228
static ERTS_INLINE void
181
 
reset_ignores(void)
 
229
forget_removed(struct pollset_info* psi)
182
230
{
183
 
    struct erts_fd_list *fdlp = ignored_list;
 
231
#ifdef ERTS_SMP
 
232
    struct removed_fd* fdlp;
 
233
    struct removed_fd* tofree;
 
234
 
 
235
    /* Fast track: if (atomic_ptr(removed_list)==NULL) return; */
 
236
 
 
237
    erts_smp_spin_lock(&psi->removed_list_lock);
 
238
    fdlp = psi->removed_list;
 
239
    psi->removed_list = NULL;
 
240
    erts_smp_spin_unlock(&psi->removed_list_lock);
184
241
 
185
242
    while (fdlp) {
186
 
        struct erts_fd_list *ffdlp = fdlp;
 
243
        ErtsDrvEventState *state;
 
244
        erts_smp_mtx_t* mtx = fd_mtx(fdlp->fd);
 
245
        erts_smp_mtx_lock(mtx);
187
246
#ifdef ERTS_SYS_CONTINOUS_FD_NUMBERS
188
 
        drv_ev_state[(int) fdlp->fd].flags &= ~ERTS_EV_FLG_IGNORE;
 
247
        state = &drv_ev_state[(int) fdlp->fd];
 
248
        ASSERT(state->remove_cnt > 0);
 
249
        state->remove_cnt--;
189
250
#else
190
 
        {
191
 
            ErtsDrvEventState *state = hash_get_drv_ev_state(fdlp->fd);
192
 
            if (state != NULL) 
193
 
                state->flags &= ~ERTS_EV_FLG_IGNORE;
 
251
        state = hash_get_drv_ev_state(fdlp->fd);
 
252
        ASSERT(state);
 
253
        ASSERT(state->remove_cnt > 0);
 
254
        if (--state->remove_cnt == 0 && state->type == ERTS_EV_TYPE_NONE) {
 
255
            hash_erase_drv_ev_state(state);
194
256
        }
195
257
#endif
 
258
        erts_smp_mtx_unlock(mtx);
 
259
        tofree = fdlp;
196
260
        fdlp = fdlp->next;
197
 
        fd_list_free(ffdlp);
 
261
        removed_fd_free(tofree);
198
262
    }
199
 
    ignored_list = NULL;
 
263
#endif /* ERTS_SMP */
200
264
}
201
265
 
202
266
#ifdef ERTS_SYS_CONTINOUS_FD_NUMBERS
207
271
    int new_len = min_ix + 1 + ERTS_DRV_EV_STATE_EXTRA_SIZE;
208
272
    if (new_len > max_fds)
209
273
        new_len = max_fds;
210
 
    drv_ev_state = (drv_ev_state_len
211
 
                     ? erts_realloc(ERTS_ALC_T_DRV_EV_STATE,
212
 
                                    drv_ev_state,
213
 
                                    sizeof(ErtsDrvEventState)*new_len)
214
 
                     : erts_alloc(ERTS_ALC_T_DRV_EV_STATE,
215
 
                                  sizeof(ErtsDrvEventState)*new_len));
216
 
    for (i = drv_ev_state_len; i < new_len; i++) {
217
 
        drv_ev_state[i].fd = (ErtsSysFdType) i;
218
 
        drv_ev_state[i].driver.select = NULL;
219
 
        drv_ev_state[i].events = 0;
220
 
        drv_ev_state[i].flags = 0;
221
 
        drv_ev_state[i].type = ERTS_EV_TYPE_NONE;
 
274
 
 
275
    erts_smp_mtx_lock(&drv_ev_state_grow_lock);
 
276
    if (erts_smp_atomic_read(&drv_ev_state_len) <= min_ix) {
 
277
        for (i=0; i<DRV_EV_STATE_LOCK_CNT; i++) { /* lock all fd's */
 
278
            erts_smp_mtx_lock(&drv_ev_state_locks[i].lck);
 
279
        }
 
280
        drv_ev_state = (drv_ev_state
 
281
                        ? erts_realloc(ERTS_ALC_T_DRV_EV_STATE,
 
282
                                       drv_ev_state,
 
283
                                       sizeof(ErtsDrvEventState)*new_len)
 
284
                        : erts_alloc(ERTS_ALC_T_DRV_EV_STATE,
 
285
                                     sizeof(ErtsDrvEventState)*new_len));
 
286
        for (i = erts_smp_atomic_read(&drv_ev_state_len); i < new_len; i++) {
 
287
            drv_ev_state[i].fd = (ErtsSysFdType) i;
 
288
            drv_ev_state[i].driver.select = NULL;
 
289
            drv_ev_state[i].events = 0;
 
290
            drv_ev_state[i].remove_cnt = 0;
 
291
            drv_ev_state[i].type = ERTS_EV_TYPE_NONE;
 
292
        }
 
293
        erts_smp_atomic_set(&drv_ev_state_len, new_len);
 
294
        for (i=0; i<DRV_EV_STATE_LOCK_CNT; i++) {
 
295
            erts_smp_mtx_unlock(&drv_ev_state_locks[i].lck);
 
296
        }
222
297
    }
223
 
    drv_ev_state_len = new_len;
 
298
    /*else already grown by racing thread */
 
299
 
 
300
    erts_smp_mtx_unlock(&drv_ev_state_grow_lock);
224
301
}
225
 
#endif
 
302
#endif /* ERTS_SYS_CONTINOUS_FD_NUMBERS */
 
303
 
226
304
 
227
305
static ERTS_INLINE void
228
306
abort_task(Eterm id, ErtsPortTaskHandle *pthp, short type)
278
356
static void
279
357
deselect(ErtsDrvEventState *state, int mode)
280
358
{
281
 
    ErtsPollEvents old_events = state->events;
282
359
    ErtsPollEvents rm_events;
283
 
    ERTS_SMP_LC_ASSERT(erts_smp_lc_mtx_is_locked(&drv_ev_state_mtx));
 
360
    ERTS_SMP_LC_ASSERT(erts_smp_lc_mtx_is_locked(fd_mtx(state->fd)));
284
361
    ASSERT(state->events);
285
362
 
286
363
    abort_tasks(state, mode);
300
377
        }
301
378
    }
302
379
 
303
 
    state->events = ERTS_CIO_POLL_CTL(pollset, state->fd, rm_events, 0);
 
380
    state->events = ERTS_CIO_POLL_CTL(pollset.ps, state->fd, rm_events, 0);
304
381
 
305
382
    if (!(state->events)) {
306
383
        switch (state->type) {
325
402
        }
326
403
            
327
404
        state->driver.select = NULL;
328
 
        state->flags = 0;
329
405
        state->type = ERTS_EV_TYPE_NONE;
 
406
        remember_removed(state, &pollset);
330
407
    }
331
 
    check_ignore(state, state->events, old_events);
332
408
}
333
409
 
334
410
int
342
418
    ErtsPollEvents ctl_events = (ErtsPollEvents) 0;
343
419
    ErtsPollEvents new_events, old_events;
344
420
    ErtsDrvEventState *state;
 
421
    int ret;
345
422
 
346
423
    ERTS_SMP_LC_ASSERT(erts_drvport2port(ix)
347
424
                       && erts_lc_is_port_locked(erts_drvport2port(ix)));
348
425
 
349
426
#ifdef ERTS_SYS_CONTINOUS_FD_NUMBERS
350
 
    if (fd < 0)
351
 
        return -1;
352
 
 
353
 
    if (fd >= max_fds) {
354
 
        select_large_fd_error(ix, fd, mode, on);
355
 
        return -1;
356
 
    }
357
 
#endif
358
 
 
359
 
    erts_smp_mtx_lock(&drv_ev_state_mtx);
360
 
 
361
 
#ifdef ERTS_SYS_CONTINOUS_FD_NUMBERS
362
 
    if (fd >= drv_ev_state_len)
 
427
    if ((unsigned)fd >= (unsigned)erts_smp_atomic_read(&drv_ev_state_len)) {
 
428
        if (fd < 0)
 
429
            return -1;    
 
430
        if (fd >= max_fds) {
 
431
            select_large_fd_error(ix, fd, mode, on);
 
432
            return -1;
 
433
        }
363
434
        grow_drv_ev_state(fd);
 
435
    }
 
436
#endif
 
437
 
 
438
    erts_smp_mtx_lock(fd_mtx(fd));
 
439
 
 
440
#ifdef ERTS_SYS_CONTINOUS_FD_NUMBERS
364
441
    state = &drv_ev_state[(int) fd];
365
442
#else
366
443
    /* Could use hash_new directly, but want to keep the normal case fast */
369
446
        state = hash_new_drv_ev_state(fd);
370
447
    }
371
448
#endif
372
 
    
 
449
 
373
450
#if ERTS_CIO_HAVE_DRV_EVENT
374
451
    if (state->type == ERTS_EV_TYPE_DRV_EV)
375
 
        select_steal(ix, state, mode, on);;
 
452
        select_steal(ix, state, mode, on);
376
453
#endif
377
454
 
378
455
    if (mode & DO_READ) {
396
473
           ? (state->type == ERTS_EV_TYPE_DRV_SEL)
397
474
           : (state->type == ERTS_EV_TYPE_NONE));
398
475
 
399
 
    new_events = ERTS_CIO_POLL_CTL(pollset, state->fd, ctl_events, on);
400
 
    if (new_events & (ERTS_POLL_EV_ERR|ERTS_POLL_EV_NVAL))
401
 
        goto error;
 
476
    new_events = ERTS_CIO_POLL_CTL(pollset.ps, state->fd, ctl_events, on);
 
477
    if (new_events & (ERTS_POLL_EV_ERR|ERTS_POLL_EV_NVAL)) {
 
478
        ret = -1;
 
479
        goto done;
 
480
    }
402
481
 
403
482
    old_events = state->events;
404
483
 
444
523
                erts_free(ERTS_ALC_T_DRV_SEL_D_STATE,
445
524
                          state->driver.select);
446
525
                state->driver.select = NULL;
447
 
                state->flags = 0;
448
526
                state->type = ERTS_EV_TYPE_NONE;
 
527
                remember_removed(state, &pollset);
449
528
            }
450
529
        }
451
530
    }
452
 
    check_ignore(state, new_events, old_events);
453
 
 
454
 
#ifndef ERTS_SYS_CONTINOUS_FD_NUMBERS
455
 
    if (state->type == ERTS_EV_TYPE_NONE) {
456
 
        hash_erase_drv_ev_state(state);
457
 
    }
458
 
#endif
459
 
    
460
 
    erts_smp_mtx_unlock(&drv_ev_state_mtx);
461
 
 
462
 
    return 0;
463
 
 
464
 
 error:
465
 
 
466
 
#ifndef ERTS_SYS_CONTINOUS_FD_NUMBERS
467
 
    if (state->type == ERTS_EV_TYPE_NONE) {
468
 
        hash_erase_drv_ev_state(state);
469
 
    }
470
 
#endif
471
 
 
472
 
   erts_smp_mtx_unlock(&drv_ev_state_mtx);
473
 
    return -1;
 
531
   
 
532
    ret = 0;
 
533
 
 
534
done:
 
535
#ifndef ERTS_SYS_CONTINOUS_FD_NUMBERS
 
536
    if (state->type == ERTS_EV_TYPE_NONE && state->remove_cnt == 0) {
 
537
        hash_erase_drv_ev_state(state);
 
538
    }
 
539
#endif
 
540
    erts_smp_mtx_unlock(fd_mtx(fd));
 
541
    return ret;
474
542
}
475
543
 
476
544
int
487
555
    ErtsPollEvents remove_events;
488
556
    Eterm id = drvport2id(ix);
489
557
    ErtsDrvEventState *state;
 
558
    int ret;
490
559
 
491
560
    ERTS_SMP_LC_ASSERT(erts_drvport2port(ix)
492
561
                       && erts_lc_is_port_locked(erts_drvport2port(ix)));
493
562
 
494
563
#ifdef ERTS_SYS_CONTINOUS_FD_NUMBERS
495
 
    if (fd < 0)
496
 
        return -1;
497
 
 
498
 
    if (fd >= max_fds) {
499
 
        event_large_fd_error(ix, fd, event_data);
500
 
        return -1;
501
 
    }
502
 
#endif
503
 
 
504
 
    erts_smp_mtx_lock(&drv_ev_state_mtx);
505
 
 
506
 
#ifdef ERTS_SYS_CONTINOUS_FD_NUMBERS
507
 
    if (fd >= drv_ev_state_len)
 
564
    if ((unsigned)fd >= (unsigned)erts_smp_atomic_read(&drv_ev_state_len)) {
 
565
        if (fd < 0)
 
566
            return -1;    
 
567
        if (fd >= max_fds) {
 
568
            event_large_fd_error(ix, fd, event_data);
 
569
            return -1;
 
570
        }
508
571
        grow_drv_ev_state(fd);
 
572
    }
 
573
#endif
 
574
 
 
575
    erts_smp_mtx_lock(fd_mtx(fd));
 
576
 
 
577
#ifdef ERTS_SYS_CONTINOUS_FD_NUMBERS
509
578
    state = &drv_ev_state[(int) fd];
510
579
#else
511
580
    /* Could use hash_new directly, but want to keep the normal case fast */
533
602
    else {
534
603
        remove_events = ~event_data->events & events;
535
604
        add_events = ~events & event_data->events;
536
 
 
537
605
    }
538
606
 
539
607
    if (add_events) {
540
 
        events = ERTS_CIO_POLL_CTL(pollset, state->fd, add_events, 1);
541
 
        if (events & (ERTS_POLL_EV_ERR|ERTS_POLL_EV_NVAL))
542
 
            goto error;
 
608
        events = ERTS_CIO_POLL_CTL(pollset.ps, state->fd, add_events, 1);
 
609
        if (events & (ERTS_POLL_EV_ERR|ERTS_POLL_EV_NVAL)) {
 
610
            ret = -1;
 
611
            goto done;
 
612
        }
543
613
    }
544
614
    if (remove_events) {
545
 
        events = ERTS_CIO_POLL_CTL(pollset, state->fd, remove_events, 0);
546
 
        if (events & (ERTS_POLL_EV_ERR|ERTS_POLL_EV_NVAL))
547
 
            goto error;
 
615
        events = ERTS_CIO_POLL_CTL(pollset.ps, state->fd, remove_events, 0);
 
616
        if (events & (ERTS_POLL_EV_ERR|ERTS_POLL_EV_NVAL)) {
 
617
            ret = -1;
 
618
            goto done;
 
619
        }
548
620
    }
549
 
    if (event_data) {
 
621
    if (event_data && event_data->events != 0) {
550
622
        if (state->type == ERTS_EV_TYPE_DRV_EV) {
551
623
            state->driver.event->removed_events &= ~add_events;
552
624
            state->driver.event->removed_events |= remove_events;
569
641
                      state->driver.event);
570
642
        }
571
643
        state->driver.select = NULL;
572
 
        state->flags = 0;
573
644
        state->type = ERTS_EV_TYPE_NONE;
 
645
        remember_removed(state, &pollset);
574
646
    }
575
 
    check_ignore(state, events, state->events);
576
647
    state->events = events;
577
648
    ASSERT(event_data ? events == event_data->events : events == 0); 
578
649
 
579
 
#ifndef ERTS_SYS_CONTINOUS_FD_NUMBERS
580
 
    if (state->type == ERTS_EV_TYPE_NONE) {
581
 
        hash_erase_drv_ev_state(state);
582
 
    }
583
 
#endif
584
 
 
585
 
    erts_smp_mtx_unlock(&drv_ev_state_mtx);
586
 
    return 0;
587
 
 error:
588
 
 
589
 
#ifndef ERTS_SYS_CONTINOUS_FD_NUMBERS
590
 
    if (state->type == ERTS_EV_TYPE_NONE) {
591
 
        hash_erase_drv_ev_state(state);
592
 
    }
593
 
#endif
594
 
 
595
 
    erts_smp_mtx_unlock(&drv_ev_state_mtx);
596
 
    return -1;
 
650
    ret = 0;
 
651
 
 
652
done:
 
653
#ifndef ERTS_SYS_CONTINOUS_FD_NUMBERS
 
654
    if (state->type == ERTS_EV_TYPE_NONE && state->remove_cnt == 0) {
 
655
        hash_erase_drv_ev_state(state);
 
656
    }
 
657
#endif
 
658
    erts_smp_mtx_unlock(fd_mtx(fd));
 
659
    return ret;
597
660
#endif
598
661
}
599
662
 
845
908
void
846
909
ERTS_CIO_EXPORT(erts_check_io_interrupt)(int set)
847
910
{
848
 
    ERTS_CIO_POLL_INTR(pollset, set);
 
911
    ERTS_CIO_POLL_INTR(pollset.ps, set);
849
912
}
850
913
 
851
914
void
852
915
ERTS_CIO_EXPORT(erts_check_io_interrupt_timed)(int set, long msec)
853
916
{
854
 
    ERTS_CIO_POLL_INTR_TMD(pollset, set, msec);
 
917
    ERTS_CIO_POLL_INTR_TMD(pollset.ps, set, msec);
855
918
}
856
919
 
857
920
void
877
940
#endif
878
941
    erts_smp_activity_begin(ERTS_ACTIVITY_WAIT, NULL, NULL, NULL);
879
942
    pollres_len = sizeof(pollres)/sizeof(ErtsPollResFd);
880
 
    erts_smp_atomic_set(&in_poll_wait, 1);
881
 
    poll_ret = ERTS_CIO_POLL_WAIT(pollset, pollres, &pollres_len, &wait_time);
 
943
 
 
944
    erts_smp_atomic_set(&pollset.in_poll_wait, 1);
 
945
 
 
946
    poll_ret = ERTS_CIO_POLL_WAIT(pollset.ps, pollres, &pollres_len, &wait_time);
882
947
 
883
948
#ifdef ERTS_ENABLE_LOCK_CHECK
884
949
    erts_lc_check_exact(NULL, 0); /* No locks should be locked */
893
958
#endif
894
959
 
895
960
    if (poll_ret != 0) {
896
 
        erts_smp_atomic_set(&in_poll_wait, 0);
 
961
        erts_smp_atomic_set(&pollset.in_poll_wait, 0);
897
962
 
898
963
        if (poll_ret == EAGAIN)
899
964
            goto restart;
909
974
                          erl_errno_id(poll_ret), poll_ret);
910
975
            erts_send_error_to_logger_nogl(dsbufp);
911
976
        }
912
 
 
913
977
        return;
914
978
    }
915
979
 
916
 
    erts_smp_mtx_lock(&drv_ev_state_mtx);
917
 
    erts_smp_atomic_set(&in_poll_wait, 0);
918
 
 
919
980
    for (i = 0; i < pollres_len; i++) {
 
981
 
920
982
        ErtsSysFdType fd = (ErtsSysFdType) pollres[i].fd;
921
983
        ErtsDrvEventState *state;
 
984
 
 
985
        erts_smp_mtx_lock(fd_mtx(fd));
 
986
 
922
987
#ifdef ERTS_SYS_CONTINOUS_FD_NUMBERS
923
988
        state = &drv_ev_state[ (int) fd];
924
989
#else
925
990
        state = hash_get_drv_ev_state(fd);
926
 
        if (state == NULL) {
927
 
            continue;
 
991
        if (!state) {
 
992
            goto next_pollres;
928
993
        }
929
994
#endif
930
995
 
931
 
        if (state->flags & ERTS_EV_FLG_IGNORE)
932
 
            continue;
 
996
        /* Skip this fd if it was removed from pollset */
 
997
        if (is_removed(state)) {
 
998
            goto next_pollres;
 
999
        }
933
1000
 
934
1001
        switch (state->type) {
935
1002
        case ERTS_EV_TYPE_DRV_SEL: { /* Requested via driver_select()... */
950
1017
                 */ 
951
1018
                if ((revents & ERTS_POLL_EV_IN)
952
1019
                    || (!(revents & ERTS_POLL_EV_OUT)
953
 
                        && state->events & ERTS_POLL_EV_IN))
 
1020
                        && state->events & ERTS_POLL_EV_IN)) {
954
1021
                    iready(state->driver.select->inport, state);
955
 
                else if (state->events & ERTS_POLL_EV_OUT)
 
1022
                }
 
1023
                else if (state->events & ERTS_POLL_EV_OUT) {
956
1024
                    oready(state->driver.select->outport, state);
 
1025
                }
957
1026
            }
958
1027
            else if (revents & (ERTS_POLL_EV_IN|ERTS_POLL_EV_OUT)) {
959
 
                if (revents & ERTS_POLL_EV_OUT)
 
1028
                if (revents & ERTS_POLL_EV_OUT) {
960
1029
                    oready(state->driver.select->outport, state);
 
1030
                }
961
1031
                /* Someone might have deselected input since revents
962
1032
                   was read (true also on the non-smp emulator since
963
1033
                   oready() may have been called); therefore, update
964
1034
                   revents... */
965
1035
                revents &= ~(~state->events & ERTS_POLL_EV_IN);
966
 
                if (revents & ERTS_POLL_EV_IN)
 
1036
                if (revents & ERTS_POLL_EV_IN) {
967
1037
                    iready(state->driver.select->inport, state);
 
1038
                }
968
1039
            }
969
1040
            else if (revents & ERTS_POLL_EV_NVAL) {
970
1041
                bad_fd_in_pollset(state,
1011
1082
        }
1012
1083
        }
1013
1084
 
 
1085
        next_pollres:;
 
1086
#ifdef ERTS_SMP
 
1087
        erts_smp_mtx_unlock(fd_mtx(fd));
 
1088
#endif
1014
1089
    }
1015
1090
 
1016
 
    reset_ignores();
1017
 
 
1018
 
    erts_smp_mtx_unlock(&drv_ev_state_mtx);
 
1091
    erts_smp_atomic_set(&pollset.in_poll_wait, 0);
 
1092
    forget_removed(&pollset);
1019
1093
}
1020
1094
 
1021
1095
static void
1084
1158
}
1085
1159
 
1086
1160
#ifndef ERTS_SYS_CONTINOUS_FD_NUMBERS
1087
 
static HashValue drv_ev_state_hash(void *des)
 
1161
static SafeHashValue drv_ev_state_hash(void *des)
1088
1162
{
1089
 
    return (HashValue) ((ErtsDrvEventState *) des)->fd;
 
1163
    SafeHashValue val = (SafeHashValue) ((ErtsDrvEventState *) des)->fd;
 
1164
    return val ^ (val >> 8);  /* Good enough for aligned pointer values? */
1090
1165
}
1091
1166
 
1092
1167
static int drv_ev_state_cmp(void *des1, void *des2)
1098
1173
static void *drv_ev_state_alloc(void *des_tmpl)
1099
1174
{
1100
1175
    ErtsDrvEventState *evstate;
 
1176
    erts_smp_spin_lock(&state_prealloc_lock);
1101
1177
    if (state_prealloc_first == NULL) {
 
1178
        erts_smp_spin_unlock(&state_prealloc_lock);
1102
1179
        evstate = (ErtsDrvEventState *) 
1103
1180
            erts_alloc(ERTS_ALC_T_DRV_EV_STATE, sizeof(ErtsDrvEventState));
1104
1181
    } else {
1105
1182
        evstate = state_prealloc_first;
1106
1183
        state_prealloc_first = (ErtsDrvEventState *) evstate->hb.next;
1107
1184
        --num_state_prealloc;
 
1185
        erts_smp_spin_unlock(&state_prealloc_lock);
1108
1186
    }
1109
1187
    /* XXX: Already valid data if prealloced, could ignore template! */
1110
1188
    *evstate = *((ErtsDrvEventState *) des_tmpl);
1114
1192
 
1115
1193
static void drv_ev_state_free(void *des)
1116
1194
{
1117
 
    ((ErtsDrvEventState *) des)->hb.next = (struct hash_bucket *) state_prealloc_first;
 
1195
    erts_smp_spin_lock(&state_prealloc_lock);
 
1196
    ((ErtsDrvEventState *) des)->hb.next = &state_prealloc_first->hb;
1118
1197
    state_prealloc_first = (ErtsDrvEventState *) des;
1119
1198
    ++num_state_prealloc;
 
1199
    erts_smp_spin_unlock(&state_prealloc_lock);
1120
1200
}
1121
1201
#endif
1122
1202
 
1123
1203
void
1124
1204
ERTS_CIO_EXPORT(erts_init_check_io)(void)
1125
1205
{
1126
 
    init_fd_list_alloc();
1127
 
    ignored_list = NULL;
1128
 
    erts_smp_atomic_init(&in_poll_wait, 0);
 
1206
    erts_smp_atomic_init(&pollset.in_poll_wait, 0);
1129
1207
    ERTS_CIO_POLL_INIT();
 
1208
    pollset.ps = ERTS_CIO_NEW_POLLSET();
 
1209
 
 
1210
#ifdef ERTS_SMP
 
1211
    init_removed_fd_alloc();
 
1212
    pollset.removed_list = NULL;
 
1213
    erts_smp_spinlock_init(&pollset.removed_list_lock,
 
1214
                           "pollset_rm_list");
 
1215
    {
 
1216
        int i;
 
1217
        for (i=0; i<DRV_EV_STATE_LOCK_CNT; i++) {
 
1218
            erts_smp_mtx_init(&drv_ev_state_locks[i].lck, "drv_ev_state");
 
1219
        }
 
1220
    }
 
1221
#endif
1130
1222
#ifdef ERTS_SYS_CONTINOUS_FD_NUMBERS
1131
1223
    max_fds = ERTS_CIO_POLL_MAX_FDS();
1132
 
#endif
1133
 
    pollset = ERTS_CIO_NEW_POLLSET();
1134
 
    erts_smp_mtx_init(&drv_ev_state_mtx, "drv_ev_state");
1135
 
#ifdef ERTS_SYS_CONTINOUS_FD_NUMBERS
1136
 
    drv_ev_state_len = 0;
 
1224
    erts_smp_atomic_init(&drv_ev_state_len, 0);
1137
1225
    drv_ev_state = NULL;
 
1226
    erts_smp_mtx_init(&drv_ev_state_grow_lock, "drv_ev_state_grow");
1138
1227
#else
1139
1228
    {
1140
 
        HashFunctions hf;
 
1229
        SafeHashFunctions hf;
1141
1230
        hf.hash = &drv_ev_state_hash;
1142
1231
        hf.cmp = &drv_ev_state_cmp;
1143
1232
        hf.alloc = &drv_ev_state_alloc;
1144
1233
        hf.free = &drv_ev_state_free;
1145
1234
        num_state_prealloc = 0;
1146
1235
        state_prealloc_first = NULL;
 
1236
        erts_smp_spinlock_init(&state_prealloc_lock,"state_prealloc");
1147
1237
 
1148
 
        /* On windows, since io is not initiated, the ERTS_CIO_POLL_MAX_FDS() will return 
1149
 
           1024 unconditionally at this point, but the hash table grows if needed, so that's 
1150
 
           not a problem */
1151
 
        hash_init(ERTS_ALC_T_DRV_EV_STATE, &drv_ev_state_tab, "drv_ev_state_tab", 
1152
 
                  ERTS_CIO_POLL_MAX_FDS(), hf);
 
1238
        safe_hash_init(ERTS_ALC_T_DRV_EV_STATE, &drv_ev_state_tab, "drv_ev_state_tab", 
 
1239
                       DRV_EV_STATE_HTAB_SIZE, hf);
1153
1240
    }
1154
1241
#endif
1155
1242
}
1160
1247
#ifdef  ERTS_SYS_CONTINOUS_FD_NUMBERS
1161
1248
    return max_fds;
1162
1249
#else
1163
 
    return erts_poll_max_fds();
 
1250
    return ERTS_POLL_EXPORT(erts_poll_max_fds)();
1164
1251
#endif
1165
1252
}
1166
1253
 
1169
1256
{
1170
1257
    Uint res;
1171
1258
    ErtsPollInfo pi;
1172
 
    erts_smp_mtx_lock(&drv_ev_state_mtx);
1173
 
    ERTS_CIO_POLL_INFO(pollset, &pi);
 
1259
    ERTS_CIO_POLL_INFO(pollset.ps, &pi);
1174
1260
    res = pi.memory_size;
1175
1261
#ifdef ERTS_SYS_CONTINOUS_FD_NUMBERS
1176
 
    res += sizeof(ErtsDrvEventState)*drv_ev_state_len;
 
1262
    res += sizeof(ErtsDrvEventState) * erts_smp_atomic_read(&drv_ev_state_len);
1177
1263
#else
1178
 
    res += hash_table_sz(&drv_ev_state_tab);
 
1264
    res += safe_hash_table_sz(&drv_ev_state_tab);
1179
1265
    {
1180
 
        HashInfo hi;
1181
 
        hash_get_info(&hi, &drv_ev_state_tab);
 
1266
        SafeHashInfo hi;
 
1267
        safe_hash_get_info(&hi, &drv_ev_state_tab);
1182
1268
        res += hi.objs * sizeof(ErtsDrvEventState);
1183
1269
    }
 
1270
    erts_smp_spin_lock(&state_prealloc_lock);
1184
1271
    res += num_state_prealloc * sizeof(ErtsDrvEventState);
 
1272
    erts_smp_spin_unlock(&state_prealloc_lock);
1185
1273
#endif
1186
 
 
1187
 
    erts_smp_mtx_unlock(&drv_ev_state_mtx);
1188
1274
    return res;
1189
1275
}
1190
1276
 
1197
1283
    Sint i;
1198
1284
    ErtsPollInfo pi;
1199
1285
    
1200
 
    erts_smp_mtx_lock(&drv_ev_state_mtx);
1201
 
    ERTS_CIO_POLL_INFO(pollset, &pi);
 
1286
    ERTS_CIO_POLL_INFO(pollset.ps, &pi);
1202
1287
    memory_size = pi.memory_size;
1203
1288
#ifdef ERTS_SYS_CONTINOUS_FD_NUMBERS
1204
 
    memory_size += sizeof(ErtsDrvEventState)*drv_ev_state_len;
 
1289
    memory_size += sizeof(ErtsDrvEventState) * erts_smp_atomic_read(&drv_ev_state_len);
1205
1290
#else
1206
 
    memory_size += hash_table_sz(&drv_ev_state_tab);
 
1291
    memory_size += safe_hash_table_sz(&drv_ev_state_tab);
1207
1292
    {
1208
 
        HashInfo hi;
1209
 
        hash_get_info(&hi, &drv_ev_state_tab);
 
1293
        SafeHashInfo hi;
 
1294
        safe_hash_get_info(&hi, &drv_ev_state_tab);
1210
1295
        memory_size += hi.objs * sizeof(ErtsDrvEventState);
1211
1296
    }
 
1297
    erts_smp_spin_lock(&state_prealloc_lock);
1212
1298
    memory_size += num_state_prealloc * sizeof(ErtsDrvEventState);
 
1299
    erts_smp_spin_unlock(&state_prealloc_lock);
1213
1300
#endif
1214
 
    erts_smp_mtx_unlock(&drv_ev_state_mtx);
1215
1301
 
1216
1302
    hpp = NULL;
1217
1303
    szp = &sz;
1336
1422
#if defined(HAVE_FSTAT) && !defined(NO_FSTAT_ON_SYS_FD_TYPE)
1337
1423
    struct stat stat_buf;
1338
1424
#endif
1339
 
    
 
1425
 
1340
1426
#ifdef ERTS_SYS_CONTINOUS_FD_NUMBERS
1341
1427
    if (state->events || ep_events) {
1342
1428
        if (ep_events & ERTS_POLL_EV_NVAL) {
1348
1434
            counters->used_fds++;
1349
1435
#else
1350
1436
    if (state->events) {
1351
 
        counters->used_fds++;
 
1437
        counters->used_fds++;
1352
1438
#endif
1353
1439
        
1354
1440
        erts_printf("fd=%d ", (int) fd);
1405
1491
#endif
1406
1492
#ifdef S_ISXATTR
1407
1493
            if (S_ISXATTR(stat_buf.st_mode))
1408
 
                erts_printf("xattr ");
 
1494
                erts_printf("xattr ");
1409
1495
            else
1410
1496
#endif
1411
 
                erts_printf("unknown ");
 
1497
                erts_printf("unknown ");
1412
1498
        }
1413
1499
#else
1414
1500
        erts_printf("type=unknown ");
1552
1638
ERTS_CIO_EXPORT(erts_check_io_debug)(void)
1553
1639
{
1554
1640
#ifdef ERTS_SYS_CONTINOUS_FD_NUMBERS
1555
 
    int fd;
 
1641
    int fd, len;
1556
1642
#endif
1557
1643
    IterDebugCounters counters;
1558
1644
    ErtsDrvEventState null_des;
1559
1645
 
1560
1646
    null_des.driver.select = NULL;
1561
1647
    null_des.events = 0;
1562
 
    null_des.flags = 0;
 
1648
    null_des.remove_cnt = 0;
1563
1649
    null_des.type = ERTS_EV_TYPE_NONE;
1564
1650
 
1565
 
    erts_smp_mtx_lock(&drv_ev_state_mtx);
1566
 
 
1567
1651
    erts_printf("--- fds in pollset --------------------------------------\n");
1568
1652
 
 
1653
#ifdef ERTS_SMP
 
1654
# ifdef ERTS_ENABLE_LOCK_CHECK
 
1655
    erts_lc_check_exact(NULL, 0); /* No locks should be locked */
 
1656
# endif
 
1657
    erts_block_system(0); /* stop the world to avoid messy locking */
 
1658
#endif
 
1659
 
1569
1660
#ifdef ERTS_SYS_CONTINOUS_FD_NUMBERS
1570
1661
    counters.epep = erts_alloc(ERTS_ALC_T_TMP, sizeof(ErtsPollEvents)*max_fds);
1571
 
    ERTS_POLL_EXPORT(erts_poll_get_selected_events)(pollset, counters.epep, max_fds);
 
1662
    ERTS_POLL_EXPORT(erts_poll_get_selected_events)(pollset.ps, counters.epep, max_fds);
1572
1663
    counters.internal_fds = 0;
1573
1664
#endif
1574
1665
    counters.used_fds = 0;
1575
1666
    counters.num_errors = 0;
1576
1667
 
1577
1668
#ifdef ERTS_SYS_CONTINOUS_FD_NUMBERS
1578
 
    for (fd = 0; fd < max_fds; fd++) {
1579
 
        ErtsDrvEventState *desp = ((fd < drv_ev_state_len)
1580
 
                                   ? &drv_ev_state[fd]
1581
 
                                   : &null_des);
 
1669
    len = erts_smp_atomic_read(&drv_ev_state_len);
 
1670
    for (fd = 0; fd < len; fd++) {
 
1671
        doit_erts_check_io_debug((void *) &drv_ev_state[fd], (void *) &counters);
 
1672
    }
 
1673
    for ( ; fd < max_fds; fd++) {
1582
1674
        null_des.fd = fd;
1583
 
        doit_erts_check_io_debug((void *) desp, (void *) &counters);
 
1675
        doit_erts_check_io_debug((void *) &null_des, (void *) &counters);
1584
1676
    }
1585
1677
#else
1586
 
    hash_foreach(&drv_ev_state_tab, &doit_erts_check_io_debug, (void *) &counters);
1587
 
#endif
 
1678
    safe_hash_for_each(&drv_ev_state_tab, &doit_erts_check_io_debug, (void *) &counters);
 
1679
#endif
 
1680
 
 
1681
#ifdef ERTS_SMP
 
1682
    erts_release_system();
 
1683
#endif
 
1684
 
1588
1685
    erts_printf("\n");
1589
1686
    erts_printf("used fds=%d\n", counters.used_fds);
1590
1687
#ifdef ERTS_SYS_CONTINOUS_FD_NUMBERS
1595
1692
#ifdef ERTS_SYS_CONTINOUS_FD_NUMBERS
1596
1693
    erts_free(ERTS_ALC_T_TMP, (void *) counters.epep);
1597
1694
#endif
1598
 
    erts_smp_mtx_unlock(&drv_ev_state_mtx);
1599
1695
    return counters.num_errors;
1600
1696
}
 
1697