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

« back to all changes in this revision

Viewing changes to erts/emulator/hipe/hipe_x86_stack.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:
5
5
#endif
6
6
#include "global.h"
7
7
#include "bif.h"
8
 
#include "hipe_bif0.h"          /* for hipe_find_sdesc() */
9
8
#include "hipe_stack.h"
10
 
#include "hipe_x86_asm.h"       /* for X86_NR_ARG_REGS */
 
9
#ifdef __x86_64__
 
10
#include "hipe_amd64_asm.h"     /* for NR_ARG_REGS */
 
11
#else
 
12
#include "hipe_x86_asm.h"       /* for NR_ARG_REGS */
 
13
#endif
11
14
 
12
15
extern void nbif_fail(void);
13
16
extern void nbif_stack_trap_ra(void);
14
17
 
15
18
/*
16
 
 * These are C-wrappers for non-HiPE BIFs that may trigger a native
17
 
 * stack walk with p->hipe.narity != 0.
18
 
 */
19
 
extern Eterm check_process_code_2(Process*, Eterm, Eterm);
20
 
extern Eterm garbage_collect_1(Process*, Eterm);
21
 
 
22
 
Eterm hipe_x86_check_process_code_2(BIF_ALIST_2)
23
 
{
24
 
    Eterm ret;
25
 
 
26
 
    BIF_P->hipe.narity = 2;
27
 
    ret = check_process_code_2(BIF_P, BIF_ARG_1, BIF_ARG_2);
28
 
    BIF_P->hipe.narity = 0;
29
 
    return ret;
30
 
}
31
 
 
32
 
Eterm hipe_x86_garbage_collect_1(BIF_ALIST_1)
33
 
{
34
 
    Eterm ret;
35
 
 
36
 
    BIF_P->hipe.narity = 1;
37
 
    ret = garbage_collect_1(BIF_P, BIF_ARG_1);
38
 
    BIF_P->hipe.narity = 0;
39
 
    return ret;
40
 
}
41
 
 
42
 
/*
43
19
 * hipe_print_nstack() is called from hipe_bifs:show_nstack/1.
44
20
 */
45
21
static void print_slot(Eterm *sp, unsigned int live)
46
22
{
47
23
    Eterm val = *sp;
48
 
    printf(" | 0x%08lx | 0x%08lx | ", (long)sp, val);
 
24
    printf(" | 0x%0*lx | 0x%0*lx | ",
 
25
           2*(int)sizeof(long), (unsigned long)sp,
 
26
           2*(int)sizeof(long), val);
49
27
    if( live )
50
 
        ldisplay(val, COUT, 30);
 
28
        erts_printf("%.30T", val);
51
29
    printf("\r\n");
52
30
}
53
31
 
64
42
    unsigned int sdesc_size;
65
43
    unsigned int i;
66
44
    unsigned int nstkarity;
 
45
    static const char dashes[2*sizeof(long)+5] = {
 
46
        [0 ... 2*sizeof(long)+3] = '-'
 
47
    };
67
48
 
68
49
    nsp = p->hipe.nsp;
69
50
    nsp_end = p->hipe.nstend;
70
51
 
71
 
    nstkarity = p->hipe.narity - X86_NR_ARG_REGS;
 
52
    nstkarity = p->hipe.narity - NR_ARG_REGS;
72
53
    if( (int)nstkarity < 0 )
73
54
        nstkarity = 0;
74
55
    sdesc0.summary = nstkarity;
76
57
    sdesc = &sdesc0;
77
58
 
78
59
    printf(" |      NATIVE  STACK      |\r\n");
79
 
    printf(" |------------|------------|\r\n");
80
 
    printf(" | heap       | 0x%08lx |\r\n", (unsigned long)p->heap);
81
 
#ifndef SHARED_HEAP
82
 
    printf(" | high_water | 0x%08lx |\r\n", (unsigned long)p->high_water);
83
 
#endif
84
 
    printf(" | hend       | 0x%08lx |\r\n", (unsigned long)p->htop);
85
 
#ifndef SHARED_HEAP
86
 
    printf(" | old_heap   | 0x%08lx |\r\n", (unsigned long)p->old_heap);
87
 
    printf(" | old_hend   | 0x%08lx |\r\n", (unsigned long)p->old_hend);
88
 
#endif
89
 
    printf(" | nsp        | 0x%08lx |\r\n", (unsigned long)p->hipe.nsp);
90
 
    printf(" | nstend     | 0x%08lx |\r\n", (unsigned long)p->hipe.nstend);
91
 
    printf(" | nstblacklim| 0x%08lx |\r\n", (unsigned long)p->hipe.nstblacklim);
92
 
    printf(" | nstgraylim | 0x%08lx |\r\n", (unsigned long)p->hipe.nstgraylim);
93
 
    printf(" |------------|------------|\r\n");
94
 
    printf(" | Address    | Contents   |\r\n");
 
