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

« back to all changes in this revision

Viewing changes to erts/emulator/beam/erl_lock_check.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:
 
1
/* ``The contents of this file are subject to the Erlang Public License,
 
2
 * Version 1.1, (the "License"); you may not use this file except in
 
3
 * compliance with the License. You should have received a copy of the
 
4
 * Erlang Public License along with this software. If not, it can be
 
5
 * retrieved via the world wide web at http://www.erlang.org/.
 
6
 * 
 
7
 * Software distributed under the License is distributed on an "AS IS"
 
8
 * basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
9
 * the License for the specific language governing rights and limitations
 
10
 * under the License.
 
11
 * 
 
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
 */
 
18
 
 
19
/*
 
20
 * Description: A lock checker that checks that each thread acquires
 
21
 *              locks according to a predefined global lock order. The
 
22
 *              global lock order is used to prevent deadlocks. If the
 
23
 *              lock order is violated, an error message is printed
 
24
 *              and the emulator aborts. The lock checker is only
 
25
 *              intended to be enabled when debugging.
 
26
 *
 
27
 * Author: Rickard Green
 
28
 */
 
29
 
 
30
#ifdef HAVE_CONFIG_H
 
31
#  include "config.h"
 
32
#endif
 
33
 
 
34
/* Needed for VxWorks va_arg */
 
35
#include "sys.h"
 
36
 
 
37
#ifdef ERTS_ENABLE_LOCK_CHECK
 
38
 
 
39
#include "erl_lock_check.h"
 
40
#include "erl_term.h"
 
41
#include "erl_threads.h"
 
42
 
 
43
typedef struct {
 
44
    char *name;
 
45
    char *internal_order;
 
46
} erts_lc_lock_order_t;
 
47
 
 
48
/*
 
49
 * Global lock order for locks in the emulator.
 
50
 *
 
51
 * Locks early (low indexes) in the 'erts_lock_order' array should be
 
52
 * locked before locks late (high indexes) in the array. Each lock has
 
53
 * a name which is set on initialization. If multiple locks with the
 
54
 * same name are used, either an immediate Erlang term (e.g. internal
 
55
 * pid) or the address of the lock is used for internal lock order.
 
56
 * The immediate Erlang term used for internal lock order is also set
 
57
 * on initialization. Locks with small immediate Erlang terms should
 
58
 * be locked before locks with large immediate Erlang terms, and
 
59
 * locks with small addresses should be locked before locks with
 
60
 * large addresses. The immediate terms and adresses (boxed pointers)
 
61
 * are compared as unsigned integers not as Erlang terms.
 
62
 *
 
63
 * Once a spinlock or rw(spin)lock has been locked, the thread is not
 
64
 * allowed to lock mutexes, rwmutexes or process locks until all
 
65
 * spinlocks and rwlocks have been unlocked. This restriction is not
 
66
 * reflected by the lock order below, but the lock checker will still
 
67
 * check for violations of this restriction.
 
68
 */
 
69
static erts_lc_lock_order_t erts_lock_order[] = {
 
70
    /*
 
71
     *  "Lock name"                             "Internal lock order
 
72
     *                                           description (NULL
 
73
     *                                           if only one lock use
 
74
     *                                           the lock name)"
 
75
     */
 
76
#ifdef ERTS_SMP
 
77
    {   "io",                                   NULL                    },
 
78
    {   "bif_timers",                           NULL                    },
 
79
    {   "reg_tab",                              NULL                    },
 
80
    {   "proc_main",                            "pid"                   },
 
81
    {   "proc_link",                            "pid"                   },
 
82
    {   "proc_msgq",                            "pid"                   },
 
83
    {   "proc_status",                          "pid"                   },
 
84
    {   "proc_tab",                             NULL                    },
 
85
    {   "schdlq",                               NULL                    },
 
86
    {   "db_tab",                               "address"               },
 
87
    {   "meta_pid_to_tab",                      NULL                    },
 
88
    {   "meta_pid_to_fixed_tab",                NULL                    },
 
89
    {   "db_tables",                            NULL                    },
 
90
    {   "dist_entry",                           "address"               },
 
91
    {   "node_table",                           NULL                    },
 
92
    {   "dist_table",                           NULL                    },
 
93
    {   "sys_tracers",                          NULL                    },
 
94
    {   "trace_pattern",                        NULL                    },
 
95
    {   "module_tab",                           NULL                    },
 
96
    {   "export_tab",                           NULL                    },
 
97
    {   "fun_tab",                              NULL                    },
 
98
#endif
 
99
    {   "asyncq",                               "address"               },
 
100
#ifndef ERTS_SMP
 
101
    {   "async_ready",                          NULL                    },
 
102
#endif
 
103
    {   "efile_drv",                            "address"               },
 
104
#ifdef ENABLE_CHILD_WAITER_THREAD
 
105
    {   "child_status",                         NULL                    },
 
106
#endif
 
107
    {   "drv_ev_state",                         NULL                    },
 
108
    {   "pollset",                              "address"               },
 
109
    {   "binary_alloc",                         NULL                    },
 
110
    {   "alcu_init_atoms",                      NULL                    },
 
111
    {   "mseg_init_atoms",                      NULL                    },
 
112
#ifdef ERTS_SMP
 
113
    {   "sys_msg_q",                            NULL                    },
 
114
    {   "atom_tab",                             NULL                    },
 
115
    {   "make_ref",                             NULL                    },
 
116
    {   "message_alloc_lock",                   NULL                    },
 
117
    {   "ptimer_pre_alloc_lock",                NULL,                   },
 
118
    {   "btm_pre_alloc_lock",                   NULL,                   },
 
119
#endif
 
120
    {   "mtrace_op",                            NULL                    },
 
121
    {   "instr_x",                              NULL                    },
 
122
    {   "instr",                                NULL                    },
 
123
    {   "fix_alloc",                            "index"                 },
 
124
    {   "alcu_allocator",                       "index"                 },
 
125
    {   "mseg",                                 NULL                    },
 
126
#ifdef ERTS_SMP
 
127
    {   "gc_info",                              NULL                    },
 
128
    {   "io_wake",                              NULL                    },
 
129
    {   "timer_wheel",                          NULL                    },
 
130
    {   "timeofday",                            NULL                    },
 
131
    {   "system_block",                         NULL                    },
 
132
    {   "breakpoints",                          NULL                    },
 
133
    {   "pollsets_lock",                        NULL                    },
 
134
#endif
 
135
    {   "mtrace_buf",                           NULL                    }
 
136
};
 
