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

« back to all changes in this revision

Viewing changes to erts/emulator/beam/erl_node_tables.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 2001-2009. All Rights Reserved.
5
 
 * 
 
3
 *
 
4
 * Copyright Ericsson AB 2001-2010. 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
 
80
80
    Eterm chnl_nr;
81
81
    Eterm sysname;
82
82
    DistEntry *dep;
 
83
    erts_smp_rwmtx_opt_t rwmtx_opt = ERTS_SMP_RWMTX_OPT_DEFAULT_INITER;
 
84
    rwmtx_opt.type = ERTS_SMP_RWMTX_TYPE_FREQUENT_READ;
83
85
 
84
86
    if(((DistEntry *) dep_tmpl) == erts_this_dist_entry)
85
87
        return dep_tmpl;
92
94
 
93
95
    dep->prev                           = NULL;
94
96
    erts_refc_init(&dep->refc, -1);
95
 
    erts_smp_rwmtx_init_x(&dep->rwmtx, "dist_entry", chnl_nr);
 
97
    erts_smp_rwmtx_init_opt_x(&dep->rwmtx, &rwmtx_opt, "dist_entry", chnl_nr);
96
98
    dep->sysname                        = sysname;
97
99
    dep->cid                            = NIL;
98
100
    dep->connection_id                  = 0;
105
107
    dep->nlinks                         = NULL;
106
108
    dep->monitors                       = NULL;
107
109
 
108
 
    erts_smp_spinlock_init_x(&dep->qlock, "dist_entry_out_queue", chnl_nr);
 
110
    erts_smp_mtx_init_x(&dep->qlock, "dist_entry_out_queue", chnl_nr);
109
111
    dep->qflgs                          = 0;
110
112
    dep->qsize                          = 0;
111
113
    dep->out_queue.first                = NULL;
170
172
    ASSERT(!dep->cache);
171
173
    erts_smp_rwmtx_destroy(&dep->rwmtx);
172
174
    erts_smp_mtx_destroy(&dep->lnk_mtx);
173
 
    erts_smp_spinlock_destroy(&dep->qlock);
 
175
    erts_smp_mtx_destroy(&dep->qlock);
174
176
 
175
177
#ifdef DEBUG
176
178
    sys_memset(vdep, 0x77, sizeof(DistEntry));
233
235
    erts_smp_rwmtx_rlock(&erts_dist_table_rwmtx);
234
236
    res_dep = (DistEntry *) hash_get(&erts_dist_table, (void *) &de);
235
237
    if (res_dep) {
236
 
        long refc = erts_refc_inctest(&res_dep->refc, 1);
 
238
        erts_aint_t refc = erts_refc_inctest(&res_dep->refc, 1);
237
239
        if (refc < 2) /* Pending delete */
238
240
            erts_refc_inc(&res_dep->refc, 1);
239
241
    }
