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

« back to all changes in this revision

Viewing changes to erts/emulator/beam/erl_bif_info.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 1999-2009. All Rights Reserved.
5
 
 * 
 
3
 *
 
4
 * Copyright Ericsson AB 1999-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
 
38
38
#include "erl_instrument.h"
39
39
#include "dist.h"
40
40
#include "erl_gc.h"
41
 
#ifdef ELIB_ALLOC_IS_CLIB
42
 
#include "elib_stat.h"
43
 
#endif
 
41
#include "erl_cpu_topology.h"
44
42
#ifdef HIPE
45
43
#include "hipe_arch.h"
46
44
#endif
59
57
/* Keep erts_system_version as a global variable for easy access from a core */
60
58
static char erts_system_version[] = ("Erlang " ERLANG_OTP_RELEASE
61
59
                                     " (erts-" ERLANG_VERSION ")"
 
60
#if !HEAP_ON_C_STACK && !HALFWORD_HEAP
 
61
                                     " [no-c-stack-objects]"
 
62
#endif
62
63
#ifndef OTP_RELEASE
63
64
                                     " [source]"
64
65
#endif  
65
66
#ifdef ARCH_64
 
67
#if HALFWORD_HEAP
 
68
                                     " [64-bit halfword]"
 
69
#else
66
70
                                     " [64-bit]"
67
71
#endif
 
72
#endif
68
73
#ifdef ERTS_SMP
69
74
                                     " [smp:%bpu:%bpu]"
70
75
#endif
115
120
#endif
116
121
 
117
122
static Eterm
118
 
bld_bin_list(Uint **hpp, Uint *szp, ProcBin* pb)
 
123
bld_bin_list(Uint **hpp, Uint *szp, ErlOffHeap* oh)
119
124
{
 
125
    struct erl_off_heap_header* ohh;
120
126
    Eterm res = NIL;
121
127
    Eterm tuple;
122
128
 
123
 
    for (; pb; pb = pb->next) {
124
 
        Eterm val = erts_bld_uint(hpp, szp, (Uint) pb->val);
125
 
        Eterm orig_size = erts_bld_uint(hpp, szp, pb->val->orig_size);
126
 
 
127
 
        if (szp)
128
 
            *szp += 4+2;
129
 
        if (hpp) {
130
 
            Uint refc = (Uint) erts_smp_atomic_read(&pb->val->refc);
131
 
            tuple = TUPLE3(*hpp, val, orig_size, make_small(refc));
132
 
            res = CONS(*hpp + 4, tuple, res);
133
 
            *hpp += 4+2;
 
129
    for (ohh = oh->first; ohh; ohh = ohh->next) {
 
130
        if (ohh->thing_word == HEADER_PROC_BIN) {
 
131
            ProcBin* pb = (ProcBin*) ohh;
 
132
            Eterm val = erts_bld_uword(hpp, szp, (UWord) pb->val);
 
133
            Eterm orig_size = erts_bld_uint(hpp, szp, pb->val->orig_size);
 
134
    
 
135
            if (szp)
 
136
                *szp += 4+2;
 
137
            if (hpp) {
 
138
                Uint refc = (Uint) erts_smp_atomic_read(&pb->val->refc);
 
139
                tuple = TUPLE3(*hpp, val, orig_size, make_small(refc));
 
140
                res = CONS(*hpp + 4, tuple, res);
 
141
                *hpp += 4+2;
 
142
            }
134
143
        }
135
144
    }
136
145
    return res;
169
178
    Eterm tup;
170
179
    Eterm r = (IS_CONST(mon->ref)
171
180
               ? mon->ref
172
 
               : STORE_NC(&(pmlc->hp), &MSO(pmlc->p).externals, mon->ref));
 
181
               : STORE_NC(&(pmlc->hp), &MSO(pmlc->p), mon->ref));
173
182
    Eterm p = (IS_CONST(mon->pid)
174
183
               ? mon->pid
175
 
               : STORE_NC(&(pmlc->hp), &MSO(pmlc->p).externals, mon->pid));
 
184
               : STORE_NC(&(pmlc->hp), &MSO(pmlc->p), mon->pid));
176
185
    tup = TUPLE5(pmlc->hp, pmlc->tag, make_small(mon->type), r, p, mon->name);
177
186
    pmlc->hp += 6;
178
187
    pmlc->res = CONS(pmlc->hp, tup, pmlc->res);
233
242
    Eterm old_res, targets = NIL;
234
243
    Eterm p = (IS_CONST(lnk->pid)
235
244
               ? lnk->pid
236
 
               : STORE_NC(&(pllc->hp), &MSO(pllc->p).externals, lnk->pid));
 
245
               : STORE_NC(&(pllc->hp), &MSO(pllc->p), lnk->pid));
237
246
    if (lnk->type == LINK_NODE) {
238
247
        targets = make_small(ERTS_LINK_REFC(lnk));
239
248
    } else if (ERTS_LINK_ROOT(lnk) != NULL) {
543
552
    am_last_calls,
544
553
    am_total_heap_size,
545
554
    am_suspending,
 
555
    am_min_heap_size,
 
556
    am_min_bin_vheap_size,
546
557
#ifdef HYBRID
547
558
    am_message_binary
548
559
#endif
589
600
    case am_last_calls:                         return 24;
590
601
    case am_total_heap_size:                    return 25;
591
602
    case am_suspending:                         return 26;
 
603
    case am_min_heap_size:                      return 27;
 
604
    case am_min_bin_vheap_size:                 return 28;
592
605
#ifdef HYBRID
593
 
    case am_message_binary:                     return 27;
 
606
    case am_message_binary:                     return 29;
594
607
#endif
595
608
    default:                                    return -1;
596
609
    }
620
633
#define ERTS_PI_1_NO_OF_KEYS (sizeof(pi_1_keys)/sizeof(Eterm))
621
634
 
622
635
static Eterm pi_1_keys_list;
623
 
static Uint pi_1_keys_list_heap[2*ERTS_PI_1_NO_OF_KEYS];
 
636
#if HEAP_ON_C_STACK
 
637
static Eterm pi_1_keys_list_heap[2*ERTS_PI_1_NO_OF_KEYS];
 
638
#endif
624
639
 
625
640
static void
626
641
process_info_init(void)
627
642
{
 
643
#if HEAP_ON_C_STACK
628
644
    Eterm *hp = &pi_1_keys_list_heap[0];
 
645
#else
 
646
    Eterm *hp = erts_alloc(ERTS_ALC_T_LL_TEMP_TERM,sizeof(Eterm)*2*ERTS_PI_1_NO_OF_KEYS);
 
647
#endif
629
648
    int i;
630
649
 
631
650
    pi_1_keys_list = NIL;
994
1013
            hp = HAlloc(BIF_P, 3);
995
1014
            res = am_undefined;
996
1015
        } else {
997
 
            Eterm* current;
 
1016
            BeamInstr* current;
998
1017
 
999
1018
            if (rp->current[0] == am_erlang &&
1000
1019
                rp->current[1] == am_process_info &&
1123
1142
                        }
1124
1143
                        else {
1125
1144
                            /* Make our copy of the message */
1126
 
                            ASSERT(size_object(msg) == hfp->size);
 
1145
                            ASSERT(size_object(msg) == hfp->used_size);
1127
1146
                            msg = copy_struct(msg,
1128
 
                                              hfp->size,
 
1147
                                              hfp->used_size,
1129
1148
                                              &hp,
1130
1149
                                              &MSO(BIF_P));
1131
1150
                        }
1208
1227
        hp = HAlloc(BIF_P, 3 + mic.sz);
1209
1228
        res = NIL;
1210
1229
        for (i = 0; i < mic.mi_i; i++) {
1211
 
            item = STORE_NC(&hp, &MSO(BIF_P).externals, mic.mi[i].entity); 
 
1230
            item = STORE_NC(&hp, &MSO(BIF_P), mic.mi[i].entity); 
1212
1231
            res = CONS(hp, item, res);
1213
1232
            hp += 2;
1214
1233
        }
1241
1260
            else {
1242
1261
                /* Monitor by pid. Build {process, Pid} and cons it. */
1243
1262
                Eterm t;
1244
 
                Eterm pid = STORE_NC(&hp,
1245
 
                                     &MSO(BIF_P).externals,
1246
 
                                     mic.mi[i].entity);
 
1263
                Eterm pid = STORE_NC(&hp, &MSO(BIF_P), mic.mi[i].entity);
1247
1264
                t = TUPLE2(hp, am_process, pid);
1248
1265
                hp += 3;
1249
1266
                res = CONS(hp, t, res);
1265
1282
 
1266
1283
        res = NIL;
1267
1284
        for (i = 0; i < mic.mi_i; ++i) {
1268
 
            item = STORE_NC(&hp, &MSO(BIF_P).externals, mic.mi[i].entity); 
 
1285
            item = STORE_NC(&hp, &MSO(BIF_P), mic.mi[i].entity); 
1269
1286
            res = CONS(hp, item, res);
1270
1287
            hp += 2;
1271
1288
        }
1355
1372
        break;
1356
1373
    }
1357
1374
 
 
1375
    case am_fullsweep_after: {
 
1376
        Uint hsz = 3;
 
1377
        (void) erts_bld_uint(NULL, &hsz, MAX_GEN_GCS(rp));
 
1378
        hp = HAlloc(BIF_P, hsz);
 
1379
        res = erts_bld_uint(&hp, NULL, MAX_GEN_GCS(rp));
 
1380
        break;
 
1381
    }
 
1382
 
 
1383
    case am_min_heap_size: {
 
1384
        Uint hsz = 3;
 
1385
        (void) erts_bld_uint(NULL, &hsz, MIN_HEAP_SIZE(rp));
 
1386
        hp = HAlloc(BIF_P, hsz);
 
1387
        res = erts_bld_uint(&hp, NULL, MIN_HEAP_SIZE(rp));
 
1388
        break;
 
1389
    }
 
1390
 
 
1391
    case am_min_bin_vheap_size: {
 
1392
        Uint hsz = 3;
 
1393
        (void) erts_bld_uint(NULL, &hsz, MIN_VHEAP_SIZE(rp));
 
1394
        hp = HAlloc(BIF_P, hsz);
 
1395
        res = erts_bld_uint(&hp, NULL, MIN_VHEAP_SIZE(rp));
 
1396
        break;
 
1397
    }
 
1398
 
1358
1399
    case am_total_heap_size: {
1359
1400
        ErlMessage *mp;
1360
1401
        Uint total_heap_size;
1433
1474
        DECL_AM(minor_gcs);
1434
1475
        Eterm t;
1435
1476
 
1436
 
        hp = HAlloc(BIF_P, 3+2+3+2+3);
1437
 
        t = TUPLE2(hp, AM_minor_gcs, make_small(GEN_GCS(rp)));
1438
 
        hp += 3;
1439
 
        res = CONS(hp, t, NIL);
1440
 
        hp += 2;
1441
 
        t = TUPLE2(hp, am_fullsweep_after, make_small(MAX_GEN_GCS(rp)));
1442
 
        hp += 3;
1443
 
        res = CONS(hp, t, res);
1444
 
        hp += 2;
 
1477
        hp = HAlloc(BIF_P, 3+2 + 3+2 + 3+2 + 3+2 + 3); /* last "3" is for outside tuple */
 
1478
 
 
1479
        t = TUPLE2(hp, AM_minor_gcs, make_small(GEN_GCS(rp))); hp += 3;
 
1480
        res = CONS(hp, t, NIL); hp += 2;
 
1481
        t = TUPLE2(hp, am_fullsweep_after, make_small(MAX_GEN_GCS(rp))); hp += 3;
 
1482
        res = CONS(hp, t, res); hp += 2;
 
1483
 
 
1484
        t = TUPLE2(hp, am_min_heap_size, make_small(MIN_HEAP_SIZE(rp))); hp += 3;
 
1485
        res = CONS(hp, t, res); hp += 2;
 
1486
        t = TUPLE2(hp, am_min_bin_vheap_size, make_small(MIN_VHEAP_SIZE(rp))); hp += 3;
 
1487
        res = CONS(hp, t, res); hp += 2;
1445
1488
        break;
1446
1489
    }
1447
1490
 
1448
1491
    case am_group_leader: {
1449
1492
        int sz = NC_HEAP_SIZE(rp->group_leader);
1450
1493
        hp = HAlloc(BIF_P, 3 + sz);
1451
 
        res = STORE_NC(&hp, &MSO(BIF_P).externals, rp->group_leader);
 
1494
        res = STORE_NC(&hp, &MSO(BIF_P), rp->group_leader);
1452
1495
        break;
1453
1496
    }
1454
1497
 
1473
1516
 
1474
1517
    case am_binary: {
1475
1518
        Uint sz = 3;
1476
 
        (void) bld_bin_list(NULL, &sz, MSO(rp).mso);
 
1519
        (void) bld_bin_list(NULL, &sz, &MSO(rp));
1477
1520
        hp = HAlloc(BIF_P, sz);
1478
 
        res = bld_bin_list(&hp, NULL, MSO(rp).mso);
 
1521
        res = bld_bin_list(&hp, NULL, &MSO(rp));
1479
1522
        break;
1480
1523
    }
1481
1524
 
1502
1545
    case am_backtrace: {
1503
1546
        erts_dsprintf_buf_t *dsbufp = erts_create_tmp_dsbuf(0);
1504
1547
        erts_stack_dump(ERTS_PRINT_DSBUF, (void *) dsbufp, rp);
1505
 
        res = new_binary(BIF_P, (byte *) dsbufp->str, (int) dsbufp->str_len);
 
1548
        res = new_binary(BIF_P, (byte *) dsbufp->str, dsbufp->str_len);
1506
1549
        erts_destroy_tmp_dsbuf(dsbufp);
1507
1550
        hp = HAlloc(BIF_P, 3);
1508
1551
        break;
1592
1635
 
1593
1636
    if (sel == am_allocator_sizes && arity == 2) {
1594
1637
        return erts_allocator_info_term(BIF_P, *tp, 1);
 
1638
    } else if (sel == am_wordsize && arity == 2) {
 
1639
        if (tp[0] == am_internal) {
 
1640
            return make_small(sizeof(Eterm));
 
1641
        }
 
1642
        if (tp[0] == am_external) {
 
1643
            return make_small(sizeof(UWord));
 
1644
        }
 
1645
        goto badarg;
1595
1646
    } else if (sel == am_allocated) {
1596
1647
        if (arity == 2) {
1597
1648
            Eterm res = THE_NON_VALUE;
1637
1688
        return erts_get_cpu_topology_term(BIF_P, *tp);
1638
1689
    } else if (ERTS_IS_ATOM_STR("cpu_topology", sel) && arity == 2) {
1639
1690
        Eterm res = erts_get_cpu_topology_term(BIF_P, *tp);
 
1691
        if (res == THE_NON_VALUE)
 
1692
            goto badarg;
1640
1693
        ERTS_BIF_PREP_TRAP1(ret, erts_format_cpu_topology_trap, BIF_P, res);
1641
1694
        return ret;
1642
1695
#if defined(PURIFY) || defined(VALGRIND)
1841
1894
 
1842
1895
}
1843
1896
 
 
1897
static int is_snif_term(Eterm module_atom) {
 
1898
    int i;
 
1899
    Atom *a = atom_tab(atom_val(module_atom));
 
1900
    char *aname = (char *) a->name;
 
1901
 
 
1902
    /* if a->name has a '.' then the bif (snif) is bogus i.e a package */
 
1903
    for (i = 0; i < a->len; i++) {
 
1904
        if (aname[i] == '.')
 
1905
            return 0;
 
1906
    }
 
1907
 
 
1908
    return 1;
 
1909
}
 
1910
 
 
1911
static Eterm build_snif_term(Eterm **hpp, Uint *szp, int ix, Eterm res) {
 
1912
    Eterm tup;
 
1913
    tup = erts_bld_tuple(hpp, szp, 3, bif_table[ix].module, bif_table[ix].name, make_small(bif_table[ix].arity));
 
1914
    res = erts_bld_cons( hpp, szp, tup, res);
 
1915
    return res;
 
1916
}
 
1917
 
 
1918
static Eterm build_snifs_term(Eterm **hpp, Uint *szp, Eterm res) {
 
1919
    int i;
 
1920
    for (i = 0; i < BIF_SIZE; i++) {
 
1921
        if (is_snif_term(bif_table[i].module)) {
 
1922
            res = build_snif_term(hpp, szp, i, res);
 
1923
        }
 
1924
    }
 
1925
    return res;
 
1926
}
 
1927
 
1844
1928
BIF_RETTYPE system_info_1(BIF_ALIST_1)
1845
1929
{
1846
1930
    Eterm res;
1874
1958
                    : am_enabled);
1875
1959
        }
1876
1960
#endif
 
1961
    } else if (BIF_ARG_1 == am_build_type) {
 
1962
#if defined(DEBUG)
 
1963
        ERTS_DECL_AM(debug);
 
1964
        BIF_RET(AM_debug);
 
1965
#elif defined(PURIFY)
 
1966
        ERTS_DECL_AM(purify);
 
1967
        BIF_RET(AM_purify);
 
1968
#elif defined(QUANTIFY)
 
1969
        ERTS_DECL_AM(quantify);
 
1970
        BIF_RET(AM_quantify);
 
1971
#elif defined(PURECOV)
 
1972
        ERTS_DECL_AM(purecov);
 
1973
        BIF_RET(AM_purecov);
 
1974
#elif defined(ERTS_GCOV)
 
1975
        ERTS_DECL_AM(gcov);
 
1976
        BIF_RET(AM_gcov);
 
1977
#elif defined(VALGRIND)
 
1978
        ERTS_DECL_AM(valgrind);
 
1979
        BIF_RET(AM_valgrind);
 
1980
#elif defined(GPROF)
 
1981
        ERTS_DECL_AM(gprof);
 
1982
        BIF_RET(AM_gprof);
 
1983
#elif defined(ERTS_ENABLE_LOCK_COUNT)
 
1984
        ERTS_DECL_AM(lcnt);
 
1985
        BIF_RET(AM_lcnt);
 
1986
#else
 
1987
        BIF_RET(am_opt);
 
1988
#endif
 
1989
        BIF_RET(res);
1877
1990
    } else if (BIF_ARG_1 == am_allocated_areas) {
1878
1991
        res = erts_allocated_areas(NULL, NULL, BIF_P);
1879
1992
        BIF_RET(res);
1889
2002
        BIF_RET(db_get_trace_control_word_0(BIF_P));
1890
2003
    } else if (ERTS_IS_ATOM_STR("ets_realloc_moves", BIF_ARG_1)) {
1891
2004
        BIF_RET((erts_ets_realloc_always_moves) ? am_true : am_false);
 
2005
    } else if (ERTS_IS_ATOM_STR("ets_always_compress", BIF_ARG_1)) {
 
2006
        BIF_RET((erts_ets_always_compress) ? am_true : am_false);
 
2007
    } else if (ERTS_IS_ATOM_STR("snifs", BIF_ARG_1)) {
 
2008
        Uint size = 0;
 
2009
        Uint *szp;
 
2010
 
 
2011
        szp = &size;
 
2012
        build_snifs_term(NULL, szp, NIL);
 
2013
        hp = HAlloc(BIF_P, size);
 
2014
        res = build_snifs_term(&hp, NULL, NIL);
 
2015
        BIF_RET(res);
1892
2016
    } else if (BIF_ARG_1 == am_sequential_tracer) {
1893
2017
        val = erts_get_system_seq_tracer();
1894
2018
        ASSERT(is_internal_pid(val) || is_internal_port(val) || val==am_false)
1896
2020
        res = TUPLE2(hp, am_sequential_tracer, val);
1897
2021
        BIF_RET(res);
1898
2022
    } else if (BIF_ARG_1 == am_garbage_collection){
1899
 
        Uint val = (Uint) erts_smp_atomic_read(&erts_max_gen_gcs);
1900
 
        hp = HAlloc(BIF_P, 3+2);
1901
 
        res = TUPLE2(hp, am_fullsweep_after, make_small(val));
1902
 
        hp += 3;
1903
 
        res = CONS(hp, res, NIL);
 
2023
        Uint val = (Uint) erts_smp_atomic32_read(&erts_max_gen_gcs);
 
2024
        Eterm tup;
 
2025
        hp = HAlloc(BIF_P, 3+2 + 3+2 + 3+2);
 
2026
 
 
2027
        tup = TUPLE2(hp, am_fullsweep_after, make_small(val)); hp += 3;
 
2028
        res = CONS(hp, tup, NIL); hp += 2;
 
2029
 
 
2030
        tup = TUPLE2(hp, am_min_heap_size, make_small(H_MIN_SIZE)); hp += 3;
 
2031
        res = CONS(hp, tup, res); hp += 2;
 
2032
 
 
2033
        tup = TUPLE2(hp, am_min_bin_vheap_size, make_small(BIN_VH_MIN_SIZE)); hp += 3;
 
2034
        res = CONS(hp, tup, res); hp += 2;
 
2035
 
1904
2036
        BIF_RET(res);
1905
2037
    } else if (BIF_ARG_1 == am_fullsweep_after){
1906
 
        Uint val = (Uint) erts_smp_atomic_read(&erts_max_gen_gcs);
 
2038
        Uint val = (Uint) erts_smp_atomic32_read(&erts_max_gen_gcs);
1907
2039
        hp = HAlloc(BIF_P, 3);
1908
2040
        res = TUPLE2(hp, am_fullsweep_after, make_small(val));
1909
2041
        BIF_RET(res);
 
2042
    } else if (BIF_ARG_1 == am_min_heap_size) {
 
2043
        hp = HAlloc(BIF_P, 3);
 
2044
        res = TUPLE2(hp, am_min_heap_size,make_small(H_MIN_SIZE));
 
2045
        BIF_RET(res);
 
2046
    } else if (BIF_ARG_1 == am_min_bin_vheap_size) {
 
2047
        hp = HAlloc(BIF_P, 3);
 
2048
        res = TUPLE2(hp, am_min_bin_vheap_size,make_small(BIN_VH_MIN_SIZE));
 
2049
        BIF_RET(res);
1910
2050
    } else if (BIF_ARG_1 == am_process_count) {
1911
2051
        BIF_RET(make_small(erts_process_count()));
1912
2052
    } else if (BIF_ARG_1 == am_process_limit) {
1934
2074
        erts_smp_proc_lock(BIF_P, ERTS_PROC_LOCK_MAIN);
1935
2075
 
1936
2076
        ASSERT(dsbufp && dsbufp->str);
1937
 
        res = new_binary(BIF_P, (byte *) dsbufp->str, (int) dsbufp->str_len);
 
2077
        res = new_binary(BIF_P, (byte *) dsbufp->str, dsbufp->str_len);
1938
2078
        erts_destroy_info_dsbuf(dsbufp);
1939
2079
        BIF_RET(res);
1940
2080
    } else if (ERTS_IS_ATOM_STR("dist_ctrl", BIF_ARG_1)) {
2017
2157
        BIF_RET(erts_alloc_util_allocators((void *) BIF_P));
2018
2158
    }
2019
2159
    else if (BIF_ARG_1 == am_elib_malloc) {
2020
 
#ifdef ELIB_ALLOC_IS_CLIB
2021
 
        struct elib_stat stat;
2022
 
        DECL_AM(heap_size);
2023
 
        DECL_AM(max_alloced_size);
2024
 
        DECL_AM(alloced_size);
2025
 
        DECL_AM(free_size);
2026
 
        DECL_AM(no_alloced_blocks);
2027
 
        DECL_AM(no_free_blocks);
2028
 
        DECL_AM(smallest_alloced_block);
2029
 
        DECL_AM(largest_free_block);
2030
 
        Eterm atoms[8];
2031
 
        Eterm ints[8];
2032
 
        Uint **hpp;
2033
 
        Uint sz;
2034
 
        Uint *szp;
2035
 
        int length;
2036
 
#ifdef DEBUG
2037
 
        Uint *endp;
2038
 
#endif
2039
 
 
2040
 
        elib_stat(&stat);
2041
 
 
2042
 
        /* First find out the heap size needed ... */
2043
 
        hpp = NULL;
2044
 
        szp = &sz;
2045
 
        sz = 0;
2046
 
 
2047
 
    build_elib_malloc_term:
2048
 
        length = 0;
2049
 
        atoms[length] = AM_heap_size;
2050
 
        ints[length++] = erts_bld_uint(hpp, szp,
2051
 
                                       (Uint) stat.mem_total*sizeof(Uint));
2052
 
        atoms[length] = AM_max_alloced_size;
2053
 
        ints[length++] = erts_bld_uint(hpp, szp,
2054
 
                                       (Uint) stat.mem_max_alloc*sizeof(Uint));
2055
 
        atoms[length] = AM_alloced_size;
2056
 
        ints[length++] = erts_bld_uint(hpp, szp,
2057
 
                                       (Uint) stat.mem_alloc*sizeof(Uint));
2058
 
        atoms[length] = AM_free_size;
2059
 
        ints[length++] = erts_bld_uint(hpp, szp,
2060
 
                                       (Uint) stat.mem_free*sizeof(Uint));
2061
 
        atoms[length] = AM_no_alloced_blocks;
2062
 
        ints[length++] = erts_bld_uint(hpp, szp, (Uint) stat.mem_blocks);
2063
 
        atoms[length] = AM_no_free_blocks;
2064
 
        ints[length++] = erts_bld_uint(hpp, szp, (Uint) stat.free_blocks);
2065
 
        atoms[length] = AM_smallest_alloced_block;
2066
 
        ints[length++] = erts_bld_uint(hpp, szp,
2067
 
                                       (Uint) stat.min_used*sizeof(Uint));
2068
 
        atoms[length] = AM_largest_free_block;
2069
 
        ints[length++] = erts_bld_uint(hpp, szp,
2070
 
                                       (Uint) stat.max_free*sizeof(Uint));
2071
 
 
2072
 
 
2073
 
 
2074
 
        ASSERT(length <= sizeof(atoms)/sizeof(Eterm));
2075
 
        ASSERT(length <= sizeof(ints)/sizeof(Eterm));
2076
 
 
2077
 
        res = erts_bld_2tup_list(hpp, szp, length, atoms, ints);
2078
 
 
2079
 
        if (szp) {
2080
 
            /* ... and then build the term */
2081
 
            hp = HAlloc(BIF_P, sz);
2082
 
#ifdef DEBUG
2083
 
            endp = hp + sz;
2084
 
#endif
2085
 
 
2086
 
            szp = NULL;
2087
 
            hpp = &hp;
2088
 
            goto build_elib_malloc_term;
2089
 
        }
2090
 
 
2091
 
#ifdef DEBUG
2092
 
        ASSERT(endp == hp);
2093
 
#endif
2094
 
 
2095
 
#else /* #ifdef ELIB_ALLOC_IS_CLIB */
2096
 
        res = am_false;
2097
 
#endif /* #ifdef ELIB_ALLOC_IS_CLIB */
2098
 
 
2099
 
        BIF_RET(res);
 
2160
        /* To be removed in R15 */
 
2161
        BIF_RET(am_false);
2100
2162
    }
2101
2163
    else if (BIF_ARG_1 == am_os_version) {
2102
2164
       int major, minor, build;
2207
2269
    } else if (ERTS_IS_ATOM_STR("cpu_topology", BIF_ARG_1)) {
2208
2270
        res = erts_get_cpu_topology_term(BIF_P, am_used);
2209
2271
        BIF_TRAP1(erts_format_cpu_topology_trap, BIF_P, res);
 
2272
    } else if (ERTS_IS_ATOM_STR("update_cpu_info", BIF_ARG_1)) {
 
2273
        if (erts_update_cpu_info()) {
 
2274
            ERTS_DECL_AM(changed);
 
2275
            BIF_RET(AM_changed);
 
2276
        }
 
2277
        else {
 
2278
            ERTS_DECL_AM(unchanged);
 
2279
            BIF_RET(AM_unchanged);
 
2280
        }
2210
2281
#if defined(__GNUC__) && defined(HAVE_SOLARIS_SPARC_PERFMON)
2211
2282
    } else if (ERTS_IS_ATOM_STR("ultrasparc_read_tick1", BIF_ARG_1)) {
2212
2283
        register unsigned high asm("%l0");
2278
2349
    }
2279
2350
    /* Arguments that are unusual follow ... */
2280
2351
    else if (ERTS_IS_ATOM_STR("logical_processors", BIF_ARG_1)) {
2281
 
        int no = erts_get_cpu_configured(erts_cpuinfo);
 
2352
        int no;
 
2353
        erts_get_logical_processors(&no, NULL, NULL);
2282
2354
        if (no > 0)
2283
2355
            BIF_RET(make_small((Uint) no));
2284
2356
        else {
2287
2359
        }
2288
2360
    }
2289
2361
    else if (ERTS_IS_ATOM_STR("logical_processors_online", BIF_ARG_1)) {
2290
 
        int no = erts_get_cpu_online(erts_cpuinfo);
 
2362
        int no;
 
2363
        erts_get_logical_processors(NULL, &no, NULL);
2291
2364
        if (no > 0)
2292
2365
            BIF_RET(make_small((Uint) no));
2293
2366
        else {
2296
2369
        }
2297
2370
    }
2298
2371
    else if (ERTS_IS_ATOM_STR("logical_processors_available", BIF_ARG_1)) {
2299
 
        int no = erts_get_cpu_available(erts_cpuinfo);
 
2372
        int no;
 
2373
        erts_get_logical_processors(NULL, NULL, &no);
2300
2374
        if (no > 0)
2301
2375
            BIF_RET(make_small((Uint) no));
2302
2376
        else {
2456
2530
        BIF_RET(erts_sched_stat_term(BIF_P, 1));
2457
2531
    } else if (ERTS_IS_ATOM_STR("taints", BIF_ARG_1)) {
2458
2532
        BIF_RET(erts_nif_taints(BIF_P));
 
2533
    } else if (ERTS_IS_ATOM_STR("reader_groups_map", BIF_ARG_1)) {
 
2534
        BIF_RET(erts_get_reader_groups_map(BIF_P));
 
2535
    } else if (ERTS_IS_ATOM_STR("dist_buf_busy_limit", BIF_ARG_1)) {
 
2536
        Uint hsz = 0;
 
2537
 
 
2538
        (void) erts_bld_uint(NULL, &hsz, erts_dist_buf_busy_limit);
 
2539
        hp = hsz ? HAlloc(BIF_P, hsz) : NULL;
 
2540
        res = erts_bld_uint(&hp, NULL, erts_dist_buf_busy_limit);
 
2541
        BIF_RET(res);
2459
2542
    }
2460
2543
 
2461
2544
    BIF_ERROR(BIF_P, BADARG);
2571
2654
        hp = HAlloc(BIF_P, 3 + mic.sz);
2572
2655
        res = NIL;
2573
2656
        for (i = 0; i < mic.mi_i; i++) {
2574
 
            item = STORE_NC(&hp, &MSO(BIF_P).externals, mic.mi[i].entity); 
 
2657
            item = STORE_NC(&hp, &MSO(BIF_P), mic.mi[i].entity); 
2575
2658
            res = CONS(hp, item, res);
2576
2659
            hp += 2;
2577
2660
        }
2591
2674
        res = NIL;
2592
2675
        for (i = 0; i < mic.mi_i; i++) {
2593
2676
            Eterm t;
2594
 
            item = STORE_NC(&hp, &MSO(BIF_P).externals, mic.mi[i].entity); 
 
2677
            item = STORE_NC(&hp, &MSO(BIF_P), mic.mi[i].entity); 
2595
2678
            t = TUPLE2(hp, am_process, item);
2596
2679
            hp += 3;
2597
2680
            res = CONS(hp, t, res);
2648
2731
        erts_doforall_links(prt->nlinks, &one_link_size, &size);
2649
2732
 
2650
2733
        for (bp = prt->bp; bp; bp = bp->next)
2651
 
            size += sizeof(ErlHeapFragment) + (bp->size - 1)*sizeof(Eterm);
 
2734
            size += sizeof(ErlHeapFragment) + (bp->alloc_size - 1)*sizeof(Eterm);
2652
2735
 
2653
2736
        if (prt->linebuf)
2654
2737
            size += sizeof(LineBuf) + prt->linebuf->ovsiz;
2771
2854
            goto error;
2772
2855
        }
2773
2856
    } else if (is_export(fun)) {
2774
 
        Export* exp = (Export *) (export_val(fun))[1];
 
2857
        Export* exp = (Export *) ((UWord) (export_val(fun))[1]);
2775
2858
        switch (what) {
2776
2859
        case am_type:
2777
2860
            hp = HAlloc(p, 3);
2964
3047
        res = erts_run_queues_len(NULL);
2965
3048
        BIF_RET(make_small(res));
2966
3049
    } else if (BIF_ARG_1 == am_wall_clock) {
2967
 
        Uint w1, w2;
 
3050
        UWord w1, w2;
2968
3051
        Eterm b1, b2;
2969
3052
        wall_clock_elapsed_time_both(&w1, &w2);
2970
 
        b1 = erts_make_integer(w1,BIF_P);
2971
 
        b2 = erts_make_integer(w2,BIF_P);
 
3053
        b1 = erts_make_integer((Uint) w1,BIF_P);
 
3054
        b2 = erts_make_integer((Uint) w2,BIF_P);
2972
3055
        hp = HAlloc(BIF_P,3);
2973
3056
        res = TUPLE2(hp, b1, b2);
2974
3057
        BIF_RET(res);
3131
3214
        else if (ERTS_IS_ATOM_STR("available_internal_state", BIF_ARG_1)) {
3132
3215
            BIF_RET(am_true);
3133
3216
        }
 
3217
        else if (ERTS_IS_ATOM_STR("force_heap_frags", BIF_ARG_1)) {
 
3218
#ifdef FORCE_HEAP_FRAGS
 
3219
            BIF_RET(am_true);
 
3220
#else
 
3221
            BIF_RET(am_false);
 
3222
#endif
 
3223
        }
3134
3224
    }
3135
3225
    else if (is_tuple(BIF_ARG_1)) {
3136
3226
        Eterm* tp = tuple_val(BIF_ARG_1);
3312
3402
            else if (ERTS_IS_ATOM_STR("fake_scheduler_bindings", tp[1])) {
3313
3403
                return erts_fake_scheduler_bindings(BIF_P, tp[2]);
3314
3404
            }
 
3405
            else if (ERTS_IS_ATOM_STR("reader_groups_map", tp[1])) {
 
3406
                Sint groups;
 
3407
                if (is_not_small(tp[2]))
 
3408
                    BIF_ERROR(BIF_P, BADARG);
 
3409
                groups = signed_val(tp[2]);
 
3410
                if (groups < (Sint) 1 || groups > (Sint) INT_MAX)
 
3411
                    BIF_ERROR(BIF_P, BADARG);
 
3412
 
 
3413
                BIF_RET(erts_debug_reader_groups_map(BIF_P, (int) groups));
 
3414
            }
3315
3415
            break;
3316
3416
        }
3317
3417
        default:
3330
3430
     */
3331
3431
    if (ERTS_IS_ATOM_STR("available_internal_state", BIF_ARG_1)
3332
3432
        && (BIF_ARG_2 == am_true || BIF_ARG_2 == am_false)) {
3333
 
        long on = (long) (BIF_ARG_2 == am_true);
3334
 
        long prev_on = erts_smp_atomic_xchg(&available_internal_state, on);
 
3433
        erts_aint_t on = (erts_aint_t) (BIF_ARG_2 == am_true);
 
3434
        erts_aint_t prev_on = erts_smp_atomic_xchg(&available_internal_state, on);
3335
3435
        if (on) {
3336
3436
            erts_dsprintf_buf_t *dsbufp = erts_create_logger_dsbuf();
3337
3437
            erts_dsprintf(dsbufp, "Process %T ", BIF_P->id);
3493
3593
                }
3494
3594
            }
3495
3595
        }
 
3596
        else if (ERTS_IS_ATOM_STR("binary_loop_limit", BIF_ARG_1)) {
 
3597
            /* Used by binary_module_SUITE (stdlib) */
 
3598
            Uint max_loops;
 
3599
            if (is_atom(BIF_ARG_2) && ERTS_IS_ATOM_STR("default", BIF_ARG_2)) {
 
3600
                max_loops = erts_binary_set_loop_limit(-1);
 
3601
                BIF_RET(make_small(max_loops));
 
3602
            } else if (term_to_Uint(BIF_ARG_2, &max_loops) != 0) {
 
3603
                max_loops = erts_binary_set_loop_limit(max_loops);
 
3604
                BIF_RET(make_small(max_loops));
 
3605
            }
 
3606
        }
3496
3607
        else if (ERTS_IS_ATOM_STR("re_loop_limit", BIF_ARG_1)) {
3497
3608
            /* Used by re_SUITE (stdlib) */
3498
3609
            Uint max_loops;
3517
3628
        }
3518
3629
        else if (ERTS_IS_ATOM_STR("hipe_test_reschedule_suspend", BIF_ARG_1)) {
3519
3630
            /* Used by hipe test suites */
3520
 
            long flag = erts_smp_atomic_read(&hipe_test_reschedule_flag);
 
3631
            erts_aint_t flag = erts_smp_atomic_read(&hipe_test_reschedule_flag);
3521
3632
            if (!flag && BIF_ARG_2 != am_false) {
3522
3633
                erts_smp_atomic_set(&hipe_test_reschedule_flag, 1);
3523
3634
                erts_suspend(BIF_P, ERTS_PROC_LOCK_MAIN, NULL);
3592
3703
 
3593
3704
#ifdef ERTS_ENABLE_LOCK_COUNT
3594
3705
static Eterm lcnt_build_lock_stats_term(Eterm **hpp, Uint *szp, erts_lcnt_lock_stats_t *stats, Eterm res) {
3595
 
    unsigned long tries = 0, colls = 0;
 
3706
    Uint tries = 0, colls = 0;
3596
3707
    unsigned long timer_s = 0, timer_ns = 0, timer_n = 0;
3597
3708
    unsigned int  line = 0;
3598
3709
    
3605
3716
     * [{{file, line}, {tries, colls, {seconds, nanoseconds, n_blocks}}}]
3606
3717
     */
3607
3718
    
3608
 
    ethr_atomic_read(&stats->tries, (long *)&tries);
3609
 
    ethr_atomic_read(&stats->colls, (long *)&colls);
 
3719
    tries = (Uint) ethr_atomic_read(&stats->tries);
 
3720
    colls = (Uint) ethr_atomic_read(&stats->colls);
3610
3721
   
3611
3722
    line     = stats->line; 
3612
3723
    timer_s  = stats->timer.s;
3651
3762
    ASSERT(ltype);
3652
3763
    
3653
3764
    type  = am_atom_put(ltype, strlen(ltype));           
3654
 
 
3655
3765
    name  = am_atom_put(lock->name, strlen(lock->name)); 
3656
3766
 
3657
3767
    if (lock->flag & ERTS_LCNT_LT_ALLOC) {
3658
3768
        /* use allocator types names as id's for allocator locks */
3659
 
        ltype = ERTS_ALC_A2AD(signed_val(lock->id));
 
3769
        ltype = (char *) ERTS_ALC_A2AD(signed_val(lock->id));
3660
3770
        id    = am_atom_put(ltype, strlen(ltype));
3661
3771
    } else if (lock->flag & ERTS_LCNT_LT_PROCLOCK) {
3662
3772
        /* use registered names as id's for process locks if available */
3725
3835
{
3726
3836
#ifdef ERTS_ENABLE_LOCK_COUNT
3727
3837
    Eterm res = NIL;
3728
 
    erts_smp_proc_unlock(BIF_P, ERTS_PROC_LOCK_MAIN);
3729
 
    erts_smp_block_system(0);
3730
 
 
3731
 
    if (BIF_ARG_1 == am_info) {
 
3838
#endif
 
3839
 
 
3840
 
 
3841
    if (BIF_ARG_1 == am_enabled) {
 
3842
#ifdef ERTS_ENABLE_LOCK_COUNT
 
3843
        BIF_RET(am_true);
 
3844
#else
 
3845
        BIF_RET(am_false);
 
3846
#endif
 
3847
    }
 
3848
#ifdef ERTS_ENABLE_LOCK_COUNT
 
3849
 
 
3850
    else if (BIF_ARG_1 == am_info) {
3732
3851
        erts_lcnt_data_t *data; 
3733
3852
        Uint hsize = 0;
3734
3853
        Uint *szp;
3735
3854
        Eterm* hp;
3736
3855
 
 
3856
        erts_smp_proc_unlock(BIF_P, ERTS_PROC_LOCK_MAIN);
 
3857
        erts_smp_block_system(0);
 
3858
 
3737
3859
        erts_lcnt_set_rt_opt(ERTS_LCNT_OPT_SUSPEND);
3738
 
 
3739
3860
        data = erts_lcnt_get_data();
3740
3861
 
3741
3862
        /* calculate size */
3750
3871
        res = lcnt_build_result_term(&hp, NULL, data, res);
3751
3872
        
3752
3873
        erts_lcnt_clear_rt_opt(ERTS_LCNT_OPT_SUSPEND);
 
3874
 
 
3875
        erts_smp_release_system();
 
3876
        erts_smp_proc_lock(BIF_P, ERTS_PROC_LOCK_MAIN);
3753
3877
        
3754
 
        goto done;
 
3878
        BIF_RET(res);
3755
3879
    } else if (BIF_ARG_1 == am_clear) {
 
3880
        erts_smp_proc_unlock(BIF_P, ERTS_PROC_LOCK_MAIN);
 
3881
        erts_smp_block_system(0);
 
3882
 
3756
3883
        erts_lcnt_clear_counters();
3757
 
        res = am_ok;
3758
 
        goto done;
 
3884
 
 
3885
        erts_smp_release_system();
 
3886
        erts_smp_proc_lock(BIF_P, ERTS_PROC_LOCK_MAIN);
 
3887
 
 
3888
        BIF_RET(am_ok);
3759
3889
    } else if (is_tuple(BIF_ARG_1)) {
3760
 
        Uint prev = 0;
3761
3890
        Eterm* tp = tuple_val(BIF_ARG_1);
 
3891
 
3762
3892
        switch (arityval(tp[0])) {
3763
3893
            case 2:
3764
 
                if (ERTS_IS_ATOM_STR("process_locks", tp[1])) {
3765
 
                    if (tp[2] == am_true) {
3766
 
                        prev = erts_lcnt_set_rt_opt(ERTS_LCNT_OPT_PROCLOCK);
3767
 
                        if (prev) res = am_true;
3768
 
                        else res = am_false;
3769
 
                        goto done;
3770
 
                    } else if (tp[2] == am_false) {
3771
 
                        prev = erts_lcnt_clear_rt_opt(ERTS_LCNT_OPT_PROCLOCK);
3772
 
                        if (prev) res = am_true;
3773
 
                        else res = am_false;
3774
 
                        goto done;
3775
 
                    }
 
3894
                if (ERTS_IS_ATOM_STR("copy_save", tp[1])) {
 
3895
                    erts_smp_proc_unlock(BIF_P, ERTS_PROC_LOCK_MAIN);
 
3896
                    erts_smp_block_system(0);
 
3897
                    if (tp[2] == am_true) {
 
3898
 
 
3899
                        res = erts_lcnt_set_rt_opt(ERTS_LCNT_OPT_COPYSAVE) ? am_true : am_false;
 
3900
 
 
3901
                    } else if (tp[2] == am_false) {
 
3902
 
 
3903
                        res = erts_lcnt_clear_rt_opt(ERTS_LCNT_OPT_COPYSAVE) ? am_true : am_false;
 
3904
 
 
3905
                    } else {
 
3906
                        erts_smp_release_system();
 
3907
                        erts_smp_proc_lock(BIF_P, ERTS_PROC_LOCK_MAIN);
 
3908
                        BIF_ERROR(BIF_P, BADARG);
 
3909
                    }
 
3910
                    erts_smp_release_system();
 
3911
                    erts_smp_proc_lock(BIF_P, ERTS_PROC_LOCK_MAIN);
 
3912
                    BIF_RET(res);
 
3913
 
 
3914
                } else if (ERTS_IS_ATOM_STR("process_locks", tp[1])) {
 
3915
                    erts_smp_proc_unlock(BIF_P, ERTS_PROC_LOCK_MAIN);
 
3916
                    erts_smp_block_system(0);
 
3917
                    if (tp[2] == am_true) {
 
3918
 
 
3919
                        res = erts_lcnt_set_rt_opt(ERTS_LCNT_OPT_PROCLOCK) ? am_true : am_false;
 
3920
 
 
3921
                    } else if (tp[2] == am_false) {
 
3922
 
 
3923
                        res = erts_lcnt_set_rt_opt(ERTS_LCNT_OPT_PROCLOCK) ? am_true : am_false;
 
3924
 
 
3925
                    } else {
 
3926
                        erts_smp_release_system();
 
3927
                        erts_smp_proc_lock(BIF_P, ERTS_PROC_LOCK_MAIN);
 
3928
                        BIF_ERROR(BIF_P, BADARG);
 
3929
                    }
 
3930
                    erts_smp_release_system();
 
3931
                    erts_smp_proc_lock(BIF_P, ERTS_PROC_LOCK_MAIN);
 
3932
                    BIF_RET(res);
3776
3933
                 }
3777
3934
            break;
3778
3935
     
3781
3938
        }
3782
3939
    } 
3783
3940
 
3784
 
    erts_smp_release_system();
3785
 
    erts_smp_proc_lock(BIF_P, ERTS_PROC_LOCK_MAIN);
3786
3941
#endif 
3787
3942
    BIF_ERROR(BIF_P, BADARG);
3788
 
#ifdef ERTS_ENABLE_LOCK_COUNT
3789
 
done:    
3790
 
    erts_smp_release_system();
3791
 
    erts_smp_proc_lock(BIF_P, ERTS_PROC_LOCK_MAIN);
3792
 
    BIF_RET(res);
3793
 
#endif 
3794
3943
}
3795
3944
 
3796
3945
void