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

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
23
23
#include "erl_vm.h"
24
24
#include "global.h"
25
25
#include "erl_process.h"
 
26
#include "erl_nmgc.h"
26
27
#include "error.h"
27
28
#include "erl_driver.h"
28
29
#include "bif.h"
33
34
#include "erl_binary.h"
34
35
#include "erl_db.h"
35
36
#include "erl_instrument.h"
 
37
#include "dist.h"
36
38
#ifdef ELIB_ALLOC_IS_CLIB
37
39
#include "elib_stat.h"
38
40
#endif
 
41
#ifdef HIPE
 
42
#include "hipe_arch.h"
 
43
#endif
 
44
 
 
45
#ifdef VALGRIND
 
46
#include <valgrind/valgrind.h>
 
47
#include <valgrind/memcheck.h>
 
48
#endif
39
49
 
40
50
#define DECL_AM(S) Eterm AM_ ## S = am_atom_put(#S, sizeof(#S) - 1)
 
51
#define INIT_AM(S) AM_ ## S = am_atom_put(#S, sizeof(#S) - 1)
41
52
 
42
53
#ifdef USE_THREADS
43
54
extern int erts_async_max_threads;
45
56
/* Keep erts_system_version as a global variable for easy access from a core */
46
57
static char erts_system_version[] = ("Erlang (" EMULATOR ")"
47
58
                                     " emulator version " ERLANG_VERSION
 
59
#ifndef OTP_RELEASE
 
60
                                     " [source]"
 
61
#endif  
48
62
#ifdef ARCH_64
49
63
                                     " [64-bit]"
50
64
#endif
51
 
#ifndef OTP_RELEASE
52
 
                                     " [source]"
53
 
#endif  
 
65
#ifdef ERTS_SMP
 
66
                                     " [smp:%bpu]"
 
67
#endif
 
68
#ifdef USE_THREADS
 
69
                                     " [async-threads:%d]"
 
70
#endif
54
71
#ifdef HIPE
55
72
                                     " [hipe]"
56
73
#endif  
57
 
#ifdef SHARED_HEAP
58
 
                                     " [shared heap]"
 
74
#ifdef HYBRID
 
75
                                     " [hybrid heap]"
 
76
#endif
 
77
#ifdef INCREMENTAL
 
78
                                     " [incremental GC]"
59
79
#endif
60
80
#ifdef ET_DEBUG
61
81
#if ET_DEBUG
65
85
#ifdef DEBUG
66
86
                                     " [debug-compiled]"
67
87
#endif  
68
 
#ifdef USE_THREADS
69
 
                                     " [threads:%d]"
70
 
#endif
71
 
#ifdef USE_KERNEL_POLL
72
 
                                     " [kernel-poll]"
73
 
#endif  
 
88
#ifdef ERTS_ENABLE_LOCK_CHECK
 
89
                                     " [lock-checking]"
 
90
#endif
 
91
#ifdef ERTS_ENABLE_KERNEL_POLL
 
92
                                     " [kernel-poll:%s]"
 
93
#endif  
 
94
#ifdef HEAP_FRAG_ELIM_TEST
 
95
                                     " [no-frag]"
 
96
#endif
 
97
#ifdef PURIFY
 
98
                                     " [purify-compiled]"
 
99
#endif  
 
100
#ifdef VALGRIND
 
101
                                     " [valgrind-compiled]"
 
102
#endif
74
103
                                     "\n");
75
104
 
 
105
#if defined(PURIFY) || defined(VALGRIND)
 
106
static Eterm AM_error_checker;
 
107
#ifdef VALGRIND
 
108
static Eterm AM_valgrind;
 
109
#endif
 
110
#endif
76
111
 
77
112
#define ASIZE(a) (sizeof(a)/sizeof(a[0]))
78
113
 
95
130
        if (szp)
96
131
            *szp += 4+2;
97
132
        if (hpp) {
98
 
            tuple = TUPLE3(*hpp, val, orig_size, make_small(pb->val->refc));
 
133
            Uint refc = (Uint) erts_smp_atomic_read(&pb->val->refc);
 
134
            tuple = TUPLE3(*hpp, val, orig_size, make_small(refc));
99
135
            res = CONS(*hpp + 4, tuple, res);
100
136
            *hpp += 4+2;
101
137
        }
103
139
    return res;
104
140
}
105
141
 
106
 
static Eterm
107
 
make_link_list(Process *p, ErlLink *ls)
 
142
 
 
143
/*
 
144
  make_monitor_list:
 
145
  returns a list of records..
 
146
  -record(erl_monitor, {
 
147
            type, % MON_ORIGIN or MON_TARGET (1 or 3)
 
148
            ref,
 
149
            pid, % Process or nodename
 
150
            name % registered name or []
 
151
          }).
 
152
*/
 
153
 
 
154
static void do_calc_mon_size(ErtsMonitor *mon, void *vpsz)
 
155
{
 
156
    Uint *psz = vpsz;
 
157
    *psz += IS_CONST(mon->ref) ? 0 : NC_HEAP_SIZE(mon->ref);
 
158
    *psz += IS_CONST(mon->pid) ? 0 : NC_HEAP_SIZE(mon->pid);
 
159
    *psz += 8; /* CONS + 5-tuple */ 
 
160
}
 
161
 
 
162
typedef struct {
 
163
    Process *p;
 
164
    Eterm *hp;
 
165
    Eterm res;
 
166
    Eterm tag;
 
167
} MonListContext;
 
168
 
 
169
static void do_make_one_mon_element(ErtsMonitor *mon, void * vpmlc)
 
170
{
 
171
    MonListContext *pmlc = vpmlc;
 
172
    Eterm tup;
 
173
    Eterm r = (IS_CONST(mon->ref)
 
174
               ? mon->ref
 
175
               : STORE_NC(&(pmlc->hp), &MSO(pmlc->p).externals, mon->ref));
 
176
    Eterm p = (IS_CONST(mon->pid)
 
177
               ? mon->pid
 
178
               : STORE_NC(&(pmlc->hp), &MSO(pmlc->p).externals, mon->pid));
 
179
    tup = TUPLE5(pmlc->hp, pmlc->tag, make_small(mon->type), r, p, mon->name);
 
180
    pmlc->hp += 6;
 
181
    pmlc->res = CONS(pmlc->hp, tup, pmlc->res);
 
182
    pmlc->hp += 2;
 
183
}
 
184
 
 
185
static Eterm 
 
186
make_monitor_list(Process *p, ErtsMonitor *root)
 
187
{
 
188
    DECL_AM(erl_monitor);
 
189
    Uint sz = 0;
 
190
    MonListContext mlc;
 
191
 
 
192
    erts_doforall_monitors(root, &do_calc_mon_size, &sz);
 
193
    if (sz == 0) {
 
194
        return NIL;
 
195
    }
 
196
    mlc.p = p;
 
197
    mlc.hp = HAlloc(p,sz);
 
198
    mlc.res = NIL;
 
199
    mlc.tag = AM_erl_monitor;
 
200
    erts_doforall_monitors(root, &do_make_one_mon_element, &mlc);
 
201
    return mlc.res;
 
202
}
 
203
 
 
204
/*
 
205
  make_link_list:
 
206
  returns a list of records..
 
207
  -record(erl_link, {
 
208
            type, % LINK_NODE or LINK_PID (1 or 3)
 
209
            pid, % Process or nodename
 
210
            targets % List of erl_link's or nil
 
211
          }).
 
212
*/
 
213
 
 
214
static void do_calc_lnk_size(ErtsLink *lnk, void *vpsz)
 
215
{
 
216
    Uint *psz = vpsz;
 
217
    *psz += IS_CONST(lnk->pid) ? 0 : NC_HEAP_SIZE(lnk->pid);
 
218
    if (lnk->type != LINK_NODE && lnk->root != NULL) { 
 
219
        /* Node links use this pointer as ref counter... */
 
220
        erts_doforall_links(lnk->root,&do_calc_lnk_size,vpsz);
 
221
    }
 
222
    *psz += 7; /* CONS + 4-tuple */ 
 
223
}
 
224
 
 
225
typedef struct {
 
226
    Process *p;
 
227
    Eterm *hp;
 
228
    Eterm res;
 
229
    Eterm tag;
 
230
} LnkListContext;
 
231
 
 
232
static void do_make_one_lnk_element(ErtsLink *lnk, void * vpllc)
 
233
{
 
234
    LnkListContext *pllc = vpllc;
 
235
    Eterm tup;
 
236
    Eterm old_res, targets = NIL;
 
237
    Eterm p = (IS_CONST(lnk->pid)
 
238
               ? lnk->pid
 
239
               : STORE_NC(&(pllc->hp), &MSO(pllc->p).externals, lnk->pid));
 
240
    if (lnk->type == LINK_NODE) {
 
241
        targets = make_small(ERTS_LINK_ROOT_AS_UINT(lnk));
 
242
    } else if (lnk->root != NULL) {
 
243
        old_res = pllc->res;
 
244
        pllc->res = NIL;
 
245
        erts_doforall_links(lnk->root,&do_make_one_lnk_element, vpllc);
 
246
        targets = pllc->res;
 
247
        pllc->res = old_res;
 
248
    }
 
249
    tup = TUPLE4(pllc->hp, pllc->tag, make_small(lnk->type), p, targets);
 
250
    pllc->hp += 5;
 
251
    pllc->res = CONS(pllc->hp, tup, pllc->res);
 
252
    pllc->hp += 2;
 
253
}
 
254
 
 
255
static Eterm 
 
256
make_link_list(Process *p, ErtsLink *root, Eterm tail)
108
257
{
109
258
    DECL_AM(erl_link);
110
 
    Eterm tup;
111
 
    Eterm res;
112
 
    Eterm *hp;
113
 
    ErlLink *l;
114
 
    Uint s;
115
 
#ifdef DEBUG
116
 
    Eterm *endp;
117
 
#endif
118
 
 
119
 
    for(l = ls, s = 0; l; l = l->next) {
120
 
        s += IS_CONST(l->item) ? 0 : NC_HEAP_SIZE(l->item);
121
 
        s += IS_CONST(l->data) ? 0 : NC_HEAP_SIZE(l->data);
122
 
        s += IS_CONST(l->ref)  ? 0 : NC_HEAP_SIZE(l->ref);
123
 
        s += 2 /* 1 cons cell */ + 6 /* 1 five-tuple */;
124
 
    }
125
 
 
126
 
    if(!s)
127
 
        return NIL;
128
 
 
129
 
    hp = HAlloc(p, s);
130
 
 
131
 
#ifdef DEBUG
132
 
    endp = hp + s;
133
 
#endif
134
 
 
135
 
    for(l = ls, res = NIL; l; l = l->next) {
136
 
        Eterm i = (IS_CONST(l->item)
137
 
                   ? l->item
138
 
                   : STORE_NC(&hp, &MSO(p).externals, l->item));
139
 
        Eterm d = (IS_CONST(l->data)
140
 
                   ? l->data
141
 
                   : STORE_NC(&hp, &MSO(p).externals, l->data));
142
 
        Eterm r = (IS_CONST(l->ref)
143
 
                   ? l->ref
144
 
                   : STORE_NC(&hp, &MSO(p).externals, l->ref));
145
 
        tup = TUPLE5(hp, AM_erl_link, make_small(l->type), i, d, r);
146
 
        hp += 6;
147
 
        res = CONS(hp, tup, res);
148
 
        hp += 2;
149
 
    }
150
 
 
151
 
#ifdef DEBUG
152
 
    ASSERT(hp == endp);
153
 
#endif
154
 
    
155
 
    return res;
 
259
    Uint sz = 0;
 
260
    LnkListContext llc;
 
261
 
 
262
    erts_doforall_links(root, &do_calc_lnk_size, &sz);
 
263
    if (sz == 0) {
 
264
        return tail;
 
265
    }
 
266
    llc.p = p;
 
267
    llc.hp = HAlloc(p,sz);
 
268
    llc.res = tail;
 
269
    llc.tag = AM_erl_link;
 
270
    erts_doforall_links(root, &do_make_one_lnk_element, &llc);
 
271
    return llc.res;
156
272
}
157
273
 
158
 
char*
159
 
erts_get_system_version(int *lenp)
 
274
int
 
275
erts_print_system_version(int to, void *arg, Process *c_p)
160
276
{
 
277
    return erts_print(to, arg, erts_system_version
 
278
#ifdef ERTS_SMP
 
279
                      , erts_get_no_schedulers()
 
280
#endif
161
281
#ifdef USE_THREADS
162
 
    static char sbuf[sizeof(erts_system_version) + 20];
163
 
 
164
 
    sprintf(sbuf, erts_system_version, erts_async_max_threads);
165
 
    if (lenp != NULL) {
166
 
        *lenp = sys_strlen(sbuf);
167
 
    }
168
 
    return sbuf;
169
 
#else
170
 
    if (lenp != NULL) {
171
 
        *lenp = sizeof(erts_system_version) - 1;
172
 
    }
173
 
    return erts_system_version;
174
 
#endif
 
282
                      , erts_async_max_threads
 
283
#endif
 
284
#ifdef ERTS_ENABLE_KERNEL_POLL
 
285
                      , erts_use_kernel_poll ? "true" : "false"
 
286
#endif
 
287
        );
175
288
}
176
289
 
 
290
BIF_RETTYPE
 
291
process_info_aux(Process *BIF_P, Process *rp, Eterm rpid, Eterm item);
 
292
 
177
293
Eterm
178
294
process_info_1(Process* p, Eterm pid)
179
295
{
194
310
        am_reductions,
195
311
        am_garbage_collection,
196
312
    };
 
313
    Process *rp;
197
314
    Eterm items[ASIZE(keys)+2];
198
315
    Eterm result = NIL;
199
316
    Eterm tmp;
201
318
    int i;
202
319
    int next = 0;