255
257
{
256
258
    DistEntry *res;
257
259
    DistEntry de;
258
 
    long refc;
 
260
    erts_aint_t refc;
259
261
    res = erts_find_dist_entry(sysname);
260
262
    if (res)
261
263
        return res;
277
279
    erts_smp_rwmtx_rlock(&erts_dist_table_rwmtx);
278
280
    res = hash_get(&erts_dist_table, (void *) &de);
279
281
    if (res) {
280
 
        long refc = erts_refc_inctest(&res->refc, 1);
 
282
        erts_aint_t refc = erts_refc_inctest(&res->refc, 1);
281
283
        if (refc < 2) /* Pending delete */
282
284
            erts_refc_inc(&res->refc, 1);
283
285
    }
580
582
    ErlNode ne;
581
583
    ne.sysname = sysname;
582
584
    ne.creation = creation;
 
585
 
 
586
    erts_smp_rwmtx_rlock(&erts_node_table_rwmtx);
 
587
    res = hash_get(&erts_node_table, (void *) &ne);
 
588
    if (res && res != erts_this_node) {
 
589
        erts_aint_t refc = erts_refc_inctest(&res->refc, 0);
 
590
        if (refc < 2) /* New or pending delete */
 
591
            erts_refc_inc(&res->refc, 1);
 
592
    }
 
593
    erts_smp_rwmtx_runlock(&erts_node_table_rwmtx);
 
594
    if (res)
 
595
        return res;
 
596
 
583
597
    erts_smp_rwmtx_rwlock(&erts_node_table_rwmtx);
584
598
    res = hash_put(&erts_node_table, (void *) &ne);
585
599
    ASSERT(res);
586
600
    if (res != erts_this_node) {
587
 
        long refc = erts_refc_inctest(&res->refc, 0);
 
601
        erts_aint_t refc = erts_refc_inctest(&res->refc, 0);
588
602
        if (refc < 2) /* New or pending delete */
589
603
            erts_refc_inc(&res->refc, 1);
590
604
    }
696
710
 
697
711
void erts_init_node_tables(void)
698
712
{
 
713
    erts_smp_rwmtx_opt_t rwmtx_opt = ERTS_SMP_RWMTX_OPT_DEFAULT_INITER;
699
714
    HashFunctions f;
700
715
 
 
716
    rwmtx_opt.type = ERTS_SMP_RWMTX_TYPE_FREQUENT_READ;
 
717
    rwmtx_opt.lived = ERTS_SMP_RWMTX_LONG_LIVED;
 
718
 
701
719
    f.hash  = (H_FUN)                   dist_table_hash;
702
720
    f.cmp   = (HCMP_FUN)                dist_table_cmp;
703
721
    f.alloc = (HALLOC_FUN)              dist_table_alloc;
719
737
    erts_this_dist_entry->prev                          = NULL;
720
738
    erts_refc_init(&erts_this_dist_entry->refc, 1); /* erts_this_node */
721
739
 
722
 
    erts_smp_rwmtx_init_x(&erts_this_dist_entry->rwmtx,
723
 
                          "dist_entry",
724
 
                          make_small(ERST_INTERNAL_CHANNEL_NO));
 
740
    erts_smp_rwmtx_init_opt_x(&erts_this_dist_entry->rwmtx,
 
741
                              &rwmtx_opt,
 
742
                              "dist_entry",
 
743
                              make_small(ERST_INTERNAL_CHANNEL_NO));
725
744
    erts_this_dist_entry->sysname                       = am_Noname;
726
745
    erts_this_dist_entry->cid                           = NIL;
727
746
    erts_this_dist_entry->connection_id                 = 0;
736
755
    erts_this_dist_entry->nlinks                        = NULL;
737
756
    erts_this_dist_entry->monitors                      = NULL;
738
757
 
739
 
    erts_smp_spinlock_init_x(&erts_this_dist_entry->qlock,
740
 
                             "dist_entry_out_queue",
741
 
                             make_small(ERST_INTERNAL_CHANNEL_NO));
 
758
    erts_smp_mtx_init_x(&erts_this_dist_entry->qlock,
 
759
                        "dist_entry_out_queue",
 
760
                        make_small(ERST_INTERNAL_CHANNEL_NO));
742
761
    erts_this_dist_entry->qflgs                         = 0;
743
762
    erts_this_dist_entry->qsize                         = 0;
744
763
    erts_this_dist_entry->out_queue.first               = NULL;
772
791
 
773
792
    (void) hash_put(&erts_node_table, (void *) erts_this_node);
774
793
 
775
 
    erts_smp_rwmtx_init(&erts_node_table_rwmtx, "node_table");
776
 
    erts_smp_rwmtx_init(&erts_dist_table_rwmtx, "dist_table");
 
794
    erts_smp_rwmtx_init_opt(&erts_node_table_rwmtx, &rwmtx_opt, "node_table");
 
795
    erts_smp_rwmtx_init_opt(&erts_dist_table_rwmtx, &rwmtx_opt, "dist_table");
777
796
 
778
797
    references_atoms_need_init = 1;
779
798
}
1087
1106
static void
1088
1107
insert_offheap(ErlOffHeap *oh, int type, Eterm id)
1089
1108
{
1090
 
    if(oh->externals) {
1091
 
        ExternalThing *etp = oh->externals;
1092
 
        while (etp) {
1093
 
            insert_node(etp->node, type, id);
1094
 
            etp = etp->next;
1095
 
        }
1096
 
    }
 
1109
    union erl_off_heap_ptr u;
 
1110
    struct insert_offheap2_arg a;
 
1111
    a.type = BIN_REF;
1097
1112
 
1098
 
    if(oh->mso) {
1099
 
        ProcBin *pb;
1100
 
        struct insert_offheap2_arg a;
1101
 
        a.type = BIN_REF;
1102
 
        for(pb = oh->mso; pb; pb = pb->next) {
1103
 
            if(IsMatchProgBinary(pb->val)) {
 
1113
    for (u.hdr = oh->first; u.hdr; u.hdr = u.hdr->next) {
 
1114
        switch (thing_subtag(u.hdr->thing_word)) {
 
1115
        case REFC_BINARY_SUBTAG:
 
1116
            if(IsMatchProgBinary(u.pb->val)) {
1104
1117
                InsertedBin *ib;
1105
1118
                int insert_bin = 1;
1106
1119
                for (ib = inserted_bins; ib; ib = ib->next)
1107
 
                    if(ib->bin_val == pb->val) {
 
1120
                    if(ib->bin_val == u.pb->val) {
1108
1121
                        insert_bin = 0;
1109
1122
                        break;
1110
1123
                    }
1111
1124
                if (insert_bin) {
1112
 
                    Uint id_heap[BIG_UINT_HEAP_SIZE];
 
1125
#if HALFWORD_HEAP
 
1126
                    UWord val = (UWord) u.pb->val;
 
1127
                    DeclareTmpHeapNoproc(id_heap,BIG_UINT_HEAP_SIZE*2); /* extra place allocated */
 
1128
#else
 
1129
                    DeclareTmpHeapNoproc(id_heap,BIG_UINT_HEAP_SIZE);
 
1130
#endif
1113
1131
                    Uint *hp = &id_heap[0];
1114
1132
                    InsertedBin *nib;
1115
 
                    a.id = erts_bld_uint(&hp, NULL, (Uint) pb->val);
1116
 
                    erts_match_prog_foreach_offheap(pb->val,
 
1133
#if HALFWORD_HEAP
 
1134
                    int actual_need = BIG_UWORD_HEAP_SIZE(val);
 
1135
                    ASSERT(actual_need <= (BIG_UINT_HEAP_SIZE*2));
 
1136
                    UseTmpHeapNoproc(actual_need);
 
1137
                    a.id = erts_bld_uword(&hp, NULL, (UWord) val);
 
1138
#else
 
1139
                    UseTmpHeapNoproc(BIG_UINT_HEAP_SIZE);
 
1140
                    a.id = erts_bld_uint(&hp, NULL, (Uint) u.pb->val);
 
1141
#endif
 
1142
                    erts_match_prog_foreach_offheap(u.pb->val,
1117
1143
                                                    insert_offheap2,
1118
1144
                                                    (void *) &a);
1119
1145
                    nib = erts_alloc(ERTS_ALC_T_NC_TMP, sizeof(InsertedBin));
1120
 
                    nib->bin_val = pb->val;
 
1146
                    nib->bin_val = u.pb->val;
1121
1147
                    nib->next = inserted_bins;
1122
1148
                    inserted_bins = nib;
 
1149
#if HALFWORD_HEAP
 
1150
                    UnUseTmpHeapNoproc(actual_need);
 
1151
#else
 
1152
                    UnUseTmpHeapNoproc(BIG_UINT_HEAP_SIZE);
 
1153
#endif
1123
1154
                }
1124
 
            }
 
1155
            }           
 
1156
            break;
 
1157
        case FUN_SUBTAG:
 
1158
            break; /* No need to */
 
1159
        default:
 
1160
            ASSERT(is_external_header(u.hdr->thing_word));
 
1161
            insert_node(u.ext->node, type, id);
 
1162
            break;
1125
1163
        }
1126
1164
    }
1127
 
 
1128
 
#if 0
1129
 
    if(oh->funs) {
1130
 
        /* No need to */
1131
 
    }
1132
 
#endif
1133
1165
}
1134
1166
 
1135
1167
static void doit_insert_monitor(ErtsMonitor *monitor, void *p)
1190
1222
insert_bif_timer(Eterm receiver, Eterm msg, ErlHeapFragment *bp, void *arg)
1191
1223
{
1192
1224
    if (bp) {
1193
 
        Eterm heap[3];
 
1225
        DeclareTmpHeapNoproc(heap,3);
 
1226
 
 
1227
        UseTmpHeapNoproc(3);
1194
1228
        insert_offheap(&bp->off_heap,
1195
1229
                       TIMER_REF,
1196
1230
                       (is_internal_pid(receiver)
1197
1231
                        ? receiver
1198
1232
                        : TUPLE2(&heap[0], AM_process, receiver)));
 
1233
        UnUseTmpHeapNoproc(3);
1199
1234
    }
1200
1235
}
1201
1236
 
1230
1265
    DistEntry *dep;
1231
1266
    HashInfo hi;
1232
1267
    int i;
1233
 
    Eterm heap[3];
 
1268
    DeclareTmpHeapNoproc(heap,3);
1234
1269
 
1235
1270
    inserted_bins = NULL;
1236
1271
 
1251
1286
    /* Go through the hole system, and build a table of all references
1252
1287
       to ErlNode and DistEntry structures */
1253
1288
 
 
1289
    UseTmpHeapNoproc(3);
1254
1290
    insert_node(erts_this_node,
1255
1291
                SYSTEM_REF,
1256
1292
                TUPLE2(&heap[0], AM_system, am_undefined));
1261
1297
                   HEAP_REF,
1262
1298
                   TUPLE2(&heap[0], AM_processes, am_undefined));
1263
1299
#endif
 
1300
    UnUseTmpHeapNoproc(3);
1264
1301
 
1265
1302
    /* Insert all processes */
1266
1303
    for (i = 0; i < erts_max_processes; i++)
1267
1304
        if (process_tab[i]) {
1268
1305
            ErlMessage *msg;
 
1306
 
1269
1307
            /* Insert Heap */
1270
1308
            insert_offheap(&(process_tab[i]->off_heap),
1271
1309
                           HEAP_REF,
1352
1390
 
1353
1391
    { /* Add binaries stored elsewhere ... */
1354
1392
        ErlOffHeap oh;
1355
 
        ProcBin pb[2] = {{0},{0}};
1356
 
        ProcBin *mso = NULL;
 
1393
        ProcBin pb[2];
1357
1394
        int i = 0;
1358
1395
        Binary *default_match_spec;
1359
1396
        Binary *default_meta_match_spec;
1360
1397
 
1361
 
        /* Only the ProcBin members val and next will be inspected
 
1398
        oh.first = NULL;
 
1399
        /* Only the ProcBin members thing_word, val and next will be inspected
1362
1400
           (by insert_offheap()) */
1363
1401
#undef  ADD_BINARY
1364
 
#define ADD_BINARY(Bin)                                 \
1365
 
        if ((Bin)) {                                    \
1366
 
            pb[i].val = (Bin);                          \
1367
 
            pb[i].next = mso;                           \
1368
 
            mso = &pb[i];                               \
1369
 
            i++;                                        \
 
1402
#define ADD_BINARY(Bin)                                      \
 
1403
        if ((Bin)) {                                         \
 
1404
            pb[i].thing_word = REFC_BINARY_SUBTAG;           \
 
1405
            pb[i].val = (Bin);                               \
 
1406
            pb[i].next = oh.first;                           \
 
1407
            oh.first = (struct erl_off_heap_header*) &pb[i]; \
 
1408
            i++;                                             \
1370
1409
        }
1371
1410
 
1372
1411
        erts_get_default_trace_pattern(NULL,
1378
1417
        ADD_BINARY(default_match_spec);
1379
1418
        ADD_BINARY(default_meta_match_spec);
1380
1419
 
1381
 
        oh.mso = mso;
1382
 
        oh.externals = NULL;
1383
 
#ifndef HYBRID /* FIND ME! */
1384
 
        oh.funs = NULL;
1385
 
#endif
1386
1420
        insert_offheap(&oh, BIN_REF, AM_match_spec);
1387
1421
#undef  ADD_BINARY
1388
1422
    }