~statik/ubuntu/maverick/erlang/erlang-merge-testing

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-01 10:14:38 UTC
  • mfrom: (3.1.4 sid)
  • Revision ID: james.westby@ubuntu.com-20090501101438-6qlr6rsdxgyzrg2z
Tags: 1:13.b-dfsg-2
* Cleaned up patches: removed unneeded patch which helped to support
  different SCTP library versions, made sure that changes for m68k
  architecture applied only when building on this architecture.
* Removed duplicated information from binary packages descriptions.
* Don't require libsctp-dev build-dependency on solaris-i386 architecture
  which allows to build Erlang on Nexenta (thanks to Tim Spriggs for
  the suggestion).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
/* ``The contents of this file are subject to the Erlang Public License,
 
1
/*
 
2
 * %CopyrightBegin%
 
3
 * 
 
4
 * Copyright Ericsson AB 2008-2009. All Rights Reserved.
 
5
 * 
 
6
 * The contents of this file are subject to the Erlang Public License,
2
7
 * Version 1.1, (the "License"); you may not use this file except in
3
8
 * compliance with the License. You should have received a copy of the
4
9
 * Erlang Public License along with this software. If not, it can be
5
 
 * retrieved via the world wide web at http://www.erlang.org/.
 
10
 * retrieved online at http://www.erlang.org/.
6
11
 * 
7
12
 * Software distributed under the License is distributed on an "AS IS"
8
13
 * basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
9
14
 * the License for the specific language governing rights and limitations
10
15
 * under the License.
11
16
 * 
12
 
 * The Initial Developer of the Original Code is Ericsson Utvecklings AB.
13
 
 * Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
14
 
 * AB. All Rights Reserved.''
15
 
 * 
16
 
 *     $Id$
 
17
 * %CopyrightEnd%
17
18
 */
 
19
 
18
20
/*
19
21
 * Description: Statistics for locks.
20
22
 *
40
42
/* globals, dont access these without locks or blocks */
41
43
 
42
44
ethr_mutex lcnt_data_lock;
43
 
 
44
45
erts_lcnt_data_t *erts_lcnt_data;
 
46
Uint16 erts_lcnt_rt_options;
 
47
erts_lcnt_time_t timer_start;
 
48
const char *str_undefined = "undefined";
45
49
 
46
50
static ethr_tsd_key lcnt_thr_data_key;
47
51
static int lcnt_n_thr;
 
52
static erts_lcnt_thread_data_t *lcnt_thread_data[1024]; 
48
53
 
49
54
/* local functions */
50
55
 
57
62
}
58
63
 
59
64
 
60
 
