~ubuntu-branches/ubuntu/lucid/erlang/lucid-updates

« back to all changes in this revision

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

  • Committer: Elliot Murphy
  • Date: 2009-12-22 02:56:21 UTC
  • mfrom: (3.3.5 sid)
  • Revision ID: elliot@elliotmurphy.com-20091222025621-qv3rja8gbpiabkbe
Tags: 1:13.b.3-dfsg-2ubuntu1
* Merge with Debian testing; remaining Ubuntu changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to. (LP #438365)
  - 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.
* Fixed dialyzer(1) manpage which was placed into section 3 and conflicted
  with dialyzer(3erl).
* New upstream release (it adds a new binary package erlang-erl-docgen).
* Refreshed patches, removed most of emacs.patch which is applied upstream.
* Linked run_test binary from erlang-common-test package to /usr/bin.
* Fixed VCS headers in debian/control.
* Moved from prebuilt manpages to generated from sources. This adds
  erlang-manpages binary package and xsltproc build dependency.

Show diffs side-by-side

added added

removed removed

Lines of Context:
101
101
#define SEGSZ   (1 << SEGSZ_EXP)
102
102
#define SEGSZ_MASK (SEGSZ-1)
103
103
 
104
 
#define NSEG_1     1 /* Size of first segment table */ 
 
104
#define NSEG_1     2 /* Size of first segment table (must be at least 2) */ 
105
105
#define NSEG_2   256 /* Size of second segment table */
106
106
#define NSEG_INC 128 /* Number of segments to grow after that */
107
107
 
304
304
};
305
305
 
306
306
/* A segment that also contains a segment table */
307
 
struct ext_segment {
 
307
struct ext_segment {    
308
308
    struct segment s; /* The segment itself. Must be first */
309
 
 
310
 
    struct segment** last_segtab; /* Used if table is shrinking */
311
 
