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

« back to all changes in this revision

Viewing changes to erts/emulator/beam/erl_process_dump.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:
28
28
#include "bif.h"
29
29
#include "erl_db.h"
30
30
#include "dist.h"
31
 
#include "error.h"
32
31
#include "beam_catches.h"
33
32
#include "erl_binary.h"
34
33
 
37
36
 
38
37
#define OUR_NIL _make_header(0,_TAG_HEADER_FLOAT)
39
38
 
40
 
static void dump_process_info(Process *p, CIO to);
41
 
static void dump_element(Eterm x, CIO fd);
42
 
static void dump_element_nl(Eterm x, CIO fd);
43
 
static int stack_element_dump(Process* p, Eterm* sp, int yreg, CIO fd);
44
 
static void print_function_from_pc(Eterm* x, CIO fd);
45
 
static void heap_dump(Eterm x, CIO fd);
46
 
static void dump_binaries(Binary* root, CIO fd);
47
 
static void dump_externally(Eterm term, CIO fd);
 
39
static void dump_process_info(int to, void *to_arg, Process *p);
 
40
static void dump_element(int to, void *to_arg, Eterm x);
 
41
static void dump_element_nl(int to, void *to_arg, Eterm x);
 
42
static int stack_element_dump(int to, void *to_arg, Process* p, Eterm* sp,
 
43
                              int yreg);
 
44
static void print_function_from_pc(int to, void *to_arg, Eterm* x);
 
45
static void heap_dump(int to, void *to_arg, Eterm x);
 
46
static void dump_binaries(int to, void *to_arg, Binary* root);
 
47
static void dump_externally(int to, void *to_arg, Eterm term);
48
48
 
49
49
static Binary* all_binaries;
50
50
 
53
53
 
54
54
 
55
55
void
56
 
erts_deep_process_dump(CIO to)
 
56
erts_deep_process_dump(int to, void *to_arg)
57
57
{
58
58
    int i;
59
59
 
65
65
               Process* p = process_tab[i];
66
66
 
67
67
               if (p->status != P_GARBING) {
68
 
                   dump_process_info(p, to);
 
68
                   dump_process_info(to, to_arg, p);
69
69
               }
70
70
           }
71
71
       }
72
72
    }
73
73
 
74
 
    dump_binaries(all_binaries, to);
 
74
    dump_binaries(to, to_arg, all_binaries);
75
75
}
76
76
 
77
77
static void
78
 
dump_process_info(Process *p, CIO to)
 
78
dump_process_info(int to, void *to_arg, Process *p)
79
79
{
80
80
    Eterm* sp;
81
81
    ErlMessage* mp;
 
82
    ErlFunThing* fptr;
82
83
    int yreg = -1;
83
84
 
 
85
    ERTS_SMP_MSGQ_MV_INQ2PRIVQ(p);
 
86
 
84
87
    if (p->msg.first) {
85
 
        erl_printf(to, "=proc_messages:");
86
 
        display(p->id, to);
87
 
        erl_printf(to, "\n");
 
88
        erts_print(to, to_arg, "=proc_messages:%T\n", p->id);
88
89
        for (mp = p->msg.first; mp != NULL; mp = mp->next) {
89
90
            Eterm mesg = ERL_MESSAGE_TERM(mp);
90
 
            dump_element(mesg, to);
 
91
            dump_element(to, to_arg, mesg);
91
92
            mesg = ERL_MESSAGE_TOKEN(mp);
92
 
            erl_printf(to, ":");
93
 
            dump_element(mesg, to);
94
 
            erl_printf(to, "\n");
 
93
            erts_print(to, to_arg, ":");
 
94
            dump_element(to, to_arg, mesg);
 
95
            erts_print(to, to_arg, "\n");
95
96
        }
96
97
    }
97
98
 
98
99
    if (p->dictionary) {
99
 
        erl_printf(to, "=proc_dictionary:");
100
 
        display(p->id, to);
101
 
        erl_printf(to, "\n");
102
 
        erts_deep_dictionary_dump(p->dictionary, dump_element_nl, to);
 
100
        erts_print(to, to_arg, "=proc_dictionary:%T\n", p->id);
 
101
        erts_deep_dictionary_dump(to, to_arg,
 
102
                                  p->dictionary, dump_element_nl);
103
103
    }
104
104
 
105
105
    if (p->debug_dictionary) {
106
 
        erl_printf(to, "=debug_proc_dictionary:");
107
 
        display(p->id, to);
108
 
        erl_printf(to, "\n");
109
 
        erts_deep_dictionary_dump(p->debug_dictionary, dump_element_nl, to);
 
106
        erts_print(to, to_arg, "=debug_proc_dictionary:%T\n", p->id);
 
107
        erts_deep_dictionary_dump(to, to_arg,
 
108
                                  p->debug_dictionary, dump_element_nl);
110
109
    }
111
110
 
112
 
    erl_printf(to, "=proc_stack:");
113
 
    display(p->id, to);
114
 
    erl_printf(to, "\n");
 
111
    erts_print(to, to_arg, "=proc_stack:%T\n", p->id);
115
112
 
116
113
    for (sp = p->stop; sp < STACK_START(p); sp++) {
117
 
        yreg = stack_element_dump(p, sp, yreg, to);
118
 
    }
119
 
 
120
 
    erl_printf(to, "=proc_heap:");
121
 
    display(p->id, to);
122
 
    erl_printf(to, "\n");
 
114
        yreg = stack_element_dump(to, to_arg, p, sp, yreg);
 
115
    }
 
