~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to erts/emulator/beam/time.c

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
76
76
#include "erl_vm.h"
77
77
#include "global.h"
78
78
 
79
 
#define TIW_SIZE 8192           /* timing wheel size (should be a power of 2) */
 
79
#ifdef ERTS_ENABLE_LOCK_CHECK
 
80
#define ASSERT_NO_LOCKED_LOCKS          erts_lc_check_exact(NULL, 0)
 
81
#else
 
82
#define ASSERT_NO_LOCKED_LOCKS
 
83
#endif
 
84
 
 
85
 
 
86
#if defined(ERTS_TIMER_THREAD) || 1
 
87
/* I don't yet know why, but using a mutex instead of a spinlock
 
88
   or spin-based rwlock avoids excessive delays at startup. */
 
89
static erts_smp_rwmtx_t tiw_lock;
 
90
#define tiw_read_lock()         erts_smp_rwmtx_rlock(&tiw_lock)
 
91
#define tiw_read_unlock()       erts_smp_rwmtx_runlock(&tiw_lock)
 
92
#define tiw_write_lock()        erts_smp_rwmtx_rwlock(&tiw_lock)
 
93
#define tiw_write_unlock()      erts_smp_rwmtx_rwunlock(&tiw_lock)
 
94
#define tiw_init_lock()         erts_smp_rwmtx_init(&tiw_lock, "timer_wheel")
 
95
#else
 
96
static erts_smp_rwlock_t tiw_lock;
 
97
#define tiw_read_lock()         erts_smp_read_lock(&tiw_lock)
 
98
#define tiw_read_unlock()       erts_smp_read_unlock(&tiw_lock)
 
99
#define tiw_write_lock()        erts_smp_write_lock(&tiw_lock)
 
100
#define tiw_write_unlock()      erts_smp_write_unlock(&tiw_lock)
 
101
#define tiw_init_lock()         erts_smp_rwlock_init(&tiw_lock, "timer_wheel")
 
102
#endif
 
103
 
 
104
/* BEGIN tiw_lock protected variables 
 
105
**
 
106
** The individual timer cells in tiw are also protected by the same mutex.
 
107
*/
 
108
 
 
109
#ifdef SMALL_MEMORY
 
110
#define TIW_SIZE 8192
 
111
#else
 
112
#define TIW_SIZE 65536          /* timing wheel size (should be a power of 2) */
 
113
#endif
80
114
static ErlTimer** tiw;          /* the timing wheel, allocated in init_time() */
81
115
static Uint tiw_pos;            /* current position in wheel */
82
116
static Uint tiw_nto;            /* number of timeouts in wheel */
83
 
static ErlTimer* tm_list;       /* new timers created while bumping */
 
117
 
 
118
/* END tiw_lock protected variables */
84
119
 
85
120
/* Actual interval time chosen by sys_init_time() */
86
 
static int itime;
87
 
static int bump_lock;  /* set while bumping */
88
 
 
89
 
void
90
 
increment_time(int ticks)
91
 
{
92
 
    do_time += ticks;
93
 
}
94
 
 
95
 
static void
96
 
insert_timer(ErlTimer* p, Uint t)
97
 
{
98
 
    Uint tm;
99
 
    Uint ticks;
100
 
 
101
 
    /* The current slot (tiw_pos) in timing wheel is the next slot to be
102
 
     * be processed. Hence no extra time tick is needed.
103
 
     *
104
 
     * (x + y - 1)/y is precisely the "number of bins" formula.
105
 
     */
106
 
    ticks = (t + itime - 1) / itime;
107
 
    ticks += do_time;           /* Add backlog of unprocessed time */
108
 
    
109
 
    /* calculate slot */
110
 
    tm = (ticks + tiw_pos) % TIW_SIZE;
111
 
    p->slot = (Uint) tm;
112
 
    p->count = (Uint) (ticks / TIW_SIZE);
113
 
  
114
 
    /* insert at head of list at slot */
115
 
    p->next = tiw[tm];
116
 
    tiw[tm] = p;
117
 
    tiw_nto++;
118
 
}
119
 
 
120
 