203
320
 
 
321
    if (is_external_pid(pid)
 
322
        && external_pid_dist_entry(pid) == erts_this_dist_entry)
 
323
        return am_undefined;
 
324
        
 
325
    if (is_not_internal_pid(pid)
 
326
        || internal_pid_index(pid) >= erts_max_processes) {
 
327
        BIF_ERROR(p, BADARG);
 
328
    }
 
329
 
 
330
    rp = erts_pid2proc(p, ERTS_PROC_LOCK_MAIN,
 
331
                       pid, ERTS_PROC_LOCKS_ALL);
 
332
    if (!rp) {
 
333
        return am_undefined;
 
334
    }
 
335
 
204
336
    /*
205
337
     * The dollar dictionary is special. We will only show it if its is non-empty.
206
338
     */
207
339
 
208
 
    tmp = process_info_2(p, pid, am_DollarDictionary);
 
340
    tmp = process_info_aux(p, rp, rp->id, am_DollarDictionary);
209
341
    if (is_non_value(tmp)) {
210
342
        return THE_NON_VALUE;
211
343
    } else if (is_tuple(tmp)) {
219
351
     * Registered name is also special.
220
352
     */
221
353
    
222
 
    tmp = process_info_2(p, pid, am_registered_name);
 
354
    tmp = process_info_aux(p, rp, rp->id, am_registered_name);
223
355
    if (is_tuple(tmp)) {
224
356
        items[next++] = tmp;
225
357
    }
231
363
    for (i = 0; i < ASIZE(keys); i++) {
232
364
        Eterm item;
233
365
 
234
 
        item = process_info_2(p, pid, keys[i]);
 
366
        item = process_info_aux(p, rp, rp->id, keys[i]);
235
367
        if (item == am_undefined) {
236
 
            return am_undefined;
 
368
            result = am_undefined;
 
369
            goto done;
237
370
        }
238
371
        items[next++] = item;
239
372
    }
248
381
        hp += 2;
249
382
    }
250
383
 
 
384
 
 
385
 done:
 
386
#ifdef ERTS_SMP
 
387
    erts_smp_proc_unlock(rp, 
 
388
                         (rp != p
 
389
                          ? ERTS_PROC_LOCKS_ALL
 
390
                          : (ERTS_PROC_LOCKS_ALL & ~ERTS_PROC_LOCK_MAIN)));
 
391
#endif
251
392
    return result;
252
393
}
253
394
 
 
395
typedef struct {
 
396
    Eterm entity;
 
397
    Eterm node;
 
398
} MonitorInfo;
 
399
 
 
400
typedef struct {
 
401
    MonitorInfo *mi;
 
402
    Uint mi_i;
 
403
    Uint mi_max;
 
404
    int sz;
 
405
} MonitorInfoCollection;
 
406
 
 
407
#define INIT_MONITOR_INFOS(MIC) do {            \
 
408
    (MIC).mi = NULL;                            \
 
409
    (MIC).mi_i = (MIC).mi_max = 0;              \
 
410
    (MIC).sz = 0;                               \
 
411
} while(0)
 
412
 
 
413
#define MI_INC 50
 
414
#define EXTEND_MONITOR_INFOS(MICP)                                      \
 
415
do {                                                                    \
 
416
    if ((MICP)->mi_i >= (MICP)->mi_max) {                               \
 
417
        (MICP)->mi = ((MICP)->mi ? erts_realloc(ERTS_ALC_T_TMP,         \
 
418
                                                (MICP)->mi,             \
 
419
                                                ((MICP)->mi_max+MI_INC) \
 
420
                                                * sizeof(MonitorInfo))  \
 
421
                      : erts_alloc(ERTS_ALC_T_TMP,                      \
 
422
                                   MI_INC*sizeof(MonitorInfo)));        \
 
423
        (MICP)->mi_max += MI_INC;                                       \
 
424
    }                                                                   \
 
425
 } while (0)
 
426
#define DESTROY_MONITOR_INFOS(MIC)                      \
 
427
do {                                                    \
 
428
    if ((MIC).mi != NULL) {                             \
 
429
        erts_free(ERTS_ALC_T_TMP, (void *) (MIC).mi);   \
 
430
    }                                                   \
 
431
 } while (0)
 
432
 
 
433
static void collect_one_link(ErtsLink *lnk, void *vmicp)
 
