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

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
/*
2
2
 * %CopyrightBegin%
3
 
 * 
4
 
 * Copyright Ericsson AB 1998-2009. All Rights Reserved.
5
 
 * 
 
3
 *
 
4
 * Copyright Ericsson AB 1998-2011. All Rights Reserved.
 
5
 *
6
6
 * The contents of this file are subject to the Erlang Public License,
7
7
 * Version 1.1, (the "License"); you may not use this file except in
8
8
 * compliance with the License. You should have received a copy of the
9
9
 * Erlang Public License along with this software. If not, it can be
10
10
 * retrieved online at http://www.erlang.org/.
11
 
 * 
 
11
 *
12
12
 * Software distributed under the License is distributed on an "AS IS"
13
13
 * basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
 * the License for the specific language governing rights and limitations
15
15
 * under the License.
16
 
 * 
 
16
 *
17
17
 * %CopyrightEnd%
18
18
 */
19
19
 
43
43
#else
44
44
# define HEXF "%08bpX"
45
45
#endif
 
46
#define TermWords(t) (((t) / (sizeof(BeamInstr)/sizeof(Eterm))) + !!((t) % (sizeof(BeamInstr)/sizeof(Eterm))))
46
47
 
47
48
void dbg_bt(Process* p, Eterm* sp);
48
 
void dbg_where(Eterm* addr, Eterm x0, Eterm* reg);
 
49
void dbg_where(BeamInstr* addr, Eterm x0, Eterm* reg);
49
50
 
50
 
static void print_big(int to, void *to_arg, Eterm* addr);
51
 
static int print_op(int to, void *to_arg, int op, int size, Eterm* addr);
 
51
static int print_op(int to, void *to_arg, int op, int size, BeamInstr* addr);
52
52
Eterm
53
53
erts_debug_same_2(Process* p, Eterm term1, Eterm term2)
54
54
{
124
124
    BIF_ERROR(p, BADARG);
125
125
}
126
126
 
 
127
#if 0 /* Kept for conveninence when hard debugging. */
 
128
void debug_dump_code(BeamInstr *I, int num)
 
129
{
 
130
    BeamInstr *code_ptr = I;
 
131
    BeamInstr *end = code_ptr + num;
 
132
    erts_dsprintf_buf_t *dsbufp;
 
133
    BeamInstr instr;
 
134
    int i;
 
135
 
 
136
    dsbufp = erts_create_tmp_dsbuf(0);
 
137
    while (code_ptr < end) {
 
138
        erts_print(ERTS_PRINT_DSBUF, (void *) dsbufp, HEXF ": ", code_ptr);
 
139
        instr = (BeamInstr) code_ptr[0];
 
140
        for (i = 0; i < NUM_SPECIFIC_OPS; i++) {
 
141
            if (instr == (BeamInstr) BeamOp(i) && opc[i].name[0] != '\0') {
 
142
                code_ptr += print_op(ERTS_PRINT_DSBUF, (void *) dsbufp,
 
143
                                     i, opc[i].sz-1, code_ptr+1) + 1;
 
144
                break;
 
145
            }
 
146
        }
 
147
        if (i >= NUM_SPECIFIC_OPS) {
 
148
            erts_print(ERTS_PRINT_DSBUF, (void *) dsbufp,
 
149
                       "unknown " HEXF "\n", instr);
 
150
            code_ptr++;
 
151
        }
 
152
    }
 
153
    dsbufp->str[dsbufp->str_len] = 0;
 
154
    erts_fprintf(stderr,"%s", dsbufp->str);
 
155
    erts_destroy_tmp_dsbuf(dsbufp);
 
156
}
 
157
#endif
 
158
 
 
159
BIF_RETTYPE
 
160
erts_debug_instructions_0(BIF_ALIST_0)
 
161
{
 
162
    int i = 0;
 
163
    Uint needed = num_instructions * 2;
 
164
    Eterm* hp;
 
165
    Eterm res = NIL;
 
166
 
 
167
    for (i = 0; i < num_instructions; i++) {
 
168
        needed += 2*strlen(opc[i].name);
 
169
    }
 
170
    hp = HAlloc(BIF_P, needed);
 
171
    for (i = num_instructions-1; i >= 0; i--) {
 
172
        Eterm s = erts_bld_string_n(&hp, 0, opc[i].name, strlen(opc[i].name));
 
173
        res = erts_bld_cons(&hp, 0, s, res);
 
174
    }
 
175
    return res;
 
176
}
 