137
 
 
138
#define ERTS_LOCK_ORDER_SIZE \
 
139
  (sizeof(erts_lock_order)/sizeof(erts_lc_lock_order_t))
 
140
 
 
141
#define LOCK_IS_TYPE_ORDER_VIOLATION(LCK_FLG, LCKD_FLG)                 \
 
142
  (((LCKD_FLG) & (ERTS_LC_FLG_LT_SPINLOCK|ERTS_LC_FLG_LT_RWSPINLOCK))   \
 
143
   && ((LCK_FLG)                                                        \
 
144
       & ERTS_LC_FLG_LT_ALL                                             \
 
145
       & ~(ERTS_LC_FLG_LT_SPINLOCK|ERTS_LC_FLG_LT_RWSPINLOCK)))
 
146
 
 
147
static char *
 
148
lock_type(Uint16 flags)
 
149
{
 
150
    switch (flags & ERTS_LC_FLG_LT_ALL) {
 
151
    case ERTS_LC_FLG_LT_SPINLOCK:       return "[spinlock]";
 
152
    case ERTS_LC_FLG_LT_RWSPINLOCK:     return "[rw(spin)lock]";
 
153
    case ERTS_LC_FLG_LT_MUTEX:          return "[mutex]";
 
154
    case ERTS_LC_FLG_LT_RWMUTEX:        return "[rwmutex]";
 
155
    case ERTS_LC_FLG_LT_PROCLOCK:       return "[proclock]";
 
156
    default:                            return "";
 
157
    }
 
158
}
 
159
 
 
160
static char *
 
161
rw_op_str(Uint16 flags)
 
162
{
 
163
    switch (flags & ERTS_LC_FLG_LO_READ_WRITE) {
 
164
    case ERTS_LC_FLG_LO_READ_WRITE:
 
165
        return " (rw)";
 
166
    case ERTS_LC_FLG_LO_READ:
 
167
        return " (r)";
 
168
    case ERTS_LC_FLG_LO_WRITE:
 
169
        erts_fprintf(stderr, "\nInternal error\n");
 
170
        abort();
 
171
    default:
 
172
        break;
 
173
    }
 
174
    return "";
 
175
}
 
176
 
 
177
typedef struct erts_lc_locked_lock_t_ erts_lc_locked_lock_t;
 
178
struct erts_lc_locked_lock_t_ {
 
179
    erts_lc_locked_lock_t *next;
 
180
    erts_lc_locked_lock_t *prev;
 
181
    Eterm extra;
 
182
    Sint16 id;
 
183
    Uint16 flags;
 
184
};
 
185
 
 
186
typedef struct erts_lc_locked_locks_t_ erts_lc_locked_locks_t;
 
187
struct erts_lc_locked_locks_t_ {
 
188
    char *thread_name;
 
189
    erts_tid_t tid;
 
190
    erts_lc_locked_locks_t *next;
 
191
    erts_lc_locked_locks_t *prev;
 
192
    erts_lc_locked_lock_t *first;
 
193
    erts_lc_locked_lock_t *last;
 
194
};
 
195
 
 
196
typedef union erts_lc_free_block_t_ erts_lc_free_block_t;
 
197
union erts_lc_free_block_t_ {
 
198
    erts_lc_free_block_t *next;
 
199
    erts_lc_locked_lock_t lock;
 
200
};
 
201
 
 
202
static ethr_tsd_key locks_key;
 
203
 
 
204
static erts_lc_locked_locks_t *erts_locked_locks;
 
205
 
 
206
static erts_lc_free_block_t *free_blocks;
 
207
 
 
208
#ifdef ERTS_LC_STATIC_ALLOC
 
209
#define ERTS_LC_FB_CHUNK_SIZE 10000
 
210
#else
 
211
#define ERTS_LC_FB_CHUNK_SIZE 10
 
212
#endif
 
213
 
 
214
#ifdef ETHR_HAVE_NATIVE_LOCKS
 
215
static ethr_spinlock_t free_blocks_lock;
 
216
#define ERTS_LC_LOCK    ethr_spin_lock
 
217
#define ERTS_LC_UNLOCK  ethr_spin_unlock
 
218
#else
 
219
static ethr_mutex free_blocks_lock;
 
220
#define ERTS_LC_LOCK    ethr_mutex_lock
 
221
#define ERTS_LC_UNLOCK  ethr_mutex_unlock
 
222
#endif
 
223
 
 
224
static ERTS_INLINE void
 
225
lc_lock(void)
 
226
{
 
227
    if (ERTS_LC_LOCK(&free_blocks_lock) != 0)
 
228
        abort();
 
229
}
 
230
 
 
231
static ERTS_INLINE void
 
232
lc_unlock(void)
 
233
{
 
234
    if (ERTS_LC_UNLOCK(&free_blocks_lock) != 0)
 
235
        abort();
 
236
}
 
237
 
 
238
static ERTS_INLINE void lc_free(void *p)
 
239
{
 
240
    erts_lc_free_block_t *fb = (erts_lc_free_block_t *) p;
 
241
#ifdef DEBUG
 
242
    memset((void *) p, 0xdf, sizeof(erts_lc_free_block_t));
 
243
#endif
 
244
    lc_lock();
 
245
    fb->next = free_blocks;
 
246
    free_blocks = fb;
 
247
    lc_unlock();   
 
248
}
 
249
 
 
250
#ifdef ERTS_LC_STATIC_ALLOC
 