void
121
 
bump_timer(void)
 
121
static int itime; /* Constant after init */
 
122
 
 
123
#if defined(ERTS_TIMER_THREAD)
 
124
static SysTimeval time_start;   /* start of current time interval */
 
125
static long ticks_end;          /* time_start+ticks_end == time_wakeup */
 
126
static long ticks_latest;       /* delta from time_start at latest time update*/
 
127
 
 
128
static ERTS_INLINE long time_gettimeofday(SysTimeval *now)
 
129
{
 
130
    long elapsed;
 
131
 
 
132
    sys_gettimeofday(now);
 
133
    now->tv_usec = 1000 * (now->tv_usec / 1000); /* ms resolution */
 
134
    elapsed = (1000 * (now->tv_sec - time_start.tv_sec) +
 
135
               (now->tv_usec - time_start.tv_usec) / 1000);
 
136
    // elapsed /= CLOCK_RESOLUTION;
 
137
    return elapsed;
 
138
}
 
139
 
 
140
static long do_time_update(void)
 
141
{
 
142
    SysTimeval now;
 
143
    long elapsed;
 
144
 
 
145
    elapsed = time_gettimeofday(&now);
 
146
    ticks_latest = elapsed;
 
147
    return elapsed;
 
148
}
 
149
 
 
150
static ERTS_INLINE long do_time_read(void)
 
151
{
 
152
    return ticks_latest;
 
153
}
 
154
 
 
155
static long do_time_reset(void)
 
156
{
 
157
    SysTimeval now;
 
158
    long elapsed;
 
159
 
 
160
    elapsed = time_gettimeofday(&now);
 
161
    time_start = now;
 
162
    ticks_end = LONG_MAX;
 
163
    ticks_latest = 0;
 
164
    return elapsed;
 
165
}
 
166
 
 
167
static ERTS_INLINE void do_time_init(void)
 
168
{
 
169
    (void)do_time_reset();
 
170
}
 
171
 
 
172
#else
 
173
erts_smp_atomic_t do_time;      /* set at clock interrupt */
 
174
static ERTS_INLINE long do_time_read(void) { return erts_smp_atomic_read(&do_time); }
 
175
static ERTS_INLINE long do_time_update(void) { return do_time_read(); }
 
176
static ERTS_INLINE void do_time_init(void) { erts_smp_atomic_init(&do_time, 0L); }
 
177
#endif
 
178
 
 
179
/* get the time (in units of itime) to the next timeout,
 
180
   or -1 if there are no timeouts                     */
 
181
 
 
182
static int next_time_internal(void) /* PRE: tiw_lock taken by caller */
 
183
{
 
184
    int i, tm, nto;
 
185
    unsigned int min;
 
186
    ErlTimer* p;
 
187
    long dt;
 
188
  
 
189
    if (tiw_nto == 0)
 
190
        return -1;      /* no timeouts in wheel */
 
191
  
 
192
    /* start going through wheel to find next timeout */
 
193
    tm = nto = 0;
 
194
    min = (unsigned int) -1;    /* max unsigned int */
 
195
    i = tiw_pos;
 
196
    do {
 
197
        p = tiw[i];
 
198
        while (p != NULL) {
 
199
            nto++;
 
200
            if (p->count == 0) {
 
201
                /* found next timeout */
 
202
                dt = do_time_read();
 
203
                return ((tm >= dt) ? (tm - dt) : 0);
 
204
            } else {
 
205
                /* keep shortest time in 'min' */
 
206
                if (tm + p->count*TIW_SIZE < min)
 
207
                    min = tm + p->count*TIW_SIZE;
 
208
            }
 
209
            p = p->next;
 
210
        }
 
211
        /* when we have found all timeouts the shortest time will be in min */
 
212
        if (nto == tiw_nto) break;
 
213
        tm++;
 
214
        i = (i + 1) % TIW_SIZE;
 
215
    } while (i != tiw_pos);
 
216
    dt = do_time_read();
 
217
    return ((min >= dt) ? (min - dt) : 0);
 
218
}
 
