~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
/*
2
2
 * %CopyrightBegin%
3
 
 * 
4
 
 * Copyright Ericsson AB 1996-2009. All Rights Reserved.
5
 
 * 
 
3
 *
 
4
 * Copyright Ericsson AB 1996-2011. All Rights Reserved.
 
5
 *
6
6
 * The contents of this file are subject to the Erlang Public License,
7
7
 * Version 1.1, (the "License"); you may not use this file except in
8
8
 * compliance with the License. You should have received a copy of the
9
9
 * Erlang Public License along with this software. If not, it can be
10
10
 * retrieved online at http://www.erlang.org/.
11
 
 * 
 
11
 *
12
12
 * Software distributed under the License is distributed on an "AS IS"
13
13
 * basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
 * the License for the specific language governing rights and limitations
15
15
 * under the License.
16
 
 * 
 
16
 *
17
17
 * %CopyrightEnd%
18
18
 */
19
19
 
78
78
** The main meta table, containing all ets tables.
79
79
*/
80
80
#ifdef ERTS_SMP
81
 
#  define META_MAIN_TAB_LOCK_CNT 16
82
 
static union {
83
 
    erts_smp_spinlock_t lck;
84
 
    byte _cache_line_alignment[64];
85
 
}meta_main_tab_locks[META_MAIN_TAB_LOCK_CNT];
 
81
 
 
82
#define ERTS_META_MAIN_TAB_LOCK_TAB_BITS 8
 
83
#define ERTS_META_MAIN_TAB_LOCK_TAB_SIZE (1 << ERTS_META_MAIN_TAB_LOCK_TAB_BITS)
 
84
#define ERTS_META_MAIN_TAB_LOCK_TAB_MASK (ERTS_META_MAIN_TAB_LOCK_TAB_SIZE - 1)
 
85
 
 
86
typedef union {
 
87
    erts_smp_rwmtx_t rwmtx;
 
88
    byte cache_line_align__[ERTS_ALC_CACHE_LINE_ALIGN_SIZE(
 
89
                                sizeof(erts_smp_rwmtx_t))];
 
90
} erts_meta_main_tab_lock_t;
 
91
 
 
92
static erts_meta_main_tab_lock_t *meta_main_tab_locks;
 
93
 
86
94
#endif
87
95
static struct {
88
96
    union {
89
97
        DbTable *tb;     /* Only directly readable if slot is ALIVE */
90
 
        Uint next_free;  /* (index<<2)|1 if slot is FREE */
 
98
        UWord next_free;  /* (index<<2)|1 if slot is FREE */
91
99
    }u;
92
100
} *meta_main_tab;
93
101
 
104
112
#define MARK_SLOT_DEAD(i) (meta_main_tab[(i)].u.next_free |= 2)
105
113
#define GET_ANY_SLOT_TAB(i) ((DbTable*)(meta_main_tab[(i)].u.next_free & ~(1|2))) /* dead or alive */
106
114
 
107
 
static ERTS_INLINE void meta_main_tab_lock(unsigned slot)
108
 
{
109
 
#ifdef ERTS_SMP
110
 
    erts_smp_spin_lock(&meta_main_tab_locks[slot % META_MAIN_TAB_LOCK_CNT].lck);
111
 
#endif
112
 
}
113
 
 
114
 
static ERTS_INLINE void meta_main_tab_unlock(unsigned slot)
115
 