251
 
 
252
static void *lc_core_alloc(void)
 
253
{
 
254
    lc_unlock();
 
255
    erts_fprintf(stderr, "Lock checker out of memory!\n");
 
256
    abort();
 
257
}
 
258
 
 
259
#else
 
260
 
 
261
static void *lc_core_alloc(void)
 
262
{
 
263
    int i;
 
264
    erts_lc_free_block_t *fbs;
 
265
    lc_unlock();
 
266
    fbs = (erts_lc_free_block_t *) malloc(sizeof(erts_lc_free_block_t)
 
267
                                          * ERTS_LC_FB_CHUNK_SIZE);
 
268
    if (!fbs) {
 
269
        erts_fprintf(stderr, "Lock checker failed to allocate memory!\n");
 
270
        abort();
 
271
    }
 
272
    for (i = 1; i < ERTS_LC_FB_CHUNK_SIZE - 1; i++) {
 
273
#ifdef DEBUG
 
274
        memset((void *) &fbs[i], 0xdf, sizeof(erts_lc_free_block_t));
 
275
#endif
 
276
        fbs[i].next = &fbs[i+1];
 
277
    }
 
278
#ifdef DEBUG
 
279
    memset((void *) &fbs[ERTS_LC_FB_CHUNK_SIZE-1],
 
280
           0xdf, sizeof(erts_lc_free_block_t));
 
281
#endif
 
282
    lc_lock();
 
283
    fbs[ERTS_LC_FB_CHUNK_SIZE-1].next = free_blocks;
 
284
    free_blocks = &fbs[1];
 
285
    return (void *) &fbs[0];
 
286
}
 
287
 
 
288
#endif
 
289
 
 
290
static ERTS_INLINE void *lc_alloc(void)
 
291
{
 
292
    void *res;
 
293
    lc_lock();
 
294
    if (!free_blocks)
 
295
        res = lc_core_alloc();
 
296
    else {
 
297
        res = (void *) free_blocks;
 
298
        free_blocks = free_blocks->next;
 
299
    }
 
300
    lc_unlock();
 
301
    return res;
 
302
}
 
303
 
 
304
 
 
305
static erts_lc_locked_locks_t *
 
306
create_locked_locks(char *thread_name)
 
307
{
 
308
    erts_lc_locked_locks_t *l_lcks = malloc(sizeof(erts_lc_locked_locks_t));
 
309
    if (!l_lcks)
 
310
        abort();
 
311
 
 
312
    l_lcks->thread_name = strdup(thread_name ? thread_name : "unknown");
 
313
    if (!l_lcks->thread_name)
 
314
        abort();
 
315
 
 
316
    l_lcks->tid = erts_thr_self();
 
317
    l_lcks->first = NULL;
 
318
    l_lcks->last = NULL;
 
319
    l_lcks->prev = NULL;
 
320
    lc_lock();
 
321
    l_lcks->next = erts_locked_locks;
 
322
    if (erts_locked_locks)
 
323
        erts_locked_locks->prev = l_lcks;
 
324
    erts_locked_locks = l_lcks;
 
325
    lc_unlock();
 
326
    erts_tsd_set(locks_key, (void *) l_lcks);
 
327
    return l_lcks;
 
328
}
 
329
 
 
330
static void
 
331
destroy_locked_locks(erts_lc_locked_locks_t *l_lcks)
 
332
{
 
333
    ASSERT(l_lcks->thread_name);
 
334
    free((void *) l_lcks->thread_name);
 
335
    ASSERT(l_lcks->first == NULL);
 
336
    ASSERT(l_lcks->last == NULL);
 
337
 
 
338
    lc_lock();
 
339
    if (l_lcks->prev)
 
340
        l_lcks->prev->next = l_lcks->next;
 
341
    else {
 
342
        ASSERT(erts_locked_locks == l_lcks);
 
343
        erts_locked_locks = l_lcks->next;
 
344
    }
 
345
 
 
346
    if (l_lcks->next)
 
347
        l_lcks->next->prev = l_lcks->prev;
 
348
    lc_unlock();
 
349
 
 
350
    free((void *) l_lcks);
 
351
 
 
352
}
 
353
 
 
354
static ERTS_INLINE erts_lc_locked_locks_t *
 
355
get_my_locked_locks(void)
 
356
{
 
357
    return erts_tsd_get(locks_key);
 
358
}
 
359
 
 
360
static ERTS_INLINE erts_lc_locked_locks_t *
 
361
make_my_locked_locks(void)
 
362
{
 
363
    erts_lc_locked_locks_t *l_lcks = get_my_locked_locks();
 
364
    if (l_lcks)
 
365
        return l_lcks;
 
366
    else
 
367
        return create_locked_locks(NULL);
 
368
}
 
369
 
 
370
static ERTS_INLINE erts_lc_locked_lock_t *
 
371
new_locked_lock(erts_lc_lock_t *lck, Uint16 op_flags)
 
372
{
 
373
    erts_lc_locked_lock_t *l_lck = (erts_lc_locked_lock_t *) lc_alloc();
 
374
    l_lck->next = NULL;
 
375
    l_lck->prev = NULL;
 
376
    l_lck->id = lck->id;
 
377
    l_lck->extra = lck->extra;
 
378
    l_lck->flags = lck->flags | op_flags;
 
379
    return l_lck;
 
380
}
 
381
 
 
382
static void
 
383
print_lock2(char *prefix, Sint16 id, Eterm extra, Uint16 flags, char *suffix)
 
384
{
 
385
    char *lname = (0 <= id && id < ERTS_LOCK_ORDER_SIZE
 
386
                   ? erts_lock_order[id].name
 
387
                   : "unknown");
 
388
    if (is_boxed(extra))
 
389
        erts_fprintf(stderr,
 
390
                     "%s'%s:%p%s'%s%s",
 
391
                     prefix,
 
392
                     lname,
 
393
                     boxed_val(extra),
 
394
                     lock_type(flags),
 
395
                     rw_op_str(flags),
 
396
                     suffix);
 
397
    else
 
398
        erts_fprintf(stderr,
 
399
                     "%s'%s:%T%s'%s%s",
 
400
                     prefix,
 
401
                     lname,
 
402
                     extra,
 
403
                     lock_type(flags),
 
404
                     rw_op_str(flags),
 
405
                     suffix);
 
406
}
 