219
 
 
220
#if !defined(ERTS_TIMER_THREAD)
 
221
/* Private export to erl_time_sup.c */
 
222
int next_time(void)
 
223
{
 
224
    int ret;
 
225
 
 
226
    tiw_write_lock();
 
227
    (void)do_time_update();
 
228
    ret = next_time_internal();
 
229
    tiw_write_unlock();
 
230
    return ret;
 
231
}
 
232
#endif
 
233
 
 
234
static ERTS_INLINE void bump_timer_internal(long dt) /* PRE: tiw_lock is write-locked */
122
235
{
123
236
    Uint keep_pos;
124
237
    Uint count;
125
 
    ErlTimer* p;
126
 
    ErlTimer** prev;
127
 
    Uint dtime = do_time;  /* local copy */
 
238
    ErlTimer *p, **prev, *timeout_head, **timeout_tail;
 
239
    Uint dtime = (unsigned long)dt;  
128
240
 
129
 
    do_time = 0;
130
241
    /* no need to bump the position if there aren't any timeouts */
131
242
    if (tiw_nto == 0) {
 
243
        tiw_write_unlock();
132
244
        return;
133
245
    }
134
246
 
135
 
    bump_lock = 1; /* avoid feedback loops in timeout proc */
136
 
 
137
247
    /* if do_time > TIW_SIZE we want to go around just once */
138
248
    count = (Uint)(dtime / TIW_SIZE) + 1;
139
249
    keep_pos = (tiw_pos + dtime) % TIW_SIZE;
140
250
    if (dtime > TIW_SIZE) dtime = TIW_SIZE;
141
251
  
 
252
    timeout_head = NULL;
 
253
    timeout_tail = &timeout_head;
142
254
    while (dtime > 0) {
143
255
        /* this is to decrease the counters with the right amount */
144
256
        /* when dtime >= TIW_SIZE */
149
261
                *prev = p->next;        /* Remove from list */
150
262
                tiw_nto--;
151
263
                p->next = NULL;
152
 
                p->slot = 0;
153
 
                p->active = 0;
154
 
                (*p->timeout)(p->arg);  /* call timeout callback */
 
264
                p->active = 0;          /* Make sure cancel callback
 
265
                                           isn't called */
 
266
                *timeout_tail = p;      /* Insert in timeout queue */
 
267
                timeout_tail = &p->next;
155
268
            }
156
269
            else {
157
270
                /* no timeout, just decrease counter */
162
275
        tiw_pos = (tiw_pos + 1) % TIW_SIZE;
163
276
        dtime--;
164
277
    }
165
 
    bump_lock = 0;
166
278
    tiw_pos = keep_pos;
167
 
 
168
 
    /* do_time should be 0 during timeout/set_timer feedback 
169
 
     ** tiw_pos is also updated before inserting new timers 
170
 
     */
171
 
    if ((p = tm_list) != NULL) {
172
 
        tm_list = NULL;
173
 
        while (p != NULL) {
174
 
            ErlTimer* p_next = p->next;
175
 
            insert_timer(p, p->count);
176
 
            p = p_next;
177
 
        }
 
279
    
 
280
    tiw_write_unlock();
 
281
    
 
282
    /* Call timedout timers callbacks */
 
283
    while (timeout_head) {
 
284
        p = timeout_head;
 
285
        timeout_head = p->next;
 
286
        /* Here comes hairy use of the timer fields!
 
287
         * They are reset without having the lock.
 
288
         * It is assumed that no code but this will
 
289
         * accesses any field until the ->timeout
 
290
         * callback is called.
 
291
         */
 
292
        p->next = NULL;
 
293
        p->slot = 0;
 
294
        (*p->timeout)(p->arg);
178
295
    }
179
296
}
180
297
 
 
298
#if defined(ERTS_TIMER_THREAD)
 
299
static void timer_thread_bump_timer(void)
 
300
{
 
301
    tiw_write_lock();
 
302
    bump_timer_internal(do_time_reset());
 
303
}
 
304
#else
 
305
void bump_timer(long dt) /* dt is value from do_time */
 
306
{
 
307
    tiw_write_lock();
 
308
    bump_timer_internal(dt);
 
309
}
 
310
#endif
 
311
 
181
312
Uint
182
313
erts_timer_wheel_memory_size(void)
183
314
{
184
315
    return (Uint) TIW_SIZE * sizeof(ErlTimer*);
185
316
}
186
317
 
 
318
#if defined(ERTS_TIMER_THREAD)
 
319
static struct erts_iwait *timer_thread_iwait;
 
320
 
 
321
static int timer_thread_setup_delay(SysTimeval *rem_time)
 
322
{
 
323
    long elapsed;
 
324
    int ticks;
 
325
 
 
326
    tiw_write_lock();
 
327
    elapsed = do_time_update();
 
328
    ticks = next_time_internal();
 
329
    if (ticks == -1)    /* timer queue empty */
 
330
        ticks = 100*1000*1000;
 
331
    if (elapsed > ticks)
 
332
        elapsed = ticks;
 
333
    ticks -= elapsed;
 
334
    //ticks *= CLOCK_RESOLUTION;
 
335
    rem_time->tv_sec = ticks / 1000;
 
336
    rem_time->tv_usec = 1000 * (ticks % 1000);
 
337
    ticks_end = ticks;
 
338
    tiw_write_unlock();
 
339
    return ticks;
 
340
}
 
341
 
 
342
static void *timer_thread_start(void *ignore)
 
343
{
 
344
    SysTimeval delay;
 
345
 
 
346
#ifdef ERTS_ENABLE_LOCK_CHECK
 
347
    erts_lc_set_thread_name("timer");
 
348
#endif
 
349
    erts_register_blockable_thread();
 
350
 
 
351
    for(;;) {
 
352
        if (timer_thread_setup_delay(&delay)) {
 
353
            erts_smp_activity_begin(ERTS_ACTIVITY_WAIT, NULL, NULL, NULL);
 
354
            ASSERT_NO_LOCKED_LOCKS;
 
355
            erts_iwait_wait(timer_thread_iwait, &delay);
 
356
            ASSERT_NO_LOCKED_LOCKS;
 
357
            erts_smp_activity_end(ERTS_ACTIVITY_WAIT, NULL, NULL, NULL);
 
358
        }
 
359
        else
 
360
            erts_smp_chk_system_block(NULL, NULL, NULL);
 
361
        timer_thread_bump_timer();
 
362
        ASSERT_NO_LOCKED_LOCKS;
 
363
    }
 
364
    /*NOTREACHED*/
 
365
    return NULL;
 
366
}
 
367
 
 
368
static ERTS_INLINE void timer_thread_post_insert(Uint ticks)
 
369
{
 
370
    if ((Sint)ticks < ticks_end)
 
371
        erts_iwait_interrupt(timer_thread_iwait);
 
372
}
 
373
 
 
374
static void timer_thread_init(void)
 
375
{
 
376
    erts_tid_t tid;
 
377
 
 
378
    timer_thread_iwait = erts_iwait_init();
 
379
    erts_thr_create(&tid, timer_thread_start, NULL, 1);
 
380
}
 
381
 
 
382
#else
 
383
static ERTS_INLINE void timer_thread_post_insert(Uint ticks) { }
 
384
static ERTS_INLINE void timer_thread_init(void) { }
 
385
#endif
 
386
 
187
387
/* this routine links the time cells into a free list at the start
188
388
   and sets the time queue as empty */
189
389
void
191
391
{
192
392
    int i;
193
393
 
 
394
    tiw_init_lock();
 
395
 
194
396
    tiw = (ErlTimer**) erts_alloc(ERTS_ALC_T_TIMER_WHEEL,
195
397
                                  TIW_SIZE * sizeof(ErlTimer*));
196
398
    for(i = 0; i < TIW_SIZE; i++)
197
399
        tiw[i] = NULL;
198
 
    do_time = tiw_pos = tiw_nto = 0;
199
 
    tm_list = NULL;
200
 
    bump_lock = 0;
 
400
    do_time_init();
 
401
    tiw_pos = tiw_nto = 0;
201
402
 
202
403
    /* system dependent init */
203
404
    itime = erts_init_time_sup();
 
405
 
 
406
    timer_thread_init();
204
407
}
205
408
 
206
409
/*
207
410
** Insert a process into the time queue, with a timeout 't'
208
411
*/
 
412
static void
 
413
insert_timer(ErlTimer* p, Uint t)
 
414
{
 
415
    Uint tm;
 
416
    Uint ticks;
 
417
 
 
418
    /* The current slot (tiw_pos) in timing wheel is the next slot to be
 
419
     * be processed. Hence no extra time tick is needed.
 
420
     *
 
421
     * (x + y - 1)/y is precisely the "number of bins" formula.
 
422
     */
 
423
    ticks = (t + itime - 1) / itime;
 
424
    ticks += do_time_update(); /* Add backlog of unprocessed time */
 
425
    
 
426
    /* calculate slot */
 
427
    tm = (ticks + tiw_pos) % TIW_SIZE;
 
428
    p->slot = (Uint) tm;
 
429
    p->count = (Uint) (ticks / TIW_SIZE);
 
430
  
 
431
    /* insert at head of list at slot */
 
432
    p->next = tiw[tm];
 
433
    tiw[tm] = p;
 
434
    tiw_nto++;
 
435
 
 
436
    timer_thread_post_insert(ticks);
 
437
}
 
438
 
209
439
void
210
440
erl_set_timer(ErlTimer* p, ErlTimeoutProc timeout, ErlCancelProc cancel,
211
441
              void* arg, Uint t)
212
442
{
213
 
    if (p->active)  /* XXX assert ? */
 
443
    erts_deliver_time();
 
444
    tiw_write_lock();
 
445
    if (p->active) { /* XXX assert ? */
 
446
        tiw_write_unlock();
214
447
        return;
 
448
    }
215
449
    p->timeout = timeout;
216
450
    p->cancel = cancel;
217
451
    p->arg = arg;
218
452
    p->active = 1;
219
 
    if (bump_lock) {
220
 
        p->next = tm_list;
221
 
        tm_list = p;
222
 
        p->count = t;  /* time is saved here used by bump */
223
 
    } else {
224
 
        insert_timer(p, t);
225
 
    }
 
453
    insert_timer(p, t);
 
454
    tiw_write_unlock();
 
455
#if defined(ERTS_SMP) && !defined(ERTS_TIMER_THREAD)
 
456
    erts_wake_io_thread();
 
457
#endif
226
458
}
227
459
 
228
460
void
231
463
    ErlTimer *tp;
232
464
    ErlTimer **prev;
233
465
 
234
 
    if (!p->active)  /* allow repeated cancel (drivers) */
 
466
    tiw_write_lock();
 
467
    if (!p->active) { /* allow repeated cancel (drivers) */
 
468
        tiw_write_unlock();
235
469
        return;
 
470
    }
236
471
    /* find p in linked list at slot p->slot and remove it */
237
472
    prev = &tiw[p->slot];
238
473
    while ((tp = *prev) != NULL) {
242
477
            p->next = NULL;
243
478
            p->slot = p->count = 0;
244
479
            p->active = 0;
245
 
            if (p->cancel != NULL)
 
480
            if (p->cancel != NULL) {
 
481
                tiw_write_unlock();
246
482
                (*p->cancel)(p->arg);
247
 
            break;
248
 
        }
249
 
        prev = &tp->next;
250
 
    }
251
 
}
252
 
 
253
 