116
 
 
117
    erts_print(to, to_arg, "=proc_heap:%T\n", p->id);
 
118
 
 
119
#ifndef HYBRID /* FIND ME! */
 
120
    /*
 
121
     * We dump funs in the external format. Therefore, we must be sure
 
122
     * sure that any part of the heap referenced by the funs's environments
 
123
     * have not been destroyed. Dump the funs now.
 
124
     */
 
125
    for (fptr = MSO(p).funs; fptr != 0; fptr = fptr->next) {
 
126
        erts_print(to, to_arg, ADDR_FMT ":", fptr);
 
127
        dump_externally(to, to_arg, make_fun((Eterm)fptr));
 
128
        erts_putc(to, to_arg, '\n');
 
129
        * (Eterm *) fptr = OUR_NIL;
 
130
    }
 
131
#endif
123
132
 
124
133
    for (sp = p->stop; sp < STACK_START(p); sp++) {
125
134
        Eterm term = *sp;
126
135
 
127
136
        if (!is_catch(term) && !is_CP(term)) {
128
 
            heap_dump(term, to);
 
137
            heap_dump(to, to_arg, term);
129
138
        }
130
139
    }
131
140
    
132
141
    for (mp = p->msg.first; mp != NULL; mp = mp->next) {
133
142
        Eterm mesg = ERL_MESSAGE_TERM(mp);
134
 
        heap_dump(mesg, to);
 
143
        heap_dump(to, to_arg, mesg);
135
144
        mesg = ERL_MESSAGE_TOKEN(mp);
136
 
        heap_dump(mesg, to);
 
145
        heap_dump(to, to_arg, mesg);
137
146
    }
138
147
 
139
148
    if (p->dictionary) {
140
 
        erts_deep_dictionary_dump(p->dictionary, heap_dump, to);
 
149
        erts_deep_dictionary_dump(to, to_arg, p->dictionary, heap_dump);
141
150
    }
142
151
 
143
152
    if (p->debug_dictionary) {
144
 
        erts_deep_dictionary_dump(p->debug_dictionary, heap_dump, to);
 
153
        erts_deep_dictionary_dump(to, to_arg, p->debug_dictionary, heap_dump);
145
154
    }
146
155
}
147
156
 
148
157
static void
149
 
dump_element(Eterm x, CIO fd)
 