407
 
 
408
static void
 
409
print_lock(char *prefix, erts_lc_lock_t *lck, char *suffix)
 
410
{
 
411
    print_lock2(prefix, lck->id, lck->extra, lck->flags, suffix);
 
412
}
 
413
 
 
414
static void
 
415
print_curr_locks(erts_lc_locked_locks_t *l_lcks)
 
416
{
 
417
    erts_lc_locked_lock_t *l_lck;
 
418
    if (!l_lcks || !l_lcks->first)
 
419
        erts_fprintf(stderr,
 
420
                     "Currently no locks are locked by the %s thread.\n",
 
421
                     l_lcks->thread_name);
 
422
    else {
 
423
        erts_fprintf(stderr,
 
424
                     "Currently these locks are locked by the %s thread:\n",
 
425
                     l_lcks->thread_name);
 
426
        for (l_lck = l_lcks->first; l_lck; l_lck = l_lck->next)
 
427
            print_lock2("  ", l_lck->id, l_lck->extra, l_lck->flags, "\n");
 
428
    }
 
429
}
 
430
 
 
431
static void
 
432
print_lock_order(void)
 
433
{
 
434
    int i;
 
435
    erts_fprintf(stderr, "Lock order:\n");
 
436
    for (i = 1; i < ERTS_LOCK_ORDER_SIZE; i++) {
 
437
        if (erts_lock_order[i].internal_order)
 
438
            erts_fprintf(stderr,
 
439
                         "  %s:%s\n",
 
440
                         erts_lock_order[i].name,
 
441
                         erts_lock_order[i].internal_order);
 
442
        else
 
443
            erts_fprintf(stderr, "  %s\n", erts_lock_order[i].name);
 
444
    }
 
445
}
 
446
 
 
447
static void
 
448
uninitialized_lock(void)
 
449
{
 
450
    erts_fprintf(stderr, "Performing operations on uninitialized lock!\n");
 
451
    print_curr_locks(get_my_locked_locks());
 
452
    abort();
 
453
}
 
454
 
 
455
static void
 
456
lock_twice(char *prefix, erts_lc_locked_locks_t *l_lcks, erts_lc_lock_t *lck,
 
457
           Uint16 op_flags)
 
458
{
 
459
    erts_fprintf(stderr, "%s%s", prefix, rw_op_str(op_flags));
 
460
    print_lock(" ", lck, " lock which is already locked by thread!\n");
 
461
    print_curr_locks(l_lcks);
 
462
    abort();
 
463
}
 
464
 
 
465
static void
 
466
unlock_op_mismatch(erts_lc_locked_locks_t *l_lcks, erts_lc_lock_t *lck,
 
467
                   Uint16 op_flags)
 
468
{
 
469
    erts_fprintf(stderr, "Unlocking%s ", rw_op_str(op_flags));
 
470
    print_lock("", lck, " lock which mismatch previous lock operation!\n");
 
471
    print_curr_locks(l_lcks);
 
472
    abort();
 
473
}
 
474
 
 
475
static void
 
476
unlock_of_not_locked(erts_lc_locked_locks_t *l_lcks, erts_lc_lock_t *lck)
 
477
{
 
478
    print_lock("Unlocking ", lck, " lock which is not locked by thread!\n");
 
479
    print_curr_locks(l_lcks);
 
480
    abort();
 
481
}
 
482
 
 
483
static void
 
484
lock_order_violation(erts_lc_locked_locks_t *l_lcks, erts_lc_lock_t *lck)
 
485
{
 
486
    print_lock("Lock order violation occured when locking ", lck, "!\n");
 
487
    print_curr_locks(l_lcks);
 
488
    print_lock_order();
 
489
    abort();
 
490
}
 
491
 
 
492
static void
 
493
type_order_violation(char *op, erts_lc_locked_locks_t *l_lcks,
 
494
                     erts_lc_lock_t *lck)
 
495
{
 
496
    erts_fprintf(stderr, "Lock type order violation occured when ");
 
497
    print_lock(op, lck, "!\n");
 
498
    ASSERT(l_lcks);
 
499
    print_curr_locks(l_lcks);
 
500
    abort();
 
501
}
 
502
 
 
503
static void
 
504
lock_mismatch(erts_lc_locked_locks_t *l_lcks, int exact,
 
505
              int failed_have, erts_lc_lock_t *have, int have_len,
 
506
              int failed_have_not, erts_lc_lock_t *have_not, int have_not_len)
 
507
{
 
508
    int i;
 
509
    erts_fprintf(stderr, "Lock mismatch found!\n");
 
510
    if (failed_have >= 0) {
 
511
        ASSERT(have && have_len > failed_have);
 
512
        print_lock2("At least the ",
 
513
                   have[failed_have].id, have[failed_have].extra, 0,
 
514
                   " lock is not locked when it should have been\n");
 
515
    }
 
516
    else if (failed_have_not >= 0) {
 
517
        ASSERT(have_not && have_not_len > failed_have_not);
 
518
        print_lock2("At least the ",
 
519
                    have_not[failed_have_not].id,
 
520
                    have_not[failed_have_not].extra,
 
521
                    0,
 
522
                    " lock is locked when it should not have been\n");
 
523
    }
 
524
    if (exact) {
 
525
        if (!have || have_len <= 0)
 
526
            erts_fprintf(stderr,
 
527
                         "Thread should not have any locks locked at all\n");
 
528
        else {
 
529
            erts_fprintf(stderr,
 
530
                         "Thread should have these and only these locks "
 
531
                         "locked:\n");
 
532
            for (i = 0; i < have_len; i++)
 
533
                print_lock2("  ", have[i].id, have[i].extra, 0, "\n");
 
534
        }
 
535
    }
 
536
    else {
 
537
        if (have && have_len > 0) {
 
538
            erts_fprintf(stderr,
 
539
                         "Thread should at least have these locks locked:\n");
 
540
            for (i = 0; i < have_len; i++)
 
541
                print_lock2("  ", have[i].id, have[i].extra, 0, "\n");
 
542
        }
 
543
        if (have_not && have_not_len > 0) {
 
544
            erts_fprintf(stderr,
 
545
                         "Thread should at least not have these locks "
 
546
                         "locked:\n");
 
547
            for (i = 0; i < have_not_len; i++)
 
548
                print_lock2("  ", have_not[i].id, have_not[i].extra, 0, "\n");
 
549
        }
 
550
    }
 
551
    print_curr_locks(l_lcks);
 
552
    abort();
 
553
}
 