/* get the time (in units of itime) to the next timeout,
254
 
   or -1 if there are no timeouts                     */
255
 
 
256
 
int next_time()
257
 
{
258
 
    int i, tm, nto;
259
 
    unsigned int min;
260
 
    ErlTimer* p;
261
 
  
262
 
    if (tiw_nto == 0) return -1;        /* no timeouts in wheel */
263
 
  
264
 
    /* start going through wheel to find next timeout */
265
 
    tm = nto = 0;
266
 
    min = (unsigned int) -1;    /* max unsigned int */
267
 
    i = tiw_pos;
268
 
    do {
269
 
        p = tiw[i];
270
 
        while (p != NULL) {
271
 
            nto++;
272
 
            if (p->count == 0) {
273
 
                /* found next timeout */
274
 
                return ((tm >= do_time) ? (tm - do_time) : 0);
275
483
            } else {
276
 
                /* keep shortest time in 'min' */
277
 
                if (tm + p->count*TIW_SIZE < min)
278
 
                    min = tm + p->count*TIW_SIZE;
 
484
                tiw_write_unlock();
279
485
            }
280
 
            p = p->next;
 
486
            return;
 
487
        } else {
 
488
            prev = &tp->next;
281
489
        }
282
 
        /* when we have found all timeouts the shortest time will be in min */
283
 
        if (nto == tiw_nto) break;
284
 
        tm++;
285
 
        i = (i + 1) % TIW_SIZE;
286
 
    } while (i != tiw_pos);
287
 
    return ((min >= do_time) ? (min - do_time) : 0);
 
490
    }
 