434
{
 
435
    MonitorInfoCollection *micp = vmicp;
 
436
    EXTEND_MONITOR_INFOS(micp);
 
437
    if (!(lnk->type == LINK_PID)) {
 
438
        return;
 
439
    }
 
440
    micp->mi[micp->mi_i].entity = lnk->pid;
 
441
    micp->sz += 2 + NC_HEAP_SIZE(lnk->pid);
 
442
    micp->mi_i++;
 
443
 
444
 
 
445
static void collect_one_origin_monitor(ErtsMonitor *mon, void *vmicp)
 
446
{
 
447
    MonitorInfoCollection *micp = vmicp;
 
448
 
 
449
    if (mon->type != MON_ORIGIN) {
 
450
        return;
 
451
    }
 
452
    EXTEND_MONITOR_INFOS(micp);
 
453
    if (is_atom(mon->pid)) { /* external by name */
 
454
        micp->mi[micp->mi_i].entity = mon->name;
 
455
        micp->mi[micp->mi_i].node = mon->pid;
 
456
        micp->sz += 3; /* need one 2-tuple */
 
457
    } else if (is_external_pid(mon->pid)) { /* external by pid */
 
458
        micp->mi[micp->mi_i].entity = mon->pid;
 
459
        micp->mi[micp->mi_i].node = NIL;
 
460
        micp->sz += NC_HEAP_SIZE(mon->pid);
 
461
    } else if (!is_nil(mon->name)) { /* internal by name */
 
462
        micp->mi[micp->mi_i].entity = mon->name;
 
463
        micp->mi[micp->mi_i].node = erts_this_dist_entry->sysname;
 
464
        micp->sz += 3; /* need one 2-tuple */
 
465
    } else { /* internal by pid */
 
466
        micp->mi[micp->mi_i].entity = mon->pid;
 
467
        micp->mi[micp->mi_i].node = NIL;
 
468
        /* no additional heap space needed */
 
469
    }
 
470
    micp->mi_i++;
 
471
    micp->sz += 2 + 3; /* For a cons cell and a 2-tuple */
 
472
}
 
473
 
 
474
static void collect_one_target_monitor(ErtsMonitor *mon, void *vmicp)
 
475
{
 
476
    MonitorInfoCollection *micp = vmicp;
 
477
 
 
478
    if (mon->type != MON_TARGET) {
 
479
        return;
 
480
    }
 
481
 
 
482
    EXTEND_MONITOR_INFOS(micp);
 
483
  
 
484
    micp->mi[micp->mi_i].node = NIL;
 
485
    micp->mi[micp->mi_i].entity = mon->pid;
 
486
    micp->sz += (NC_HEAP_SIZE(mon->pid) + 2 /* cons */);
 
487
    micp->mi_i++;
 
488
}
 
489
 
 
490
 
 
491
static void one_link_size(ErtsLink *lnk, void *vpu)
 
492
{
 
493
    Uint *pu = vpu;
 
494
    *pu += ERTS_LINK_SIZE*sizeof(Uint);
 
495
    if(!IS_CONST(lnk->pid))
 
496
        *pu += NC_HEAP_SIZE(lnk->pid)*sizeof(Uint);
 
497
    if (lnk->type != LINK_NODE && lnk->root != NULL) {
 
498
        erts_doforall_links(lnk->root,&one_link_size,vpu);
 
499
    }
 
500
}
 
501
static void one_mon_size(ErtsMonitor *mon, void *vpu)
 
502
{
 
503
    Uint *pu = vpu;
 
504
    *pu += ERTS_MONITOR_SIZE*sizeof(Uint);
 
505
    if(!IS_CONST(mon->pid))
 
506
        *pu += NC_HEAP_SIZE(mon->pid)*sizeof(Uint);
 
507
    if(!IS_CONST(mon->ref))
 
508
        *pu += NC_HEAP_SIZE(mon->ref)*sizeof(Uint);
 
509
}
 
510
 
254
511
BIF_RETTYPE process_info_2(BIF_ALIST_2) 
255
512
{
256
 
    Eterm item, term, list;
 
513
    int flags;
257
514
    Eterm res;
258
515
    Process *rp;
259
 
    Eterm* hp;
260
 
    int i, j;
261
516
    Eterm pid = BIF_ARG_1;
 
517
    Uint32 info_locks;
262
518
 
263
519
    if (is_external_pid(pid)
264
520
        && external_pid_dist_entry(pid) == erts_this_dist_entry)
272
528
    if (is_not_atom(BIF_ARG_2))
273
529
        BIF_ERROR(BIF_P, BADARG);
274
530
 
275
 
    item = BIF_ARG_2;
276
 
    
277
 
    rp = process_tab[internal_pid_index(BIF_ARG_1)];
278
 
 
279
 
    /* if the process is not active return undefined */
280
 
    if (INVALID_PID(rp, BIF_ARG_1)) {
281
 
        BIF_RET(am_undefined);
282
 
    }
283
 
    res = NIL;
 
531
    flags = 0;
 
532
    info_locks = ERTS_PROC_LOCK_MAIN; 
 
533
 
 
534
    switch (BIF_ARG_2) {
 
535
    case am_internal_status:
 
536
        flags = ERTS_P2P_FLG_ALLOW_OTHER_X;
 
537
#ifdef ERTS_SMP
 
538
    case am_status:
 
539
        info_locks = ERTS_PROC_LOCK_STATUS;
 
540
        break;
 
541
    case am_messages:
 
542
    case am_message_queue_len:
 
543
        info_locks |= ERTS_PROC_LOCK_MSGQ;
 
544
        break;
 
545
    case am_links:
 
546
    case am_monitors:
 
547
    case am_monitored_by:
 
548
        info_locks = ERTS_PROC_LOCK_LINK;
 
549
        break;
 
550
    case am_memory:
 
551
        info_locks |= ERTS_PROC_LOCK_LINK|ERTS_PROC_LOCK_MSGQ;
 
552
    default:
 
553
#endif
 
554
        break;
 
555
    }
 
556
 
 
557
    rp = erts_pid2proc_opt(BIF_P, ERTS_PROC_LOCK_MAIN, pid, info_locks, flags);
 
558
    if (rp || BIF_ARG_2 == am_internal_status)
 
559
        res = process_info_aux(BIF_P, rp, pid, BIF_ARG_2);
 
560
    else {
 
561
        res = am_undefined; /* if the process is not active return undefined */
 
562
    }
 
563
 
 
564
#ifdef ERTS_SMP
 
565
    if (BIF_P == rp)
 
566
        info_locks &= ~ERTS_PROC_LOCK_MAIN;
 
567
    if (rp && info_locks)
 
568
        erts_smp_proc_unlock(rp, info_locks);
 
569
#endif
 
570
 
 
571
    BIF_RET(res);
 
572
}
 
573
 
 
574
BIF_RETTYPE
 
575
process_info_aux(Process *BIF_P, Process *rp, Eterm rpid, Eterm item)
 
576
{
 
577
    Eterm *hp;
 
578
    Eterm res = NIL;
 
579
 
 
580
    /* internal_status is a little special... */
 
581
    ASSERT(rp || item == am_internal_status);
284
582
 
285
583
    if (item == am_registered_name) {
286
584
        if (rp->reg != NULL) {
326
624
                     rp->initial[INITIAL_FUN],
327
625
                     make_small(rp->initial[INITIAL_ARI]));
328
626
        hp += 4;
329
 
    } else if (item == am_status ) {
 
627
    } else if (item == am_status || item == am_internal_status) {
 
628
        res = erts_process_status(BIF_P, ERTS_PROC_LOCK_MAIN, rp, rpid);
 
629
        if (res == am_undefined)
 
630
            BIF_RET(res);
330
631
        hp = HAlloc(BIF_P, 3);
331
 
        switch (rp->status) {
332
 
        case P_RUNABLE:
333
 
            res = am_runnable;
334
 
            break;
335
 
        case P_WAITING:
336
 
            res = am_waiting;
337
 
            break;
338
 
        case P_RUNNING:
339
 
            res = am_running;
340
 
            break;
341
 
        case P_SUSPENDED:
342
 
            res = am_suspended;
343
 
            break;
344
 
        case P_EXITING:
345
 
            res = am_exiting;
346
 
            break;
347
 
        default:
348
 
            res = am_undefined;
349
 
        }
350
632
    } else if (item == am_messages) {
351
633
        ErlMessage* mp;
352
 
        Eterm* cons;
353
 
        int n = rp->msg.len;
354
 
        Uint size;
 
634
        int n;
 
635
 
 
636
        ERTS_SMP_MSGQ_MV_INQ2PRIVQ(rp);
 
637
        n = rp->msg.len;
355
638
 
356
639
        if (n == 0) {
357
640
            hp = HAlloc(BIF_P, 3);
358
 
            res = NIL;
359
641
        } else {
360
 
            size = 0;
361
 
            if (rp != BIF_P) {
362
 
                mp = rp->msg.first;
363
 
                while(mp != NULL) {
364
 
                    size += size_object(ERL_MESSAGE_TERM(mp));
365
 
                    mp = mp->next;
 
642
            Eterm* ma = (Eterm *) erts_alloc(ERTS_ALC_T_TMP, n*sizeof(Eterm));
 
643
            int i;
 
644
 
 
645
            i = 0;
 
646
            for (mp = rp->msg.first; mp != NULL; mp = mp->next) {
 
647
#ifdef HYBRID
 
648
                /*
 
649
                 * Hybrid: Almost all messages already are in the message area.
 
650
                 */
 
651
                if (NO_COPY(ERL_MESSAGE_TERM(mp)) || rp == BIF_P) {
 
652
                    /* Constant, already in message area, or same process. */
 
653
                    ma[i] = ERL_MESSAGE_TERM(mp);
 
654
                } else {
 
655
                    ma[i] = copy_object(ERL_MESSAGE_TERM(mp), BIF_P);
366
656
                }
367
 
            }
368
 
            hp = HAlloc(BIF_P, 3 + size + 2*n);
369
 
            hp += 2*n;          /* skip the list !!! */
370
 
            cons = hp - 2;
371
 
            res = make_list(cons); /* first cons cell */
372
 
            /* Build with back-pointers (as cons whould have done) */
373
 
            mp = rp->msg.first;
374
 
            while(mp != NULL) {
 
657
#else
 
658
                /*
 
659
                 * We must copy the message if it belongs to another process.
 
660
                 */
375
661
                if (rp == BIF_P) {
376
 
                    cons[0] = ERL_MESSAGE_TERM(mp);
 
662
#if defined(ERTS_SMP) && !defined(HEAP_FRAG_ELIM_TEST)
 
663
                    if (mp->bp) {
 
664
                        erts_move_msg_mbuf_to_proc_mbufs(BIF_P, mp);
 
665
                    }
 
666
#endif
 
667
                    ma[i] = ERL_MESSAGE_TERM(mp);
377
668
                } else {
378
 
                    cons[0] = copy_object(ERL_MESSAGE_TERM(mp), BIF_P);
 
669
                    ma[i] = copy_object(ERL_MESSAGE_TERM(mp), BIF_P);
379
670
                }
380
 
                cons -= 2;      /* next cell */
381
 
                cons[3] = make_list(cons); /* write tail */
382
 
                mp = mp->next;
383
 
            }
384
 
            cons[3] = NIL; 
 
671
#endif
 
672
                i++;
 
673
            }
 
674
            hp = HAlloc(BIF_P, 3+2*n);
 
675
            for (i = n-1; i >= 0; i--) {
 
676
                res = CONS(hp, ma[i], res);
 
677
                hp += 2;
 
678
            }
 
679
            erts_free(ERTS_ALC_T_TMP, (void *) ma);
385
680
        }
386
681
    } else if (item == am_message_queue_len) {
387
682
        hp = HAlloc(BIF_P, 3);
 
683
        ERTS_SMP_MSGQ_MV_INQ2PRIVQ(rp);
388
684
        res = make_small(rp->msg.len);
389
685
    } else if (item == am_links) {
390
 
        int sz = 0;
391
 
        ErlLink* lnk;
 
686
        MonitorInfoCollection mic;
 
687
        int i;
392
688
        Eterm item;
393
689
 
394
 
        for (lnk = rp->links; lnk; lnk = lnk->next) {
395
 
            if (lnk->type == LNK_LINK) {
396
 
                sz += NC_HEAP_SIZE(lnk->item);
397
 
                sz += 2;
398
 
            }
399
 
        }
400
 
        hp = HAlloc(BIF_P, 3 + sz);
 
690
        INIT_MONITOR_INFOS(mic);
 
691
 
 
692
        erts_doforall_links(rp->nlinks,&collect_one_link,&mic);
 
693
 
 
694
        hp = HAlloc(BIF_P, 3 + mic.sz);
401
695
        res = NIL;
402
 
        for (lnk = rp->links; lnk; lnk = lnk->next) {
403
 
            if (lnk->type == LNK_LINK) {
404
 
                item = STORE_NC(&hp, &MSO(BIF_P).externals, lnk->item); 
405
 
                res = CONS(hp, item, res);
406
 
                hp += 2;
407
 
            }
 
696
        for (i = 0; i < mic.mi_i; i++) {
 
697
            item = STORE_NC(&hp, &MSO(BIF_P).externals, mic.mi[i].entity); 
 
698
            res = CONS(hp, item, res);
 
699
            hp += 2;
408
700
        }
 
701
        DESTROY_MONITOR_INFOS(mic);
 
702
 
409
703
    } else if (item == am_monitors) {
410
 
#undef  MI_INC
411
 
#define MI_INC 50
412
 
        int sz = 0;
413
 
        struct {
414
 
            Eterm entity;
415
 
            Eterm node;
416
 
        } *mi = NULL;
417
 
        Uint mi_i = 0;
418
 
        Uint mi_max = 0;
419
 
        ErlLink* lnk;
420
 
        ErlLink **lnkp;
421
 
 
422
 
        /* lnk->item is the monitor link origin end */
423
 
        for (lnk = rp->links; lnk; lnk = lnk->next) {
424
 
            if (mi_i >= mi_max) {
425
 
                mi = (mi ? erts_realloc(ERTS_ALC_T_TMP,
426
 
                                        mi,
427
 
                                        (mi_max+MI_INC)*sizeof(*mi))
428
 
                      : erts_alloc(ERTS_ALC_T_TMP, MI_INC*sizeof(*mi)));
429
 
                mi_max += MI_INC;
430
 
            }
431
 
            if (lnk->type == LNK_LINK1 && rp->id == lnk->item) {
432
 
                
433
 
                if (is_atom(lnk->data)) {
434
 
                    /* Dist monitor by name. */
435
 
                    DistEntry *dep;
436
 
 
437
 
                    ASSERT(is_node_name_atom(lnk->data));
438
 
                    dep = erts_sysname_to_connected_dist_entry(lnk->data);
439
 
                    if (!dep)
440
 
                        continue;
441
 
                    lnkp = find_link_by_ref(&dep->links, lnk->ref);
442
 
                    mi[mi_i].entity = (*lnkp)->data;
443
 
                    mi[mi_i].node = lnk->data;
444
 
 
445
 
                    /* Will need an additional 2-tuple. */
446
 
                    sz += 3;
447
 
                } else if (is_internal_pid(lnk->data)) {
448
 
                    Process *p = pid2proc(lnk->data);
449
 
                    if (!p)
450
 
                        continue;
451
 
                    lnkp = find_link_by_ref(&p->links, lnk->ref);
452
 
                    if (!lnkp)
453
 
                        continue;
454
 
                    if (is_atom((*lnkp)->data)) { /* Local monitor by name. */
455
 
                        mi[mi_i].entity = (*lnkp)->data;
456
 
                        mi[mi_i].node = erts_this_dist_entry->sysname;
457
 
                        /* Will need an additional 2-tuple. */
458
 
                        sz += 3;
459
 
                    }
460
 
                    else
461
 
                        mi[mi_i].entity = lnk->data;
462
 
                }
463
 
                else {
464
 
                    ASSERT(is_external_pid(lnk->data));
465
 
                    mi[mi_i].entity = lnk->data;
466
 
                    sz += NC_HEAP_SIZE(lnk->data);
467
 
                }
468
 
                mi_i++;
469
 
                sz += 2 + 3; /* For a cons cell and a 2-tuple */
470
 
            }
471
 
        }
472
 
        hp = HAlloc(BIF_P, 3 + sz);
 
704
        MonitorInfoCollection mic;
 
705
        int i;
 
706
 
 
707
        INIT_MONITOR_INFOS(mic);
 
708
        erts_doforall_monitors(rp->monitors,&collect_one_origin_monitor,&mic);
 
709
        hp = HAlloc(BIF_P, 3 + mic.sz);
473
710
        res = NIL;
474
 
        for (mi_max = mi_i, mi_i = 0; mi_i < mi_max; mi_i++) {
475
 
            if (is_atom(mi[mi_i].entity)) {
 
711
        for (i = 0; i < mic.mi_i; i++) {
 
712
            if (is_atom(mic.mi[i].entity)) {
476
713
                /* Monitor by name. 
477
714
                 * Build {process, {Name, Node}} and cons it. 
478
715
                 */
479
716
                Eterm t1, t2;
480
717
 
481
 
                t1 = TUPLE2(hp, mi[mi_i].entity, mi[mi_i].node);
 
718
                t1 = TUPLE2(hp, mic.mi[i].entity, mic.mi[i].node);
482
719
                hp += 3;
483
720
                t2 = TUPLE2(hp, am_process, t1);
484
721
                hp += 3;
490
727
                Eterm t;
491
728
                Eterm pid = STORE_NC(&hp,
492
729
                                     &MSO(BIF_P).externals,
493
 
                                     mi[mi_i].entity);
 
730
                                     mic.mi[i].entity);
494
731
                t = TUPLE2(hp, am_process, pid);
495
732
                hp += 3;
496
733
                res = CONS(hp, t, res);
497
734
                hp += 2;
498
735
            }
499
736
        }
500
 
        if (mi)
501
 
            erts_free(ERTS_ALC_T_TMP, (void *) mi);
502
 
#undef  MI_INC
 
737
        DESTROY_MONITOR_INFOS(mic);
503
738
    } else if (item == am_monitored_by) {
504
 
        int sz = 0;
505
 
        ErlLink* lnk;
 
739
        MonitorInfoCollection mic;
 
740
        int i;
506
741
        Eterm item;
507
742
 
508
 
        /* lnk->item is the monitor link origin end */
509
 
        for (lnk = rp->links; lnk; lnk = lnk->next) {
510
 
            if (lnk->type == LNK_LINK1 && rp->id != lnk->item) {
511
 
                sz += NC_HEAP_SIZE(lnk->item);
512
 
                sz += 2;
513
 
            }
514
 
        }
515
 
        hp = HAlloc(BIF_P, 3 + sz);
 
743
        INIT_MONITOR_INFOS(mic);
 
744
        erts_doforall_monitors(rp->monitors,&collect_one_target_monitor,&mic);
 
745
        hp = HAlloc(BIF_P, 3 + mic.sz);
 
746
 
516
747
        res = NIL;
517
 
        for (lnk = rp->links; lnk; lnk = lnk->next) {
518
 
            if (lnk->type == LNK_LINK1 && rp->id != lnk->item) {
519
 
                item = STORE_NC(&hp, &MSO(BIF_P).externals, lnk->item); 
520
 
                res = CONS(hp, item, res);
521
 
                hp += 2;
522
 
            }
 
748
        for (i = 0; i < mic.mi_i; ++i) {
 
749
            item = STORE_NC(&hp, &MSO(BIF_P).externals, mic.mi[i].entity); 
 
750
            res = CONS(hp, item, res);
 
751
            hp += 2;
523
752
        }
 
753
        DESTROY_MONITOR_INFOS(mic);
524
754
    } else if (item == am_dictionary) {
525
 
        res = dictionary_copy(BIF_P, rp->dictionary);
 
755
        res = erts_dictionary_copy(BIF_P, rp->dictionary);
526
756
        hp = HAlloc(BIF_P, 3);
527
757
    } else if (item == am_DollarDictionary) {
528
 
        res = dictionary_copy(BIF_P, rp->debug_dictionary);
 
758
        res = erts_dictionary_copy(BIF_P, rp->debug_dictionary);
529
759
        hp = HAlloc(BIF_P, 3);
530
760
    } else if (item == am_trap_exit) {
531
761
        hp = HAlloc(BIF_P, 3);
537
767
        hp = HAlloc(BIF_P, 3);
538
768
        res = rp->error_handler;
539
769
    } else if (item == am_heap_size) {
540
 
        hp = HAlloc(BIF_P, 3);
541
 
        res = make_small(HEAP_SIZE(rp));
 
770
        Uint hsz = 3;
 
771
        (void) erts_bld_uint(NULL, &hsz, HEAP_SIZE(rp));
 
772
        hp = HAlloc(BIF_P, hsz);
 
773
        res = erts_bld_uint(&hp, NULL, HEAP_SIZE(rp));
542
774
    } else if (item == am_stack_size) {
543
 
        hp = HAlloc(BIF_P, 3);
544
 
        res = make_small(STACK_START(rp) - rp->stop);
 
775
        Uint stack_size = STACK_START(rp) - rp->stop;
 
776
        Uint hsz = 3;
 
777
        (void) erts_bld_uint(NULL, &hsz, stack_size);
 
778
        hp = HAlloc(BIF_P, hsz);
 
779
        res = erts_bld_uint(&hp, NULL, stack_size);
545
780
    } else if (item == am_memory) { /* Memory consumed in bytes */
546
781
        Uint size = 0;
547
782
        Uint hsz = 3;
548
 
        ErlLink* lnk;
549
 
 
550
783
        size += sizeof(Process);
551
784
 
552
 
        for(lnk = rp->links; lnk; lnk = lnk->next)
553
 
            size += erts_link_size(lnk);
 
785
        ERTS_SMP_MSGQ_MV_INQ2PRIVQ(rp);
554
786
 
555
 
#ifdef SHARED_HEAP
556
 
        size += (rp->stack - rp->send) * sizeof(Eterm);
557
 
#else
 
787
        erts_doforall_links(rp->nlinks, &one_link_size, &size);
 
788
        erts_doforall_monitors(rp->monitors, &one_mon_size, &size);
558
789
        size += (rp->heap_sz + rp->mbuf_sz) * sizeof(Eterm);
559
790
        if (rp->old_hend && rp->old_heap)
560
791
            size += (rp->old_hend - rp->old_heap) * sizeof(Eterm);
561
 
#endif
562
792
 
563
793
        size += rp->msg.len * sizeof(ErlMessage);
564
794
 
590
820
         */
591
821
        res = STORE_NC(&hp, &MSO(BIF_P).externals, rp->group_leader);
592
822
    } else if (item == am_reductions) {
593
 
        Uint reds;
594
 
 
595
 
        hp = HAlloc(BIF_P, 3);
596
 
        reds = rp->reds + erts_current_reductions(BIF_P, rp);
597
 
        res = make_small_or_big(reds, BIF_P);
 
823
        Uint reds = rp->reds + erts_current_reductions(BIF_P, rp);
 
824
        Uint hsz = 3;
 
825
        (void) erts_bld_uint(NULL, &hsz, reds);
 
826
        hp = HAlloc(BIF_P, hsz);
 
827
        res = erts_bld_uint(&hp, NULL, reds);
598
828
    } else if (item == am_priority) {
599
829
        hp = HAlloc(BIF_P, 3);
600
 
        switch(rp->prio) {
601
 
        case PRIORITY_MAX:
602
 
            res = am_max; break;
603
 
        case PRIORITY_HIGH:
604
 
            res = am_high; break;
605
 
        case PRIORITY_NORMAL:
606
 
            res = am_normal; break;
607
 
        case PRIORITY_LOW:
608
 
            res = am_low; break;
609
 
        }
 
830
        res = erts_get_process_priority(rp);
610
831
    } else if (item == am_trace) {
611
832
        hp = HAlloc(BIF_P, 3);
612
 
        res = make_small(rp->flags & TRACE_FLAGS);
 
833
        res = make_small(rp->trace_flags & TRACEE_FLAGS);
613
834
    } else if (item == am_binary) {
614
835
        Uint sz = 3;
615
836
        (void) bld_bin_list(NULL, &sz, MSO(rp).mso);
616
837
        hp = HAlloc(BIF_P, sz);
617
838
        res = bld_bin_list(&hp, NULL, MSO(rp).mso);
 
839
#ifdef HYBRID
 
840
    } else if (item == am_message_binary) {
 
841
        Uint sz = 3;
 
842
        (void) bld_bin_list(NULL, &sz, erts_global_offheap.mso);
 
843
        hp = HAlloc(BIF_P, sz);
 
844
        res = bld_bin_list(&hp, NULL, erts_global_offheap.mso);
 
845
#endif
618
846
    } else if (item == am_sequential_trace_token) {
619
847
 
620
848
        /*
626
854
        hp = HAlloc(BIF_P, 3);
627
855
        res = make_small(catchlevel(BIF_P));
628
856
    } else if (item == am_backtrace) {
629
 
        cerr_pos = 0;
630
 
        erts_stack_dump(rp, CBUF);
631
 
        res = new_binary(BIF_P, tmp_buf, cerr_pos);
 
857
        erts_dsprintf_buf_t *dsbufp = erts_create_tmp_dsbuf(0);
 
858
        erts_stack_dump(ERTS_PRINT_DSBUF, (void *) dsbufp, rp);
 
859
        res = new_binary(BIF_P, (byte *) dsbufp->str, (int) dsbufp->str_len);
 
860
        erts_destroy_tmp_dsbuf(dsbufp);
632
861
        hp = HAlloc(BIF_P, 3);
633
862
    } else if (item == am_last_calls) {
634
863
        if (rp->ct == NULL) {
635
864
            hp = HAlloc(BIF_P, 3);
636
865
            res = am_false;
637
866
        } else {
638
 
            hp = HAlloc(BIF_P, rp->ct->n*(2+4) + 3);
639
 
            /* one cons cell and a 3-struct,
640
 
               and the 2-tuple below */
 
867
            /*
 
868
             * One cons cell and a 3-struct, and a 2-tuple.
 
869
             * Might be less than that, if there are sends, receives or timeouts,
 
870
             * so we must do a HRelease() to avoid creating holes.
 
871
             */
 
872
            Uint needed = rp->ct->n*(2+4) + 3;
 
873
            Eterm* limit;
 
874
            Eterm term, list;
 
875
            int i, j;
 
876
 
 
877
            hp = HAlloc(BIF_P, needed);
 
878
            limit = hp + needed;
641
879
            list = NIL;
642
880
            for (i = 0; i < rp->ct->n; i++) {
643
881
                j = rp->ct->cur - i - 1;
660
898
                hp += 2;
661
899
            }
662
900
            res = list;
 
901
            res = TUPLE2(hp, item, res);
 
902
            hp += 3;
 
903
            HRelease(BIF_P,limit,hp);
 
904
            BIF_RET(res);
663
905
        }
664
906
    } else {
665
907
        BIF_ERROR(BIF_P, BADARG);
666
908
    }
667
909
    BIF_RET(TUPLE2(hp, item, res));
668
910
}
 
911
#undef MI_INC
669
912
 
670
913
/*
671
914
 * This function takes care of calls to erlang:system_info/1 when the argument
683
926
 
684
927
 
685
928
    if (sel == am_memory) {
 
929
        Eterm res;
686
930
        if (arity != 2)
687
931
            return am_badarg;
688
 
        return erts_memory(NULL, BIF_P, *tp);
 
932
        erts_smp_proc_unlock(BIF_P, ERTS_PROC_LOCK_MAIN);
 
933
        res = erts_memory(NULL, NULL, BIF_P, *tp);
 
934
        erts_smp_proc_lock(BIF_P, ERTS_PROC_LOCK_MAIN);
 
935
        return res;
689
936
    } else if (sel == am_allocated) {
690
937
        if (arity == 2) {
691
 
            int len;
692
 
 
693
 
            if (!is_string(*tp))
694
 
                return THE_NON_VALUE;
695
 
       
696
 
            if ((len = intlist_to_buf(*tp, tmp_buf, TMP_BUF_SIZE-1)) < 0)
697
 
                return THE_NON_VALUE;
698
 
            tmp_buf[len] = '\0';
699
 
 
700
 
            if (erts_instr_dump_memory_map(tmp_buf))
701
 
                return am_true;
702
 
            else
703
 
                return am_false;
 
938
            Eterm res = THE_NON_VALUE;
 
939
            char *buf;
 
940
            int len = is_string(*tp);
 
941
            if (len <= 0)
 
942
                return res;
 
943
            buf = (char *) erts_alloc(ERTS_ALC_T_TMP, len+1);
 
944
            if (intlist_to_buf(*tp, buf, len) != len)
 
945
                erl_exit(1, "%s:%d: Internal error\n", __FILE__, __LINE__);
 
946
            buf[len] = '\0';
 
947
            res = erts_instr_dump_memory_map(buf) ? am_true : am_false;
 
948
            erts_free(ERTS_ALC_T_TMP, (void *) buf);
 
949
            return res;
704
950
        }
705
951
        else if (arity == 3 && tp[0] == am_status) {
706
952
            if (is_atom(tp[1]))
707
953
                return erts_instr_get_stat(BIF_P, tp[1], 1);
708
954
            else {
709
 
                int len;
710
 
                if (!is_string(tp[1]))
711
 
                    return THE_NON_VALUE;
712
 
       
713
 
                if ((len = intlist_to_buf(tp[1], tmp_buf, TMP_BUF_SIZE-1)) < 0)
714
 
                    return THE_NON_VALUE;
715
 
                tmp_buf[len] = '\0';
716
 
 
717
 
                if (erts_instr_dump_stat(tmp_buf, 1))
718
 
                    return am_true;
719
 
                else
720
 
                    return am_false;
 
955
                Eterm res = THE_NON_VALUE;
 
956
                char *buf;
 
957
                int len = is_string(tp[1]);
 
958
                if (len <= 0)
 
959
                    return res;
 
960
                buf = (char *) erts_alloc(ERTS_ALC_T_TMP, len+1);
 
961
                if (intlist_to_buf(tp[1], buf, len) != len)
 
962
                    erl_exit(1, "%s:%d: Internal error\n", __FILE__, __LINE__);
 
963
                buf[len] = '\0';
 
964
                res = erts_instr_dump_stat(buf, 1) ? am_true : am_false;
 
965
                erts_free(ERTS_ALC_T_TMP, (void *) buf);
 
966
                return res;
721
967
            }
722
968
        }
723
969
        else
724
970
            return THE_NON_VALUE;
725
 
#ifdef PURIFY
726
 
    } else if (sel == am_purify) {
 
971
#if defined(PURIFY) || defined(VALGRIND)
 
972
    } else if (sel == AM_error_checker
 
973
#if defined(PURIFY)
 
974
               || sel == am_purify
 
975
#elif defined(VALGRIND)
 
976
               || sel == AM_valgrind
 
977
#endif
 
978
        ) {
727
979
        if (*tp == am_memory) {
728
 
            BIF_RET(make_small_or_big(purify_new_leaks(), BIF_P));
 
980
#if defined(PURIFY)
 
981
            BIF_RET(erts_make_integer(purify_new_leaks(), BIF_P));
 
982
#elif defined(VALGRIND)
 
983
            VALGRIND_DO_LEAK_CHECK;
 
984
            BIF_RET(make_small(0));
 
985
#endif
729
986
        } else if (*tp == am_fd) {
730
 
            BIF_RET(make_small_or_big(purify_new_fds_inuse(), BIF_P));
 
987
#if defined(PURIFY)
 
988
            BIF_RET(erts_make_integer(purify_new_fds_inuse(), BIF_P));
 
989
#elif defined(VALGRIND)
 
990
            /* Not present in valgrind... */
 
991
            BIF_RET(make_small(0));
 
992
#endif
731
993
        } else if (*tp == am_running) {
 
994
#if defined(PURIFY)
732
995
            BIF_RET(purify_is_running() ? am_true : am_false);
 
996
#elif defined(VALGRIND)
 
997
            BIF_RET(RUNNING_ON_VALGRIND ? am_true : am_false);
 
998
#endif
733
999
        } else if (is_list(*tp)) {
734
 
            int r;
735
 
 
736
 
            r = io_list_to_buf(*tp, (char*) tmp_buf, TMP_BUF_SIZE - 1);
737
 
            if (r >= 0) {
738
 
                tmp_buf[TMP_BUF_SIZE - 1 - r] = '\0';
739
 
                purify_printf("%s\n", tmp_buf);
740
 
            } else {
741
 
                return THE_NON_VALUE;
 
1000
#if defined(PURIFY)
 
1001
#define ERTS_ERROR_CHECKER_PRINTF purify_printf
 
1002
#elif defined(VALGRIND)
 
1003
#define ERTS_ERROR_CHECKER_PRINTF VALGRIND_PRINTF
 
1004
#endif
 
1005
            int buf_size = 8*1024; /* Try with 8KB first */
 
1006
            char *buf = erts_alloc(ERTS_ALC_T_TMP, buf_size);
 
1007
            int r = io_list_to_buf(*tp, (char*) buf, buf_size - 1);
 
1008
            if (r < 0) {
 
1009
                erts_free(ERTS_ALC_T_TMP, (void *) buf);
 
1010
                buf_size = io_list_len(*tp);
 
1011
                if (buf_size < 0)
 
1012
                    return THE_NON_VALUE;
 
1013
                buf_size++;
 
1014
                buf = erts_alloc(ERTS_ALC_T_TMP, buf_size);
 
1015
                r = io_list_to_buf(*tp, (char*) buf, buf_size - 1);
 
1016
                ASSERT(r == buf_size - 1);
742
1017
            }
 
1018
            buf[buf_size - 1 - r] = '\0';
 
1019
            ERTS_ERROR_CHECKER_PRINTF("%s\n", buf);
 
1020
            erts_free(ERTS_ALC_T_TMP, (void *) buf);
743
1021
            BIF_RET(am_true);
 
1022
#undef ERTS_ERROR_CHECKER_PRINTF
744
1023
        }
745
1024
#endif
746
1025
#ifdef QUANTIFY
778
1057
        }
779
1058
        BIF_RET(am_true);
780
1059
#endif
781
 
    } else if (sel == am_link_list) {
782
 
        ErlLink *links = NULL;
783
 
        if(is_internal_pid(*tp)) {
784
 
            Process *p = pid2proc(*tp);
785
 
            if(p)
786
 
                links = p->links;
787
 
            else
788
 
                return am_undefined;
789
 
        }
790
 
        else if(is_internal_port(*tp)) {
791
 
            Port *p = id2port(*tp);
792
 
            if(p)
793
 
                links = p->links;
794
 
            else
795
 
                return am_undefined;
796
 
        }
797
 
        else if(is_node_name_atom(*tp)) {
798
 
            DistEntry *dep = erts_find_dist_entry(*tp);
799
 
            if(dep)
800
 
                links = dep->links;
801
 
            else
802
 
                return am_undefined;
803
 
        }
804
 
        else
805
 
            return THE_NON_VALUE;
806
 
 
807
 
        return make_link_list(BIF_P, links);
808
 
    }
809
 
    else if (sel == am_allocator && arity == 2) {
 
1060
    } else if (sel == am_allocator && arity == 2) {
810
1061
        return erts_allocator_info_term(BIF_P, *tp);
811
1062
    }
812
 
 
813
1063
    return THE_NON_VALUE;
814
1064
}
815
1065
 
 
1066
#define INFO_DSBUF_INC_SZ 256
 
1067
 
 
1068
static erts_dsprintf_buf_t *
 
1069
grow_info_dsbuf(erts_dsprintf_buf_t *dsbufp, size_t need)
 
1070
{
 
1071
    size_t size;
 
1072
    size_t free_size = dsbufp->size - dsbufp->str_len;
 
1073
 
 
1074
    ASSERT(dsbufp);
 
1075
 
 
1076
    if (need <= free_size)
 
1077
        return dsbufp;
 
1078
    size = need - free_size + INFO_DSBUF_INC_SZ;
 
1079
    size = ((size + INFO_DSBUF_INC_SZ - 1)/INFO_DSBUF_INC_SZ)*INFO_DSBUF_INC_SZ;
 
1080
    size += dsbufp->size;
 
1081
    ASSERT(dsbufp->str_len + need <= size);
 
1082
    dsbufp->str = (char *) erts_realloc(ERTS_ALC_T_INFO_DSBUF,
 
1083
                                        (void *) dsbufp->str,
 
1084
                                        size);
 
1085
    dsbufp->size = size;
 
1086
    return dsbufp;
 
1087
}
 
1088
 
 
1089
static erts_dsprintf_buf_t *
 
1090
erts_create_info_dsbuf(Uint size)
 
1091
{
 
1092
    Uint init_size = size ? size : INFO_DSBUF_INC_SZ;
 
1093
    erts_dsprintf_buf_t init = ERTS_DSPRINTF_BUF_INITER(grow_info_dsbuf);
 
1094
    erts_dsprintf_buf_t *dsbufp = erts_alloc(ERTS_ALC_T_INFO_DSBUF,
 
1095
                                             sizeof(erts_dsprintf_buf_t));
 
1096
    sys_memcpy((void *) dsbufp, (void *) &init, sizeof(erts_dsprintf_buf_t));
 
1097
    dsbufp->str = (char *) erts_alloc(ERTS_ALC_T_INFO_DSBUF, init_size);
 
1098
    dsbufp->str[0] = '\0';
 
1099
    dsbufp->size = init_size;
 
1100
    return dsbufp;
 
1101
}
 
1102
 
 
1103
static void
 
1104
erts_destroy_info_dsbuf(erts_dsprintf_buf_t *dsbufp)
 
1105
{
 
1106
    if (dsbufp->str)
 
1107
        erts_free(ERTS_ALC_T_INFO_DSBUF, (void *) dsbufp->str);
 
1108
    erts_free(ERTS_ALC_T_INFO_DSBUF, (void *) dsbufp);
 
1109
}
 
1110
 
 
1111
 
816
1112
BIF_RETTYPE system_info_1(BIF_ALIST_1)
817
1113
{
818
1114
    Eterm res;
819
1115
    Eterm* hp;
820
1116
    Eterm val;
821
 
    unsigned count;
822
1117
    int i;
823
1118
    DECL_AM(ets_realloc_moves);
824
1119
    DECL_AM(dist_ctrl);
825
1120
 
826
 
    cerr_pos = 0;
827
 
 
828
1121
    if (is_tuple(BIF_ARG_1)) {
829
1122
        Eterm* tp = tuple_val(BIF_ARG_1);
830
1123
        Uint arity = *tp++;
832
1125
        if (is_non_value(res))
833
1126
            goto error;
834
1127
        return res;
 
1128
    } else if (BIF_ARG_1 == am_compat_rel) {
 
1129
        ASSERT(erts_compat_rel > 0);
 
1130
        BIF_RET(make_small(erts_compat_rel));
835
1131
    } else if (BIF_ARG_1 == am_memory) {
836
 
        BIF_RET(erts_memory(NULL, BIF_P, THE_NON_VALUE));
 
1132
        erts_smp_proc_unlock(BIF_P, ERTS_PROC_LOCK_MAIN);
 
1133
        res = erts_memory(NULL, NULL, BIF_P, THE_NON_VALUE);
 
1134
        erts_smp_proc_lock(BIF_P, ERTS_PROC_LOCK_MAIN);
 
1135
        BIF_RET(res);
837
1136
    } else if (BIF_ARG_1 == am_allocated_areas) {
838
 
        BIF_RET(erts_allocated_areas(NULL, BIF_P));
 
1137
        erts_smp_proc_unlock(BIF_P, ERTS_PROC_LOCK_MAIN);
 
1138
        res = erts_allocated_areas(NULL, NULL, BIF_P);
 
1139
        erts_smp_proc_lock(BIF_P, ERTS_PROC_LOCK_MAIN);
 
1140
        BIF_RET(res);
839
1141
    } else if (BIF_ARG_1 == am_allocated) {
840
1142
        BIF_RET(erts_instr_get_memory_map(BIF_P));
841
1143
    } else if (BIF_ARG_1 == am_hipe_architecture) {
842
1144
#if defined(HIPE)
843
 
#  define MAKE_STR2(x) #x
844
 
#  define MAKE_STR(s) MAKE_STR2(s)
845
 
        static char arch[] = MAKE_STR(HIPE_ARCHITECTURE);
846
 
        BIF_RET(am_atom_put(arch, sizeof(arch) - 1));
847
 
#  undef MAKE_STR
 
1145
        BIF_RET(hipe_arch_name);
848
1146
#else
849
1147
        BIF_RET(am_undefined);
850
1148
#endif
853
1151
    } else if (BIF_ARG_1 == AM_ets_realloc_moves) {
854
1152
        BIF_RET((erts_ets_realloc_always_moves) ? am_true : am_false);
855
1153
    } else if (BIF_ARG_1 == am_sequential_tracer) {
856
 
        if (is_pid(system_seq_tracer) || is_port(system_seq_tracer)) {
857
 
            val = STORE_NC_IN_PROC(BIF_P, system_seq_tracer);
858
 
        } else {
859
 
            val = am_false;
860
 
        }
 
1154
        val = erts_get_system_seq_tracer();
 
1155
        ASSERT(is_internal_pid(val) || is_internal_port(val) || val==am_false)
861
1156
        hp = HAlloc(BIF_P, 3);
862
1157
        res = TUPLE2(hp, am_sequential_tracer, val);
863
1158
        BIF_RET(res);
864
1159
    } else if (BIF_ARG_1 == am_garbage_collection){
 
1160
        Uint val = (Uint) erts_smp_atomic_read(&erts_max_gen_gcs);
865
1161
        hp = HAlloc(BIF_P, 3+2);
866
 
        res = TUPLE2(hp, am_fullsweep_after, make_small(erts_max_gen_gcs));
 
1162
        res = TUPLE2(hp, am_fullsweep_after, make_small(val));
867
1163
        hp += 3;
868
1164
        res = CONS(hp, res, NIL);
869
1165
        BIF_RET(res);
870
1166
    } else if (BIF_ARG_1 == am_fullsweep_after){
 
1167
        Uint val = (Uint) erts_smp_atomic_read(&erts_max_gen_gcs);
871
1168
        hp = HAlloc(BIF_P, 3);
872
 
        res = TUPLE2(hp, am_fullsweep_after, make_small(erts_max_gen_gcs));
 
1169
        res = TUPLE2(hp, am_fullsweep_after, make_small(val));
873
1170
        BIF_RET(res);
874
1171
    } else if (BIF_ARG_1 == am_process_count) {
875
 
        count = 0;
876
 
        for (i = 0; i < erts_max_processes; i++) {
877
 
            if (process_tab[i] != NULL && process_tab[i]->status != P_EXITING) {
878
 
                count++;
879
 
            }
880
 
        }
881
 
        BIF_RET(make_small(count));
 
1172
        BIF_RET(make_small(erts_process_count()));
882
1173
    } else if (BIF_ARG_1 == am_process_limit) {
883
1174
        BIF_RET(make_small(erts_max_processes));
884
 
    } else if (BIF_ARG_1 == am_info) {
885
 
        info(CBUF);
886
 
    } else if (BIF_ARG_1 == am_procs)
887
 
        process_info(CBUF);
888
 
    else if (BIF_ARG_1 == am_loaded)
889
 
        loaded(CBUF);
890
 
    else if (BIF_ARG_1 == am_dist)
891
 
        distribution_info(CBUF);
892
 
    else if (BIF_ARG_1 == AM_dist_ctrl) {
 
1175
    } else if (BIF_ARG_1 == am_info
 
1176
               || BIF_ARG_1 == am_procs
 
1177
               || BIF_ARG_1 == am_loaded
 
1178
               || BIF_ARG_1 == am_dist) {
 
1179
        erts_dsprintf_buf_t *dsbufp = erts_create_info_dsbuf(0);
 
1180
 
 
1181
        /* Need to be the only thread running... */
 
1182
        erts_smp_proc_unlock(BIF_P, ERTS_PROC_LOCK_MAIN);
 
1183
        erts_smp_block_system(0);
 
1184
 
 
1185
        if (BIF_ARG_1 == am_info)
 
1186
            info(ERTS_PRINT_DSBUF, (void *) dsbufp);
 
1187
        else if (BIF_ARG_1 == am_procs)
 
1188
            process_info(ERTS_PRINT_DSBUF, (void *) dsbufp);
 
1189
        else if (BIF_ARG_1 == am_loaded)
 
1190
            loaded(ERTS_PRINT_DSBUF, (void *) dsbufp);
 
1191
        else
 
1192
            distribution_info(ERTS_PRINT_DSBUF, (void *) dsbufp);
 
1193
 
 
1194
        erts_smp_release_system();
 
1195
        erts_smp_proc_lock(BIF_P, ERTS_PROC_LOCK_MAIN);
 
1196
 
 
1197
        ASSERT(dsbufp && dsbufp->str);
 
1198
        res = new_binary(BIF_P, (byte *) dsbufp->str, (int) dsbufp->str_len);
 
1199
        erts_destroy_info_dsbuf(dsbufp);
 
1200
        BIF_RET(res);
 
1201
    } else if (BIF_ARG_1 == AM_dist_ctrl) {
893
1202
        DistEntry *dep;
894
1203
        i = 0;
 
1204
        ERTS_SMP_LOCK_NODE_TABLES_AND_ENTRIES;
895
1205
        for (dep = erts_visible_dist_entries; dep; dep = dep->next) 
896
1206
            ++i;
897
1207
        for (dep = erts_hidden_dist_entries; dep; dep = dep->next)
914
1224
            res = CONS(hp, tpl, res);
915
1225
            hp += 2;
916
1226
        }
 
1227
        ERTS_SMP_UNLOCK_NODE_TABLES_AND_ENTRIES;
917
1228
        BIF_RET(res);
918
1229
    } else if (BIF_ARG_1 == am_system_version) {
919
 
        char *sys_ver;
920
 
        int sys_ver_len;
921
 
 
922
 
        sys_ver = erts_get_system_version(&sys_ver_len);
923
 
        hp = HAlloc(BIF_P, sys_ver_len*2);
924
 
        BIF_RET(buf_to_intlist(&hp, sys_ver, sys_ver_len, NIL));
 
1230
        erts_dsprintf_buf_t *dsbufp = erts_create_tmp_dsbuf(0);
 
1231
        erts_print_system_version(ERTS_PRINT_DSBUF, (void *) dsbufp, BIF_P);
 
1232
        hp = HAlloc(BIF_P, dsbufp->str_len*2);
 
1233
        res = buf_to_intlist(&hp, dsbufp->str, dsbufp->str_len, NIL);
 
1234
        erts_destroy_tmp_dsbuf(dsbufp);
 
1235
        BIF_RET(res);
925
1236
    } else if (BIF_ARG_1 == am_system_architecture) {
926
 
        int n;
927
 
 
928
 
        sys_strcpy((char*)tmp_buf, ERLANG_ARCHITECTURE);
929
 
        n = sys_strlen((char*)tmp_buf);
930
 
        hp = HAlloc(BIF_P, n*2);
931
 
        BIF_RET(buf_to_intlist(&hp, tmp_buf, n, NIL));
 
1237
        hp = HAlloc(BIF_P, 2*(sizeof(ERLANG_ARCHITECTURE)-1));
 
1238
        BIF_RET(buf_to_intlist(&hp,
 
1239
                               ERLANG_ARCHITECTURE,
 
1240
                               sizeof(ERLANG_ARCHITECTURE)-1,
 
1241
                               NIL));
932
1242
    } 
933
1243
    else if (BIF_ARG_1 == am_memory_types) {
934
1244
        return erts_instr_get_type_info(BIF_P);
936
1246
    else if (BIF_ARG_1 == am_os_type) {
937
1247
       Eterm type = am_atom_put(os_type, strlen(os_type));
938
1248
       Eterm flav, tup;
 
1249
       char *buf = erts_alloc(ERTS_ALC_T_TMP, 1024); /* More than enough */
939
1250
 
940
 
       os_flavor(tmp_buf, TMP_BUF_SIZE);
941
 
       flav = am_atom_put(tmp_buf, strlen(tmp_buf));
 
1251
       os_flavor(buf, 1024);
 
1252
       flav = am_atom_put(buf, strlen(buf));
942
1253
       hp = HAlloc(BIF_P, 3);
943
1254
       tup = TUPLE2(hp, type, flav);
 
1255
       erts_free(ERTS_ALC_T_TMP, (void *) buf);
944
1256
       BIF_RET(tup);
945
1257
    }
946
1258
    else if (BIF_ARG_1 == am_allocator) {
1056
1368
    else if (BIF_ARG_1 == am_version) {
1057
1369
        int n = strlen(ERLANG_VERSION);
1058
1370
        hp = HAlloc(BIF_P, ((sizeof ERLANG_VERSION)-1) * 2);
1059
 
        BIF_RET(buf_to_intlist(&hp, (byte*)ERLANG_VERSION, n, NIL));
 
1371
        BIF_RET(buf_to_intlist(&hp, ERLANG_VERSION, n, NIL));
1060
1372
    }
1061
1373
    else if (BIF_ARG_1 == am_machine) {
1062
1374
        int n = strlen(EMULATOR);
1063
1375
        hp = HAlloc(BIF_P, n*2);
1064
 
        BIF_RET(buf_to_intlist(&hp, (byte*)EMULATOR, n, NIL));
 
1376
        BIF_RET(buf_to_intlist(&hp, EMULATOR, n, NIL));
1065
1377
    }
1066
1378
    else if (BIF_ARG_1 == am_garbage_collection) {
1067
1379
        BIF_RET(am_generational);
 
1380
#ifndef ERTS_SMP /* Not supported with smp emulator */
1068
1381
    } else if (BIF_ARG_1 == am_instruction_counts) {
 
1382
#ifdef DEBUG
 
1383
        Eterm *endp;
 
1384
#endif
 
1385
        Eterm *hp, **hpp;
 
1386
        Uint hsz, *hszp;
1069
1387
        int i;
1070
 
        hp = HAlloc(BIF_P, num_instructions*5);
 
1388
 
 
1389
        hpp = NULL;
 
1390
        hsz = 0;
 
1391
        hszp = &hsz;
 
1392
 
 
1393
    bld_instruction_counts:
 
1394
 
1071
1395
        res = NIL;
1072
1396
        for (i = num_instructions-1; i >= 0; i--) {
1073
 
            Eterm tuple;
1074
 
            Eterm atom = am_atom_put(opc[i].name, strlen(opc[i].name));
1075
 
            Eterm count = make_small_or_big(opc[i].count, BIF_P);
1076
 
 
1077
 
            tuple = TUPLE2(hp, atom, count);
1078
 
            hp += 3;
1079
 
            res = CONS(hp, tuple, res);
1080
 
            hp += 2;
1081
 
        }
 
1397
            res = erts_bld_cons(hpp, hszp,
 
1398
                                erts_bld_tuple(hpp, hszp, 2,
 
1399
                                               am_atom_put(opc[i].name,
 
1400
                                                           strlen(opc[i].name)),
 
1401
                                               erts_bld_uint(hpp, hszp,
 
1402
                                                             opc[i].count)),
 
1403
                                res);
 
1404
        }
 
1405
 
 
1406
        if (!hpp) {
 
1407
            hp = HAlloc(BIF_P, hsz);
 
1408
            hpp = &hp;
 
1409
#ifdef DEBUG
 
1410
            endp = hp + hsz;
 
1411
#endif
 
1412
            hszp = NULL;
 
1413
            goto bld_instruction_counts;
 
1414
        }
 
1415
 
 
1416
#ifdef DEBUG
 
1417
        ASSERT(endp == hp);
 
1418
#endif
 
1419
 
1082
1420
        BIF_RET(res);
 
1421
#endif /* #ifndef ERTS_SMP */
1083
1422
    } else if (BIF_ARG_1 == am_wordsize) {
1084
1423
        return make_small(sizeof(Eterm));
1085
1424
    } else if (BIF_ARG_1 == am_endian) {
1091
1430
    } else if (BIF_ARG_1 == am_heap_sizes) {
1092
1431
        return erts_heap_sizes(BIF_P);
1093
1432
    } else if (BIF_ARG_1 == am_global_heaps_size) {
1094
 
#ifdef SHARED_HEAP
 
1433
#ifdef HYBRID
1095
1434
        Uint hsz = 0;
1096
1435
        Uint sz = 0;
1097
1436
 
1098
1437
        sz += global_heap_sz;
1099
 
        sz += global_mbuf_sz;
 
1438
#ifdef INCREMENTAL
 
1439
        /* The size of the old generation is a bit hard to define here...
 
1440
         * The amount of live data in the last collection perhaps..? */
 
1441
        sz = 0;
 
1442
#else
1100
1443
        if (global_old_hend && global_old_heap)
1101
1444
            sz += global_old_hend - global_old_heap;
 
1445
#endif
1102
1446
 
1103
1447
        sz *= sizeof(Eterm);
1104
1448
 
1110
1454
#endif
1111
1455
        return res;
1112
1456
    } else if (BIF_ARG_1 == am_heap_type) {
1113
 
#ifdef SHARED_HEAP
1114
 
        return am_shared;
 
1457
#if defined(HYBRID)
 
1458
        return am_hybrid;
1115
1459
#else
1116
 
        return am_separate;
 
1460
        return am_private;
1117
1461
#endif
1118
1462
#if defined(__GNUC__) && defined(HAVE_SOLARIS_SPARC_PERFMON)
1119
1463
    } else if (BIF_ARG_1 == am_ultrasparc_read_tick1) {
1185
1529
        return am_false;
1186
1530
    } else {
1187
1531
        /* Arguments that are unusual... */
1188
 
        DECL_AM(node_and_dist_references);
 
1532
        DECL_AM(constant_pool_support);
 
1533
        DECL_AM(scheduler_id);
 
1534
        DECL_AM(schedulers);
 
1535
        DECL_AM(smp_support);
 
1536
        DECL_AM(lock_checking);
 
1537
        DECL_AM(kernel_poll);
 
1538
        DECL_AM(check_io);
1189
1539
        DECL_AM(stop_memory_trace);
1190
1540
 
1191
 
        if (BIF_ARG_1 == AM_node_and_dist_references) {
1192
 
            /*
1193
 
             * OBSERVE! Only supposed to be used for testing, and debugging.
1194
 
             */
1195
 
            BIF_RET(erts_get_node_and_dist_references(BIF_P));
 
1541
        if (BIF_ARG_1 == AM_smp_support) {
 
1542
#ifdef ERTS_SMP
 
1543
            BIF_RET(am_true);
 
1544
#else
 
1545
            BIF_RET(am_false);
 
1546
#endif
 
1547
        } else if (BIF_ARG_1 == AM_constant_pool_support) {
 
1548
#if defined(HEAP_FRAG_ELIM_TEST)
 
1549
            BIF_RET(am_true);
 
1550
#else
 
1551
            BIF_RET(am_false);
 
1552
#endif
 
1553
        } else if (BIF_ARG_1 == AM_scheduler_id) {
 
1554
#ifdef ERTS_SMP
 
1555
            ASSERT(BIF_P->scheduler_data);
 
1556
            BIF_RET(erts_make_integer(BIF_P->scheduler_data->no, BIF_P));
 
1557
#else
 
1558
            BIF_RET(make_small(1));
 
1559
#endif
 
1560
        } else if (BIF_ARG_1 == AM_schedulers) {
 
1561
            res = make_small(erts_get_no_schedulers());
 
1562
            BIF_RET(res);
 
1563
        } else if (BIF_ARG_1 == AM_kernel_poll) {
 
1564
#ifdef ERTS_ENABLE_KERNEL_POLL
 
1565
            BIF_RET(erts_use_kernel_poll ? am_true : am_false);
 
1566
#else
 
1567
            BIF_RET(am_false);
 
1568
#endif    
 
1569
        } else if (BIF_ARG_1 == AM_lock_checking) {
 
1570
#ifdef ERTS_ENABLE_LOCK_CHECK
 
1571
            BIF_RET(am_true);
 
1572
#else
 
1573
            BIF_RET(am_false);
 
1574
#endif
 
1575
        } else if (BIF_ARG_1 == AM_check_io) {
 
1576
            BIF_RET(erts_check_io_info(BIF_P));
1196
1577
        } else if (BIF_ARG_1 == AM_stop_memory_trace) {
1197
1578
            erts_mtrace_stop();
1198
1579
            BIF_RET(am_true);
1201
1582
    error:
1202
1583
        BIF_ERROR(BIF_P, BADARG);
1203
1584
    }
1204
 
    res = new_binary(BIF_P, tmp_buf, cerr_pos);
1205
 
    BIF_RET(res);
1206
1585
}
1207
1586
 
1208
1587
Eterm
1218
1597
    };
1219
1598
    Eterm items[ASIZE(keys)];
1220
1599
    Eterm result = NIL;
1221
 
    Eterm tmp;
 
1600
    Eterm reg_name;
1222
1601
    Eterm* hp;
 
1602
    Uint need;
1223
1603
    int i;
1224
1604
 
1225
1605
    /*
1238
1618
        }
1239
1619
        items[i] = item;
1240
1620
    }
 
1621
    reg_name = port_info_2(p, pid, am_registered_name);
1241
1622
 
1242
1623
    /*
1243
1624
     * Build the resulting list.
1244
1625
     */
1245
1626
 
1246
 
    hp = HAlloc(p, 2*ASIZE(keys)+2);
 
1627
    need = 2*ASIZE(keys);
 
1628
    if (is_tuple(reg_name)) {
 
1629
        need += 2;
 
1630
    }
 
1631
    hp = HAlloc(p, need);
1247
1632
    for (i = ASIZE(keys) - 1; i >= 0; i--) {
1248
1633
        result = CONS(hp, items[i], result);
1249
1634
        hp += 2;
1250
1635
    }
1251
 
    
1252
 
    /*
1253
 
     * Registered name is special.
1254
 
     */
1255
 
    
1256
 
    tmp = port_info_2(p, pid, am_registered_name);
1257
 
    if (is_tuple(tmp)) {
1258
 
        result = CONS(hp, tmp, result);
 
1636
    if (is_tuple(reg_name)) {
 
1637
        result = CONS(hp, reg_name, result);
1259
1638
    }
1260
1639
 
1261
1640
    return result;
1275
1654
 
1276
1655
BIF_RETTYPE port_info_2(BIF_ALIST_2)
1277
1656
{
 
1657
    BIF_RETTYPE ret;
1278
1658
    Eterm portid = BIF_ARG_1;
 
1659
    Port *prt;
1279
1660
    Eterm item = BIF_ARG_2;
1280
1661
    Eterm res;
1281
1662
    Eterm* hp;
1282
1663
    int count;
1283
 
    int portix;
1284
 
    Process *p;
1285
 
    Port *pt;
1286
 
 
1287
 
    if (is_atom(portid)) {
1288
 
        whereis_name(portid, &p, &pt);
1289
 
        if (pt != NULL)
1290
 
            portid = pt->id;
1291
 
        else
1292
 
            BIF_ERROR(BIF_P, BADARG);
1293
 
    }
1294
 
 
1295
 
    if (is_external_port(portid)
1296
 
        && external_port_dist_entry(portid) == erts_this_dist_entry)
 
1664
 
 
1665
    if (is_internal_port(portid))
 
1666
        prt = erts_id2port(portid, BIF_P, ERTS_PROC_LOCK_MAIN);
 
1667
    else if (is_atom(portid))
 
1668
        erts_whereis_name(BIF_P, ERTS_PROC_LOCK_MAIN, 0,
 
1669
                          portid, NULL, 0, 0, &prt);
 
1670
    else if (is_external_port(portid)
 
1671
             && external_port_dist_entry(portid) == erts_this_dist_entry)
1297
1672
        BIF_RET(am_undefined);
1298
 
 
1299
 
    if (is_not_internal_port(portid)) {
 
1673
    else {
1300
1674
        BIF_ERROR(BIF_P, BADARG);
1301
1675
    }
1302
 
    if (((portix = internal_port_index(portid)) >= erts_max_ports)
1303
 
        || INVALID_PORT(erts_port+portix, portid)) {
 
1676
 
 
1677
    if (!prt) {
1304
1678
        BIF_RET(am_undefined);
1305
1679
    }
1306
1680
 
1309
1683
        res = make_small(internal_port_number(portid));
1310
1684
    }
1311
1685
    else if (item == am_links) {
1312
 
        int sz = 0;
1313
 
        ErlLink* lnk;
 
1686
        MonitorInfoCollection mic;
 
1687
        int i;
1314
1688
        Eterm item;
1315
1689
 
1316
 
        for (lnk = erts_port[portix].links; lnk; lnk = lnk->next) {
1317
 
            if (lnk->type == LNK_LINK) {
1318
 
                sz += NC_HEAP_SIZE(lnk->item); 
1319
 
                sz += 2;
1320
 
            }
1321
 
        }
1322
 
        hp = HAlloc(BIF_P, 3 + sz);
 
1690
        INIT_MONITOR_INFOS(mic);
 
1691
 
 
1692
        erts_doforall_links(prt->nlinks, &collect_one_link, &mic);
 
1693
 
 
1694
        hp = HAlloc(BIF_P, 3 + mic.sz);
1323
1695
        res = NIL;
1324
 
        for (lnk = erts_port[portix].links; lnk; lnk = lnk->next) {
1325
 
            if (lnk->type == LNK_LINK) {
1326
 
                item = STORE_NC(&hp, &MSO(BIF_P).externals, lnk->item); 
1327
 
                res = CONS(hp, item, res);
1328
 
                hp += 2;
1329
 
            }
 
1696
        for (i = 0; i < mic.mi_i; i++) {
 
1697
            item = STORE_NC(&hp, &MSO(BIF_P).externals, mic.mi[i].entity); 
 
1698
            res = CONS(hp, item, res);
 
1699
            hp += 2;
1330
1700
        }
 
1701
        DESTROY_MONITOR_INFOS(mic);
 
1702
 
1331
1703
    }
1332
1704
    else if (item == am_name) {
1333
 
        count = sys_strlen(erts_port[portix].name);
 
1705
        count = sys_strlen(prt->name);
1334
1706
 
1335
1707
        hp = HAlloc(BIF_P, 3 + 2*count);
1336
 
        res = buf_to_intlist(&hp,(byte*)erts_port[portix].name,count,NIL);
 
1708
        res = buf_to_intlist(&hp, prt->name, count, NIL);
1337
1709
    }
1338
1710
    else if (item == am_connected) {
1339
1711
        hp = HAlloc(BIF_P, 3);
1340
 
        res = erts_port[portix].connected; /* internal pid */
 
1712
        res = prt->connected; /* internal pid */
1341
1713
    }
1342
1714
    else if (item == am_input) {
1343
 
        hp = HAlloc(BIF_P, 3);
1344
 
        res = make_small_or_big(erts_port[portix].bytes_in, BIF_P);
 
1715
        Uint hsz = 3;
 
1716
        Uint n = prt->bytes_in;
 
1717
        (void) erts_bld_uint(NULL, &hsz, n);
 
1718
        hp = HAlloc(BIF_P, hsz);
 
1719
        res = erts_bld_uint(&hp, NULL, n);
1345
1720
    }
1346
1721
    else if (item == am_output) {
1347
 
        hp = HAlloc(BIF_P, 3);
1348
 
        res = make_small_or_big(erts_port[portix].bytes_out, BIF_P);
 
1722
        Uint hsz = 3;
 
1723
        Uint n = prt->bytes_out;
 
1724
        (void) erts_bld_uint(NULL, &hsz, n);
 
1725
        hp = HAlloc(BIF_P, hsz);
 
1726
        res = erts_bld_uint(&hp, NULL, n);
1349
1727
    }
1350
1728
    else if (item == am_registered_name) {
1351
1729
        RegProc *reg;
1352
 
        hp = HAlloc(BIF_P, 3);
1353
 
        reg = erts_port[portix].reg;
1354
 
        if (reg == NULL)
1355
 
            BIF_RET(NIL);
1356
 
        else
 
1730
        reg = prt->reg;
 
1731
        if (reg == NULL) {
 
1732
            ERTS_BIF_PREP_RET(ret, NIL);
 
1733
            goto done;
 
1734
        } else {
 
1735
            hp = HAlloc(BIF_P, 3);
1357
1736
            res = reg->name;
 
1737
        }
1358
1738
    }
1359
1739
    else if (item == am_memory) {
1360
1740
        /* All memory consumed in bytes (the Port struct should not be
1362
1742
         */
1363
1743
        Uint hsz = 3;
1364
1744
        Uint size = 0;
1365
 
        ErlLink* lnk;
1366
1745
        ErlHeapFragment* bp;
1367
1746
 
1368
1747
        hp = HAlloc(BIF_P, 3);
1369
1748
 
1370
 
        for(lnk = erts_port[portix].links; lnk; lnk = lnk->next)
1371
 
            size += erts_link_size(lnk);
 
1749
        erts_doforall_links(prt->nlinks, &one_link_size, &size);
1372
1750
 
1373
 
        for (bp = erts_port[portix].bp; bp; bp = bp->next)
 
1751
        for (bp = prt->bp; bp; bp = bp->next)
1374
1752
            size += sizeof(ErlHeapFragment) + (bp->size - 1)*sizeof(Eterm);
1375
1753
 
1376
 
        if (erts_port[portix].linebuf)
1377
 
            size += sizeof(LineBuf) + erts_port[portix].linebuf->ovsiz;
 
1754
        if (prt->linebuf)
 
1755
            size += sizeof(LineBuf) + prt->linebuf->ovsiz;
1378
1756
 
1379
1757
        /* ... */
1380
1758
 
1386
1764
        hp = HAlloc(BIF_P, hsz);
1387
1765
        res = erts_bld_uint(&hp, NULL, size);
1388
1766
    }
1389
 
    else
1390
 
        BIF_ERROR(BIF_P, BADARG);
1391
 
    BIF_RET(TUPLE2(hp, item, res));
 
1767
    else {
 
1768
        ERTS_BIF_PREP_ERROR(ret, BIF_P, BADARG);
 
1769
        goto done;
 
1770
    }
 
1771
 
 
1772
    ERTS_BIF_PREP_RET(ret, TUPLE2(hp, item, res));
 
1773
 
 
1774
 done:
 
1775
 
 
1776
    erts_smp_io_unlock();
 
1777
 
 
1778
    return ret;
1392
1779
}
1393
1780
 
1394
1781
 
1395
1782
Eterm
1396
1783
fun_info_2(Process* p, Eterm fun, Eterm what)
1397
1784
{
 
1785
    Eterm* hp;
 
1786
    Eterm val;
 
1787
 
1398
1788
    if (is_fun(fun)) {
1399
1789
        ErlFunThing* funp = (ErlFunThing *) fun_val(fun);
1400
 
        Eterm val;
1401
 
        Eterm* hp;
1402
1790
 
1403
1791
        switch (what) {
 
1792
        case am_type:
 
1793
            hp = HAlloc(p, 3);
 
1794
            val = am_local;
 
1795
            break;
1404
1796
        case am_pid:
1405
1797
            hp = HAlloc(p, 3);
1406
1798
            val = funp->creator;
1439
1831
            }
1440
1832
            break;
1441
1833
        case am_refc:
 
1834
            val = erts_make_integer(erts_smp_atomic_read(&funp->fe->refc), p);
1442
1835
            hp = HAlloc(p, 3);
1443
 
            val = make_small_or_big(funp->fe->refc, p);
1444
1836
            break;
1445
1837
        case am_arity:
1446
1838
            hp = HAlloc(p, 3);
1453
1845
        default:
1454
1846
            goto error;
1455
1847
        }
1456
 
        return TUPLE2(hp, what, val);
 
1848
    } else if (is_export(fun)) {
 
1849
        Export* exp = (Export *) (export_val(fun))[1];
 
1850
        switch (what) {
 
1851
        case am_type:
 
1852
            hp = HAlloc(p, 3);
 
1853
            val = am_external;
 
1854
            break;
 
1855
        case am_pid:
 
1856
            hp = HAlloc(p, 3);
 
1857
            val = am_undefined;
 
1858
            break;
 
1859
        case am_module:
 
1860
            hp = HAlloc(p, 3);
 
1861
            val = exp->code[0];
 
1862
            break;
 
1863
        case am_new_index:
 
1864
            hp = HAlloc(p, 3);
 
1865
            val = am_undefined;
 
1866
            break;
 
1867
        case am_new_uniq:
 
1868
            hp = HAlloc(p, 3);
 
1869
            val = am_undefined;
 
1870
            break;
 
1871
        case am_index:
 
1872
            hp = HAlloc(p, 3);
 
1873
            val = am_undefined;
 
1874
            break;
 
1875
        case am_uniq:
 
1876
            hp = HAlloc(p, 3);
 
1877
            val = am_undefined;
 
1878
            break;
 
1879
        case am_env:
 
1880
            hp = HAlloc(p, 3);
 
1881
            val = NIL;
 
1882
            break;
 
1883
        case am_refc:
 
1884
            hp = HAlloc(p, 3);
 
1885
            val = am_undefined;
 
1886
            break;
 
1887
        case am_arity:
 
1888
            hp = HAlloc(p, 3);
 
1889
            val = make_small(exp->code[2]);
 
1890
            break;
 
1891
        case am_name:
 
1892
            hp = HAlloc(p, 3);
 
1893
            val = exp->code[1];
 
1894
            break;
 
1895
        default:
 
1896
            goto error;
 
1897
        }
 
1898
    } else {
 
1899
    error:
 
1900
        BIF_ERROR(p, BADARG);
1457
1901
    }
1458
 
 
1459
 
 error:
1460
 
    BIF_ERROR(p, BADARG);
 
1902
    return TUPLE2(hp, what, val);
1461
1903
}
1462
1904
 
1463
1905
 
1468
1910
    Eterm res;
1469
1911
    Eterm* hp;
1470
1912
 
1471
 
    if (is_not_atom(BIF_ARG_1))
1472
 
        BIF_ERROR(BIF_P, BADARG);
1473
 
 
1474
1913
    if (BIF_ARG_1 == am_context_switches) {
 
1914
        Eterm cs = erts_make_integer(erts_get_total_context_switches(), BIF_P);
1475
1915
        hp = HAlloc(BIF_P, 3);
1476
 
        res = TUPLE2(hp, make_small_or_big(context_switches, BIF_P), SMALL_ZERO);
1477
 
        BIF_RET(res);
1478
 
    }
1479
 
    else if (BIF_ARG_1 == am_garbage_collection) {
1480
 
        hp = HAlloc(BIF_P, 4);
1481
 
        res = TUPLE3(hp, make_small_or_big(garbage_cols, BIF_P),
1482
 
                     make_small_or_big(reclaimed, BIF_P),
1483
 
                     SMALL_ZERO);
1484
 
        BIF_RET(res);
1485
 
    }
1486
 
    else if (BIF_ARG_1 == am_reductions) {
1487
 
        Uint reds;
1488
 
        Eterm b1, b2;
1489
 
 
1490
 
        reds = reductions + erts_current_reductions(BIF_P, BIF_P);
1491
 
        b1 = make_small_or_big(reds, BIF_P);
1492
 
        b2 = make_small_or_big(reds - last_reds, BIF_P);
1493
 
        hp = HAlloc(BIF_P,3);
1494
 
        res = TUPLE2(hp, b1, b2); 
1495
 
        last_reds  = reds;
1496
 
        BIF_RET(res);
1497
 
    }
1498
 
    else if (BIF_ARG_1 == am_runtime) {
 
1916
        res = TUPLE2(hp, cs, SMALL_ZERO);
 
1917
        BIF_RET(res);
 
1918
    } else if (BIF_ARG_1 == am_garbage_collection) {
 
1919
        Uint hsz = 4;
 
1920
        ErtsGCInfo gc_info;
 
1921
        Eterm gcs;
 
1922
        Eterm recl;
 
1923
        erts_gc_info(&gc_info);
 
1924
        (void) erts_bld_uint(NULL, &hsz, gc_info.garbage_collections);
 
1925
        (void) erts_bld_uint(NULL, &hsz, gc_info.reclaimed);
 
1926
        hp = HAlloc(BIF_P, hsz);
 
1927
        gcs = erts_bld_uint(&hp, NULL, gc_info.garbage_collections);
 
1928
        recl = erts_bld_uint(&hp, NULL, gc_info.reclaimed);
 
1929
        res = TUPLE3(hp, gcs, recl, SMALL_ZERO);
 
1930
        BIF_RET(res);
 
1931
    } else if (BIF_ARG_1 == am_reductions) {
 
1932
        Uint reds;
 
1933
        Uint diff;
 
1934
        Uint hsz = 3;
 
1935
        Eterm b1, b2;
 
1936
 
 
1937
        erts_get_total_reductions(&reds, &diff);
 
1938
        (void) erts_bld_uint(NULL, &hsz, reds);
 
1939
        (void) erts_bld_uint(NULL, &hsz, diff);
 
1940
        hp = HAlloc(BIF_P, hsz);
 
1941
        b1 = erts_bld_uint(&hp, NULL, reds);
 
1942
        b2 = erts_bld_uint(&hp, NULL, diff);
 
1943
        res = TUPLE2(hp, b1, b2); 
 
1944
        BIF_RET(res);
 
1945
    } else if (BIF_ARG_1 == am_exact_reductions) {
 
1946
        Uint reds;
 
1947
        Uint diff;
 
1948
        Uint hsz = 3;
 
1949
        Eterm b1, b2;
 
1950
 
 
1951
        erts_get_exact_total_reductions(BIF_P, &reds, &diff);
 
1952
        (void) erts_bld_uint(NULL, &hsz, reds);
 
1953
        (void) erts_bld_uint(NULL, &hsz, diff);
 
1954
        hp = HAlloc(BIF_P, hsz);
 
1955
        b1 = erts_bld_uint(&hp, NULL, reds);
 
1956
        b2 = erts_bld_uint(&hp, NULL, diff);
 
1957
        res = TUPLE2(hp, b1, b2); 
 
1958
        BIF_RET(res);
 
1959
    } else if (BIF_ARG_1 == am_runtime) {
1499
1960
        unsigned long u1, u2, dummy;
1500
1961
        Eterm b1, b2;
1501
1962
        elapsed_time_both(&u1,&dummy,&u2,&dummy);
1502
 
        b1 = make_small_or_big(u1,BIF_P);
1503
 
        b2 = make_small_or_big(u2,BIF_P);
 
1963
        b1 = erts_make_integer(u1,BIF_P);
 
1964
        b2 = erts_make_integer(u2,BIF_P);
1504
1965
        hp = HAlloc(BIF_P,3);
1505
1966
        res = TUPLE2(hp, b1, b2);
1506
1967
        BIF_RET(res);
1507
 
    }
1508
 
    else if (BIF_ARG_1 ==  am_run_queue) {
 
1968
    } else if (BIF_ARG_1 ==  am_run_queue) {
1509
1969
        res = sched_q_len();
1510
1970
        BIF_RET(make_small(res));
1511
 
    }
1512
 
    else if (BIF_ARG_1 == am_wall_clock) {
 
1971
    } else if (BIF_ARG_1 == am_wall_clock) {
1513
1972
        Uint w1, w2;
1514
1973
        Eterm b1, b2;
1515
1974
        wall_clock_elapsed_time_both(&w1, &w2);
1516
 
        b1 = make_small_or_big(w1,BIF_P);
1517
 
        b2 = make_small_or_big(w2,BIF_P);
 
1975
        b1 = erts_make_integer(w1,BIF_P);
 
1976
        b2 = erts_make_integer(w2,BIF_P);
1518
1977
        hp = HAlloc(BIF_P,3);
1519
1978
        res = TUPLE2(hp, b1, b2);
1520
1979
        BIF_RET(res);
1521
 
    }
1522
 
    else if (BIF_ARG_1 == am_io) {
 
1980
    } else if (BIF_ARG_1 == am_io) {
1523
1981
        Eterm r1, r2;
1524
1982
        Eterm in, out;
1525
 
        in = make_small_or_big(bytes_in,BIF_P);
1526
 
        out = make_small_or_big(bytes_out,BIF_P); 
1527
 
        hp = HAlloc(BIF_P, 9);
 
1983
        Uint hsz = 9;
 
1984
        
 
1985
        erts_smp_io_safe_lock(BIF_P, ERTS_PROC_LOCK_MAIN);
 
1986
 
 
1987
        (void) erts_bld_uint(NULL, &hsz, bytes_in);
 
1988
        (void) erts_bld_uint(NULL, &hsz, bytes_out);
 
1989
        hp = HAlloc(BIF_P, hsz);
 
1990
        in = erts_bld_uint(&hp, NULL, bytes_in);
 
1991
        out = erts_bld_uint(&hp, NULL, bytes_out);
 
1992
 
 
1993
        erts_smp_io_unlock();
 
1994
 
1528
1995
        r1 = TUPLE2(hp,  am_input, in);
1529
1996
        hp += 3;
1530
1997
        r2 = TUPLE2(hp, am_output, out);
1539
2006
    BIF_RET(erts_error_logger_warnings);
1540
2007
}
1541
2008
 
 
2009
static erts_smp_atomic_t available_internal_state;
 
2010
 
 
2011
BIF_RETTYPE erts_debug_get_internal_state_1(BIF_ALIST_1)
 
2012
{
 
2013
    /*
 
2014
     * NOTE: Only supposed to be used for testing, and debugging.
 
2015
     */
 
2016
 
 
2017
    if (!erts_smp_atomic_read(&available_internal_state)) {
 
2018
        BIF_ERROR(BIF_P, EXC_UNDEF);
 
2019
    }
 
2020
 
 
2021
    if (is_atom(BIF_ARG_1)) {
 
2022
        DECL_AM(node_and_dist_references);
 
2023
        DECL_AM(DbTable_words);
 
2024
        DECL_AM(next_pid);
 
2025
        DECL_AM(next_port);
 
2026
        DECL_AM(check_io_debug);
 
2027
        DECL_AM(available_internal_state);
 
2028
 
 
2029
        if (BIF_ARG_1 == AM_node_and_dist_references) {
 
2030
            /* Used by node_container_SUITE (emulator) */
 
2031
            Eterm res = erts_get_node_and_dist_references(BIF_P);
 
2032
            BIF_RET(res);
 
2033
        }
 
2034
        else if (BIF_ARG_1 == AM_next_pid || BIF_ARG_1 == AM_next_port) {
 
2035
            /* Used by node_container_SUITE (emulator) */
 
2036
            Eterm res;
 
2037
            if (BIF_ARG_1 == AM_next_pid)
 
2038
                res = erts_test_next_pid(0, 0);
 
2039
            else {
 
2040
                erts_smp_io_safe_lock(BIF_P, ERTS_PROC_LOCK_MAIN);
 
2041
                res = erts_test_next_port(0, 0);
 
2042
                erts_smp_io_unlock();
 
2043
            }
 
2044
            if (res < 0)
 
2045
                BIF_RET(am_false);
 
2046
            BIF_RET(erts_make_integer(res, BIF_P));
 
2047
        }
 
2048
        else if (BIF_ARG_1 == AM_DbTable_words) {
 
2049
            /* Used by ets_SUITE (stdlib) */
 
2050
            size_t words = (sizeof(DbTable) + sizeof(Uint) - 1)/sizeof(Uint);
 
2051
            BIF_RET(make_small((Uint) words));
 
2052
        }
 
2053
        else if (BIF_ARG_1 == AM_check_io_debug) {
 
2054
            /* Used by (emulator) */
 
2055
            int res;
 
2056
#ifdef HAVE_ERTS_CHECK_IO_DEBUG
 
2057
            res = erts_check_io_debug();
 
2058
#else
 
2059
            res = 0;
 
2060
#endif
 
2061
            ASSERT(res >= 0);
 
2062
            BIF_RET(erts_make_integer((Uint) res, BIF_P));
 
2063
        }
 
2064
        else if (BIF_ARG_1 == AM_available_internal_state) {
 
2065
            BIF_RET(am_true);
 
2066
        }
 
2067
    }
 
2068
    else if (is_tuple(BIF_ARG_1)) {
 
2069
        Eterm* tp = tuple_val(BIF_ARG_1);
 
2070
        switch (arityval(tp[0])) {
 
2071
        case 2: {
 
2072
            DECL_AM(link_list);
 
2073
            DECL_AM(monitor_list);
 
2074
            DECL_AM(channel_number);
 
2075
            DECL_AM(have_pending_exit);
 
2076
 
 
2077
            if (tp[1] == AM_link_list) {
 
2078
                /* Used by erl_link_SUITE (emulator) */
 
2079
                if(is_internal_pid(tp[2])) {
 
2080
                    Eterm res;
 
2081
                    Process *p;
 
2082
 
 
2083
                    p = erts_pid2proc(BIF_P,
 
2084
                                      ERTS_PROC_LOCK_MAIN,
 
2085
                                      tp[2],
 
2086
                                      ERTS_PROC_LOCK_LINK);
 
2087
                    if (!p) {
 
2088
                        ERTS_SMP_ASSERT_IS_NOT_EXITING(BIF_P);
 
2089
                        BIF_RET(am_undefined);
 
2090
                    }
 
2091
                    res = make_link_list(BIF_P, p->nlinks, NIL);
 
2092
                    erts_smp_proc_unlock(p, ERTS_PROC_LOCK_LINK);
 
2093
                    BIF_RET(res);
 
2094
                }
 
2095
                else if(is_internal_port(tp[2])) {
 
2096
                    Eterm res;
 
2097
                    Port *p = erts_id2port(tp[2], BIF_P, ERTS_PROC_LOCK_MAIN);
 
2098
                    if(p)
 
2099
                        res = make_link_list(BIF_P, p->nlinks, NIL);
 
2100
                    else
 
2101
                        res = am_undefined;
 
2102
                    erts_smp_io_unlock();
 
2103
                    BIF_RET(res);
 
2104
                }
 
2105
                else if(is_node_name_atom(tp[2])) {
 
2106
                    DistEntry *dep = erts_find_dist_entry(tp[2]);
 
2107
                    if(dep) {
 
2108
                        Eterm subres;
 
2109
                        erts_smp_dist_entry_lock(dep);
 
2110
                        subres = make_link_list(BIF_P, dep->nlinks, NIL);
 
2111
                        subres = make_link_list(BIF_P, dep->node_links, subres);
 
2112
                        erts_smp_dist_entry_unlock(dep);
 
2113
                        erts_deref_dist_entry(dep);
 
2114
                        BIF_RET(subres);
 
2115
                    } else {
 
2116
                        BIF_RET(am_undefined);
 
2117
                    }
 
2118
                }
 
2119
            }
 
2120
            else if (tp[1] == AM_monitor_list) {
 
2121
                /* Used by erl_link_SUITE (emulator) */
 
2122
                if(is_internal_pid(tp[2])) {
 
2123
                    Process *p;
 
2124
                    Eterm res;
 
2125
 
 
2126
                    p = erts_pid2proc(BIF_P,
 
2127
                                      ERTS_PROC_LOCK_MAIN,
 
2128
                                      tp[2],
 
2129
                                      ERTS_PROC_LOCK_LINK);
 
2130
                    if (!p) {
 
2131
                        ERTS_SMP_ASSERT_IS_NOT_EXITING(BIF_P);
 
2132
                        BIF_RET(am_undefined);
 
2133
                    }
 
2134
                    res = make_monitor_list(BIF_P, p->monitors);
 
2135
                    erts_smp_proc_unlock(p, ERTS_PROC_LOCK_LINK);
 
2136
                    BIF_RET(res);
 
2137
                } else if(is_node_name_atom(tp[2])) {
 
2138
                    DistEntry *dep = erts_find_dist_entry(tp[2]);
 
2139
                    if(dep) {
 
2140
                        Eterm ml;
 
2141
                        erts_smp_dist_entry_lock(dep);
 
2142
                        ml = make_monitor_list(BIF_P, dep->monitors);
 
2143
                        erts_smp_dist_entry_unlock(dep);
 
2144
                        erts_deref_dist_entry(dep);
 
2145
                        BIF_RET(ml);
 
2146
                    } else {
 
2147
                        BIF_RET(am_undefined);
 
2148
                    }
 
2149
                }
 
2150
            }
 
2151
            else if (tp[1] == AM_channel_number) {
 
2152
                Eterm res;
 
2153
                DistEntry *dep = erts_find_dist_entry(tp[2]);
 
2154
                if (!dep)
 
2155
                    res = am_undefined;
 
2156
                else {
 
2157
                    Uint cno = dist_entry_channel_no(dep);
 
2158
                    res = make_small(cno);
 
2159
                    erts_deref_dist_entry(dep);
 
2160
                }
 
2161
                BIF_RET(res);
 
2162
            }
 
2163
            else if (tp[1] == AM_have_pending_exit) {
 
2164
                Process *rp = erts_pid2proc(BIF_P, ERTS_PROC_LOCK_MAIN,
 
2165
                                            tp[2], ERTS_PROC_LOCK_STATUS);
 
2166
                if (!rp) {
 
2167
                    BIF_RET(am_undefined);
 
2168
                }
 
2169
                else {
 
2170
                    Eterm res = ERTS_PROC_PENDING_EXIT(rp) ? am_true : am_false;
 
2171
                    erts_smp_proc_unlock(rp, ERTS_PROC_LOCK_STATUS);
 
2172
                    BIF_RET(res);
 
2173
                }
 
2174
            }
 
2175
 
 
2176
            break;
 
2177
        }
 
2178
        default:
 
2179
            break;
 
2180
        }
 
2181
    }
 
2182
    BIF_ERROR(BIF_P, BADARG);
 
2183
}
 
2184
 
 
2185
BIF_RETTYPE erts_debug_set_internal_state_2(BIF_ALIST_2)
 
2186
{
 
2187
    DECL_AM(available_internal_state);
 
2188
    /*
 
2189
     * NOTE: Only supposed to be used for testing, and debugging.
 
2190
     */
 
2191
 
 
2192
    if (BIF_ARG_1 == AM_available_internal_state
 
2193
        && (BIF_ARG_2 == am_true || BIF_ARG_2 == am_false)) {
 
2194
        long on = (long) (BIF_ARG_2 == am_true);
 
2195
        long prev_on = erts_smp_atomic_xchg(&available_internal_state, on);
 
2196
        if (on) {
 
2197
            erts_dsprintf_buf_t *dsbufp = erts_create_logger_dsbuf();
 
2198
            erts_dsprintf(dsbufp, "Process %T ", BIF_P->id);
 
2199
            if (erts_is_alive())
 
2200
                erts_dsprintf(dsbufp, "on node %T ", erts_this_node->sysname);
 
2201
            erts_dsprintf(dsbufp,
 
2202
                          "enabled access to the emulator internal state.\n");
 
2203
            erts_dsprintf(dsbufp,
 
2204
                          "NOTE: This is an erts internal test feature and "
 
2205
                          "should *only* be used by OTP test-suites.\n");
 
2206
            erts_send_warning_to_logger(BIF_P->group_leader, dsbufp);
 
2207
        }
 
2208
        BIF_RET(prev_on ? am_true : am_false);
 
2209
    }
 
2210
 
 
2211
    if (!erts_smp_atomic_read(&available_internal_state)) {
 
2212
        BIF_ERROR(BIF_P, EXC_UNDEF);
 
2213
    }
 
2214
 
 
2215
    if (is_atom(BIF_ARG_1)) {
 
2216
        DECL_AM(next_pid);
 
2217
        DECL_AM(next_port);
 
2218
        DECL_AM(send_fake_exit_signal);
 
2219
        
 
2220
        if (BIF_ARG_1 == AM_next_pid || BIF_ARG_1 == AM_next_port) {
 
2221
            /* Used by node_container_SUITE (emulator) */
 
2222
            Uint next;
 
2223
 
 
2224
            if (term_to_Uint(BIF_ARG_2, &next) != 0) {
 
2225
                Eterm res;
 
2226
 
 
2227
                if (BIF_ARG_1 == AM_next_pid)
 
2228
                    res = erts_test_next_pid(1, next);
 
2229
                else {
 
2230
                    erts_smp_io_safe_lock(BIF_P, ERTS_PROC_LOCK_MAIN);
 
2231
                    res = erts_test_next_port(1, next);
 
2232
                    erts_smp_io_unlock();
 
2233
                }
 
2234
                if (res < 0)
 
2235
                    BIF_RET(am_false);
 
2236
                BIF_RET(erts_make_integer(res, BIF_P));
 
2237
            }
 
2238
        }
 
2239
        else if (BIF_ARG_1 == AM_send_fake_exit_signal) {
 
2240
            /* Used by signal_SUITE (emulator) */
 
2241
 
 
2242
            /* Testcases depend on the exit being received via
 
2243
               a pending exit when the receiver is the same as
 
2244
               the caller.  */
 
2245
            if (is_tuple(BIF_ARG_2)) {
 
2246
                Eterm* tp = tuple_val(BIF_ARG_2);
 
2247
                if (arityval(tp[0]) == 3
 
2248
                    && (is_pid(tp[1]) || is_port(tp[1]))
 
2249
                    && is_internal_pid(tp[2])) {
 
2250
                    int xres;
 
2251
                    Uint32 rp_locks = ERTS_PROC_LOCKS_XSIG_SEND;
 
2252
                    Process *rp = erts_pid2proc(BIF_P, ERTS_PROC_LOCK_MAIN,
 
2253
                                                tp[2], rp_locks);
 
2254
                    if (!rp) {
 
2255
                        DECL_AM(dead);
 
2256
                        BIF_RET(AM_dead);
 
2257
                    }
 
2258
 
 
2259
#ifdef ERTS_SMP
 
2260
                    if (BIF_P == rp)
 
2261
                        rp_locks |= ERTS_PROC_LOCK_MAIN;
 
2262
#endif
 
2263
                    xres = erts_send_exit_signal(NULL, /* NULL in order to
 
2264
                                                          force a pending exit
 
2265
                                                          when we send to our
 
2266
                                                          selves. */
 
2267
                                                 tp[1],
 
2268
                                                 rp,
 
2269
                                                 &rp_locks,
 
2270
                                                 tp[3],
 
2271
                                                 NIL,
 
2272
                                                 NULL,
 
2273
                                                 0);
 
2274
#ifdef ERTS_SMP
 
2275
                    if (BIF_P == rp)
 
2276
                        rp_locks &= ~ERTS_PROC_LOCK_MAIN;
 
2277
#endif
 
2278
                    erts_smp_proc_unlock(rp, rp_locks);
 
2279
                    if (xres > 1) {
 
2280
                        DECL_AM(message);
 
2281
                        BIF_RET(AM_message);
 
2282
                    }
 
2283
                    else if (xres == 0) {
 
2284
                        DECL_AM(unaffected);
 
2285
                        BIF_RET(AM_unaffected);
 
2286
                    }
 
2287
                    else {
 
2288
                        DECL_AM(exit);
 
2289
                        BIF_RET(AM_exit);
 
2290
                    }
 
2291
                }
 
2292
            }
 
2293
        }
 
2294
    }
 
2295
 
 
2296
    BIF_ERROR(BIF_P, BADARG);
 
2297
}
 
2298
 
1542
2299
void
1543
2300
erts_bif_info_init(void)
1544
2301
{
1545
 
 
 
2302
#if defined(PURIFY) || defined(VALGRIND)
 
2303
    INIT_AM(error_checker);
 
2304
#ifdef VALGRIND
 
2305
    INIT_AM(valgrind);
 
2306
#endif
 
2307
#endif
 
2308
    erts_smp_atomic_init(&available_internal_state, 0);
1546
2309
}