{
116
 
#ifdef ERTS_SMP
117
 
    erts_smp_spin_unlock(&meta_main_tab_locks[slot % META_MAIN_TAB_LOCK_CNT].lck);
 
115
static ERTS_INLINE erts_smp_rwmtx_t *
 
116
get_meta_main_tab_lock(unsigned slot)
 
117
{
 
118
#ifdef ERTS_SMP
 
119
    return &meta_main_tab_locks[slot & ERTS_META_MAIN_TAB_LOCK_TAB_MASK].rwmtx;
 
120
#else
 
121
    return NULL;
118
122
#endif
119
123
}
120
124
 
166
170
typedef enum {
167
171
    LCK_READ=1,     /* read only access */
168
172
    LCK_WRITE=2,    /* exclusive table write access */
169
 
    LCK_WRITE_REC=3 /* record write access */
 
173
    LCK_WRITE_REC=3, /* record write access */
 
174
    LCK_NONE=4
170
175
} db_lock_kind_t;
171
176
 
172
177
extern DbTableMethod db_hash;
174
179
 
175
180
int user_requested_db_max_tabs;
176
181
int erts_ets_realloc_always_moves;
 
182
int erts_ets_always_compress;
177
183
static int db_max_tabs;
178
184
static DbTable *meta_pid_to_tab; /* Pid mapped to owned tables */
179
185
static DbTable *meta_pid_to_fixed_tab; /* Pid mapped to fixed tables */
187
193
 
188
194
static void fix_table_locked(Process* p, DbTable* tb);
189
195
static void unfix_table_locked(Process* p,  DbTable* tb, db_lock_kind_t* kind);
190
 
static void set_heir(Process* me, DbTable* tb, Eterm heir, Eterm heir_data);
 
196
static void set_heir(Process* me, DbTable* tb, Eterm heir, UWord heir_data);
191
197
static void free_heir_data(DbTable*);
192
198
static void free_fixations_locked(DbTable *tb);
193
199
 
213
219
 * Static traps
214
220
 */
215
221
static Export ets_delete_continue_exp;
216
 
 
217
 
static ERTS_INLINE DbTable* db_ref(DbTable* tb)
218
 
{
219
 
    if (tb != NULL) {
220
 
        erts_refc_inc(&tb->common.ref, 2);
221
 
    }
222
 
    return tb;
223
 
}
224
 
 
225
 
static ERTS_INLINE DbTable* db_unref(DbTable* tb)
226
 
{
227
 
    if (!erts_refc_dectest(&tb->common.ref, 0)) {
 
222
        
 
223
static void
 
224
free_dbtable(DbTable* tb)
 
225
{
228
226
#ifdef HARDDEBUG
229
227
        if (erts_smp_atomic_read(&tb->common.memory_size) != sizeof(DbTable)) {
230
 
            erts_fprintf(stderr, "ets: db_unref memory remain=%ld fix=%x\n",
231
 
                         erts_smp_atomic_read(&tb->common.memory_size)-sizeof(DbTable), 
 
228
            erts_fprintf(stderr, "ets: free_dbtable memory remain=%ld fix=%x\n",
 
229
                         erts_smp_atomic_read(&tb->common.memory_size)-sizeof(DbTable),
232
230
                         tb->common.fixations);
233
231
        }
234
 
        erts_fprintf(stderr, "ets: db_unref(%T) deleted!!!\r\n", 
 
232
        erts_fprintf(stderr, "ets: free_dbtable(%T) deleted!!!\r\n",
235
233
                     tb->common.id);
236
234
 
237
 
        erts_fprintf(stderr, "ets: db_unref: meta_pid_to_tab common.memory_size = %ld\n",
 
235
        erts_fprintf(stderr, "ets: free_dbtable: meta_pid_to_tab common.memory_size = %ld\n",
238
236
                     erts_smp_atomic_read(&meta_pid_to_tab->common.memory_size));
239
237
        print_table(ERTS_PRINT_STDOUT, NULL, 1, meta_pid_to_tab);
240
238
 
241
239
 
242
 
        erts_fprintf(stderr, "ets: db_unref: meta_pid_to_fixed_tab common.memory_size = %ld\n",
 
240
        erts_fprintf(stderr, "ets: free_dbtable: meta_pid_to_fixed_tab common.memory_size = %ld\n",
243
241
                     erts_smp_atomic_read(&meta_pid_to_fixed_tab->common.memory_size));
244
242
        print_table(ERTS_PRINT_STDOUT, NULL, 1, meta_pid_to_fixed_tab);
245
 
        
246
243
#endif
247
244
#ifdef ERTS_SMP
248
245
        erts_smp_rwmtx_destroy(&tb->common.rwlock);
249
246
        erts_smp_mtx_destroy(&tb->common.fixlock);
250
247
#endif
251
248
        ASSERT(is_immed(tb->common.heir_data));
252
 
        erts_db_free(ERTS_ALC_T_DB_TABLE, tb, (void *) tb, sizeof(DbTable));                 
 
249
        erts_db_free(ERTS_ALC_T_DB_TABLE, tb, (void *) tb, sizeof(DbTable));
253
250
        ERTS_ETS_MISC_MEM_ADD(-sizeof(DbTable));
254
 
        return NULL;
255
 
    }
256
 
    return tb;
257
 
}
258
 
 
259
 
static ERTS_INLINE void db_init_lock(DbTable* tb, char *rwname, char* fixname)
260
 
{
261
 
    erts_refc_init(&tb->common.ref, 1);
262
 
    erts_refc_init(&tb->common.fixref, 0);
263
 
#ifdef ERTS_SMP
264
 
# ifdef ERTS_ENABLE_LOCK_COUNT
265
 
    erts_smp_rwmtx_init_x(&tb->common.rwlock, rwname, tb->common.the_name);
 
251
}
 
252
 
 
253
#ifdef ERTS_SMP
 
254
static void
 
255
chk_free_dbtable(void *vtb)
 
256
{
 
257
    DbTable * tb = (DbTable *) vtb;
 
258
    ERTS_THR_MEMORY_BARRIER;
 
259
    if (erts_refc_dectest(&tb->common.ref, 0) == 0)
 
260
        free_dbtable(tb);
 
261
}
 
262
#endif
 
263
 
 
264
static void schedule_free_dbtable(DbTable* tb)
 
265
{
 
266
    /*
 
267
     * NON-SMP case: Caller is *not* allowed to access the *tb
 
268
     *               structure after this function has returned!          
 
269
     * SMP case:     Caller is allowed to access the *tb structure
 
270
     *               until the bif has returned (we typically
 
271
     *               need to unlock the table lock after this
 
272
     *               function has returned).
 
273
     */
 
274
#ifdef ERTS_SMP
 
275
    int scheds = erts_get_max_no_executing_schedulers();
 
276
    ASSERT(scheds >= 1);
 
277
    ASSERT(erts_refc_read(&tb->common.ref, 0) == 0);
 
278
    erts_refc_init(&tb->common.ref, scheds);
 
279
    ERTS_THR_MEMORY_BARRIER;
 
280
    erts_smp_schedule_misc_aux_work(0, scheds, chk_free_dbtable, tb);
 
281
#else
 
282
    free_dbtable(tb);
 
283
#endif
 
284
}
 
285
 
 
286
static ERTS_INLINE void db_init_lock(DbTable* tb, int use_frequent_read_lock,
 
287
                                     char *rwname, char* fixname)
 
288
{
 
289
#ifdef ERTS_SMP
 
290
    erts_smp_rwmtx_opt_t rwmtx_opt = ERTS_SMP_RWMTX_OPT_DEFAULT_INITER;
 
291
    if (use_frequent_read_lock)
 
292
        rwmtx_opt.type = ERTS_SMP_RWMTX_TYPE_FREQUENT_READ;
 
293
#endif
 
294
#ifdef ERTS_SMP
 
295
    erts_smp_rwmtx_init_opt_x(&tb->common.rwlock, &rwmtx_opt,
 
296
                              rwname, tb->common.the_name);
266
297
    erts_smp_mtx_init_x(&tb->common.fixlock, fixname, tb->common.the_name);
267
 
# else
268
 
    erts_smp_rwmtx_init(&tb->common.rwlock, rwname);
269
 
    erts_smp_mtx_init(&tb->common.fixlock, fixname);
270
 
# endif
271
298
    tb->common.is_thread_safe = !(tb->common.status & DB_FINE_LOCKED);
272
299
#endif
273
300
}
274
301
 
275
 
static ERTS_INLINE void db_lock_take_over_ref(DbTable* tb, db_lock_kind_t kind)
 
302
static ERTS_INLINE void db_lock(DbTable* tb, db_lock_kind_t kind)
276
303
{
277
304
#ifdef ERTS_SMP
278
305
    ASSERT(tb != meta_pid_to_tab && tb != meta_pid_to_fixed_tab);
300
327
#endif
301
328
}
302
329
 
303
 
static ERTS_INLINE void db_lock(DbTable* tb, db_lock_kind_t kind)
304
 
{
305
 
    (void) db_ref(tb);
306
 
#ifdef ERTS_SMP
307
 
    db_lock_take_over_ref(tb, kind);
308
 
#endif
309
 
}
310
 
 
311
330
static ERTS_INLINE void db_unlock(DbTable* tb, db_lock_kind_t kind)
312
331
{
 
332
    /*
 
333
     * In NON-SMP case tb may refer to an already deallocated
 
334
     * DbTable structure. That is, ONLY the SMP case is allowed
 
335
     * to follow the tb pointer!
 
336
     */
313
337
#ifdef ERTS_SMP
314
338
    ASSERT(tb != meta_pid_to_tab && tb != meta_pid_to_fixed_tab);
315
339
 
336
360
        }
337
361
    }
338
362
#endif
339
 
    (void) db_unref(tb); /* May delete table... */
340
363
}
341
364
 
342
365
 
354
377
}
355
378
 
356
379
static ERTS_INLINE
357
 
DbTable* db_get_table(Process *p,
358
 
                      Eterm id,
359
 
                      int what,
360
 
                      db_lock_kind_t kind)
 
380
DbTable* db_get_table_aux(Process *p,
 
381
                          Eterm id,
 
382
                          int what,
 
383
                          db_lock_kind_t kind,
 
384
                          int meta_already_locked)
361
385
{
362
386
    DbTable *tb = NULL;
 
387
    erts_smp_rwmtx_t *mtl = NULL;
 
388
 
 
389
    /*
 
390
     * IMPORTANT: Only scheduler threads are allowed
 
391
     *            to access tables. Memory management
 
392
     *            depend on it.
 
393
     */
 
394
    ASSERT(erts_get_scheduler_data());
363
395
 
364
396
    if (is_small(id)) {
365
397
        Uint slot = unsigned_val(id) & meta_main_tab_slot_mask;
366
 
        meta_main_tab_lock(slot);
367
 
        if (slot < db_max_tabs && IS_SLOT_ALIVE(slot)) {
368
 
            /* SMP: inc to prevent race, between unlock of meta_main_tab_lock
369
 
             * and the table locking outside the meta_main_tab_lock
370
 
             */
371
 
            tb = db_ref(meta_main_tab[slot].u.tb);
372
 
        }
373
 
        meta_main_tab_unlock(slot);
 
398
        if (!meta_already_locked) {
 
399
            mtl = get_meta_main_tab_lock(slot);
 
400
            erts_smp_rwmtx_rlock(mtl);
 
401
        }
 
402
#if defined(ERTS_SMP) && defined(ERTS_ENABLE_LOCK_CHECK)
 
403
        else {
 
404
            erts_smp_rwmtx_t *test_mtl = get_meta_main_tab_lock(slot);
 
405
            ERTS_SMP_LC_ASSERT(erts_lc_rwmtx_is_rlocked(test_mtl)
 
406
                               || erts_lc_rwmtx_is_rwlocked(test_mtl));
 
407
        }
 
408
#endif
 
409
        if (slot < db_max_tabs && IS_SLOT_ALIVE(slot))
 
410
            tb = meta_main_tab[slot].u.tb;
374
411
    }
375
412
    else if (is_atom(id)) {
376
 
        erts_smp_rwmtx_t* rwlock;
377
 
        struct meta_name_tab_entry* bucket = meta_name_tab_bucket(id,&rwlock);
378
 
        erts_smp_rwmtx_rlock(rwlock);
 
413
        struct meta_name_tab_entry* bucket = meta_name_tab_bucket(id,&mtl);
 
414
        if (!meta_already_locked)
 
415
            erts_smp_rwmtx_rlock(mtl);
 
416
        else{
 
417
            ERTS_SMP_LC_ASSERT(erts_lc_rwmtx_is_rlocked(mtl)
 
418
                               || erts_lc_rwmtx_is_rwlocked(mtl));
 
419
            mtl = NULL;
 
420
        }
 
421
 
379
422
        if (bucket->pu.tb != NULL) {
380
423
            if (is_atom(bucket->u.name_atom)) { /* single */
381
 
                if (bucket->u.name_atom == id) {
382
 
                    tb = db_ref(bucket->pu.tb);
383
 
                }
 
424
                if (bucket->u.name_atom == id)
 
425
                    tb = bucket->pu.tb;
384
426
            }
385
427
            else { /* multi */
386
428
                Uint cnt = unsigned_val(bucket->u.mcnt);
387
429
                Uint i;
388
430
                for (i=0; i<cnt; i++) {
389
431
                    if (bucket->pu.mvec[i].u.name_atom == id) {
390
 
                        tb = db_ref(bucket->pu.mvec[i].pu.tb);
 
432
                        tb = bucket->pu.mvec[i].pu.tb;
391
433
                        break;
392
434
                    }
393
435
                }
394
436
            }
395
437
        }
396
 
        erts_smp_rwmtx_runlock(rwlock);
397
438
    }
398
439
    if (tb) {
399
 
        db_lock_take_over_ref(tb, kind);
400
 
        if (tb->common.id == id && ((tb->common.status & what) != 0 || 
401
 
                                    p->id == tb->common.owner)) {
402
 
            return tb;
 
440
        db_lock(tb, kind);
 
441
        if (tb->common.id != id
 
442
            || ((tb->common.status & what) == 0 && p->id != tb->common.owner)) {
 
443
            db_unlock(tb, kind);
 
444
            tb = NULL;
403
445
        }
404
 
        db_unlock(tb, kind);
405
446
    }
406
 
    return NULL;
 
447
    if (mtl)
 
448
        erts_smp_rwmtx_runlock(mtl);
 
449
    return tb;
 
450
}
 
451
 
 
452
static ERTS_INLINE
 
453
DbTable* db_get_table(Process *p,
 
454
                      Eterm id,
 
455
                      int what,
 
456
                      db_lock_kind_t kind)
 
457
{
 
458
    return db_get_table_aux(p, id, what, kind, 0);
407
459
}
408
460
 
409
461
/* Requires meta_main_tab_locks[slot] locked.
418
470
    erts_smp_spin_unlock(&meta_main_tab_main_lock);
419
471
}
420
472
 
421
 
static int insert_named_tab(Eterm name_atom, DbTable* tb)
 
473
static int insert_named_tab(Eterm name_atom, DbTable* tb, int have_lock)
422
474
{
423
475
    int ret = 0;
424
476
    erts_smp_rwmtx_t* rwlock;
425
477
    struct meta_name_tab_entry* new_entry;
426
478
    struct meta_name_tab_entry* bucket = meta_name_tab_bucket(name_atom,
427
479
                                                              &rwlock);
428
 
 
429
 
    erts_smp_rwmtx_rwlock(rwlock);
 
480
    if (!have_lock)
 
481
        erts_smp_rwmtx_rwlock(rwlock);
430
482
 
431
483
    if (bucket->pu.tb == NULL) { /* empty */
432
484
        new_entry = bucket;
473
525
    ret = 1; /* Ok */
474
526
 
475
527
done:
476
 
    erts_smp_rwmtx_rwunlock(rwlock);
 
528
    if (!have_lock)
 
529
        erts_smp_rwmtx_rwunlock(rwlock);
477
530
    return ret;
478
531
}
479
532
 
480
 
static int remove_named_tab(Eterm name_atom)
 
533
static int remove_named_tab(DbTable *tb, int have_lock)
481
534
{
482
535
    int ret = 0;
483
536
    erts_smp_rwmtx_t* rwlock;
 
537
    Eterm name_atom = tb->common.id;
484
538
    struct meta_name_tab_entry* bucket = meta_name_tab_bucket(name_atom,
485
539
                                                              &rwlock);
486
 
    erts_smp_rwmtx_rwlock(rwlock);
 
540
#ifdef ERTS_SMP
 
541
    if (!have_lock && erts_smp_rwmtx_tryrwlock(rwlock) == EBUSY) {
 
542
        /*
 
543
         * We keep our increased refc over this op in order to
 
544
         * prevent the table from disapearing.
 
545
         */
 
546
        erts_smp_rwmtx_rwunlock(&tb->common.rwlock);
 
547
        erts_smp_rwmtx_rwlock(rwlock);
 
548
        erts_smp_rwmtx_rwlock(&tb->common.rwlock);
 
549
    }
 
550
#endif
 
551
 
 
552
    ERTS_SMP_LC_ASSERT(erts_lc_rwmtx_is_rwlocked(rwlock));
 
553
 
487
554
    if (bucket->pu.tb == NULL) {
488
555
        goto done;
489
556
    }
534
601
    ret = 1; /* Ok */
535
602
 
536
603
done:
537
 
    erts_smp_rwmtx_rwunlock(rwlock);
 
604
    if (!have_lock)
 
605
        erts_smp_rwmtx_rwunlock(rwlock);
538
606
    return ret;
539
607
}
540
608
 
543
611
*/
544
612
static ERTS_INLINE void local_fix_table(DbTable* tb)
545
613
{
546
 
    erts_refc_inc(&tb->common.fixref, 1);
 
614
    erts_refc_inc(&tb->common.ref, 1);
547
615
}           
548
616
static ERTS_INLINE void local_unfix_table(DbTable* tb)
549
617
{       
550
 
    if (erts_refc_dectest(&tb->common.fixref, 0) == 0) {
 
618
    if (erts_refc_dectest(&tb->common.ref, 0) == 0) {
551
619
        ASSERT(IS_HASH_TABLE(tb->common.status));
552
620
        db_unfix_table_hash(&(tb->hash));
553
621
    }
709
777
    int cret = DB_ERROR_BADITEM;
710
778
    Eterm list;
711
779
    Eterm iter;
712
 
    Eterm cell[2];
 
780
    DeclareTmpHeap(cell,2,BIF_P);
713
781
    DbUpdateHandle handle;
714
782
 
715
783
    if ((tb = db_get_table(BIF_P, BIF_ARG_1, DB_WRITE, LCK_WRITE_REC)) == NULL) {
716
784
        BIF_ERROR(BIF_P, BADARG);
717
785
    }
 
786
    UseTmpHeap(2,BIF_P);
718
787
    if (!(tb->common.status & (DB_SET | DB_ORDERED_SET))) {
719
788
        goto bail_out;
720
789
    }
767
836
    tb->common.meth->db_finalize_dbterm(&handle);
768
837
 
769
838
bail_out:
 
839
    UnUseTmpHeap(2,BIF_P);
770
840
    db_unlock(tb, LCK_WRITE_REC);
771
841
 
772
842
    switch (cret) {
799
869
    Eterm* ret_list_currp = NULL;
800
870
    Eterm* ret_list_prevp = NULL;
801
871
    Eterm iter;
802
 
    Eterm cell[2];
803
 
    Eterm tuple[3];
 
872
    DeclareTmpHeap(cell,5,BIF_P);
 
873
    Eterm *tuple = cell+2;
804
874
    DbUpdateHandle handle;
805
875
    Uint halloc_size = 0; /* overestimated heap usage */
806
876
    Eterm* htop;          /* actual heap usage */
810
880
    if ((tb = db_get_table(BIF_P, BIF_ARG_1, DB_WRITE, LCK_WRITE_REC)) == NULL) {
811
881
        BIF_ERROR(BIF_P, BADARG);
812
882
    }
 
883
 
 
884
    UseTmpHeap(5,BIF_P);
 
885
 
813
886
    if (!(tb->common.status & (DB_SET | DB_ORDERED_SET))) {
814
887
        goto bail_out;
815
888
    }
837
910
        Eterm upop;
838
911
        Eterm* tpl;
839
912
        Sint position;
840
 
        Eterm incr, warp, oldcnt;
 
913
        Eterm incr, warp;
 
914
        Wterm oldcnt;
841
915
 
842
916
        if (is_not_list(iter)) {
843
917
            goto finalize;
876
950
                position > arityval(handle.dbterm->tpl[0])) {
877
951
                goto finalize;
878
952
            }
879
 
            oldcnt = handle.dbterm->tpl[position];
 
953
            oldcnt = db_do_read_element(&handle, position);
880
954
            if (is_big(oldcnt)) {
881
955
                halloc_size += BIG_NEED_SIZE(big_arity(oldcnt));
882
956
            }
912
986
        Eterm* tpl = tuple_val(CAR(list_val(iter)));
913
987
        Sint position = signed_val(tpl[1]);
914
988
        Eterm incr = tpl[2];
915
 
        Eterm oldcnt = handle.dbterm->tpl[position];
 
989
        Wterm oldcnt = db_do_read_element(&handle,position);
916
990
        Eterm newcnt = db_add_counter(&htop, oldcnt, incr);
917
991
 
918
992
        if (newcnt == NIL) {
925
999
 
926
1000
        if (arityval(*tpl) == 4) { /* Maybe warp it */
927
1001
            Eterm threshold = tpl[3];
928
 
            if ((cmp(incr,make_small(0)) < 0) ? /* negative increment? */
929
 
                (cmp(newcnt,threshold) < 0) :  /* if negative, check if below */
930
 
                (cmp(newcnt,threshold) > 0)) { /* else check if above threshold */
 
1002
            if ((CMP(incr,make_small(0)) < 0) ? /* negative increment? */
 
1003
                (CMP(newcnt,threshold) < 0) :  /* if negative, check if below */
 
1004
                (CMP(newcnt,threshold) > 0)) { /* else check if above threshold */
931
1005
 
932
1006
                newcnt = tpl[4];
933
1007
            }
956
1030
    tb->common.meth->db_finalize_dbterm(&handle);
957
1031
 
958
1032
bail_out:
 
1033
    UnUseTmpHeap(5,BIF_P);
959
1034
    db_unlock(tb, LCK_WRITE_REC);
960
1035
 
961
1036
    switch (cret) {
1132
1207
{
1133
1208
    DbTable* tb;
1134
1209
    Eterm ret;
 
1210
    erts_smp_rwmtx_t *lck1, *lck2;
1135
1211
 
1136
1212
#ifdef HARDDEBUG
1137
1213
    erts_fprintf(stderr,
1140
1216
                BIF_P->initial[0], BIF_P->initial[1], BIF_P->initial[2]);
1141
1217
#endif
1142
1218
 
1143
 
    if ((tb = db_get_table(BIF_P, BIF_ARG_1, DB_WRITE, LCK_WRITE)) == NULL) {
1144
 
        BIF_ERROR(BIF_P, BADARG);
1145
 
    }
1146
1219
 
1147
1220
    if (is_not_atom(BIF_ARG_2)) {
 
1221
        BIF_ERROR(BIF_P, BADARG);
 
1222
    }
 
1223
 
 
1224
    (void) meta_name_tab_bucket(BIF_ARG_2, &lck1);
 
1225
 
 
1226
    if (is_small(BIF_ARG_1)) {
 
1227
        Uint slot = unsigned_val(BIF_ARG_1) & meta_main_tab_slot_mask;
 
1228
        lck2 = get_meta_main_tab_lock(slot);
 
1229
    }
 
1230
    else if (is_atom(BIF_ARG_1)) {
 
1231
        (void) meta_name_tab_bucket(BIF_ARG_1, &lck2);
 
1232
        if (lck1 == lck2)
 
1233
            lck2 = NULL;
 
1234
        else if (lck1 > lck2) {
 
1235
            erts_smp_rwmtx_t *tmp = lck1;
 
1236
            lck1 = lck2;
 
1237
            lck2 = tmp;
 
1238
        }
 
1239
    }
 
1240
    else {
 
1241
        BIF_ERROR(BIF_P, BADARG);
 
1242
    }
 
1243
 
 
1244
    erts_smp_rwmtx_rwlock(lck1);
 
1245
    if (lck2)
 
1246
        erts_smp_rwmtx_rwlock(lck2);
 
1247
 
 
1248
    tb = db_get_table_aux(BIF_P, BIF_ARG_1, DB_WRITE, LCK_WRITE, 1);
 
1249
    if (!tb)
1148
1250
        goto badarg;
1149
 
    }
1150
1251
 
1151
1252
    if (is_not_atom(tb->common.id)) { /* Not a named table */
1152
1253
        tb->common.the_name = BIF_ARG_2;
1153
1254
        goto done;
1154
1255
    }
1155
1256
 
1156
 
    if (!insert_named_tab(BIF_ARG_2,tb)) {
 
1257
    if (!insert_named_tab(BIF_ARG_2, tb, 1))
1157
1258
        goto badarg;
1158
 
    }
1159
 
    if (!remove_named_tab(tb->common.id)) {
 
1259
 
 
1260
    if (!remove_named_tab(tb, 1))
1160
1261
        erl_exit(1,"Could not find named tab %s", tb->common.id);
1161
 
    }
1162
1262
 
1163
1263
    tb->common.id = tb->common.the_name = BIF_ARG_2;
1164
1264
 
1165
1265
 done:
1166
1266
    ret = tb->common.id;
1167
1267
    db_unlock(tb, LCK_WRITE);
 
1268
    erts_smp_rwmtx_rwunlock(lck1);
 
1269
    if (lck2)
 
1270
        erts_smp_rwmtx_rwunlock(lck2);
1168
1271
    BIF_RET(ret);
1169
1272
 badarg:
1170
 
    db_unlock(tb, LCK_WRITE);
 
1273
    if (tb)
 
1274
        db_unlock(tb, LCK_WRITE);
 
1275
    erts_smp_rwmtx_rwunlock(lck1);
 
1276
    if (lck2)
 
1277
        erts_smp_rwmtx_rwunlock(lck2);
1171
1278
    BIF_ERROR(BIF_P, BADARG);    
1172
1279
}
1173
1280
 
1185
1292
    Eterm val;
1186
1293
    Eterm ret;
1187
1294
    Eterm heir;
1188
 
    Eterm heir_data;
 
1295
    UWord heir_data;
1189
1296
    Uint32 status;
1190
1297
    Sint keypos;
1191
 
    int is_named, is_fine_locked;
 
1298
    int is_named, is_fine_locked, frequent_read, is_compressed;
1192
1299
    int cret;
1193
 
    Eterm meta_tuple[3];
 
1300
    DeclareTmpHeap(meta_tuple,3,BIF_P);
1194
1301
    DbTableMethod* meth;
 
1302
    erts_smp_rwmtx_t *mmtl;
1195
1303
 
1196
1304
    if (is_not_atom(BIF_ARG_1)) {
1197
1305
        BIF_ERROR(BIF_P, BADARG);
1204
1312
    keypos = 1;
1205
1313
    is_named = 0;
1206
1314
    is_fine_locked = 0;
 
1315
    frequent_read = 0;
1207
1316
    heir = am_none;
1208
 
    heir_data = am_undefined;
 
1317
    heir_data = (UWord) am_undefined;
 
1318
    is_compressed = erts_ets_always_compress;
1209
1319
 
1210
1320
    list = BIF_ARG_2;
1211
1321
    while(is_list(list)) {
1237
1347
                        is_fine_locked = 0;
1238
1348
                    } else break;
1239
1349
                }
 
1350
                else if (tp[1] == am_read_concurrency) {
 
1351
                    if (tp[2] == am_true) {
 
1352
                        frequent_read = 1;
 
1353
                    } else if (tp[2] == am_false) {
 
1354
                        frequent_read = 0;
 
1355
                    } else break;
 
1356
                }
1240
1357
                else if (tp[1] == am_heir && tp[2] == am_none) {
1241
1358
                    heir = am_none;
1242
1359
                    heir_data = am_undefined;
1261
1378
        else if (val == am_named_table) {
1262
1379
            is_named = 1;
1263
1380
        }
 
1381
        else if (val == am_compressed) {
 
1382
            is_compressed = 1;
 
1383
        }
1264
1384
        else if (val == am_set || val == am_protected)
1265
1385
            ;
1266
1386
        else break;
1285
1405
        BIF_ERROR(BIF_P, BADARG);
1286
1406
    }
1287
1407
 
 
1408
#ifdef ERTS_SMP
 
1409
    if (frequent_read && !(status & DB_PRIVATE))
 
1410
        status |= DB_FREQ_READ;
 
1411
#endif
 
1412
 
1288
1413
    /* we create table outside any table lock
1289
1414
     * and take the unusal cost of destroy table if it
1290
1415
     * fails to find a slot 
1307
1432
    tb->common.type = status & ERTS_ETS_TABLE_TYPES;
1308
1433
    /* Note, 'type' is *read only* from now on... */
1309
1434
#endif
1310
 
    db_init_lock(tb, "db_tab", "db_tab_fix");
 
1435
    erts_refc_init(&tb->common.ref, 0);
 
1436
    db_init_lock(tb, status & (DB_FINE_LOCKED|DB_FREQ_READ),
 
1437
                 "db_tab", "db_tab_fix");
1311
1438
    tb->common.keypos = keypos;
1312
1439
    tb->common.owner = BIF_P->id;
1313
1440
    set_heir(BIF_P, tb, heir, heir_data);
1315
1442
    erts_smp_atomic_init(&tb->common.nitems, 0);
1316
1443
 
1317
1444
    tb->common.fixations = NULL;
 
1445
    tb->common.compress = is_compressed;
1318
1446
 
1319
1447
    cret = meth->db_create(BIF_P, tb);
1320
1448
    ASSERT(cret == DB_ERROR_NONE);
1327
1455
                                      "** Too many db tables **\n");
1328
1456
        free_heir_data(tb);
1329
1457
        tb->common.meth->db_free_table(tb);
1330
 
        erts_db_free(ERTS_ALC_T_DB_TABLE, tb, (void *) tb, sizeof(DbTable));
1331
 
        ERTS_ETS_MISC_MEM_ADD(-sizeof(DbTable));
 
1458
        free_dbtable(tb);
1332
1459
        BIF_ERROR(BIF_P, SYSTEM_LIMIT);
1333
1460
    }
1334
1461
 
1350
1477
    tb->common.id = ret;
1351
1478
    tb->common.slot = slot;           /* store slot for erase */
1352
1479
 
1353
 
    meta_main_tab_lock(slot);
 
1480
    mmtl = get_meta_main_tab_lock(slot);
 
1481
    erts_smp_rwmtx_rwlock(mmtl);
1354
1482
    meta_main_tab[slot].u.tb = tb;
1355
1483
    ASSERT(IS_SLOT_ALIVE(slot));
1356
 
    meta_main_tab_unlock(slot);
 
1484
    erts_smp_rwmtx_rwunlock(mmtl);
1357
1485
 
1358
 
    if (is_named && !insert_named_tab(BIF_ARG_1, tb)) {
1359
 
        meta_main_tab_lock(slot);
 
1486
    if (is_named && !insert_named_tab(BIF_ARG_1, tb, 0)) {
 
1487
        mmtl = get_meta_main_tab_lock(slot);
 
1488
        erts_smp_rwmtx_rwlock(mmtl);
1360
1489
        free_slot(slot);
1361
 
        meta_main_tab_unlock(slot);
 
1490
        erts_smp_rwmtx_rwunlock(mmtl);
1362
1491
 
1363
 
        db_lock_take_over_ref(tb,LCK_WRITE);
 
1492
        db_lock(tb,LCK_WRITE);
1364
1493
        free_heir_data(tb);
1365
1494
        tb->common.meth->db_free_table(tb);
 
1495
        schedule_free_dbtable(tb);
1366
1496
        db_unlock(tb,LCK_WRITE);
1367
1497
        BIF_ERROR(BIF_P, BADARG);
1368
1498
    }
1380
1510
                     erts_smp_atomic_read(&meta_pid_to_fixed_tab->common.memory_size));
1381
1511
#endif
1382
1512
 
 
1513
    UseTmpHeap(3,BIF_P);
 
1514
 
1383
1515
    db_meta_lock(meta_pid_to_tab, LCK_WRITE_REC);
1384
1516
    if (db_put_hash(meta_pid_to_tab,
1385
1517
                    TUPLE2(meta_tuple, BIF_P->id, make_small(slot)),
1388
1520
    }
1389
1521
    db_meta_unlock(meta_pid_to_tab, LCK_WRITE_REC);
1390
1522
 
 
1523
    UnUseTmpHeap(3,BIF_P);
 
1524
 
1391
1525
    BIF_RET(ret);
1392
1526
}
1393
1527
 
1494
1628
{
1495
1629
    int trap;
1496
1630
    DbTable* tb;
 
1631
    erts_smp_rwmtx_t *mmtl;
1497
1632
 
1498
1633
#ifdef HARDDEBUG
1499
1634
    erts_fprintf(stderr,
1515
1650
    tb->common.status &= ~(DB_PROTECTED|DB_PUBLIC|DB_PRIVATE);
1516
1651
    tb->common.status |= DB_DELETE;
1517
1652
 
1518
 
    meta_main_tab_lock(tb->common.slot);
 
1653
    mmtl = get_meta_main_tab_lock(tb->common.slot);
 
1654
#ifdef ERTS_SMP
 
1655
    if (erts_smp_rwmtx_tryrwlock(mmtl) == EBUSY) {
 
1656
        /*
 
1657
         * We keep our increased refc over this op in order to
 
1658
         * prevent the table from disapearing.
 
1659
         */
 
1660
        erts_smp_rwmtx_rwunlock(&tb->common.rwlock);
 
1661
        erts_smp_rwmtx_rwlock(mmtl);
 
1662
        erts_smp_rwmtx_rwlock(&tb->common.rwlock);
 
1663
    }
 
1664
#endif
1519
1665
    /* We must keep the slot, to be found by db_proc_dead() if process dies */
1520
1666
    MARK_SLOT_DEAD(tb->common.slot);
1521
 
    meta_main_tab_unlock(tb->common.slot);
1522
 
    if (is_atom(tb->common.id)) {
1523
 
        remove_named_tab(tb->common.id);
1524
 
    }
 
1667
    erts_smp_rwmtx_rwunlock(mmtl);
 
1668
    if (is_atom(tb->common.id))
 
1669
        remove_named_tab(tb, 0);
1525
1670
    
1526
1671
    if (tb->common.owner != BIF_P->id) {
1527
 
        Eterm meta_tuple[3];
 
1672
        DeclareTmpHeap(meta_tuple,3,BIF_P);
1528
1673
 
1529
1674
        /*
1530
1675
         * The table is being deleted by a process other than its owner.
1532
1677
         * current process will be killed (e.g. by an EXIT signal), we will
1533
1678
         * now transfer the ownership to the current process.
1534
1679
         */
 
1680
        UseTmpHeap(3,BIF_P);
1535
1681
        db_meta_lock(meta_pid_to_tab, LCK_WRITE_REC);
1536
1682
        db_erase_bag_exact2(meta_pid_to_tab, tb->common.owner,
1537
1683
                            make_small(tb->common.slot));
1543
1689
                    TUPLE2(meta_tuple,BIF_P->id,make_small(tb->common.slot)),
1544
1690
                    0);
1545
1691
        db_meta_unlock(meta_pid_to_tab, LCK_WRITE_REC);
 
1692
        UnUseTmpHeap(3,BIF_P);
1546
1693
    }    
1547
1694
    /* disable inheritance */
1548
1695
    free_heir_data(tb);
1559
1706
         * (it looks like an continuation pointer), but that is will crash the
1560
1707
         * emulator if this BIF is call traced.
1561
1708
         */
 
1709
#if HALFWORD_HEAP
 
1710
        Eterm *hp = HAlloc(BIF_P, 3);
 
1711
        hp[0] = make_pos_bignum_header(2);
 
1712
        *((UWord *) (UWord) (hp+1)) = (UWord) tb;
 
1713
#else
1562
1714
        Eterm *hp = HAlloc(BIF_P, 2);
1563
1715
        hp[0] = make_pos_bignum_header(1);
1564
1716
        hp[1] = (Eterm) tb;
 
1717
#endif
1565
1718
        BIF_TRAP1(&ets_delete_continue_exp, BIF_P, make_big(hp));
1566
1719
    }
1567
1720
    else {
1576
1729
{
1577
1730
    Process* to_proc = NULL;
1578
1731
    ErtsProcLocks to_locks = ERTS_PROC_LOCK_MAIN;
1579
 
    Eterm buf[5];
 
1732
    DeclareTmpHeap(buf,5,BIF_P);
1580
1733
    Eterm to_pid = BIF_ARG_2;
1581
1734
    Eterm from_pid;
1582
1735
    DbTable* tb = NULL;
1598
1751
        goto badarg;  /* or should we be idempotent? return false maybe */
1599
1752
    }
1600
1753
 
 
1754
    UseTmpHeap(5,BIF_P);
1601
1755
    db_meta_lock(meta_pid_to_tab, LCK_WRITE_REC);
1602
1756
    db_erase_bag_exact2(meta_pid_to_tab, tb->common.owner,
1603
1757
                        make_small(tb->common.slot));
1615
1769
                      TUPLE4(buf, am_ETS_TRANSFER, tb->common.id, from_pid, BIF_ARG_3), 
1616
1770
                      0);
1617
1771
    erts_smp_proc_unlock(to_proc, to_locks);
 
1772
    UnUseTmpHeap(5,BIF_P);
1618
1773
    BIF_RET(am_true);
1619
1774
 
1620
1775
badarg:
1629
1784
    Eterm* tp;
1630
1785
    Eterm opt;
1631
1786
    Eterm heir = THE_NON_VALUE;
1632
 
    Eterm heir_data = THE_NON_VALUE;
 
1787
    UWord heir_data = (UWord) THE_NON_VALUE;
1633
1788
    Uint32 protection = 0;
1634
 
    Eterm fakelist[2];
 
1789
    DeclareTmpHeap(fakelist,2,BIF_P);
1635
1790
    Eterm tail;
1636
1791
 
 
1792
    UseTmpHeap(2,BIF_P);
1637
1793
    for (tail = is_tuple(BIF_ARG_2) ? CONS(fakelist, BIF_ARG_2, NIL) : BIF_ARG_2;       
1638
1794
          is_list(tail);
1639
1795
          tail = CDR(list_val(tail))) {
1686
1842
    }
1687
1843
 
1688
1844
    db_unlock (tb,LCK_WRITE);
 
1845
    UnUseTmpHeap(2,BIF_P);
1689
1846
    BIF_RET(am_true);
1690
1847
 
1691
1848
badarg:
 
1849
    UnUseTmpHeap(2,BIF_P);
1692
1850
    if (tb != NULL) {
1693
1851
        db_unlock(tb,LCK_WRITE);
1694
1852
    }
1901
2059
    previous = NIL;
1902
2060
    j = 0;
1903
2061
    for(i = 0; (i < t_max_tabs && j < t_tabs_cnt); i++) {
1904
 
        meta_main_tab_lock(i);
 
2062
        erts_smp_rwmtx_t *mmtl = get_meta_main_tab_lock(i);
 
2063
        erts_smp_rwmtx_rlock(mmtl);
1905
2064
        if (IS_SLOT_ALIVE(i)) {
1906
2065
            j++;
1907
2066
            tb = meta_main_tab[i].u.tb;
1908
2067
            previous = CONS(hp, tb->common.id, previous);
1909
2068
            hp += 2;
1910
2069
        }
1911
 
        meta_main_tab_unlock(i);
 
2070
        erts_smp_rwmtx_runlock(mmtl);
1912
2071
    }
1913
2072
    HRelease(BIF_P, hendp, hp);
1914
2073
    BIF_RET(previous);
1954
2113
BIF_RETTYPE ets_match_2(BIF_ALIST_2)
1955
2114
{
1956
2115
    Eterm ms;
1957
 
    Eterm buff[8];
 
2116
    DeclareTmpHeap(buff,8,BIF_P);
1958
2117
    Eterm *hp = buff;
1959
 
    /*hp = HAlloc(BIF_P, 8);*/
 
2118
    Eterm res;
 
2119
 
 
2120
    UseTmpHeap(8,BIF_P);
1960
2121
    ms = CONS(hp, am_DollarDollar, NIL);
1961
2122
    hp += 2;
1962
2123
    ms = TUPLE3(hp, BIF_ARG_2, NIL, ms); 
1963
2124
    hp += 4;
1964
2125
    ms = CONS(hp, ms, NIL);
1965
 
    return ets_select_2(BIF_P, BIF_ARG_1, ms);
 
2126
    res = ets_select_2(BIF_P, BIF_ARG_1, ms);
 
2127
    UnUseTmpHeap(8,BIF_P);
 
2128
    return res;
1966
2129
}
1967
2130
 
1968
2131
BIF_RETTYPE ets_match_3(BIF_ALIST_3)
1969
2132
{
1970
2133
    Eterm ms;
1971
 
    Eterm buff[8];
 
2134
    DeclareTmpHeap(buff,8,BIF_P);
1972
2135
    Eterm *hp = buff;
1973
 
    /*hp = HAlloc(BIF_P, 8);*/
 
2136
    Eterm res;
 
2137
 
 
2138
    UseTmpHeap(8,BIF_P);
1974
2139
    ms = CONS(hp, am_DollarDollar, NIL);
1975
2140
    hp += 2;
1976
2141
    ms = TUPLE3(hp, BIF_ARG_2, NIL, ms); 
1977
2142
    hp += 4;
1978
2143
    ms = CONS(hp, ms, NIL);
1979
 
    return ets_select_3(BIF_P, BIF_ARG_1, ms, BIF_ARG_3);
 
2144
    res = ets_select_3(BIF_P, BIF_ARG_1, ms, BIF_ARG_3);
 
2145
    UnUseTmpHeap(8,BIF_P);
 
2146
    return res;
1980
2147
}
1981
2148
 
1982
2149
 
2390
2557
BIF_RETTYPE ets_match_object_2(BIF_ALIST_2)
2391
2558
{
2392
2559
    Eterm ms;
2393
 
    Eterm buff[8];
 
2560
    DeclareTmpHeap(buff,8,BIF_P);
2394
2561
    Eterm *hp = buff;
2395
 
    /*hp = HAlloc(BIF_P, 8);*/
 
2562
    Eterm res;
 
2563
 
 
2564
    UseTmpHeap(8,BIF_P);
2396
2565
    ms = CONS(hp, am_DollarUnderscore, NIL);
2397
2566
    hp += 2;
2398
2567
    ms = TUPLE3(hp, BIF_ARG_2, NIL, ms); 
2399
2568
    hp += 4;
2400
2569
    ms = CONS(hp, ms, NIL);
2401
 
    return ets_select_2(BIF_P, BIF_ARG_1, ms);
 
2570
    res = ets_select_2(BIF_P, BIF_ARG_1, ms);
 
2571
    UnUseTmpHeap(8,BIF_P);
 
2572
    return res;
2402
2573
}
2403
2574
 
2404
2575
BIF_RETTYPE ets_match_object_3(BIF_ALIST_3)
2405
2576
{
2406
2577
    Eterm ms;
2407
 
    Eterm buff[8];
 
2578
    DeclareTmpHeap(buff,8,BIF_P);
2408
2579
    Eterm *hp = buff;
2409
 
    /*hp = HAlloc(BIF_P, 8);*/
 
2580
    Eterm res;
 
2581
 
 
2582
    UseTmpHeap(8,BIF_P);
2410
2583
    ms = CONS(hp, am_DollarUnderscore, NIL);
2411
2584
    hp += 2;
2412
2585
    ms = TUPLE3(hp, BIF_ARG_2, NIL, ms); 
2413
2586
    hp += 4;
2414
2587
    ms = CONS(hp, ms, NIL);
2415
 
    return ets_select_3(BIF_P, BIF_ARG_1, ms, BIF_ARG_3);
 
2588
    res = ets_select_3(BIF_P, BIF_ARG_1, ms, BIF_ARG_3);
 
2589
    UnUseTmpHeap(8,BIF_P);
 
2590
    return res;
2416
2591
}
2417
2592
 
2418
2593
/* 
2422
2597
BIF_RETTYPE ets_info_1(BIF_ALIST_1)
2423
2598
{
2424
2599
    static Eterm fields[] = {am_protection, am_keypos, am_type, am_named_table,
2425
 
        am_node, am_size, am_name, am_heir, am_owner, am_memory};
 
2600
        am_node, am_size, am_name, am_heir, am_owner, am_memory, am_compressed};
2426
2601
    Eterm results[sizeof(fields)/sizeof(Eterm)];
2427
2602
    DbTable* tb;
2428
2603
    Eterm res;
2538
2713
    Binary *mp;
2539
2714
    Eterm res;
2540
2715
    Uint32 dummy;
2541
 
    Uint sz;
2542
2716
 
2543
2717
    if (!(is_list(BIF_ARG_1) || BIF_ARG_1 == NIL) || !is_binary(BIF_ARG_2)) {
2544
2718
    error:
2563
2737
            BIF_TRAP3(bif_export[BIF_ets_match_spec_run_r_3],
2564
2738
                      BIF_P,lst,BIF_ARG_2,ret);
2565
2739
        }
2566
 
        res = db_prog_match(BIF_P, mp, CAR(list_val(lst)), 0, &dummy);
 
2740
        res = db_prog_match(BIF_P, mp, CAR(list_val(lst)), NULL, NULL, 0,
 
2741
                            ERTS_PAM_COPY_RESULT, &dummy);
2567
2742
        if (is_value(res)) {
2568
 
            sz = size_object(res);
2569
 
            hp = HAlloc(BIF_P, sz + 2);
2570
 
            res = copy_struct(res, sz, &hp, &MSO(BIF_P));
 
2743
            hp = HAlloc(BIF_P, 2);
2571
2744
            ret = CONS(hp,res,ret);
2572
2745
            /*hp += 2;*/
2573
2746
        } 
2590
2763
{
2591
2764
    DbTable init_tb;
2592
2765
    int i;
2593
 
    extern Eterm* em_apply_bif;
 
2766
    extern BeamInstr* em_apply_bif;
2594
2767
    Eterm *hp;
2595
2768
    unsigned bits;
2596
2769
    size_t size;
2597
2770
 
2598
2771
#ifdef ERTS_SMP
2599
 
    for (i=0; i<META_MAIN_TAB_LOCK_CNT; i++) {
2600
 
#ifdef ERTS_ENABLE_LOCK_COUNT
2601
 
        erts_smp_spinlock_init_x(&meta_main_tab_locks[i].lck, "meta_main_tab_slot", make_small(i));
2602
 
#else
2603
 
        erts_smp_spinlock_init(&meta_main_tab_locks[i].lck, "meta_main_tab_slot");
2604
 
#endif
 
2772
    erts_smp_rwmtx_opt_t rwmtx_opt = ERTS_SMP_RWMTX_OPT_DEFAULT_INITER;
 
2773
    rwmtx_opt.type = ERTS_SMP_RWMTX_TYPE_FREQUENT_READ;
 
2774
    rwmtx_opt.lived = ERTS_SMP_RWMTX_LONG_LIVED;
 
2775
 
 
2776
    meta_main_tab_locks =
 
2777
        erts_alloc_permanent_cache_aligned(ERTS_ALC_T_DB_TABLES,
 
2778
                                           sizeof(erts_meta_main_tab_lock_t)
 
2779
                                           * ERTS_META_MAIN_TAB_LOCK_TAB_SIZE);
 
2780
 
 
2781
    for (i = 0; i < ERTS_META_MAIN_TAB_LOCK_TAB_SIZE; i++) {
 
2782
        erts_smp_rwmtx_init_opt_x(&meta_main_tab_locks[i].rwmtx, &rwmtx_opt,
 
2783
                                  "meta_main_tab_slot", make_small(i));
2605
2784
    }
2606
2785
    erts_smp_spinlock_init(&meta_main_tab_main_lock, "meta_main_tab_main");
2607
2786
    for (i=0; i<META_NAME_TAB_LOCK_CNT; i++) {
2608
 
#ifdef ERTS_ENABLE_LOCK_COUNT
2609
 
        erts_smp_rwmtx_init_x(&meta_name_tab_rwlocks[i].lck, "meta_name_tab", make_small(i));
2610
 
#else
2611
 
        erts_smp_rwmtx_init(&meta_name_tab_rwlocks[i].lck, "meta_name_tab");
2612
 
#endif
 
2787
        erts_smp_rwmtx_init_opt_x(&meta_name_tab_rwlocks[i].lck, &rwmtx_opt,
 
2788
                                  "meta_name_tab", make_small(i));
2613
2789
    }
2614
2790
#endif
2615
2791
 
2677
2853
    erts_smp_atomic_init(&meta_pid_to_tab->common.nitems, 0);
2678
2854
    meta_pid_to_tab->common.slot   = -1;
2679
2855
    meta_pid_to_tab->common.meth   = &db_hash;
 
2856
    meta_pid_to_tab->common.compress = 0;
2680
2857
 
2681
 
    erts_refc_init(&meta_pid_to_tab->common.ref, 1);
2682
 
    erts_refc_init(&meta_pid_to_tab->common.fixref, 0);
 
2858
    erts_refc_init(&meta_pid_to_tab->common.ref, 0);
2683
2859
    /* Neither rwlock or fixlock used
2684
2860
    db_init_lock(meta_pid_to_tab, "meta_pid_to_tab", "meta_pid_to_tab_FIX");*/
2685
2861
 
2709
2885
    erts_smp_atomic_init(&meta_pid_to_fixed_tab->common.nitems, 0);
2710
2886
    meta_pid_to_fixed_tab->common.slot   = -1;
2711
2887
    meta_pid_to_fixed_tab->common.meth   = &db_hash;
 
2888
    meta_pid_to_fixed_tab->common.compress = 0;
2712
2889
 
2713
 
    erts_refc_init(&meta_pid_to_fixed_tab->common.ref, 1);
2714
 
    erts_refc_init(&meta_pid_to_fixed_tab->common.fixref, 0);
 
2890
    erts_refc_init(&meta_pid_to_fixed_tab->common.ref, 0);
2715
2891
    /* Neither rwlock or fixlock used
2716
2892
    db_init_lock(meta_pid_to_fixed_tab, "meta_pid_to_fixed_tab", "meta_pid_to_fixed_tab_FIX");*/
2717
2893
 
2727
2903
    ets_select_delete_continue_exp.code[1] = am_atom_put("delete_trap",11);
2728
2904
    ets_select_delete_continue_exp.code[2] = 1;
2729
2905
    ets_select_delete_continue_exp.code[3] =
2730
 
        (Eterm) em_apply_bif;
 
2906
        (BeamInstr) em_apply_bif;
2731
2907
    ets_select_delete_continue_exp.code[4] = 
2732
 
        (Eterm) &ets_select_delete_1;
 
2908
        (BeamInstr) &ets_select_delete_1;
2733
2909
 
2734
2910
    /* Non visual BIF to trap to. */
2735
2911
    memset(&ets_select_count_continue_exp, 0, sizeof(Export));
2739
2915
    ets_select_count_continue_exp.code[1] = am_atom_put("count_trap",11);
2740
2916
    ets_select_count_continue_exp.code[2] = 1;
2741
2917
    ets_select_count_continue_exp.code[3] =
2742
 
        (Eterm) em_apply_bif;
 
2918
        (BeamInstr) em_apply_bif;
2743
2919
    ets_select_count_continue_exp.code[4] = 
2744
 
        (Eterm) &ets_select_count_1;
 
2920
        (BeamInstr) &ets_select_count_1;
2745
2921
 
2746
2922
    /* Non visual BIF to trap to. */
2747
2923
    memset(&ets_select_continue_exp, 0, sizeof(Export));
2751
2927
    ets_select_continue_exp.code[1] = am_atom_put("select_trap",11);
2752
2928
    ets_select_continue_exp.code[2] = 1;
2753
2929
    ets_select_continue_exp.code[3] =
2754
 
        (Eterm) em_apply_bif;
 
2930
        (BeamInstr) em_apply_bif;
2755
2931
    ets_select_continue_exp.code[4] = 
2756
 
        (Eterm) &ets_select_trap_1;
 
2932
        (BeamInstr) &ets_select_trap_1;
2757
2933
 
2758
2934
    /* Non visual BIF to trap to. */
2759
2935
    memset(&ets_delete_continue_exp, 0, sizeof(Export));
2761
2937
    ets_delete_continue_exp.code[0] = am_ets;
2762
2938
    ets_delete_continue_exp.code[1] = am_atom_put("delete_trap",11);
2763
2939
    ets_delete_continue_exp.code[2] = 1;
2764
 
    ets_delete_continue_exp.code[3] = (Eterm) em_apply_bif;
2765
 
    ets_delete_continue_exp.code[4] = (Eterm) &ets_delete_trap;
 
2940
    ets_delete_continue_exp.code[3] = (BeamInstr) em_apply_bif;
 
2941
    ets_delete_continue_exp.code[4] = (BeamInstr) &ets_delete_trap;
2766
2942
 
2767
2943
    hp = ms_delete_all_buff;
2768
2944
    ms_delete_all = CONS(hp, am_true, NIL);
2856
3032
{
2857
3033
    Process* to_proc;
2858
3034
    ErtsProcLocks to_locks = ERTS_PROC_LOCK_MAIN;
2859
 
    Eterm buf[5];
 
3035
    DeclareTmpHeap(buf,5,p);
2860
3036
    Eterm to_pid;
2861
 
    Eterm heir_data;
 
3037
    UWord heir_data;
2862
3038
 
2863
3039
    ASSERT(tb->common.owner == p->id);
2864
3040
    ASSERT(is_internal_pid(tb->common.heir));
2869
3045
                                to_pid, to_locks,
2870
3046
                                ERTS_P2P_FLG_TRY_LOCK);
2871
3047
    if (to_proc == ERTS_PROC_LOCK_BUSY) {
2872
 
        db_ref(tb); /* while unlocked */
2873
3048
        db_unlock(tb,LCK_WRITE);    
2874
3049
        to_proc = erts_pid2proc(p, ERTS_PROC_LOCK_MAIN,
2875
3050
                                to_pid, to_locks);    
2876
3051
        db_lock(tb,LCK_WRITE);
2877
 
        tb = db_unref(tb);
2878
3052
        ASSERT(tb != NULL);
2879
3053
    
2880
3054
        if (tb->common.owner != p->id) {
2901
3075
        erts_smp_proc_unlock(to_proc, to_locks);
2902
3076
        return 0; /* heir dead and pid reused, table still mine */
2903
3077
    }
 
3078
    UseTmpHeap(5,p);
2904
3079
    db_meta_lock(meta_pid_to_tab, LCK_WRITE_REC);
2905
3080
    db_erase_bag_exact2(meta_pid_to_tab, tb->common.owner,
2906
3081
                        make_small(tb->common.slot));
2912
3087
                TUPLE2(buf,to_pid,make_small(tb->common.slot)),
2913
3088
                0);
2914
3089
    db_meta_unlock(meta_pid_to_tab, LCK_WRITE_REC);
2915
 
    
 
3090
    UnUseTmpHeap(5,p);
2916
3091
    db_unlock(tb,LCK_WRITE);
2917
3092
    heir_data = tb->common.heir_data;
2918
3093
    if (!is_immed(heir_data)) {
2919
 
        Eterm* tpv = DBTERM_BUF((DbTerm*)heir_data); /* tuple_val */
 
3094
        Eterm* tpv = ((DbTerm*)heir_data)->tpl; /* tuple_val */
2920
3095
        ASSERT(arityval(*tpv) == 1);
2921
3096
        heir_data = tpv[1];
2922
3097
    }
2981
3156
            while (state->slots.ix < state->slots.size) {
2982
3157
                DbTable *tb = NULL;
2983
3158
                Sint ix = unsigned_val(state->slots.arr[state->slots.ix]);
2984
 
                meta_main_tab_lock(ix);
 
3159
                erts_smp_rwmtx_t *mmtl = get_meta_main_tab_lock(ix);
 
3160
                erts_smp_rwmtx_rlock(mmtl);
2985
3161
                if (!IS_SLOT_FREE(ix)) {
2986
 
                    tb = db_ref(GET_ANY_SLOT_TAB(ix));
 
3162
                    tb = GET_ANY_SLOT_TAB(ix);
2987
3163
                    ASSERT(tb);
2988
3164
                }
2989
 
                meta_main_tab_unlock(ix);
 
3165
                erts_smp_rwmtx_runlock(mmtl);
2990
3166
                if (tb) {
2991
3167
                    int do_yield;
2992
 
                    db_lock_take_over_ref(tb, LCK_WRITE);
 
3168
                    db_lock(tb, LCK_WRITE);
2993
3169
                    /* Ownership may have changed since
2994
3170
                       we looked up the table. */
2995
3171
                    if (tb->common.owner != pid) {
3018
3194
                            tb->common.status |= DB_DELETE;
3019
3195
 
3020
3196
                            if (is_atom(tb->common.id))
3021
 
                                remove_named_tab(tb->common.id);
 
3197
                                remove_named_tab(tb, 0);
3022
3198
 
3023
3199
                            free_heir_data(tb);
3024
3200
                            free_fixations_locked(tb);
3068
3244
            while (state->slots.ix < state->slots.size) {
3069
3245
                DbTable *tb = NULL;
3070
3246
                Sint ix = unsigned_val(state->slots.arr[state->slots.ix]);
3071
 
                meta_main_tab_lock(ix);
 
3247
                erts_smp_rwmtx_t *mmtl = get_meta_main_tab_lock(ix);
 
3248
                erts_smp_rwmtx_rlock(mmtl);
3072
3249
                if (IS_SLOT_ALIVE(ix)) {
3073
 
                    tb = db_ref(meta_main_tab[ix].u.tb);
 
3250
                    tb = meta_main_tab[ix].u.tb;
3074
3251
                    ASSERT(tb);
3075
3252
                }
3076
 
                meta_main_tab_unlock(ix);
 
3253
                erts_smp_rwmtx_runlock(mmtl);
3077
3254
                if (tb) {
3078
3255
                    int reds;
3079
3256
                    DbFixation** pp;
3080
3257
 
3081
 
                    db_lock_take_over_ref(tb, LCK_WRITE_REC);
 
3258
                    db_lock(tb, LCK_WRITE_REC);
3082
3259
                    #ifdef ERTS_SMP
3083
3260
                    erts_smp_mtx_lock(&tb->common.fixlock);
3084
3261
                    #endif
3088
3265
                          pp = &(*pp)->next) {
3089
3266
                        if ((*pp)->pid == pid) {
3090
3267
                            DbFixation* fix = *pp;
3091
 
                            erts_refc_add(&tb->common.fixref,-fix->counter,0);
 
3268
                            erts_aint_t diff = -((erts_aint_t) fix->counter);
 
3269
                            erts_refc_add(&tb->common.ref,diff,0);
3092
3270
                            *pp = fix->next;
3093
3271
                            erts_db_free(ERTS_ALC_T_DB_FIXATION,
3094
3272
                                         tb, fix, sizeof(DbFixation));
3158
3336
static void fix_table_locked(Process* p, DbTable* tb)
3159
3337
{
3160
3338
    DbFixation *fix;
3161
 
    Eterm meta_tuple[3];
 
3339
    DeclareTmpHeap(meta_tuple,3,p);
3162
3340
 
3163
3341
#ifdef ERTS_SMP
3164
3342
    erts_smp_mtx_lock(&tb->common.fixlock);
3165
3343
#endif
3166
 
    erts_refc_inc(&tb->common.fixref,1);
 
3344
    erts_refc_inc(&tb->common.ref,1);
3167
3345
    fix = tb->common.fixations;
3168
3346
    if (fix == NULL) { 
3169
3347
        get_now(&(tb->common.megasec),
3192
3370
    erts_smp_mtx_unlock(&tb->common.fixlock);
3193
3371
#endif
3194
3372
    p->flags |= F_USING_DB;        
 
3373
    UseTmpHeap(3,p);
3195
3374
    db_meta_lock(meta_pid_to_fixed_tab, LCK_WRITE_REC);
3196
3375
    if (db_put_hash(meta_pid_to_fixed_tab,
3197
3376
                    TUPLE2(meta_tuple, p->id, make_small(tb->common.slot)),
3198
3377
                    0) != DB_ERROR_NONE) {
 
3378
        UnUseTmpHeap(3,p);
3199
3379
        erl_exit(1,"Could not insert ets metadata in safe_fixtable.");
3200
3380
    }   
 
3381
    UnUseTmpHeap(3,p);
3201
3382
    db_meta_unlock(meta_pid_to_fixed_tab, LCK_WRITE_REC);
3202
3383
}
3203
3384
 
3214
3395
    for (pp = &tb->common.fixations; *pp != NULL; pp = &(*pp)->next) {
3215
3396
        if ((*pp)->pid == p->id) {
3216
3397
            DbFixation* fix = *pp;
3217
 
            erts_refc_dec(&tb->common.fixref,0);
 
3398
            erts_refc_dec(&tb->common.ref,0);
3218
3399
            --(fix->counter);
3219
3400
            ASSERT(fix->counter >= 0);
3220
3401
            if (fix->counter > 0) {
3240
3421
unlocked:
3241
3422
 
3242
3423
    if (!IS_FIXED(tb) && IS_HASH_TABLE(tb->common.status)
3243
 
        && erts_smp_atomic_read(&tb->hash.fixdel) != (long)NULL) {
 
3424
        && erts_smp_atomic_read(&tb->hash.fixdel) != (erts_aint_t)NULL) {
3244
3425
#ifdef ERTS_SMP
3245
3426
        if (*kind_p == LCK_READ && tb->common.is_thread_safe) {
3246
3427
            /* Must have write lock while purging pseudo-deleted (OTP-8166) */
3262
3443
 
3263
3444
    fix = tb->common.fixations;
3264
3445
    while (fix != NULL) {
 
3446
        erts_aint_t diff = -((erts_aint_t) fix->counter);
 
3447
        erts_refc_add(&tb->common.ref,diff,0);
3265
3448
        next_fix = fix->next;
3266
3449
        db_meta_lock(meta_pid_to_fixed_tab, LCK_WRITE_REC);
3267
3450
        db_erase_bag_exact2(meta_pid_to_fixed_tab,
3277
3460
    tb->common.fixations = NULL;
3278
3461
}
3279
3462
 
3280
 
static void set_heir(Process* me, DbTable* tb, Eterm heir, Eterm heir_data)
 
3463
static void set_heir(Process* me, DbTable* tb, Eterm heir, UWord heir_data)
3281
3464
{       
3282
3465
    tb->common.heir = heir;
3283
3466
    if (heir == am_none) {
3298
3481
    }
3299
3482
 
3300
3483
    if (!is_immed(heir_data)) {
3301
 
        Eterm tmp[2];
3302
 
        /* Make a dummy 1-tuple around data to use db_get_term() */
3303
 
        heir_data = (Eterm) db_get_term(&tb->common, NULL, 0,
3304
 
                                        TUPLE1(tmp,heir_data));
 
3484
        DeclareTmpHeap(tmp,2,me);
 
3485
        Eterm wrap_tpl;
 
3486
        int size;
 
3487
        DbTerm* dbterm;
 
3488
        Eterm* top;
 
3489
        ErlOffHeap tmp_offheap;
 
3490
 
 
3491
        UseTmpHeap(2,me);
 
3492
        /* Make a dummy 1-tuple around data to use DbTerm */
 
3493
        wrap_tpl = TUPLE1(tmp,heir_data);
 
3494
        size = size_object(wrap_tpl);
 
3495
        dbterm = erts_db_alloc(ERTS_ALC_T_DB_HEIR_DATA, (DbTable *)tb,
 
3496
                               (sizeof(DbTerm) + sizeof(Eterm)*(size-1)));
 
3497
        dbterm->size = size;
 
3498
        top = dbterm->tpl;
 
3499
        tmp_offheap.first  = NULL;
 
3500
        copy_struct(wrap_tpl, size, &top, &tmp_offheap);
 
3501
        dbterm->first_oh = tmp_offheap.first;
 
3502
        heir_data = (UWord)dbterm;
 
3503
        UnUseTmpHeap(2,me);
3305
3504
        ASSERT(!is_immed(heir_data));
3306
3505
    }
3307
3506
    tb->common.heir_data = heir_data;
3311
3510
{
3312
3511
    if (tb->common.heir != am_none && !is_immed(tb->common.heir_data)) {
3313
3512
        DbTerm* p = (DbTerm*) tb->common.heir_data;
3314
 
        db_free_term_data(p);
3315
 
        erts_db_free(ERTS_ALC_T_DB_TERM, tb, (void *)p,
 
3513
        db_cleanup_offheap_comp(p);
 
3514
        erts_db_free(ERTS_ALC_T_DB_HEIR_DATA, tb, (void *)p,
3316
3515
                     sizeof(DbTerm) + (p->size-1)*sizeof(Eterm));
3317
3516
    }
3318
3517
    #ifdef DEBUG
3324
3523
{
3325
3524
    int trap;
3326
3525
    Eterm* ptr = big_val(cont);
3327
 
    DbTable *tb = (DbTable *) ptr[1];
 
3526
    DbTable *tb = *((DbTable **) (UWord) (ptr + 1));
3328
3527
 
 
3528
#if HALFWORD_HEAP
 
3529
    ASSERT(*ptr == make_pos_bignum_header(2));
 
3530
#else
3329
3531
    ASSERT(*ptr == make_pos_bignum_header(1));
3330
 
 
 
3532
#endif
3331
3533
    db_lock(tb, LCK_WRITE);
3332
3534
    trap = free_table_cont(p, tb, 0, 1);
3333
3535
    db_unlock(tb, LCK_WRITE);
3350
3552
                           int clean_meta_tab)
3351
3553
{
3352
3554
    Eterm result;
 
3555
    erts_smp_rwmtx_t *mmtl;
3353
3556
 
3354
3557
#ifdef HARDDEBUG
3355
3558
    if (!first) {
3375
3578
                     tb->common.id);
3376
3579
#endif
3377
3580
        /* Completely done - we will not get called again. */
3378
 
        meta_main_tab_lock(tb->common.slot);
 
3581
        mmtl = get_meta_main_tab_lock(tb->common.slot);
 
3582
#ifdef ERTS_SMP
 
3583
        if (erts_smp_rwmtx_tryrwlock(mmtl) == EBUSY) {
 
3584
            erts_smp_rwmtx_rwunlock(&tb->common.rwlock);
 
3585
            erts_smp_rwmtx_rwlock(mmtl);
 
3586
            erts_smp_rwmtx_rwlock(&tb->common.rwlock);
 
3587
        }
 
3588
#endif
3379
3589
        free_slot(tb->common.slot);
3380
 
        meta_main_tab_unlock(tb->common.slot);
 
3590
        erts_smp_rwmtx_rwunlock(mmtl);
3381
3591
 
3382
3592
        if (clean_meta_tab) {
3383
3593
            db_meta_lock(meta_pid_to_tab, LCK_WRITE_REC);
3385
3595
                                make_small(tb->common.slot));
3386
3596
            db_meta_unlock(meta_pid_to_tab, LCK_WRITE_REC);
3387
3597
        }
3388
 
        db_unref(tb);
 
3598
        schedule_free_dbtable(tb);
3389
3599
        BUMP_REDS(p, 100);
3390
3600
        return 0;
3391
3601
    }
3433
3643
        ret = erts_this_dist_entry->sysname;
3434
3644
    } else if (What == am_named_table) {
3435
3645
        ret = is_atom(tb->common.id) ? am_true : am_false;
 
3646
    } else if (What == am_compressed) {
 
3647
        ret = tb->common.compress ? am_true : am_false;
 
3648
    }
3436
3649
    /*
3437
3650
     * For debugging purposes
3438
3651
     */
3439
 
    } else if (What == am_data) { 
 
3652
    else if (What == am_data) {
3440
3653
        print_table(ERTS_PRINT_STDOUT, NULL, 1, tb);
3441
3654
        ret = am_true;
3442
3655
    } else if (What == am_atom_put("fixed",5)) {