static char* lock_type(Uint16 flag) {
 
65
static char* lcnt_lock_type(Uint16 flag) {
61
66
    switch(flag & ERTS_LCNT_LT_ALL) {
62
67
    case ERTS_LCNT_LT_SPINLOCK:   return "spinlock";
63
68
    case ERTS_LCNT_LT_RWSPINLOCK: return "rw_spinlock";
68
73
    }
69
74
}
70
75
 
 
76
static void lcnt_clear_stats(erts_lcnt_lock_stats_t *stats) {
 
77
    ethr_atomic_set(&stats->tries, 0);
 
78
    ethr_atomic_set(&stats->colls, 0);
 
79
    stats->timer.s  = 0;
 
80
    stats->timer.ns = 0;
 
81
    stats->timer_n  = 0;
 
82
    stats->file     = (char *)str_undefined;
 
83
    stats->line     = 0;
 
84
}
71
85
 
72
86
static void lcnt_time(erts_lcnt_time_t *time) {
 
87
#ifdef HAVE_GETHRTIME
73
88
    SysHrTime hr_time;
74
89
    hr_time  = sys_gethrtime();
75
90
    time->s  = (unsigned long)(hr_time / 1000000000LL);
76
91
    time->ns = (unsigned long)(hr_time - 1000000000LL*time->s);
 
92
#else    
 
93
    SysTimeval tv;
 
94
    sys_gettimeofday(&tv);
 
95
    time->s  = tv.tv_sec;
 
96
    time->ns = tv.tv_usec*1000LL;
 
97
#endif
 
98
}
 
99
 
 
100
static void lcnt_time_diff(erts_lcnt_time_t *d, erts_lcnt_time_t *t1, erts_lcnt_time_t *t0) {
 
101
    long ds;
 
102
    long dns;
 
103
    
 
104
    ds  = t1->s  - t0->s;
 
105
    dns = t1->ns - t0->ns;
 
106
        
 
107
    /* the difference should not be able to get bigger than 1 sec in ns*/
 
108
    
 
109
    if (dns < 0) {
 
110
        ds  -= 1;
 
111
        dns += 1000000000LL;
 
112
    }
 
113
 
 
114
    d->s  = ds;
 
115
    d->ns = dns;
 
116
}
 
117
 
 
118
/* difference d must be positive */
 
119
 
 
120
static void lcnt_time_add(erts_lcnt_time_t *t, erts_lcnt_time_t *d) {
 
121
    unsigned long ngns = 0;
 
122
    
 
123
    t->s  += d->s;
 
124
    t->ns += d->ns;
 
125
 
 
126
    ngns   = t->ns / 1000000000LL;
 
127
    t->ns  = t->ns % 1000000000LL;
 
128
    
 
129
    t->s  += ngns;
77
130
}
78
131
 
79
132
static erts_lcnt_thread_data_t *lcnt_thread_data_alloc(void) {
80
133
    erts_lcnt_thread_data_t *eltd;
81
 
    
 
134
   
82
135
    eltd = (erts_lcnt_thread_data_t*)malloc(sizeof(erts_lcnt_thread_data_t));
83
136
    eltd->timer_set = 0;
 
137
    eltd->lock_in_conflict = 0;
 
138
 
84
139
    eltd->id = lcnt_n_thr++;
85
 
    
 
140
    /* set thread data to array */
 
141
    lcnt_thread_data[eltd->id] = eltd;
 
142
 
86
143
    return eltd;
87
144
88
145
 
96
153
#if 0
97
154
static char* lock_opt(Uint16 flag) {
98
155
    if ((flag & ERTS_LCNT_LO_WRITE) && (flag & ERTS_LCNT_LO_READ)) return "rw";
99
 
    if (flag & ERTS_LCNT_LO_READ      )                            return "r ";
100
 
    if (flag & ERTS_LCNT_LO_WRITE     )                            return " w";
 
156
    if  (flag & ERTS_LCNT_LO_READ )                                return "r ";
 
157
    if  (flag & ERTS_LCNT_LO_WRITE)                                return " w";
101
158
    return "--";
102
159
}
103
160
 
104
 
static void print_colls(erts_lcnt_lock_t *lock, char *action, Uint16 opt) {
105
 
    long r_state, w_state;
106
 
    char buffer[256];
107
 
    erts_lcnt_thread_data_t *eltd = NULL;
108
 
   
109
 
    ethr_atomic_read(&lock->r_state, &r_state);
110
 
    ethr_atomic_read(&lock->w_state, &w_state);
111
 
    
112
 
    eltd = lcnt_get_thread_data();
113
 
    
114
 
    if (eltd) {
115
 
        sprintf(buffer, "[%d/%ld] %s %s:", eltd->id, (long)ethr_self(), action, lock_opt(opt));
116
 
        print_lock(lock, buffer);
117
 
    } else {
118
 
        fprintf(stderr, "A null thread =(\r\n");
119
 
    }
120
 
}
121
 
 
122
 
static void print_lock(erts_lcnt_lock_t *lock, char *action) {
 
161
static void print_lock_x(erts_lcnt_lock_t *lock, Uint16 flag, char *action, char *extra) {
123
162
    long int colls, tries, w_state, r_state;
 
163
    erts_lcnt_lock_stats_t *stats = NULL;
 
164
    
124
165
    float rate;
125
166
    char *type;
126
 
    type = lock_type(lock->flag);
127
 
    ethr_atomic_read(&lock->tries, &tries);
128
 
    ethr_atomic_read(&lock->colls, &colls);
 
167
    int i;
 
168
    
 
169
    type = lcnt_lock_type(lock->flag);
129
170
    ethr_atomic_read(&lock->r_state, &r_state);
130
171
    ethr_atomic_read(&lock->w_state, &w_state);
131
 
    
 
172
 
132
173
    if (tries > 0) rate = (float)(colls/(float)tries)*100;
133
174
    else rate = 0.0f;
134
 
   
135
 
    fprintf(stderr, "%8s [%25s] [type %12s] [r/w state %2ld/%2ld] [tries %9ld] [colls %9ld] [rate %3.3f %%] [acc %ld %ld (%ld)]\r\n", 
136
 
            action, lock->name, type, r_state, w_state, tries, colls, rate, lock->timer_s, lock->timer_ns, lock->timer_n);
 
175
    
 
176
    if (lock->flag & flag) {
 
177
        erts_printf("%20s [%30s] [r/w state %4ld/%4ld] id %T %s\r\n", 
 
178
                action, 
 
179
                lock->name, 
 
180
                r_state, 
 
181
                w_state, 
 
182
                lock->id, 
 
183
                extra);
 
184
        
 
185
        for(i = 0; i < lock->n_stats; i++) {
 
186
            stats = &(lock->stats[i]);
 
187
            ethr_atomic_read(&stats->tries, &tries);
 
188
            ethr_atomic_read(&stats->colls, &colls);
 
189
            fprintf(stderr, "%69s:%5d [tries %9ld] [colls %9ld] [timer_n %8ld] [timer %4ld s %6ld us]\r\n",
 
190
                    stats->file,
 
191
                    stats->line,
 
192
                    tries,
 
193
                    colls,
 
194
                    stats->timer_n,
 
195
                    stats->timer.s,
 
196
                    (unsigned long)stats->timer.ns/1000);
 
197
        }
 
198
        fprintf(stderr, "\r\n");
 
199
    }
 
200
}
 
201
 
 
202
static void print_lock(erts_lcnt_lock_t *lock, char *action) {
 
203
    print_lock_x(lock, ERTS_LCNT_LT_ALL, action, "");
137
204
}
138
205
 
139
206
#endif
140
207
 
 
208
static erts_lcnt_lock_stats_t *lcnt_get_lock_stats(erts_lcnt_lock_t *lock, char *file, unsigned int line) {
 
209
    unsigned int i;
 
210
    erts_lcnt_lock_stats_t *stats = NULL;
 
211
    
 
212
    for (i = 0; i < lock->n_stats; i++) {
 
213
        if ((lock->stats[i].file == file) && (lock->stats[i].line == line)) {
 
214
            return &(lock->stats[i]);
 
215
        }
 
216
    }
 
217
    if (lock->n_stats < ERTS_LCNT_MAX_LOCK_LOCATIONS) {
 
218
        stats = &lock->stats[lock->n_stats];
 
219
        lock->n_stats++;
 
220
 
 
221
        stats->file = file;
 
222
        stats->line = line;
 
223
        return stats;
 
224
    }
 
225
    return &lock->stats[0];
 
226
 
 
227
}
 
228
 
 
229
static void lcnt_update_stats(erts_lcnt_lock_stats_t *stats, int lock_in_conflict, erts_lcnt_time_t *time_wait) {
 
230
    
 
231
    ethr_atomic_inc(&stats->tries);
 
232
 
 
233
    /* beware of trylock */
 
234
    if (lock_in_conflict) ethr_atomic_inc(&stats->colls);
 
235
 
 
236
    if (time_wait) {
 
237
        lcnt_time_add(&(stats->timer), time_wait);
 
238
        stats->timer_n++;
 
239
    }
 
240
}
 
241
 
 
242
/* 
 
243
 * interface 
 
244
 */
 
245
 
141
246
void erts_lcnt_init() {
142
247
    erts_lcnt_thread_data_t *eltd = NULL;
143
248
    
145
250
    if (ethr_mutex_init(&lcnt_data_lock) != 0) abort();
146
251
 
147
252
    /* init tsd */    
148
 
    lcnt_n_thr = 1;    
149
 
    
 
253
    lcnt_n_thr = 0;
 
254
 
150
255
    ethr_tsd_key_create(&lcnt_thr_data_key);
151
256
 
 
257
    lcnt_lock();
 
258
 
 
259
    erts_lcnt_rt_options = ERTS_LCNT_OPT_PROCLOCK;
 
260
    
152
261
    eltd = lcnt_thread_data_alloc();
153
 
    
 
262
 
154
263
    ethr_tsd_set(lcnt_thr_data_key, eltd);
155
264
    
156
 
    lcnt_lock();
157
 
    
158
265
    /* init lcnt structure */
159
266
    erts_lcnt_data = (erts_lcnt_data_t*)malloc(sizeof(erts_lcnt_data_t));
160
267
    erts_lcnt_data->current_locks = erts_lcnt_list_init();
161
268
    erts_lcnt_data->deleted_locks = erts_lcnt_list_init();
162
 
    
 
269
 
163
270
    lcnt_unlock();
 
271
 
 
272
    /* set start timer and zero statistics */
 
273
    erts_lcnt_clear_counters();
164
274
}
165
275
 
166
276
/* list operations */
202
312
    if (tail) {
203
313
        tail->next = lock;
204
314
        lock->prev = tail;
205
 
        lock->next = NULL;
206
315
    } else {
207
 
        /* if the tail is null then head should be null as well. */
208
316
        list->head = lock;
209
317
        lock->prev = NULL;
 
318
        ASSERT(!lock->next);
210
319
    }
 
320
    lock->next = NULL;
211
321
    list->tail = lock;
 
322
    
212
323
    list->n++;
213
324
}
214
325
 
231
342
/* interface to erl_threads.h */
232
343
/* only lock on init and destroy, all others should use atomics */
233
344
void erts_lcnt_init_lock(erts_lcnt_lock_t *lock, char *name, Uint16 flag ) { 
234
 
    erts_lcnt_init_lock_extra(lock, name, flag, am_undefined);
 
345
    erts_lcnt_init_lock_x(lock, name, flag, am_undefined);
235
346
}
236
 
 
237
 
void erts_lcnt_init_lock_extra(erts_lcnt_lock_t *lock, char *name, Uint16 flag, Eterm id) { 
 
347
void erts_lcnt_init_lock_x(erts_lcnt_lock_t *lock, char *name, Uint16 flag, Eterm id) { 
 
348
    int i;
238
349
    lcnt_lock();
 
350
    
239
351
    lock->next = NULL;
240
352
    lock->prev = NULL;
241
353
    lock->flag = flag;
242
354
    lock->name = name;
243
 
    lock->id = id;
244
 
 
245
 
    lcnt_unlock();
 
355
    lock->id   = id;
246
356
 
247
357
    ethr_atomic_init(&lock->r_state, 0);
248
358
    ethr_atomic_init(&lock->w_state, 0);
249
 
    ethr_atomic_init(&lock->tries, 0);
250
 
    ethr_atomic_init(&lock->colls, 0);
251
 
 
252
 
    lock->timer_n  = 0;
253
 
    lock->timer_s  = 0;
254
 
    lock->timer_ns = 0;
255
 
 
256
 
    lcnt_lock();
257
 
  
 
359
    
 
360
#ifdef DEBUG
 
361
    ethr_atomic_init(&lock->flowstate, 0);
 
362
#endif
 
363
    
 
364
    lock->n_stats = 1;
 
365
 
 
366
    for (i = 0; i < ERTS_LCNT_MAX_LOCK_LOCATIONS; i++) {
 
367
        lcnt_clear_stats(&lock->stats[i]);
 
368
    }
258
369
    erts_lcnt_list_insert(erts_lcnt_data->current_locks, lock);
259
370
    
260
371
    lcnt_unlock();
261
 
    
262
372
}
263
373
 
264
374
void erts_lcnt_destroy_lock(erts_lcnt_lock_t *lock) {
287
397
    long r_state = 0, w_state = 0;
288
398
    erts_lcnt_thread_data_t *eltd;
289
399
    
 
400
    if (erts_lcnt_rt_options & ERTS_LCNT_OPT_SUSPEND) return;
 
401
 
 
402
    eltd = lcnt_get_thread_data();
 
403
 
 
404
    ASSERT(eltd);
290
405
    
291
 
    ethr_atomic_inc(&lock->tries);
292
406
    ethr_atomic_read(&lock->w_state, &w_state);
 
407
    
293
408
    if (option & ERTS_LCNT_LO_WRITE) {
294
409
        ethr_atomic_read(&lock->r_state, &r_state);
295
410
        ethr_atomic_inc( &lock->w_state);
297
412
    if (option & ERTS_LCNT_LO_READ) {
298
413
        ethr_atomic_inc( &lock->r_state);
299
414
    }
 
415
    
300
416
    /* we cannot acquire w_lock if either w or r are taken */
301
417
    /* we cannot acquire r_lock if w_lock is taken */   
 
418
    
302
419
    if ((w_state > 0) || (r_state > 0)){
303
 
        ethr_atomic_inc(&lock->colls);
304
 
        eltd = lcnt_get_thread_data();
305
 
        lcnt_time(&eltd->timer);
 
420
        eltd->lock_in_conflict = 1;
 
421
        if (eltd->timer_set == 0) lcnt_time(&eltd->timer);
306
422
        eltd->timer_set++;
307
 
        if (eltd->timer_set > 1) abort();
 
423
    } else {
 
424
        eltd->lock_in_conflict = 0;
308
425
    }
309
 
    
310
426
}
311
427
 
312
428
void erts_lcnt_lock(erts_lcnt_lock_t *lock) {
313
429
    long w_state;
314
430
    erts_lcnt_thread_data_t *eltd;
315
 
    ethr_atomic_inc(&lock->tries);
316
 
    /* perhaps a lock here instead of atomic? */
 
431
    
 
432
    if (erts_lcnt_rt_options & ERTS_LCNT_OPT_SUSPEND) return;
 
433
 
317
434
    ethr_atomic_read(&lock->w_state, &w_state);
318
435
    ethr_atomic_inc( &lock->w_state);
319
 
    
 
436
 
 
437
    eltd = lcnt_get_thread_data();
 
438
 
 
439
    ASSERT(eltd);
 
440
 
320
441
    if (w_state > 0) {
321
 
        ethr_atomic_inc(&lock->colls);
322
 
        eltd = lcnt_get_thread_data();
323
 
        lcnt_time(&eltd->timer);
 
442
        eltd->lock_in_conflict = 1;
 
443
        /* only set the timer if nobody else has it
 
444
         * This should only happen when proc_locks aquires several locks
 
445
         * 'atomicly'. All other locks will block the thread if w_state > 0
 
446
         * i.e. locked.
 
447
         */
 
448
        if (eltd->timer_set == 0) lcnt_time(&eltd->timer);
324
449
        eltd->timer_set++;
325
 
        if (eltd->timer_set > 1) abort();
 
450
 
 
451
    } else {
 
452
        eltd->lock_in_conflict = 0;
326
453
    }
327
 
 
328
 
        
329
 
}
330
 
 
 
454
}
 
455
 
 
456
/* if a lock wasn't really a lock operation, bad bad process locks */
 
457
 
 
458
void erts_lcnt_lock_unaquire(erts_lcnt_lock_t *lock) {
 
459
    /* should check if this thread was "waiting" */
 
460
    
 
461
    if (erts_lcnt_rt_options & ERTS_LCNT_OPT_SUSPEND) return;
 
462
 
 
463
    ethr_atomic_dec( &lock->w_state);
 
464
}
 
465
 
 
466
/* erts_lcnt_lock_post
 
467
 * used when we get a lock (i.e. directly after a lock operation)
 
468
 * if the timer was set then we had to wait for the lock
 
469
 * lock_post will calculate the wait time.
 
470
 */
331
471
void erts_lcnt_lock_post(erts_lcnt_lock_t *lock) {
 
472
    erts_lcnt_lock_post_x(lock, (char*)str_undefined, 0);
 
473
}
 
474
 
 
475
void erts_lcnt_lock_post_x(erts_lcnt_lock_t *lock, char *file, unsigned int line) {
332
476
    erts_lcnt_thread_data_t *eltd;
333
477
    erts_lcnt_time_t timer;
334
 
    long ds, dns;
 
478
    erts_lcnt_time_t time_wait;
 
479
    erts_lcnt_lock_stats_t *stats;
 
480
#ifdef DEBUG
 
481
    long flowstate;
 
482
#endif
 
483
 
 
484
    if (erts_lcnt_rt_options & ERTS_LCNT_OPT_SUSPEND) return;
 
485
    
 
486
#ifdef DEBUG
 
487
    if (!(lock->flag & (ERTS_LCNT_LT_RWMUTEX | ERTS_LCNT_LT_RWSPINLOCK))) {
 
488
        ethr_atomic_read(&lock->flowstate, &flowstate);
 
489
        ASSERT(flowstate == 0);
 
490
        ethr_atomic_inc( &lock->flowstate);
 
491
    }
 
492
#endif
335
493
    
336
494
    eltd = lcnt_get_thread_data();
 
495
    
 
496
    ASSERT(eltd);
 
497
    
 
498
    /* if lock was in conflict, time it */
 
499
        
 
500
    stats = lcnt_get_lock_stats(lock, file, line);
 
501
    
337
502
    if (eltd->timer_set) {
338
503
        lcnt_time(&timer);
339
 
        
340
 
        ds  = timer.s  - eltd->timer.s;
341
 
        dns = timer.ns - eltd->timer.ns;
342
 
        
343
 
        if (dns < 0) {
344
 
            ds  -= 1;
345
 
            dns += 1000000000;
346
 
        }
347
 
        
 
504
 
348
505
        eltd->timer_set--;
349
506
        
350
 
        /* has lock */
351
 
        lock->timer_n  += 1;
352
 
        lock->timer_s  += ds;
353
 
        lock->timer_ns += dns;
354
 
 
355
 
        if (lock->timer_ns >  1000000000) {
356
 
            lock->timer_s  += 1;
357
 
            lock->timer_ns -= 1000000000;
358
 
        }
359
 
 
360
 
        if (eltd->timer_set < 0) abort();
 
507
        lcnt_time_diff(&time_wait, &timer, &(eltd->timer));
 
508
        lcnt_update_stats(stats, eltd->lock_in_conflict, &time_wait);
 
509
        
 
510
        ASSERT(eltd->timer_set >= 0);
 
511
    } else {
 
512
        lcnt_update_stats(stats, eltd->lock_in_conflict, NULL);
361
513
    }
 
514
        
362
515
}
363
516
 
364
517
/* unlock */
365
518
 
366
519
void erts_lcnt_unlock_opt(erts_lcnt_lock_t *lock, Uint16 option) {
 
520
    if (erts_lcnt_rt_options & ERTS_LCNT_OPT_SUSPEND) return;
367
521
    if (option & ERTS_LCNT_LO_WRITE) ethr_atomic_dec(&lock->w_state);
368
522
    if (option & ERTS_LCNT_LO_READ ) ethr_atomic_dec(&lock->r_state);
369
523
}
370
524
 
371
525
void erts_lcnt_unlock(erts_lcnt_lock_t *lock) {
 
526
#ifdef DEBUG
 
527
    long w_state;  
 
528
    long flowstate;
 
529
#endif
 
530
    if (erts_lcnt_rt_options & ERTS_LCNT_OPT_SUSPEND) return;
 
531
#ifdef DEBUG
 
532
    /* flowstate */
 
533
    ethr_atomic_read(&lock->flowstate, &flowstate);
 
534
    ASSERT(flowstate == 1);
 
535
    ethr_atomic_dec( &lock->flowstate);
 
536
    
 
537
    /* write state */
 
538
    ethr_atomic_read(&lock->w_state, &w_state);
 
539
    ASSERT(w_state > 0)
 
540
#endif
372
541
    ethr_atomic_dec(&lock->w_state);
373
542
}
374
543
 
375
544
/* trylock */
376
545
 
377
546
void erts_lcnt_trylock_opt(erts_lcnt_lock_t *lock, int res, Uint16 option) {
 
547
    if (erts_lcnt_rt_options & ERTS_LCNT_OPT_SUSPEND) return;
378
548
    /* Determine lock_state via res instead of state */
379
 
    
380
 
    ethr_atomic_inc(&lock->tries);
381
 
    
382
549
    if (res != EBUSY) {
383
550
        if (option & ERTS_LCNT_LO_WRITE) ethr_atomic_inc(&lock->w_state);
384
551
        if (option & ERTS_LCNT_LO_READ ) ethr_atomic_inc(&lock->r_state);
385
 
    } else ethr_atomic_inc(&lock->colls);
 
552
        lcnt_update_stats(&(lock->stats[0]), 0, NULL);
 
553
    } else {
 
554
        ethr_atomic_inc(&lock->stats[0].tries);
 
555
        ethr_atomic_inc(&lock->stats[0].colls);
 
556
    }
386
557
}
387
558
 
388
 
    
389
 
 
 
559
   
390
560
void erts_lcnt_trylock(erts_lcnt_lock_t *lock, int res) {
391
561
    /* Determine lock_state via res instead of state */
392
 
    
393
 
    ethr_atomic_inc(&lock->tries);
394
 
    if (res != EBUSY) ethr_atomic_inc(&lock->w_state);
395
 
    else ethr_atomic_inc(&lock->colls);
 
562
#ifdef DEBUG
 
563
    long flowstate;
 
564
#endif 
 
565
    if (erts_lcnt_rt_options & ERTS_LCNT_OPT_SUSPEND) return;
 
566
    if (res != EBUSY) {
 
567
        
 
568
#ifdef DEBUG
 
569
        ethr_atomic_read(&lock->flowstate, &flowstate);
 
570
        ASSERT(flowstate == 0);
 
571
        ethr_atomic_inc( &lock->flowstate);
 
572
#endif
 
573
        ethr_atomic_inc(&lock->w_state);
 
574
        
 
575
        lcnt_update_stats(&(lock->stats[0]), 0, NULL);
 
576
 
 
577
    } else {
 
578
        ethr_atomic_inc(&lock->stats[0].tries);
 
579
        ethr_atomic_inc(&lock->stats[0].colls);
 
580
    }
396
581
}
397
582
 
398
583
/* thread operations */
399
584
 
400
 
static void lcnt_thr_init(erts_lcnt_thread_data_t *eltd) {
401
 
    void * (*function)(void *);
 
585
static void *lcnt_thr_init(erts_lcnt_thread_data_t *eltd) {
 
586
    void *(*function)(void *);
402
587
    void *argument;
403
 
    int res;
 
588
    void *res;
404
589
    function = eltd->function;
405
590
    argument = eltd->argument;
406
591
    
407
 
    res = ethr_tsd_set(lcnt_thr_data_key, eltd);
 
592
    ethr_tsd_set(lcnt_thr_data_key, eltd);
408
593
    
409
 
    function(argument);
 
594
    res = (void *)function(argument);
410
595
    free(eltd);
 
596
    return (void *)res;
411
597
}
412
598
 
413
599
    
415
601
int erts_lcnt_thr_create(ethr_tid *tid, void * (*function)(void *), void *arg, ethr_thr_opts *opts) {
416
602
    erts_lcnt_thread_data_t *eltd;
417
603
    
 
604
    lcnt_lock();
 
605
    /* lock for thread id global update */
418
606
    eltd = lcnt_thread_data_alloc();
 
607
    lcnt_unlock();
419
608
    
420
609
    eltd->function = function;
421
610
    eltd->argument = arg;
425
614
 
426
615
 
427
616
/* bindings for bifs */
428
 
/* to block or not to block or lock perhaps */
429
 
 
 
617
 
 
618
Uint16 erts_lcnt_set_rt_opt(Uint16 opt) {
 
619
    Uint16 prev;
 
620
    prev = (erts_lcnt_rt_options & opt);
 
621
    erts_lcnt_rt_options |= opt;
 
622
    return prev;
 
623
}
 
624
 
 
625
Uint16 erts_lcnt_clear_rt_opt(Uint16 opt) {                     
 
626
    Uint16 prev;
 
627
    prev = (erts_lcnt_rt_options & opt);
 
628
    erts_lcnt_rt_options &= ~opt;
 
629
    return prev;
 
630
}
430
631
 
431
632
void erts_lcnt_clear_counters(void) {
432
633
    erts_lcnt_lock_t *lock;
433
634
    erts_lcnt_lock_list_t *list;
 
635
    erts_lcnt_lock_stats_t *stats;
 
636
    int i;
434
637
 
435
638
    lcnt_lock();
436
639
 
437
640
    list = erts_lcnt_data->current_locks;
 
641
    
438
642
    for (lock = list->head; lock != NULL; lock = lock->next) {
439
 
        ethr_atomic_set(&lock->tries, 0);
440
 
        ethr_atomic_set(&lock->colls, 0);
441
 
        /* clear timers */
442
 
        lock->timer_n  = 0;
443
 
        lock->timer_s  = 0;
444
 
        lock->timer_ns = 0;
 
643
        for( i = 0; i < ERTS_LCNT_MAX_LOCK_LOCATIONS; i++) {
 
644
            stats = &lock->stats[i];
 
645
            lcnt_clear_stats(stats);
 
646
        }
 
647
        lock->n_stats = 1;
445
648
    }
446
649
 
447
650
    /* empty deleted locks in lock list */
448
651
    erts_lcnt_list_clear(erts_lcnt_data->deleted_locks);
449
652
 
 
653
    lcnt_time(&timer_start);
 
654
 
450
655
    lcnt_unlock();
451
656
}
452
657
 
453
658
erts_lcnt_data_t *erts_lcnt_get_data(void) {
 
659
    erts_lcnt_time_t timer_stop;
 
660
    
 
661
    lcnt_lock();
 
662
    
 
663
    lcnt_time(&timer_stop);
 
664
    lcnt_time_diff(&(erts_lcnt_data->duration), &timer_stop, &timer_start);
 
665
    
 
666
    lcnt_unlock();
 
667
    
454
668
    return erts_lcnt_data;
455
669
}
456
670
 
457
671
char *erts_lcnt_lock_type(Uint16 type) {
458
 
    return lock_type(type);
 
672
    return lcnt_lock_type(type);
459
673
}
460
674
 
461
675
#endif /* ifdef ERTS_ENABLE_LOCK_COUNT */