554
 
 
555
static void
 
556
thread_exit_handler(void)
 
557
{
 
558
    erts_lc_locked_locks_t *l_lcks = get_my_locked_locks();
 
559
    if (l_lcks) {
 
560
        if (l_lcks->first) {
 
561
            erts_fprintf(stderr,
 
562
                         "Thread exiting while having locked locks!\n");
 
563
            print_curr_locks(l_lcks);
 
564
            abort();
 
565
        }
 
566
        destroy_locked_locks(l_lcks);
 
567
        /* erts_tsd_set(locks_key, NULL); */
 
568
    }
 
569
}
 
570
 
 
571
void
 
572
erts_lc_set_thread_name(char *thread_name)
 
573
{
 
574
    erts_lc_locked_locks_t *l_lcks = get_my_locked_locks();
 
575
    if (!l_lcks)
 
576
        (void) create_locked_locks(thread_name);
 
577
    else {
 
578
        ASSERT(l_lcks->thread_name);
 
579
        free((void *) l_lcks->thread_name);
 
580
        l_lcks->thread_name = strdup(thread_name ? thread_name : "unknown");
 
581
        if (!l_lcks->thread_name)
 
582
            abort();
 
583
    }
 
584
}
 
585
 
 
586
int
 
587
erts_lc_assert_failed(char *file, int line, char *assertion)
 
588
{
 
589
    erts_fprintf(stderr, "%s:%d: Lock check assertion \"%s\" failed!\n",
 
590
                 file, line, assertion);
 
591
    print_curr_locks(get_my_locked_locks());
 
592
    abort();
 
593
    return 0;
 
594
}
 
595
 
 
596
void erts_lc_fail(char *fmt, ...)
 
597
{
 
598
    va_list args;
 
599
    erts_fprintf(stderr, "Lock check failed: ");
 
600
    va_start(args, fmt);
 
601
    erts_vfprintf(stderr, fmt, args);
 
602
    va_end(args);
 
603
    erts_fprintf(stderr, "\n");
 
604
    print_curr_locks(get_my_locked_locks());
 
605
    abort();
 
606
}
 
607
 
 
608
 
 
609
Sint16
 
610
erts_lc_get_lock_order_id(char *name)
 
611
{
 
612
    int i;
 
613
 
 
614
    if (!name || name[0] == '\0')
 
615
        erts_fprintf(stderr, "Missing lock name\n");
 
616
    else {
 
617
        for (i = 0; i < ERTS_LOCK_ORDER_SIZE; i++)
 
618
            if (strcmp(erts_lock_order[i].name, name) == 0)
 
619
                return i;
 
620
        erts_fprintf(stderr,
 
621
                     "Lock name '%s' missing in lock order "
 
622
                     "(update erl_lock_check.c)\n",
 
623
                     name);
 
624
    }
 
625
    abort();
 
626
    return (Sint16) -1;
 
627
}
 
628
 
 
629
 
 
630
static int
 
631
find_lock(erts_lc_locked_lock_t **l_lcks, erts_lc_lock_t *lck)
 
632
{
 
633
    erts_lc_locked_lock_t *l_lck = *l_lcks;
 
634
 
 
635
    if (l_lck) {
 
636
        if (l_lck->id == lck->id && l_lck->extra == lck->extra) {
 
637
            if ((l_lck->flags & lck->flags) == lck->flags)
 
638
                return 1;
 
639
            return 0;
 
640
        }
 
641
        else if (l_lck->id < lck->id
 
642
                 || (l_lck->id == lck->id
 
643
                     && l_lck->extra < lck->extra)) {
 
644
            for (l_lck = l_lck->next; l_lck; l_lck = l_lck->next) {
 
645
                if (l_lck->id > lck->id
 
646
                    || (l_lck->id == lck->id
 
647
                        && l_lck->extra >= lck->extra)) {
 
648
                    *l_lcks = l_lck;
 
649
                    if (l_lck->id == lck->id
 
650
                        && l_lck->extra == lck->extra
 
651
                        && ((l_lck->flags & lck->flags) == lck->flags))
 
652
                            return 1;
 
653
                    return 0;
 
654
                }
 
655
            }
 
656
        }
 
657
        else {
 
658
            for (l_lck = l_lck->prev; l_lck; l_lck = l_lck->prev) {
 
659
                if (l_lck->id < lck->id
 
660
                    || (l_lck->id == lck->id
 
661
                        && l_lck->extra <= lck->extra)) {
 
662
                    *l_lcks = l_lck;
 
663
                    if (l_lck->id == lck->id
 
664
                        && l_lck->extra == lck->extra
 
665
                        && ((l_lck->flags & lck->flags) == lck->flags))
 
666
                        return 1;
 
667
                    return 0;
 
668
                }
 
669
            }
 
670
        }
 
671
    }
 
672
    return 0;
 
673
}
 
674
 
 
675
static int
 
676
find_id(erts_lc_locked_lock_t **l_lcks, Sint16 id)
 