491
    tiw_write_unlock();
288
492
}
289
493
 
290
494
/*
297
501
time_left(ErlTimer *p)
298
502
{
299
503
    Uint left;
300
 
 
301
 
    if (!p->active)
 
504
    long dt;
 
505
 
 
506
    tiw_read_lock();
 
507
 
 
508
    if (!p->active) {
 
509
        tiw_read_unlock();
302
510
        return 0;
 
511
    }
303
512
 
304
513
    if (p->slot < tiw_pos)
305
514
        left = (p->count + 1) * TIW_SIZE + p->slot - tiw_pos;
306
515
    else
307
516
        left = p->count * TIW_SIZE + p->slot - tiw_pos;
308
 
    if (left < do_time)
 
517
    dt = do_time_read();
 
518
    if (left < dt)
309
519
        left = 0;
310
520
    else
311
 
        left -= do_time;
 
521
        left -= dt;
 
522
 
 
523
    tiw_read_unlock();
312
524
 
313
525
    return left * itime;
314
526
}
320
532
    int i;
321
533
    ErlTimer* p;
322
534
  
 
535
    tiw_read_lock();
 
536
 
323
537
    /* print the whole wheel, starting at the current position */
324
 
    erl_printf(COUT, "\ntiw_pos = %d tiw_nto %d\n\r", tiw_pos, tiw_nto);
 