60
    printf(" |%s|%s|\r\n", dashes, dashes);
 
61
    printf(" | %*s | 0x%0*lx |\r\n",
 
62
           2+2*(int)sizeof(long), "heap",
 
63
           2*(int)sizeof(long), (unsigned long)p->heap);
 
64
    printf(" | %*s | 0x%0*lx |\r\n",
 
65
           2+2*(int)sizeof(long), "high_water",
 
66
           2*(int)sizeof(long), (unsigned long)p->high_water);
 
67
    printf(" | %*s | 0x%0*lx |\r\n",
 
68
           2+2*(int)sizeof(long), "hend",
 
69
           2*(int)sizeof(long), (unsigned long)p->htop);
 
70
    printf(" | %*s | 0x%0*lx |\r\n",
 
71
           2+2*(int)sizeof(long), "old_heap",
 
72
           2*(int)sizeof(long), (unsigned long)p->old_heap);
 
73
    printf(" | %*s | 0x%0*lx |\r\n",
 
74
           2+2*(int)sizeof(long), "old_hend",
 
75
           2*(int)sizeof(long), (unsigned long)p->old_hend);
 
76
    printf(" | %*s | 0x%0*lx |\r\n",
 
77
           2+2*(int)sizeof(long), "nsp",
 
78
           2*(int)sizeof(long), (unsigned long)p->hipe.nsp);
 
79
    printf(" | %*s | 0x%0*lx |\r\n",
 
80
           2+2*(int)sizeof(long), "nstend",
 
81
           2*(int)sizeof(long), (unsigned long)p->hipe.nstend);
 
82
    printf(" | %*s| 0x%0*lx |\r\n",
 
83
           2+2*(int)sizeof(long)+1, "nstblacklim",
 
84
           2*(int)sizeof(long), (unsigned long)p->hipe.nstblacklim);
 
85
    printf(" | %*s | 0x%0*lx |\r\n",
 
86
           2+2*(int)sizeof(long), "nstgraylim",
 
87
           2*(int)sizeof(long), (unsigned long)p->hipe.nstgraylim);
 
88
    printf(" | %*s | 0x%0*x |\r\n",
 
89
           2+2*(int)sizeof(long), "narity",
 
90
           2*(int)sizeof(long), p->hipe.narity);
 
91
    printf(" |%s|%s|\r\n", dashes, dashes);
 
92
    printf(" | %*s | %*s |\r\n",
 
93
           2+2*(int)sizeof(long), "Address",
 
94
           2+2*(int)sizeof(long), "Contents");
95
95
 
96
96
    for(;;) {
97
 
        printf(" |------------|------------|\r\n");
 
97
        printf(" |%s|%s|\r\n", dashes, dashes);
98
98
        if( nsp >= nsp_end ) {
99
99
            if( nsp == nsp_end )
100
100
                return;
111
111
        mask = sdesc->livebits[0];
112
112
        for(;;) {
113
113
            if( i == sdesc_fsize(sdesc) ) {
114
 
                printf(" | 0x%08lx | 0x%08lx | ", (long)&nsp[i], ra);
 
114
                printf(" | 0x%0*lx | 0x%0*lx | ",
 
115
                       2*(int)sizeof(long), (unsigned long)&nsp[i],
 
116
                       2*(int)sizeof(long), ra);
115
117
                if( ra == (unsigned long)nbif_stack_trap_ra )
116
 
                    printf("STACK TRAP, ORIG RA 0x%08lx", (unsigned long)p->hipe.ngra);
 
118
                    printf("STACK TRAP, ORIG RA 0x%lx", (unsigned long)p->hipe.ngra);
117
119
                else
118
120
                    printf("NATIVE RA");
119
121
                if( (exnra = sdesc_exnra(sdesc1)) != 0 )
120
 
                    printf(", EXNRA 0x%08lx", exnra);
 
122
                    printf(", EXNRA 0x%lx", exnra);
121
123
                printf("\r\n");
122
124
            } else {
123
125
                print_slot(&nsp[i], (mask & 1));
147
149
 
148
150
    nsp = p->hipe.nsp;
149
151
    nsp_end = p->hipe.nstend;
150
 
    if( (unsigned)((char*)nsp_end - (char*)nsp) < MINSTACK*sizeof(Eterm*) ) {
 
152
    if( (unsigned long)((char*)nsp_end - (char*)nsp) < MINSTACK*sizeof(Eterm*) ) {
151
153
        p->hipe.nstgraylim = NULL;
152
154
        return;
153
155
    }
205
207
 
206
208
    nsp = p->hipe.nsp;
207
209
    nsp_end = p->hipe.nstend;
208
 
    nstkarity = p->hipe.narity - X86_NR_ARG_REGS;
 
210
    nstkarity = p->hipe.narity - NR_ARG_REGS;
209
211
    if( (int)nstkarity < 0 )
210
212
        nstkarity = 0;
211
213
    arity = nstkarity;