677
{
 
678
    erts_lc_locked_lock_t *l_lck = *l_lcks;
 
679
 
 
680
    if (l_lck) {
 
681
        if (l_lck->id == id)
 
682
            return 1;
 
683
        else if (l_lck->id < id) {
 
684
            for (l_lck = l_lck->next; l_lck; l_lck = l_lck->next) {
 
685
                if (l_lck->id >= id) {
 
686
                    *l_lcks = l_lck;
 
687
                    if (l_lck->id == id)
 
688
                        return 1;
 
689
                    return 0;
 
690
                }
 
691
            }
 
692
        }
 
693
        else {
 
694
            for (l_lck = l_lck->prev; l_lck; l_lck = l_lck->prev) {
 
695
                if (l_lck->id <= id) {
 
696
                    *l_lcks = l_lck;
 
697
                    if (l_lck->id == id)
 
698
                        return 1;
 
699
                    return 0;
 
700
                }
 
701
            }
 
702
        }
 
703
    }
 
704
    return 0;
 
705
}
 
706
 
 
707
void
 
708
erts_lc_have_locks(int *resv, erts_lc_lock_t *locks, int len)
 
709
{
 
710
    erts_lc_locked_locks_t *l_lcks = get_my_locked_locks();
 
711
    int i;
 
712
 
 
713
    if (!l_lcks) {
 
714
        for (i = 0; i < len; i++)
 
715
            resv[i] = 0;
 
716
    }
 
717
    else {
 
718
        erts_lc_locked_lock_t *l_lck = l_lcks->first;
 
719
        for (i = 0; i < len; i++)
 
720
            resv[i] = find_lock(&l_lck, &locks[i]);
 
721
    }
 
722
}
 
723
 
 
724
void
 
725
erts_lc_have_lock_ids(int *resv, int *ids, int len)
 
726
{
 
727
    erts_lc_locked_locks_t *l_lcks = get_my_locked_locks();
 
728
    int i;
 
729
 
 
730
    if (!l_lcks) {
 
731
        for (i = 0; i < len; i++)
 
732
            resv[i] = 0;
 
733
    }
 
734
    else {
 
735
        erts_lc_locked_lock_t *l_lck = l_lcks->first;
 
736
        for (i = 0; i < len; i++)
 
737
            resv[i] = find_id(&l_lck, ids[i]);
 
738
    }
 
739
}
 
740
 
 
741
void
 
742
erts_lc_check(erts_lc_lock_t *have, int have_len,
 
743
              erts_lc_lock_t *have_not, int have_not_len)
 
744
{
 
745
    int i;
 
746
    erts_lc_locked_locks_t *l_lcks = get_my_locked_locks();
 
747
    erts_lc_locked_lock_t *l_lck;
 
748
    
 
749
    if (have && have_len > 0) {
 
750
        if (!l_lcks)
 
751
            lock_mismatch(NULL, 0,
 
752
                          -1, have, have_len,
 
753
                          -1, have_not, have_not_len);
 
754
        l_lck = l_lcks->first;
 
755
        for (i = 0; i < have_len; i++) {
 
756
            if (!find_lock(&l_lck, &have[i]))
 
757
                lock_mismatch(l_lcks, 0,
 
758
                              i, have, have_len,
 
759
                              -1, have_not, have_not_len);
 
760
        }
 
761
    }
 
762
    if (have_not && have_not_len > 0 && l_lcks) {
 
763
        l_lck = l_lcks->first;
 
764
        for (i = 0; i < have_not_len; i++) {
 
765
            if (find_lock(&l_lck, &have_not[i]))
 
766
                lock_mismatch(l_lcks, 0,
 
767
                              -1, have, have_len,
 
768
                              i, have_not, have_not_len);
 
769
        }
 
770
    }
 
771
}
 
772
 
 
773
void
 
774
erts_lc_check_exact(erts_lc_lock_t *have, int have_len)
 
775
{
 
776
    erts_lc_locked_locks_t *l_lcks = get_my_locked_locks();
 
777
    if (!l_lcks && have && have_len > 0)
 
778
        lock_mismatch(NULL, 1,
 
779
                      -1, have, have_len,
 
780
                      -1, NULL, 0);
 
781
    else {
 
782
        int i;
 
783
        erts_lc_locked_lock_t *l_lck = l_lcks->first;
 
784
        for (i = 0; i < have_len; i++) {
 
785
            if (!find_lock(&l_lck, &have[i]))
 
786
                lock_mismatch(l_lcks, 1,
 
787
                              i, have, have_len,
 
788
                              -1, NULL, 0);
 
789
        }
 
790
        for (i = 0, l_lck = l_lcks->first; l_lck; l_lck = l_lck->next)
 
791
            i++;
 
792
        if (i != have_len)
 
793
            lock_mismatch(l_lcks, 1,
 
794
                          -1, have, have_len,
 
795
                          -1, NULL, 0);
 
796
    }
 
797
}
 
798
 
 
799
int
 
800
erts_lc_trylock_force_busy_flg(erts_lc_lock_t *lck, Uint16 op_flags)
 