538
    erts_printf("\ntiw_pos = %d tiw_nto %d\n", tiw_pos, tiw_nto);
325
539
    i = tiw_pos;
326
540
    if (tiw[i] != NULL) {
327
 
        erl_printf(COUT, "%d:\n\r", i);
 
541
        erts_printf("%d:\n", i);
328
542
        for(p = tiw[i]; p != NULL; p = p->next) {
329
 
            erl_printf(COUT, " (count %d, slot %d)\n\r",
330
 
                       p->count, p->slot);
 
543
            erts_printf(" (count %d, slot %d)\n",
 
544
                        p->count, p->slot);
331
545
        }
332
546
    }
333
547
    for(i = (i+1)%TIW_SIZE; i != tiw_pos; i = (i+1)%TIW_SIZE) {
334
548
        if (tiw[i] != NULL) {
335
 
            erl_printf(COUT, "%d:\n\r", i);
 
549
            erts_printf("%d:\n", i);
336
550
            for(p = tiw[i]; p != NULL; p = p->next) {
337
 
                erl_printf(COUT, " (count %d, slot %d)\n\r",
338
 
                           p->count, p->slot);
 
551
                erts_printf(" (count %d, slot %d)\n",
 
552
                            p->count, p->slot);
339
553
            }
340
554
        }
341
555
    }
 
556
 
 
557
    tiw_read_unlock();
342
558
}
343
559
 
344
560
#endif /* DEBUG */