158
dump_element(int to, void *to_arg, Eterm x)
150
159
{
151
160
    if (is_list(x)) {
152
 
        sys_printf(fd, "H" WORD_FMT, list_val(x));
 
161
        erts_print(to, to_arg, "H" WORD_FMT, list_val(x));
153
162
    } else if (is_boxed(x)) {
154
 
        sys_printf(fd, "H" WORD_FMT, boxed_val(x));
 
163
        erts_print(to, to_arg, "H" WORD_FMT, boxed_val(x));
155
164
    } else if (is_immed(x)) {
156
165
        if (is_atom(x)) {
157
 
            char* s = atom_tab(atom_val(x))->name;
 
166
            unsigned char* s = atom_tab(atom_val(x))->name;
158
167
            int len = atom_tab(atom_val(x))->len;
159
168
            int i;
160
169
 
161
 
            sys_printf(fd, "A%X:", atom_tab(atom_val(x))->len);
 
170
            erts_print(to, to_arg, "A%X:", atom_tab(atom_val(x))->len);
162
171
            for (i = 0; i < len; i++) {
163
 
                erl_putc(*s++, fd);
 
172
                erts_putc(to, to_arg, *s++);
164
173
            }
165
174
        } else if (is_small(x)) {
166
 
            erl_putc('I', fd);
167
 
            display(x, fd);
 
175
            erts_print(to, to_arg, "I%T", x);
168
176
        } else if (is_pid(x)) {
169
 
            erl_putc('P', fd);
170
 
            display(x, fd);
 
177
            erts_print(to, to_arg, "P%T", x);
171
178
        } else if (is_port(x)) {
172
 
            erl_printf(fd, "p<%lu.%lu>",
173
 
                       (unsigned long) port_channel_no(x),
174
 
                       (unsigned long) port_number(x));
 
179
            erts_print(to, to_arg, "p<%bpu.%bpu>",
 
180
                       port_channel_no(x), port_number(x));
175
181
        } else if (is_nil(x)) {
176
 
            erl_putc('N', fd);
 
182
            erts_putc(to, to_arg, 'N');
177
183
        }
178
184
    }
179
185
}
180
186
 
181
187
static void
182
 
dump_element_nl(Eterm x, CIO fd)
 
188
dump_element_nl(int to, void *to_arg, Eterm x)
183
189
{
184
 
    dump_element(x, fd);
185
 
    erl_putc('\n', fd);
 
190
    dump_element(to, to_arg, x);
 
191
    erts_putc(to, to_arg, '\n');
186
192
}
187
193
 
188
194
 
189
195
static int
190
 
stack_element_dump(Process* p, Eterm* sp, int yreg, CIO fd)
 
196
stack_element_dump(int to, void *to_arg, Process* p, Eterm* sp, int yreg)
191
197
{
192
198
    Eterm x = *sp;
193
199
 
194
200
    if (yreg < 0 || is_CP(x)) {
195
 
        erl_printf(fd, "%p:", sp);
 
201
        erts_print(to, to_arg, "%p:", sp);
196
202
    } else {
197
 
        sys_printf(fd, "y%d:", yreg);
 
203
        erts_print(to, to_arg, "y%d:", yreg);
198
204
        yreg++;
199
205
    }
200
206
 
201
207
    if (is_CP(x)) {
202
 
        sys_printf(fd, "SReturn addr 0x%X (", (Eterm *) x);
203
 
        print_function_from_pc(cp_val(x), fd);
204
 
        sys_printf(fd, ")\n");
 
208
        erts_print(to, to_arg, "SReturn addr 0x%X (", (Eterm *) x);
 
209
        print_function_from_pc(to, to_arg, cp_val(x));
 
210
        erts_print(to, to_arg, ")\n");
205
211
        yreg = 0;
206
212
    } else if is_catch(x) {
207
 
        sys_printf(fd, "SCatch 0x%X (", catch_pc(x));
208
 
        print_function_from_pc(catch_pc(x), fd);
209
 
        sys_printf(fd, ")\n");
 
213
        erts_print(to, to_arg, "SCatch 0x%X (", catch_pc(x));
 
214
        print_function_from_pc(to, to_arg, catch_pc(x));
 
215
        erts_print(to, to_arg, ")\n");
210
216
    } else {
211
 
        dump_element(x, fd);
212
 
        erl_putc('\n', fd);
 
217
        dump_element(to, to_arg, x);
 
218
        erts_putc(to, to_arg, '\n');
213
219
    }
214
220
    return yreg;
215
221
}
216
222
 
217
223
static void
218
 
print_function_from_pc(Eterm* x, CIO fd)
 
224
print_function_from_pc(int to, void *to_arg, Eterm* x)
219
225
{
220
226
    Eterm* addr = find_function_from_pc(x);
221
227
    if (addr == NULL) {
222
228
        if (x == beam_exit) {
223
 
            sys_printf(fd, "<terminate process>");
 
229
            erts_print(to, to_arg, "<terminate process>");
224
230
        } else if (x == beam_apply+1) {
225
 
            sys_printf(fd, "<terminate process normally>");
 
231
            erts_print(to, to_arg, "<terminate process normally>");
226
232
        } else {
227
 
            sys_printf(fd, "unknown function");
 
233
            erts_print(to, to_arg, "unknown function");
228
234
        }
229
235
    } else {
230
 
        display(addr[0], fd);
231
 
        sys_printf(fd, ":");
232
 
        display(addr[1], fd);
233
 
        sys_printf(fd, "/%d", addr[2]);
234
 
        sys_printf(fd, " + %d", ((x-addr)-2) * sizeof(Eterm));
 
236
        erts_print(to, to_arg, "%T:%T/%bpu + %bpu",
 
237
                   addr[0], addr[1], addr[2], ((x-addr)-2) * sizeof(Eterm));
235
238
    }
236
239
}
237
240
 