801
{
 
802
#ifdef ERTS_LC_DO_NOT_FORCE_BUSY_TRYLOCK_ON_LOCK_ORDER_VIOLATION
 
803
    return 0;
 
804
#else
 
805
    /*
 
806
     * Force busy trylock if locking doesn't follow lock order.
 
807
     * This in order to make sure that caller can handle
 
808
     * the situation without causing a lock order violation.
 
809
     */
 
810
    erts_lc_locked_locks_t *l_lcks;
 
811
 
 
812
    if (lck->inited != ERTS_LC_INITITALIZED)
 
813
        uninitialized_lock();
 
814
 
 
815
    if (lck->id < 0)
 
816
        return 0;
 
817
 
 
818
    l_lcks = get_my_locked_locks();
 
819
 
 
820
    if (!l_lcks || !l_lcks->first) {
 
821
        ASSERT(!l_lcks || !l_lcks->last);
 
822
        return 0;
 
823
    }
 
824
    else {
 
825
        erts_lc_locked_lock_t *tl_lck;
 
826
 
 
827
        ASSERT(l_lcks->last);
 
828
 
 
829
#if 0 /* Ok when trylocking I guess... */
 
830
        if (LOCK_IS_TYPE_ORDER_VIOLATION(lck->flags, l_lcks->last->flags))
 
831
            type_order_violation("trylocking ", l_lcks, lck);
 
832
#endif
 
833
 
 
834
        if (l_lcks->last->id < lck->id
 
835
            || (l_lcks->last->id == lck->id
 
836
                && l_lcks->last->extra < lck->extra))
 
837
            return 0;
 
838
 
 
839
        /*
 
840
         * Lock order violation
 
841
         */
 
842
 
 
843
 
 
844
        /* Check that we are not trying to lock this lock twice */
 
845
        for (tl_lck = l_lcks->last; tl_lck; tl_lck = tl_lck->prev) {
 
846
            if (tl_lck->id < lck->id
 
847
                || (tl_lck->id == lck->id && tl_lck->extra <= lck->extra)) {
 
848
                if (tl_lck->id == lck->id && tl_lck->extra == lck->extra)
 
849
                    lock_twice("Trylocking", l_lcks, lck, op_flags);
 
850
                break;
 
851
            }
 
852
        }
 
853
 
 
854
#ifndef ERTS_LC_ALLWAYS_FORCE_BUSY_TRYLOCK_ON_LOCK_ORDER_VIOLATION
 
855
        /* We only force busy if a lock order violation would occur
 
856
           and when on an even millisecond. */
 
857
        {
 
858
            erts_thr_timeval_t time;
 
859
            erts_thr_time_now(&time);
 
860
 
 
861
            if ((time.tv_nsec / 1000000) & 1)
 
862
                return 0;
 
863
        }
 
864
#endif
 
865
 
 
866
        return 1;
 
867
    }
 
868
#endif
 
869
}
 
870
 
 
871
void erts_lc_trylock_flg(int locked, erts_lc_lock_t *lck, Uint16 op_flags)
 
872
{
 
873
    erts_lc_locked_locks_t *l_lcks;
 
874
    erts_lc_locked_lock_t *l_lck;
 
875
 
 
876
    if (lck->inited != ERTS_LC_INITITALIZED)
 
877
        uninitialized_lock();
 
878
 
 
879
    if (lck->id < 0)
 
880
        return;
 
881
 
 
882
    l_lcks = make_my_locked_locks();
 
883
    l_lck = locked ? new_locked_lock(lck, op_flags) : NULL;
 
884
 
 
885
    if (!l_lcks->last) {
 
886
        ASSERT(!l_lcks->first);
 
887
        if (locked)
 
888
            l_lcks->first = l_lcks->last = l_lck;
 
889
    }
 
890
    else {
 
891
        erts_lc_locked_lock_t *tl_lck;
 
892
#if 0 /* Ok when trylocking I guess... */
 
893
        if (LOCK_IS_TYPE_ORDER_VIOLATION(lck->flags, l_lcks->last->flags))
 
894
            type_order_violation("trylocking ", l_lcks, lck);
 
895
#endif
 
896
 
 
897
        for (tl_lck = l_lcks->last; tl_lck; tl_lck = tl_lck->prev) {
 
898
            if (tl_lck->id < lck->id
 
899
                || (tl_lck->id == lck->id && tl_lck->extra <= lck->extra)) {
 
900
                if (tl_lck->id == lck->id && tl_lck->extra == lck->extra)
 
901
                    lock_twice("Trylocking", l_lcks, lck, op_flags);
 
902
                if (locked) {
 
903
                    l_lck->next = tl_lck->next;
 
904
                    l_lck->prev = tl_lck;
 
905
                    if (tl_lck->next)
 
906
                        tl_lck->next->prev = l_lck;
 
907
                    else
 
908
                        l_lcks->last = l_lck;
 
909
                    tl_lck->next = l_lck;
 
910
                }
 
911
                return;
 
912
            }
 
913
        }
 
914
 
 
915
        if (locked) {
 
916
            l_lck->next = l_lcks->first;
 
917
            l_lcks->first->prev = l_lck;
 
918
            l_lcks->first = l_lck;
 
919
        }
 
920
    }
 
921
 
 
922
}
 
923
 
 
924
void erts_lc_lock_flg(erts_lc_lock_t *lck, Uint16 op_flags)
 
925
{
 
926
    erts_lc_locked_locks_t *l_lcks;
 
927
    erts_lc_locked_lock_t *l_lck;
 
928
 
 
929
    if (lck->inited != ERTS_LC_INITITALIZED)
 
930
        uninitialized_lock();
 
931
 
 
932
    if (lck->id < 0)
 
933
        return;
 
934
 
 
935
    l_lcks = make_my_locked_locks();
 
936
    l_lck = new_locked_lock(lck, op_flags);
 
937
 
 
938
    if (!l_lcks->last) {
 
939
        ASSERT(!l_lcks->first);
 
940
        l_lcks->last = l_lcks->first = l_lck;
 
941
    }
 
942
    else if (l_lcks->last->id < lck->id
 
943
             || (l_lcks->last->id == lck->id
 
944
                 && l_lcks->last->extra < lck->extra)) {
 
945
        if (LOCK_IS_TYPE_ORDER_VIOLATION(lck->flags, l_lcks->last->flags))
 
946
            type_order_violation("locking ", l_lcks, lck);
 
947
        l_lck->prev = l_lcks->last;
 
948
        l_lcks->last->next = l_lck;
 
949
        l_lcks->last = l_lck;
 
950
    }
 
951
    else if (l_lcks->last->id == lck->id && l_lcks->last->extra == lck->extra)
 
952
        lock_twice("Locking", l_lcks, lck, op_flags);
 
953
    else
 
954
        lock_order_violation(l_lcks, lck);
 
955
}
 