    struct segment* segtab[1]; /* The segment table (may be larger) */
 
309
        
 
310
    struct segment** prev_segtab;  /* Used when table is shrinking */
 
311
    int nsegs;                     /* Size of segtab */
 
312
    struct segment* segtab[1];     /* The segment table */
312
313
};
 
314
#define SIZEOF_EXTSEG(NSEGS) \
 
315
    (sizeof(struct ext_segment) - sizeof(struct segment*) + sizeof(struct segment*)*(NSEGS))
 
316
 
 
317
#ifdef DEBUG
 
318
#  include <stddef.h> /* offsetof */
 
319
#  define EXTSEG(SEGTAB_PTR) \
 
320
    ((struct ext_segment*) (((char*)(SEGTAB_PTR)) - offsetof(struct ext_segment,segtab)))
 
321
#endif
 
322
 
 
323
 
 
324
/* How the table segments relate to each other:
 
325
 
 
326
    ext_segment:                      ext_segment:              "plain" segment
 
327
   #=================#                #================#        #=============#
 
328
   | bucket[0]       |<--+   +------->| bucket[256]    |     +->| bucket[512] |
 
329
   | bucket[1]       |   |   |        |       [257]    |     |  |       [513] |
 
330
   :                 :   |   |        :                :     |  :             :
 
331
   | bucket[255]     |   |   |        |       [511]    |     |  |       [767] |
 
332
   |-----------------|   |   |        |----------------|     |  #=============#
 
333
   | prev_segtab=NULL|   |   |   +--<---prev_segtab    |     |
 
334
   | nsegs = 2       |   |   |   |    | nsegs = 256    |     |
 
335
+->| segtab[0] -->-------+---|---|--<---segtab[0]      |<-+  |
 
336
|  | segtab[1] -->-----------+---|--<---segtab[1]      |  |  |
 
337
|  #=================#           |    | segtab[2] -->-----|--+    ext_segment:         
 
338
|                                |    :                :  |      #================#
 
339
+----------------<---------------+    | segtab[255] ->----|----->| bucket[255*256]| 
 
340
                                      #================#  |      |                | 
 
341
                                                          |      :                :
 
342
                                                          |      |----------------| 
 
343
                                                          +----<---prev_segtab    | 
 
344
                                                                 :                :
 
345
*/
 
346
 
313
347
 
314
348
/*
315
349
** Forward decl's (static functions)
316
350
*/
 
351
static struct ext_segment* alloc_ext_seg(DbTableHash* tb, unsigned seg_ix,
 
352
                                         struct segment** old_segtab);
317
353
static int alloc_seg(DbTableHash *tb);
318
354
static int free_seg(DbTableHash *tb, int free_records);
319
355
static HashDbTerm* next(DbTableHash *tb, Uint *iptr, erts_smp_rwmtx_t** lck_ptr,
576
612
int db_create_hash(Process *p, DbTable *tbl)
577
613
{
578
614
    DbTableHash *tb = &tbl->hash;
 
615
 
579
616
    erts_smp_atomic_init(&tb->szm, SEGSZ_MASK);
580
617
    erts_smp_atomic_init(&tb->nactive, SEGSZ);
581
618
    erts_smp_atomic_init(&tb->fixdel, (long)NULL);
582
 
    erts_smp_atomic_init(&tb->segtab, (long)NULL);
583
 
    tb->nsegs = 0;
584
 
    tb->nslots = 0;   
585
 
    alloc_seg(tb);
 
619
    erts_smp_atomic_init(&tb->segtab, (long) alloc_ext_seg(tb,0,NULL)->segtab);
 
620
    tb->nsegs = NSEG_1;
 
621
    tb->nslots = SEGSZ;
586
622
 
587
623
    erts_smp_atomic_init(&tb->is_resizing, 0);
588
624
#ifdef ERTS_SMP
1356
1392
    DbTableHash *tb = &tbl->hash;
1357
1393
    struct mp_info mpi;
1358
1394
    Sint slot_ix;
1359
 
    Sint save_slot_ix;
1360
1395
    HashDbTerm *current = 0;
1361
1396
    unsigned current_list_pos = 0;
1362
1397
    Eterm match_list;
1427
1462
    match_list = NIL;
1428
1463
 
1429
1464
    for(;;) {
1430
 
        if (current->hvalue != INVALID_HASH && 
1431
 
            (match_res = 
1432
 
             db_prog_match(p,mpi.mp,
1433
 
                           make_tuple(current->dbterm.tpl),
1434
 
                           0,&dummy),
1435
 
             is_value(match_res))) {
1436
 
            if (mpi.all_objects) {
1437
 
                hp = HAlloc(p, current->dbterm.size + 2);
1438
 
                match_res = copy_shallow(DBTERM_BUF(&current->dbterm),
1439
 
                                         current->dbterm.size,
1440
 
                                         &hp,
1441
 
                                         &MSO(p));
1442
 
            } else {
1443
 
                sz = size_object(match_res);
1444
 
            
1445
 
                hp = HAlloc(p, sz + 2);
1446
 
                match_res = copy_struct(match_res, sz, &hp, &MSO(p));
1447
 
            }
1448
 
            match_list = CONS(hp, match_res, match_list);
1449
 
            ++got;
1450
 
        }
1451
 
 
1452
 
        if (mpi.key_given) {  /* Key is bound */
1453
 
            current = current->next;
1454
 
            for (;;) {
1455
 
                while (current != NULL && 
1456
 
                       current->hvalue == INVALID_HASH)
1457
 
                    current = current->next;
1458
 
                if (current == NULL) {
1459
 
                    RUNLOCK_HASH(lck);
1460
 
                    if (current_list_pos == mpi.num_lists) {
1461
 
                        slot_ix = -1; /* EOT */
1462
 
                        goto done;
 
1465
        if (current != NULL) {
 
1466
            if (current->hvalue != INVALID_HASH) {
 
1467
                match_res = db_prog_match(p,mpi.mp,
 
1468
                                          make_tuple(current->dbterm.tpl),
 
1469
                                          0,&dummy);
 
1470
                if (is_value(match_res)) {
 
1471
                    if (mpi.all_objects) {
 
1472
                        hp = HAlloc(p, current->dbterm.size + 2);
 
1473
                        match_res = copy_shallow(DBTERM_BUF(&current->dbterm),
 
1474
                                                 current->dbterm.size,
 
1475
                                                 &hp,
 
1476
                                                 &MSO(p));
1463
1477
                    } else {
1464
 
                        slot_ix = mpi.lists[current_list_pos].ix;
1465
 
                        lck = RLOCK_HASH(tb, slot_ix);
1466
 
                        current = *(mpi.lists[current_list_pos].bucket);
1467
 
                        ASSERT(mpi.lists[current_list_pos].bucket == &BUCKET(tb,slot_ix));
1468
 
                        ++current_list_pos;                    
 
1478
                        sz = size_object(match_res);
 
1479
                        
 
1480
                        hp = HAlloc(p, sz + 2);
 
1481
                        match_res = copy_struct(match_res, sz, &hp, &MSO(p));
1469
1482
                    }
1470
 
                } else {
1471
 
                    break;
 
1483
                    match_list = CONS(hp, match_res, match_list);
 
1484
                    ++got;
1472
1485
                }
1473
1486
            }
1474
 
        }
1475
 
        else { /* Key is variable */
 
1487
            current = current->next;
 
1488
        }       
 
1489
        else if (mpi.key_given) {  /* Key is bound */
 
1490
            RUNLOCK_HASH(lck);
 
1491
            if (current_list_pos == mpi.num_lists) {
 
1492
                slot_ix = -1; /* EOT */
 
1493
                goto done;
 
1494
            } else {
 
1495
                slot_ix = mpi.lists[current_list_pos].ix;
 
1496
                lck = RLOCK_HASH(tb, slot_ix);
 
1497
                current = *(mpi.lists[current_list_pos].bucket);
 
1498
                ASSERT(mpi.lists[current_list_pos].bucket == &BUCKET(tb,slot_ix));
 
1499
                ++current_list_pos;                    
 
1500
            }
 
1501
        }
 
1502
        else { /* Key is variable */
1476
1503
            --num_left;
1477
 
            save_slot_ix = slot_ix;
1478
 
            if ((current =
1479
 
                 next(tb, (Uint*)&slot_ix, &lck, current)) == NULL) {
 
1504
 
 
1505
            if ((slot_ix=next_slot(tb,slot_ix,&lck)) == 0) {
1480
1506
                slot_ix = -1;
1481
1507
                break;
1482
1508
            }
1483
 
            if (slot_ix != save_slot_ix) {
1484
 
                if (chunk_size && got >= chunk_size) {
1485
 
                    RUNLOCK_HASH(lck);
1486
 
                    break;
1487
 
                }    
1488
 
                if (num_left <= 0 || MBUF(p)) {
1489
 
                    /*
1490
 
                     * We have either reached our limit, or just created some heap fragments.
1491
 
                     * Since many heap fragments will make the GC slower, trap and GC now.
1492
 
                     */
1493
 
                    RUNLOCK_HASH(lck);
1494
 
                    goto trap;
1495
 
                }
 
1509
            if (chunk_size && got >= chunk_size) {
 
1510
                RUNLOCK_HASH(lck);
 
1511
                break;
 
1512
            }    
 
1513
            if (num_left <= 0 || MBUF(p)) {
 
1514
                /*
 
1515
                 * We have either reached our limit, or just created some heap fragments.
 
1516
                 * Since many heap fragments will make the GC slower, trap and GC now.
 
1517
                 */
 
1518
                RUNLOCK_HASH(lck);
 
1519
                goto trap;
1496
1520
            }
 
1521
            current = BUCKET(tb,slot_ix);
1497
1522
        }
1498
1523
    }
1499
1524
done:
1618
1643
 
1619
1644
    for(;;) {
1620
1645
        if (current != NULL) {
1621
 
            if (current->hvalue == INVALID_HASH) {
1622
 
                current = current->next;
1623
 
                continue;
1624
 
            }
1625
 
            if (db_prog_match(p, mpi.mp, make_tuple(current->dbterm.tpl),
1626
 
                              0, &dummy) == am_true) {
1627
 
                ++got;
1628
 
            }
1629
 
            --num_left;
 
1646
            if (current->hvalue != INVALID_HASH) {
 
1647
                if (db_prog_match(p, mpi.mp, make_tuple(current->dbterm.tpl),
 
1648
                                  0, &dummy) == am_true) {
 
1649
                    ++got;
 
1650
                }
 
1651
                --num_left;
 
1652
            }
1630
1653
            current = current->next;
1631
1654
        }
1632
1655
        else { /* next bucket */
2284
2307
    return DB_ERROR_NONE;
2285
2308
}
2286
2309
 
2287
 
/* Extend (or initialize) table with one new segment
 
2310
static struct ext_segment* alloc_ext_seg(DbTableHash* tb, unsigned seg_ix,
 
2311
                                         struct segment** old_segtab)
 
2312
{
 
2313
    int nsegs;
 
2314
    struct ext_segment* eseg;
 
2315
    
 
2316
    switch (seg_ix) {
 
2317
    case 0: nsegs = NSEG_1; break;
 
2318
    case 1: nsegs = NSEG_2; break; 
 
2319
    default: nsegs = seg_ix + NSEG_INC; break;
 
2320
    }    
 
2321
    eseg = (struct ext_segment*) erts_db_alloc_fnf(ERTS_ALC_T_DB_SEG,
 
2322
                                                   (DbTable *) tb,
 
2323
                                                   SIZEOF_EXTSEG(nsegs));
 
2324
    ASSERT(eseg != NULL);       
 
2325
    sys_memset(&eseg->s, 0, sizeof(struct segment));
 
2326
    IF_DEBUG(eseg->s.is_ext_segment = 1);
 
2327
    eseg->prev_segtab = old_segtab;
 
2328
    eseg->nsegs = nsegs;
 
2329
    if (old_segtab) {
 
2330
        ASSERT(nsegs > tb->nsegs);
 
2331
        sys_memcpy(eseg->segtab, old_segtab, tb->nsegs*sizeof(struct segment*));
 
2332
    }
 
2333
#ifdef DEBUG
 
2334
    sys_memset(&eseg->segtab[seg_ix], 0, (nsegs-seg_ix)*sizeof(struct segment*));
 
2335
#endif
 
2336
    eseg->segtab[seg_ix] = &eseg->s;
 
2337
    return eseg;
 
2338
}
 
2339
 
 
2340
/* Extend table with one new segment
2288
2341
*/
2289
2342
static int alloc_seg(DbTableHash *tb)
2290
2343
{    
2291
 
    int six = tb->nslots >> SEGSZ_EXP;
2292
 
 
2293
 
    if (six == tb->nsegs) { /* New extended segment */
2294
 
        int nsegs;
2295
 
        int bytes;
2296
 
        struct ext_segment* eseg;
2297
 
        struct segment** old_segtab = SEGTAB(tb);
2298
 
 
2299
 
        switch (six) {
2300
 
        case 0: nsegs = NSEG_1; break;
2301
 
        case 1: nsegs = NSEG_2; break; 
2302
 
        default: nsegs = six + NSEG_INC; break;
2303
 
        }
2304
 
 
2305
 
        bytes = sizeof(struct ext_segment) + sizeof(struct segment*) * (nsegs-1);
2306
 
        eseg = (struct ext_segment*) erts_db_alloc_fnf(ERTS_ALC_T_DB_SEG,
2307
 
                                                       (DbTable *) tb, bytes);      
2308
 
        if (eseg == NULL) return 0;
2309
 
 
2310
 
        memset(&eseg->s, 0, sizeof(struct segment));
2311
 
        IF_DEBUG(eseg->s.is_ext_segment = 1);
2312
 
        eseg->last_segtab = old_segtab;
2313
 
        if (old_segtab) {
2314
 
            ASSERT(nsegs > tb->nsegs);
2315
 
            memcpy(eseg->segtab, old_segtab, tb->nsegs*sizeof(struct segment*));
2316
 
            memset(&eseg->segtab[six], 0, (nsegs-six)*sizeof(struct segment*));
2317
 
        }
2318
 
        eseg->segtab[six] = &eseg->s;
2319
 
        erts_smp_atomic_set(&tb->segtab, (long) eseg->segtab);
2320
 
        tb->nsegs = nsegs;
 
2344
    int seg_ix = tb->nslots >> SEGSZ_EXP;
 
2345
 
 
2346
    if (seg_ix+1 == tb->nsegs) { /* New segtab needed (extended segment) */
 
2347
        struct segment** segtab = SEGTAB(tb);
 
2348
        struct ext_segment* seg = alloc_ext_seg(tb, seg_ix, segtab);
 
2349
        if (seg == NULL) return 0;
 
2350
        segtab[seg_ix] = &seg->s;
 
2351
        /* We don't use the new segtab until next call (see "shrink race") */
2321
2352
    }
2322
2353
    else { /* Just a new plain segment */
2323
 
        struct segment** segtab = SEGTAB(tb);
2324
 
        ASSERT(six < tb->nsegs);
2325
 
        segtab[six] = (struct segment*) erts_db_alloc_fnf(ERTS_ALC_T_DB_SEG,
2326
 
                                                          (DbTable *) tb,
2327
 
                                                          sizeof(struct segment));
2328
 
        if (segtab[six] == NULL) return 0;
2329
 
        memset(segtab[six], 0, sizeof(struct segment));
 
2354
        struct segment** segtab;
 
2355
        if (seg_ix == tb->nsegs) { /* Time to start use segtab from last call */
 
2356
            struct ext_segment* eseg;
 
2357
            eseg = (struct ext_segment*) SEGTAB(tb)[seg_ix-1];
 
2358
            MY_ASSERT(eseg!=NULL && eseg->s.is_ext_segment);
 
2359
            erts_smp_atomic_set(&tb->segtab, (long) eseg->segtab);
 
2360
            tb->nsegs = eseg->nsegs;
 
2361
        }
 
2362
        ASSERT(seg_ix < tb->nsegs);
 
2363
        segtab = SEGTAB(tb);
 
2364
        ASSERT(segtab[seg_ix] == NULL);
 
2365
        segtab[seg_ix] = (struct segment*) erts_db_alloc_fnf(ERTS_ALC_T_DB_SEG,
 
2366
                                                             (DbTable *) tb,
 
2367
                                                             sizeof(struct segment));
 
2368
        if (segtab[seg_ix] == NULL) return 0;
 
2369
        sys_memset(segtab[seg_ix], 0, sizeof(struct segment));
2330
2370
    }
2331
2371
    tb->nslots += SEGSZ;
2332
2372
    return 1;
2337
2377
*/
2338
2378
static int free_seg(DbTableHash *tb, int free_records)
2339
2379
{
2340
 
    int six = (tb->nslots >> SEGSZ_EXP) - 1;
 
2380
    int seg_ix = (tb->nslots >> SEGSZ_EXP) - 1;
2341
2381
    int bytes;
2342
2382
    struct segment** segtab = SEGTAB(tb);
2343
 
    struct ext_segment* top = (struct ext_segment*) segtab[six];
 
2383
    struct ext_segment* top = (struct ext_segment*) segtab[seg_ix];
2344
2384
    int nrecords = 0;
2345
2385
 
 
2386
    ASSERT(top != NULL); 
2346
2387
#ifndef DEBUG
2347
2388
    if (free_records)
2348
2389
#endif
2359
2400
            }
2360
2401
        }
2361
2402
    }
2362
 
    if (segtab == top->segtab) { /* Extended segment */
2363
 
        MY_ASSERT(top->s.is_ext_segment);
2364
 
        erts_smp_atomic_set(&tb->segtab, (long)top->last_segtab);
2365
 
        bytes = sizeof(struct ext_segment) + sizeof(struct segment*) * (tb->nsegs-1);
2366
 
        tb->nsegs = six;
 
2403
 
 
2404
    /* The "shrink race":
 
2405
     * We must avoid deallocating an extended segment while its segtab may
 
2406
     * still be used by other threads.
 
2407
     * The trick is to stop use a segtab one call earlier. That is, stop use
 
2408
     * a segtab when the segment above it is deallocated. When the segtab is
 
2409
     * later deallocated, it has not been used for a very long time.
 
2410
     * It is even theoretically safe as we have by then rehashed the entire
 
2411
     * segment, seizing *all* locks, so there cannot exist any retarded threads
 
2412
     * still hanging in BUCKET macro with an old segtab pointer.
 
2413
     * For this to work, we must of course allocate a new segtab one call
 
2414
     * earlier in alloc_seg() as well. And this is also the reason why
 
2415
     * the minimum size of the first segtab is 2 and not 1 (NSEG_1).
 
2416
     */
 
2417
    
 
2418
    if (seg_ix == tb->nsegs-1 || seg_ix==0) { /* Dealloc extended segment */
 
2419
        MY_ASSERT(top->s.is_ext_segment);   
 
2420
        ASSERT(segtab != top->segtab || seg_ix==0);    
 
2421
        bytes = SIZEOF_EXTSEG(top->nsegs);
2367
2422
    }
2368
 
    else { /* Plain segment */
 
2423
    else { /* Dealloc plain segment */
 
2424
        struct ext_segment* newtop = (struct ext_segment*) segtab[seg_ix-1];
2369
2425
        MY_ASSERT(!top->s.is_ext_segment);
2370
 
        segtab[six] = NULL;
 
2426
        
 
2427
        if (segtab == newtop->segtab) { /* New top segment is extended */
 
2428
            MY_ASSERT(newtop->s.is_ext_segment);
 
2429
            if (newtop->prev_segtab != NULL) {
 
2430
                /* Time to use a smaller segtab */
 
2431
                erts_smp_atomic_set(&tb->segtab, (long)newtop->prev_segtab);
 
2432
                tb->nsegs = seg_ix;
 
2433
                ASSERT(tb->nsegs == EXTSEG(SEGTAB(tb))->nsegs);
 
2434
            }
 
2435
            else {
 
2436
                ASSERT(NSEG_1 > 2 && seg_ix==1);
 
2437
            }
 
2438
        }
2371
2439
        bytes = sizeof(struct segment);
2372
2440
    }
2373
2441
    
2374
2442
    erts_db_free(ERTS_ALC_T_DB_SEG, (DbTable *)tb,
2375
2443
                 (void*)top, bytes);
2376
 
 
 
2444
#ifdef DEBUG
 
2445
    if (seg_ix > 0) {
 
2446
        if (seg_ix < tb->nsegs) SEGTAB(tb)[seg_ix] = NULL;
 
2447
    } else {
 
2448
        erts_smp_atomic_set(&tb->segtab, (long)NULL);
 
2449
    }
 
2450
#endif
2377
2451
    tb->nslots -= SEGSZ;
2378
2452
    ASSERT(tb->nslots >= 0);
2379
2453
    return nrecords;
2676
2750
        DbTerm* newDbTerm;
2677
2751
        HashDbTerm* newp = erts_db_alloc(ERTS_ALC_T_DB_TERM, tbl,
2678
2752
                                         sizeof(HashDbTerm)+sizeof(Eterm)*(handle->new_size-1));    
2679
 
        memcpy(newp, oldp, sizeof(HashDbTerm)-sizeof(DbTerm));  /* copy only hashtab header */
 
2753
        sys_memcpy(newp, oldp, sizeof(HashDbTerm)-sizeof(DbTerm));  /* copy only hashtab header */
2680
2754
        *(handle->bp) = newp;
2681
2755
        newDbTerm = &newp->dbterm;
2682
2756