238
241
static void
239
 
heap_dump(Eterm x, CIO fd)
 
242
heap_dump(int to, void *to_arg, Eterm x)
240
243
{
241
244
    Eterm* ptr;
242
245
    Eterm last = OUR_NIL;
254
257
    } else if (is_list(x)) {
255
258
        ptr = list_val(x);
256
259
        if (ptr[0] != OUR_NIL) {
257
 
            sys_printf(fd, ADDR_FMT ":l", ptr);
258
 
            dump_element(ptr[0], fd);
259
 
            erl_putc('|', fd);
260
 
            dump_element(ptr[1], fd);
261
 
            erl_putc('\n', fd);
 
260
            erts_print(to, to_arg, ADDR_FMT ":l", ptr);
 
261
            dump_element(to, to_arg, ptr[0]);
 
262
            erts_putc(to, to_arg, '|');
 
263
            dump_element(to, to_arg, ptr[1]);
 
264
            erts_putc(to, to_arg, '\n');
262
265
            if (is_immed(ptr[1])) {
263
266
                ptr[1] = make_small(0);
264
267
            }
273
276
        ptr = boxed_val(x);
274
277
        hdr = *ptr;
275
278
        if (hdr != OUR_NIL) {   /* If not visited */
276
 
            sys_printf(fd, ADDR_FMT ":", ptr);
 
279
            erts_print(to, to_arg, ADDR_FMT ":", ptr);
277
280
            if (is_arity_value(hdr)) {
278
281
                Uint i;
279
282
                Uint arity = arityval(hdr);
280
283
 
281
 
                sys_printf(fd, "t" WORD_FMT ":", arity);
 
284
                erts_print(to, to_arg, "t" WORD_FMT ":", arity);
282
285
                for (i = 1; i <= arity; i++) {
283
 
                    dump_element(ptr[i], fd);
 
286
                    dump_element(to, to_arg, ptr[i]);
284
287
                    if (is_immed(ptr[i])) {
285
288
                        ptr[i] = make_small(0);
286
289
                    }
287
290
                    if (i < arity) {
288
 
                        erl_putc(',', fd);
 
291
                        erts_putc(to, to_arg, ',');
289
292
                    }
290
293
                }
291
 
                erl_putc('\n', fd);
 
294
                erts_putc(to, to_arg, '\n');
292
295
                if (arity == 0) {
293
296
                    ptr[0] = OUR_NIL;
294
297
                } else {
305
308
                GET_DOUBLE_DATA((ptr+1), f);
306
309
                i = sys_double_to_chars(f.fd, (char*) sbuf);
307
310
                sys_memset(sbuf+i, 0, 31-i);
308
 
                sys_printf(fd, "F%X:%s\n", i, sbuf);
 
311
                erts_print(to, to_arg, "F%X:%s\n", i, sbuf);
309
312
                *ptr = OUR_NIL;
310
313
            } else if (_is_bignum_header(hdr)) {
311
 
                erl_putc('B', fd);
312
 
                display(x, fd);
313
 
                erl_putc('\n', fd);
 
314
                erts_print(to, to_arg, "B%T\n", x);
314
315
                *ptr = OUR_NIL;
315
316
            } else if (is_binary_header(hdr)) {
316
317
                Uint tag = thing_subtag(hdr);
320
321
                if (tag == HEAP_BINARY_SUBTAG) {
321
322
                    byte* p;
322
323
 
323
 
                    sys_printf(fd, "Yh%X:", size);
324
 
                    GET_BINARY_BYTES(x, p);
 
324
                    erts_print(to, to_arg, "Yh%X:", size);
 
325
                    p = binary_bytes(x);
325
326
                    for (i = 0; i < size; i++) {
326
 
                        sys_printf(fd, "%02X", p[i]);
 
327
                        erts_print(to, to_arg, "%02X", p[i]);
327
328
                    }
328
329
                } else if (tag == REFC_BINARY_SUBTAG) {
329
330
                    ProcBin* pb = (ProcBin *) binary_val(x);
330
331
                    Binary* val = pb->val;
331
332
 
332
 
                    if (val->refc != 0) {
 
333
                    if (erts_smp_atomic_xchg(&val->refc, 0) != 0) {
333
334
                        val->flags = (Uint) all_binaries;
334
 
                        val->refc = 0;
335
335
                        all_binaries = val;
336
336
                    }
337
 
                    sys_printf(fd, "Yc%X:%X:%X", val,
 
337
                    erts_print(to, to_arg, "Yc%X:%X:%X", val,
338
338
                               pb->bytes - (byte *)val->orig_bytes,
339
339
                               size);
340
340
                } else if (tag == SUB_BINARY_SUBTAG) {
348
348
                    } else {    /* Heap binary */
349
349
                        val = real_bin;
350
350
                    }
351
 
                    sys_printf(fd, "Ys%X:%X:%X", val, Sb->offs, size);
 
351
                    erts_print(to, to_arg, "Ys%X:%X:%X", val, Sb->offs, size);
352
352
                }
353
 
                erl_putc('\n', fd);
 
353
                erts_putc(to, to_arg, '\n');
354
354
                *ptr = OUR_NIL;
355
355
            } else if (is_external_pid_header(hdr)) {
356
 
                erl_putc('P', fd);
357
 
                display(x, fd);
358
 
                erl_putc('\n', fd);
 
356
                erts_print(to, to_arg, "P%T\n", x);
359
357
                *ptr = OUR_NIL;
360
358
            } else if (is_external_port_header(hdr)) {
361
 
                erl_printf(fd, "p<%lu.%lu>\n",
362
 
                           (unsigned long) port_channel_no(x),
363
 
                           (unsigned long) port_number(x));
 
359
                erts_print(to, to_arg, "p<%bpu.%bpu>\n",
 
360
                           port_channel_no(x), port_number(x));
364
361
                *ptr = OUR_NIL;
365
362
            } else {
366
363
                /*
367
364
                 * All other we dump in the external term format.
368
365
                 */
369
 
                dump_externally(x, fd);
370
 
                erl_putc('\n', fd);
 
366
                dump_externally(to, to_arg, x);
 
367
                erts_putc(to, to_arg, '\n');
371
368
                *ptr = OUR_NIL;
372
369
            }
373
370
        }
380
377
}
381
378
 
382
379
static void
383
 
dump_binaries(Binary* current, CIO fd)
 
380
dump_binaries(int to, void *to_arg, Binary* current)
384
381
{
385
382
    while (current) {
386
383
        long i;
387
384
        long size = current->orig_size;
388
 
        byte* bytes = current->orig_bytes;
 
385
        byte* bytes = (byte*) current->orig_bytes;
389
386
 
390
 
        sys_printf(fd, "=binary:%X\n", current);
391
 
        sys_printf(fd, "%X:", size);
 
387
        erts_print(to, to_arg, "=binary:%X\n", current);
 
388
        erts_print(to, to_arg, "%X:", size);
392
389
        for (i = 0; i < size; i++) {
393
 
            sys_printf(fd, "%02X", bytes[i]);
 
390
            erts_print(to, to_arg, "%02X", bytes[i]);
394
391
        }
395
 
        erl_putc('\n', fd);
 
392
        erts_putc(to, to_arg, '\n');
396
393
        current = (Binary *) current->flags;
397
394
    }
398
395
}
399
396
 
400
397
static void
401
 
dump_externally(Eterm term, CIO fd)
 
398
dump_externally(int to, void *to_arg, Eterm term)
402
399
{
403
 
    byte sbuf[1024];
 
400
    byte sbuf[1024]; /* encode and hope for the best ... */
404
401
    byte* s; 
405
402
    byte* p;
406
403
 
407
404
    s = p = sbuf;
408
 
    erts_to_external_format(0, term, &p);
409
 
    sys_printf(fd, "E%X:", p-s);
 
405
    erts_to_external_format(NULL, term, &p, NULL, NULL);
 
406
    erts_print(to, to_arg, "E%X:", p-s);
410
407
    while (s < p) {
411
 
        sys_printf(fd, "%02X", *s++);
 
408
        erts_print(to, to_arg, "%02X", *s++);
412
409
    }
413
410
}