956
 
 
957
void erts_lc_unlock_flg(erts_lc_lock_t *lck, Uint16 op_flags)
 
958
{
 
959
    erts_lc_locked_locks_t *l_lcks;
 
960
    erts_lc_locked_lock_t *l_lck;
 
961
 
 
962
    if (lck->inited != ERTS_LC_INITITALIZED)
 
963
        uninitialized_lock();
 
964
 
 
965
    if (lck->id < 0)
 
966
        return;
 
967
 
 
968
    l_lcks = get_my_locked_locks();
 
969
 
 
970
    for (l_lck = l_lcks ? l_lcks->last : NULL; l_lck; l_lck = l_lck->prev) {
 
971
        if (l_lck->id == lck->id && l_lck->extra == lck->extra) {
 
972
            if ((l_lck->flags & ERTS_LC_FLG_LO_ALL) != op_flags)
 
973
                unlock_op_mismatch(l_lcks, lck, op_flags);
 
974
            if (l_lck->prev)
 
975
                l_lck->prev->next = l_lck->next;
 
976
            else
 
977
                l_lcks->first = l_lck->next;
 
978
            if (l_lck->next)
 
979
                l_lck->next->prev = l_lck->prev;
 
980
            else
 
981
                l_lcks->last = l_lck->prev;
 
982
            lc_free((void *) l_lck);
 
983
            return;
 
984
        }
 
985
    }
 
986
    
 
987
    unlock_of_not_locked(l_lcks, lck);
 
988
}
 
989
 
 
990
int
 
991
erts_lc_trylock_force_busy(erts_lc_lock_t *lck)
 
992
{
 
993
    return erts_lc_trylock_force_busy_flg(lck, 0);
 
994
}
 
995
 
 
996
void
 
997
erts_lc_trylock(int locked, erts_lc_lock_t *lck)
 
998
{
 
999
    erts_lc_trylock_flg(locked, lck, 0);
 
1000
}
 
1001
 
 
1002
void
 
1003
erts_lc_lock(erts_lc_lock_t *lck)
 
1004
{
 
1005
    erts_lc_lock_flg(lck, 0);
 
1006
}
 
1007
 
 
1008
void
 
1009
erts_lc_unlock(erts_lc_lock_t *lck)
 
1010
{
 
1011
    erts_lc_unlock_flg(lck, 0);
 
1012
}
 
1013
 
 
1014
void
 
1015
erts_lc_init_lock(erts_lc_lock_t *lck, char *name, Uint16 flags)
 
1016
{
 
1017
    lck->id = erts_lc_get_lock_order_id(name);
 
1018
    lck->extra = make_boxed(&lck->extra);
 
1019
    lck->flags = flags;
 
1020
    lck->inited = ERTS_LC_INITITALIZED;
 
1021
}
 
1022
 
 
1023
void
 
1024
erts_lc_init_lock_x(erts_lc_lock_t *lck, char *name, Uint16 flags, Eterm extra)
 
1025
{
 
1026
    lck->id = erts_lc_get_lock_order_id(name);
 
1027
    lck->extra = extra;
 
1028
    lck->flags = flags;
 
1029
    lck->inited = ERTS_LC_INITITALIZED;
 
1030
}
 
1031
 
 
1032
void
 
1033
erts_lc_destroy_lock(erts_lc_lock_t *lck)
 
1034
{
 
1035
    if (lck->inited != ERTS_LC_INITITALIZED)
 
1036
        uninitialized_lock();
 
1037
 
 
1038
    lck->inited = 0;
 
1039
    lck->id = -1;
 
1040
    lck->extra = THE_NON_VALUE;
 
1041
    lck->flags = 0;
 
1042
}
 
1043
 
 
1044
void
 
1045
erts_lc_init(void)
 
1046
{
 
1047
#ifdef ERTS_LC_STATIC_ALLOC
 
1048
    int i;
 
1049
    static erts_lc_free_block_t fbs[ERTS_LC_FB_CHUNK_SIZE];
 
1050
    for (i = 0; i < ERTS_LC_FB_CHUNK_SIZE - 1; i++) {
 
1051
#ifdef DEBUG
 
1052
        memset((void *) &fbs[i], 0xdf, sizeof(erts_lc_free_block_t));
 
1053
#endif
 
1054
        fbs[i].next = &fbs[i+1];
 
1055
    }
 
1056
#ifdef DEBUG
 
1057
    memset((void *) &fbs[ERTS_LC_FB_CHUNK_SIZE-1],
 
1058
           0xdf, sizeof(erts_lc_free_block_t));
 
1059
#endif
 
1060
    fbs[ERTS_LC_FB_CHUNK_SIZE-1].next = NULL;
 
1061
    free_blocks = &fbs[0]; 
 
1062
#else /* #ifdef ERTS_LC_STATIC_ALLOC */
 
1063
    free_blocks = NULL;
 
1064
#endif /* #ifdef ERTS_LC_STATIC_ALLOC */
 
1065
 
 
1066
#ifdef ETHR_HAVE_NATIVE_LOCKS
 
1067
    if (ethr_spinlock_init(&free_blocks_lock) != 0)
 
1068
        abort();
 
1069
#else
 
1070
    if (ethr_mutex_init(&free_blocks_lock) != 0)
 
1071
        abort();
 
1072
#endif
 
1073
 
 
1074
    erts_tsd_key_create(&locks_key);
 
1075
}
 
1076
 
 
1077
void
 
1078
erts_lc_late_init(void)
 
1079
{
 
1080
    erts_thr_install_exit_handler(thread_exit_handler);
 
1081
}
 
1082
 
 
1083
 
 
1084
/*
 
1085
 * erts_lc_pll(): print locked locks...
 
1086
 */
 
1087
void
 
1088
erts_lc_pll(void)
 
1089
{
 
1090
    print_curr_locks(get_my_locked_locks());
 
1091
}
 
1092
 
 
1093
 
 
1094
#endif /* #ifdef ERTS_ENABLE_LOCK_CHECK */