177
 
127
178
Eterm
128
179
erts_debug_disassemble_1(Process* p, Eterm addr)
129
180
{
132
183
    Eterm* tp;
133
184
    Eterm bin;
134
185
    Eterm mfa;
135
 
    Eterm* funcinfo = NULL;     /* Initialized to eliminate warning. */
136
 
    Uint* code_base;
137
 
    Uint* code_ptr = NULL;      /* Initialized to eliminate warning. */
138
 
    Uint instr;
139
 
    Uint uaddr;
 
186
    BeamInstr* funcinfo = NULL; /* Initialized to eliminate warning. */
 
187
    BeamInstr* code_base;
 
188
    BeamInstr* code_ptr = NULL; /* Initialized to eliminate warning. */
 
189
    BeamInstr instr;
 
190
    BeamInstr uaddr;
140
191
    Uint hsz;
141
192
    int i;
142
193
 
143
 
    if (term_to_Uint(addr, &uaddr)) {
144
 
        code_ptr = (Uint *) uaddr;
 
194
    if (term_to_UWord(addr, &uaddr)) {
 
195
        code_ptr = (BeamInstr *) uaddr;
145
196
        if ((funcinfo = find_function_from_pc(code_ptr)) == NULL) {
146
197
            BIF_RET(am_false);
147
198
        }
180
231
             * But this code_ptr will point to the start of the Export,
181
232
             * not the function's func_info instruction. BOOM !?
182
233
             */
183
 
            code_ptr = ((Eterm *) ep->address) - 5;
 
234
            code_ptr = ((BeamInstr *) ep->address) - 5;
184
235
            funcinfo = code_ptr+2;
185
236
        } else if (modp == NULL || (code_base = modp->code) == NULL) {
186
237
            BIF_RET(am_undef);
187
238
        } else {
188
239
            n = code_base[MI_NUM_FUNCTIONS];
189
240
            for (i = 0; i < n; i++) {
190
 
                code_ptr = (Uint *) code_base[MI_FUNCTIONS+i];
 
241
                code_ptr = (BeamInstr *) code_base[MI_FUNCTIONS+i];
191
242
                if (code_ptr[3] == name && code_ptr[4] == arity) {
192
243
                    funcinfo = code_ptr+2;
193
244
                    break;
203
254
 
204
255
    dsbufp = erts_create_tmp_dsbuf(0);
205
256
    erts_print(ERTS_PRINT_DSBUF, (void *) dsbufp, HEXF ": ", code_ptr);
206
 
    instr = (Uint) code_ptr[0];
 
257
    instr = (BeamInstr) code_ptr[0];
207
258
    for (i = 0; i < NUM_SPECIFIC_OPS; i++) {
208
 
        if (instr == (Uint) BeamOp(i) && opc[i].name[0] != '\0') {
 
259
        if (instr == (BeamInstr) BeamOp(i) && opc[i].name[0] != '\0') {
209
260
            code_ptr += print_op(ERTS_PRINT_DSBUF, (void *) dsbufp,
210
261
                                 i, opc[i].sz-1, code_ptr+1) + 1;
211
262
            break;
216
267
                   "unknown " HEXF "\n", instr);
217
268
        code_ptr++;
218
269
    }
219
 
    bin = new_binary(p, (byte *) dsbufp->str, (int) dsbufp->str_len);
 
270
    bin = new_binary(p, (byte *) dsbufp->str, dsbufp->str_len);
220
271
    erts_destroy_tmp_dsbuf(dsbufp);
221
272
    hsz = 4+4;
222
 
    (void) erts_bld_uint(NULL, &hsz, (Uint) code_ptr);
 
273
    (void) erts_bld_uword(NULL, &hsz, (BeamInstr) code_ptr);
223
274
    hp = HAlloc(p, hsz);
224
 
    addr = erts_bld_uint(&hp, NULL, (Uint) code_ptr);
 
275
    addr = erts_bld_uword(&hp, NULL, (BeamInstr) code_ptr);
225
276
    ASSERT(is_atom(funcinfo[0]));
226
277
    ASSERT(is_atom(funcinfo[1]));
227
 
    mfa = TUPLE3(hp, funcinfo[0], funcinfo[1], make_small(funcinfo[2]));
 
278
    mfa = TUPLE3(hp, (Eterm) funcinfo[0], (Eterm) funcinfo[1], make_small((Eterm) funcinfo[2]));
228
279
    hp += 4;
229
280
    return TUPLE3(hp, addr, bin, mfa);
230
281
}
236
287
 
237
288
    while (sp < stack) {
238
289
        if (is_CP(*sp)) {
239
 
            Eterm* addr = find_function_from_pc(cp_val(*sp));
 
290
            BeamInstr* addr = find_function_from_pc(cp_val(*sp));
240
291
            if (addr)
241
292
                erts_fprintf(stderr,
242
293
                             HEXF ": %T:%T/%bpu\n",
243
 
                             addr, addr[0], addr[1], addr[2]);
 
294
                             addr, (Eterm) addr[0], (Eterm) addr[1], (Uint) addr[2]);
244
295
        }
245
296
        sp++;
246
297
    }
247
298
}
248
299
 
249
300
void
250
 
dbg_where(Eterm* addr, Eterm x0, Eterm* reg)
 
301
dbg_where(BeamInstr* addr, Eterm x0, Eterm* reg)
251
302
{
252
 
    Eterm* f = find_function_from_pc(addr);
 
303
    BeamInstr* f = find_function_from_pc(addr);
253
304
 
254
305
    if (f == NULL) {
255
306
        erts_fprintf(stderr, "???\n");
259
310
 
260
311
        addr = f;
261
312
        arity = addr[2];
262
 
        erts_fprintf(stderr, HEXF ": %T:%T(", addr, addr[0], addr[1]);
 
313
        erts_fprintf(stderr, HEXF ": %T:%T(", addr, (Eterm) addr[0], (Eterm) addr[1]);
263
314
        for (i = 0; i < arity; i++)
264
315
            erts_fprintf(stderr, i ? ", %T" : "%T", i ? reg[i] : x0);
265
316
        erts_fprintf(stderr, ")\n");
267
318
}
268
319
 
269
320
static int
270
 
print_op(int to, void *to_arg, int op, int size, Eterm* addr)
 
321
print_op(int to, void *to_arg, int op, int size, BeamInstr* addr)
271
322
{
272
323
    int i;
273
 
    Uint tag;
 
324
    BeamInstr tag;
274
325
    char* sign;
275
326
    char* start_prog;           /* Start of program for packer. */
276
327
    char* prog;                 /* Current position in packer program. */
277
 
    Uint stack[8];              /* Stack for packer. */
278
 
    Uint* sp = stack;           /* Points to next free position. */
279
 
    Uint packed = 0;            /* Accumulator for packed operations. */
280
 
    Uint args[8];               /* Arguments for this instruction. */
281
 
    Uint* ap;                   /* Pointer to arguments. */
 
328
    BeamInstr stack[8];         /* Stack for packer. */
 
329
    BeamInstr* sp = stack;              /* Points to next free position. */
 
330
    BeamInstr packed = 0;               /* Accumulator for packed operations. */
 
331
    BeamInstr args[8];          /* Arguments for this instruction. */
 
332
    BeamInstr* ap;                      /* Pointer to arguments. */
 
333
    BeamInstr* unpacked;                /* Unpacked arguments */
282
334
 
283
335
    start_prog = opc[op].pack;
284
336
 
288
340
         * Avoid copying because instructions containing bignum operands
289
341
         * are bigger than actually declared.
290
342
         */
291
 
        ap = (Uint *) addr;
 
343
        ap = (BeamInstr *) addr;
292
344
    } else {
293
345
        /*
294
346
         * Copy all arguments to a local buffer for the unpacking.
324
376
                packed >>= BEAM_TIGHT_SHIFT;
325
377
                break;
326
378
            case '6':           /* Shift 16 steps */
327
 
                *ap++ = packed & 0xffff;
328
 
                packed >>= 16;
329
 
                break;
 
379
                *ap++ = packed & BEAM_LOOSE_MASK;
 
380
                packed >>= BEAM_LOOSE_SHIFT;
 
381
                break;
 
382
#ifdef ARCH_64
 
383
            case 'w':           /* Shift 32 steps */
 
384
                *ap++ = packed & BEAM_WIDE_MASK;
 
385
                packed >>= BEAM_WIDE_SHIFT;
 
386
                break;
 
387
#endif
330
388
            case 'p':
331
389
                *sp++ = *--ap;
332
390
                break;
353
411
            break;
354
412
        case 'x':               /* x(N) */
355
413
            if (reg_index(ap[0]) == 0) {
356
 
                erts_print(to, to_arg, "X[0]");
 
414
                erts_print(to, to_arg, "x[0]");
357
415
            } else {
358
416
                erts_print(to, to_arg, "x(%d)", reg_index(ap[0]));
359
417
            }
390
448
        case 'i':               /* Tagged integer */
391
449
        case 'c':               /* Tagged constant */
392
450
        case 'q':               /* Tagged literal */
393
 
            erts_print(to, to_arg, "%T", *ap);
 
451
            erts_print(to, to_arg, "%T", (Eterm) *ap);
394
452
            ap++;
395
453
            break;
396
454
        case 'A':
397
 
            erts_print(to, to_arg, "%d", arityval(ap[0]));
 
455
            erts_print(to, to_arg, "%d", arityval( (Eterm) ap[0]));
398
456
            ap++;
399
457
            break;
400
458
        case 'd':               /* Destination (x(0), x(N), y(N)) */
421
479
            ap++;
422
480
            break;
423
481
        case 'f':               /* Destination label */
424
 
            erts_print(to, to_arg, "f(%X)", *ap);
425
 
            ap++;
 
482
            {
 
483
                BeamInstr* f = find_function_from_pc((BeamInstr *)*ap);
 
484
                if (f+3 != (BeamInstr *) *ap) {
 
485
                    erts_print(to, to_arg, "f(" HEXF ")", *ap);
 
486
                } else {
 
487
                    erts_print(to, to_arg, "%T:%T/%bpu", (Eterm) f[0], (Eterm) f[1], (Eterm) f[2]);
 
488
                }
 
489
                ap++;
 
490
            }
426
491
            break;
427
492
        case 'p':               /* Pointer (to label) */
428
493
            {
429
 
                Eterm* f = find_function_from_pc((Eterm *)*ap);
430
 
 
431
 
                if (f+3 != (Eterm *) *ap) {
432
 
                    erts_print(to, to_arg, "p(%X)", *ap);
 
494
                BeamInstr* f = find_function_from_pc((BeamInstr *)*ap);
 
495
                if (f+3 != (BeamInstr *) *ap) {
 
496
                    erts_print(to, to_arg, "p(" HEXF ")", *ap);
433
497
                } else {
434
 
                    erts_print(to, to_arg, "%T:%T/%bpu", f[0], f[1], f[2]);
 
498
                    erts_print(to, to_arg, "%T:%T/%bpu", (Eterm) f[0], (Eterm) f[1], (Eterm) f[2]);
435
499
                }
436
500
                ap++;
437
501
            }
438
502
            break;
439
503
        case 'j':               /* Pointer (to label) */
440
 
            erts_print(to, to_arg, "j(%X)", *ap);
 
504
            erts_print(to, to_arg, "j(" HEXF ")", *ap);
441
505
            ap++;
442
506
            break;
443
507
        case 'e':               /* Export entry */
444
508
            {
445
509
                Export* ex = (Export *) *ap;
446
510
                erts_print(to, to_arg,
447
 
                           "%T:%T/%bpu", ex->code[0], ex->code[1], ex->code[2]);
 
511
                           "%T:%T/%bpu", (Eterm) ex->code[0], (Eterm) ex->code[1], (Uint) ex->code[2]);
448
512
                ap++;
449
513
            }
450
514
            break;
467
531
            ap++;
468
532
            break;
469
533
        case 'P':       /* Byte offset into tuple (see beam_load.c) */
470
 
            erts_print(to, to_arg, "%d", (*ap / sizeof(Eterm*)) - 1);
 
534
        case 'Q':       /* Like 'P', but packable */
 
535
            erts_print(to, to_arg, "%d", (*ap / sizeof(Eterm)) - 1);
471
536
            ap++;
472
537
            break;
473
538
        case 'l':               /* fr(N) */
487
552
     * Print more information about certain instructions.
488
553
     */
489
554
 
 
555
    unpacked = ap;
490
556
    ap = addr + size;
491
557
    switch (op) {
492
 
    case op_i_select_val_sfI:
493
 
        {
494
 
            int n = ap[-1];
495
 
 
496
 
            while (n > 0) {
497
 
                erts_print(to, to_arg, "%T f(%X) ", ap[0], ap[1]);
498
 
                ap += 2;
499
 
                size += 2;
500
 
                n--;
501
 
            }
502
 
        }
503
 
        break;
504
 
    case op_i_jump_on_val_sfII:
 
558
    case op_i_select_val_rfI:
 
559
    case op_i_select_val_xfI:
 
560
    case op_i_select_val_yfI:
 
561
        {
 
562
            int n = ap[-1];
 
563
 
 
564
            while (n > 0) {
 
565
                erts_print(to, to_arg, "%T f(" HEXF ") ", (Eterm) ap[0], ap[1]);
 
566
                ap += 2;
 
567
                size += 2;
 
568
                n--;
 
569
            }
 
570
        }
 
571
        break;
 
572
    case op_i_select_tuple_arity_rfI:
 
573
    case op_i_select_tuple_arity_xfI:
 
574
    case op_i_select_tuple_arity_yfI:
 
575
        {
 
576
            int n = ap[-1];
 
577
 
 
578
            while (n > 0) {
 
579
                Uint arity = arityval(ap[0]);
 
580
                erts_print(to, to_arg, " {%d} f(" HEXF ")", arity, ap[1]);
 
581
                ap += 2;
 
582
                size += 2;
 
583
                n--;
 
584
            }
 
585
        }
 
586
        break;
 
587
    case op_i_jump_on_val_rfII:
 
588
    case op_i_jump_on_val_xfII:
 
589
    case op_i_jump_on_val_yfII:
505
590
        {
506
591
            int n;
507
592
            for (n = ap[-2]; n > 0; n--) {
508
 
                erts_print(to, to_arg, "f(%X) ", ap[0]);
509
 
                ap++;
510
 
                size++;
511
 
            }
512
 
        }
513
 
        break;
514
 
    case op_i_select_big_sf:
515
 
        while (ap[0]) {
516
 
            int arity = thing_arityval(ap[0]);
517
 
            print_big(to, to_arg, ap);
518
 
            size += arity+1;
519
 
            ap += arity+1;
520
 
            erts_print(to, to_arg, " f(%X) ", ap[0]);
521
 
            ap++;
522
 
            size++;
523
 
        }
524
 
        ap++;
525
 
        size++;
 
593
                erts_print(to, to_arg, "f(" HEXF ") ", ap[0]);
 
594
                ap++;
 
595
                size++;
 
596
            }
 
597
        }
 
598
        break;
 
599
    case op_i_jump_on_val_zero_rfI:
 
600
    case op_i_jump_on_val_zero_xfI:
 
601
    case op_i_jump_on_val_zero_yfI:
 
602
        {
 
603
            int n;
 
604
            for (n = ap[-1]; n > 0; n--) {
 
605
                erts_print(to, to_arg, "f(" HEXF ") ", ap[0]);
 
606
                ap++;
 
607
                size++;
 
608
            }
 
609
        }
 
610
        break;
 
611
    case op_i_put_tuple_rI:
 
612
    case op_i_put_tuple_xI:
 
613
    case op_i_put_tuple_yI:
 
614
        {
 
615
            int n = unpacked[-1];
 
616
 
 
617
            while (n > 0) {
 
618
                if (!is_header(ap[0])) {
 
619
                    erts_print(to, to_arg, " %T", (Eterm) ap[0]);
 
620
                } else {
 
621
                    switch ((ap[0] >> 2) & 0x03) {
 
622
                    case R_REG_DEF:
 
623
                        erts_print(to, to_arg, " x(0)");
 
624
                        break;
 
625
                    case X_REG_DEF:
 
626
                        erts_print(to, to_arg, " x(%d)", ap[0] >> 4);
 
627
                        break;
 
628
                    case Y_REG_DEF:
 
629
                        erts_print(to, to_arg, " y(%d)", ap[0] >> 4);
 
630
                        break;
 
631
                    }
 
632
                }
 
633
                ap++, size++, n--;
 
634
            }
 
635
        }
526
636
        break;
527
637
    }
528
638
    erts_print(to, to_arg, "\n");
529
639
 
530
640
    return size;
531
641
}
532
 
 
533
 
static void
534
 
print_big(int to, void *to_arg, Eterm* addr)
535
 
{
536
 
    int i;
537
 
    int k;
538
 
 
539
 
    i = BIG_SIZE(addr);
540
 
    if (BIG_SIGN(addr))
541
 
        erts_print(to, to_arg, "-#integer(%d) = {", i);
542
 
    else
543
 
        erts_print(to, to_arg, "#integer(%d) = {", i);
544
 
    erts_print(to, to_arg, "%d", BIG_DIGIT(addr, 0));
545
 
    for (k = 1; k < i; k++)
546
 
        erts_print(to, to_arg, ",%d", BIG_DIGIT(addr, k));
547
 
    erts_print(to, to_arg, "}");
548
 
}