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

« back to all changes in this revision

Viewing changes to erts/emulator/hipe/hipe_arm_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:
 
1
/* $Id$
 
2
 */
 
3
#ifdef HAVE_CONFIG_H
 
4
#include "config.h"
 
5
#endif
 
6
#include "global.h"
 
7
#include "bif.h"
 
8
#include "hipe_stack.h"
 
9
#include "hipe_arm_asm.h"       /* for NR_ARG_REGS */
 
10
 
 
11
AEXTERN(void,nbif_fail,(void));
 
12
AEXTERN(void,nbif_stack_trap_ra,(void));
 
13
 
 
14
/*
 
15
 * hipe_print_nstack() is called from hipe_bifs:show_nstack/1.
 
16
 */
 
17
static void print_slot(Eterm *sp, unsigned int live)
 
18
{
 
19
    Eterm val = *sp;
 
20
    printf(" | 0x%0*lx | 0x%0*lx | ",
 
21
           2*(int)sizeof(long), (unsigned long)sp,
 
22
           2*(int)sizeof(long), val);
 
23
    if (live)
 
24
        erts_printf("%.30T", val);
 
25
    printf("\r\n");
 
26
}
 
27
 
 
28
void hipe_print_nstack(Process *p)
 
29
{
 
30
    Eterm *nsp;
 
31
    Eterm *nsp_end;
 
32
    const struct sdesc *sdesc1;
 
33
    const struct sdesc *sdesc;
 
34
    unsigned long ra;
 
35
    unsigned long exnra;
 
36
    unsigned int mask;
 
37
    unsigned int sdesc_size;
 
38
    unsigned int i;
 
39
    unsigned int nstkarity;
 
40
    static const char dashes[2*sizeof(long)+5] = {
 
41
        [0 ... 2*sizeof(long)+3] = '-'
 
42
    };
 
43
 
 
44
    printf(" |      NATIVE  STACK      |\r\n");
 
45
    printf(" |%s|%s|\r\n", dashes, dashes);
 
46
    printf(" | %*s | 0x%0*lx |\r\n",
 
47
           2+2*(int)sizeof(long), "heap",
 
48
           2*(int)sizeof(long), (unsigned long)p->heap);
 
49
    printf(" | %*s | 0x%0*lx |\r\n",
 
50
           2+2*(int)sizeof(long), "high_water",
 
51
           2*(int)sizeof(long), (unsigned long)p->high_water);
 
52
    printf(" | %*s | 0x%0*lx |\r\n",
 
53
           2+2*(int)sizeof(long), "hend",
 
54
           2*(int)sizeof(long), (unsigned long)p->htop);
 
55
    printf(" | %*s | 0x%0*lx |\r\n",
 
56
           2+2*(int)sizeof(long), "old_heap",
 
57
           2*(int)sizeof(long), (unsigned long)p->old_heap);
 
58
    printf(" | %*s | 0x%0*lx |\r\n",
 
59
           2+2*(int)sizeof(long), "old_hend",
 
60
           2*(int)sizeof(long), (unsigned long)p->old_hend);
 
61
    printf(" | %*s | 0x%0*lx |\r\n",
 
62
           2+2*(int)sizeof(long), "nsp",
 
63
           2*(int)sizeof(long), (unsigned long)p->hipe.nsp);
 
64
    printf(" | %*s | 0x%0*lx |\r\n",
 
65
           2+2*(int)sizeof(long), "nstend",
 
66
           2*(int)sizeof(long), (unsigned long)p->hipe.nstend);
 
67
    printf(" | %*s| 0x%0*lx |\r\n",
 
68
           2+2*(int)sizeof(long)+1, "nstblacklim",
 
69
           2*(int)sizeof(long), (unsigned long)p->hipe.nstblacklim);
 
70
    printf(" | %*s | 0x%0*lx |\r\n",
 
71
           2+2*(int)sizeof(long), "nstgraylim",
 
72
           2*(int)sizeof(long), (unsigned long)p->hipe.nstgraylim);
 
73
    printf(" | %*s | 0x%0*lx |\r\n",
 
74
           2+2*(int)sizeof(long), "nra",
 
75
           2*(int)sizeof(long), (unsigned long)p->hipe.nra);
 
76
    printf(" | %*s | 0x%0*x |\r\n",
 
77
           2+2*(int)sizeof(long), "narity",
 
78
           2*(int)sizeof(long), p->hipe.narity);
 
79
    printf(" |%s|%s|\r\n", dashes, dashes);
 
80
    printf(" | %*s | %*s |\r\n",
 
81
           2+2*(int)sizeof(long), "Address",
 
82
           2+2*(int)sizeof(long), "Contents");
 
83
 
 
84
    ra = (unsigned long)p->hipe.nra;
 
85
    if (!ra)
 
86
        return;
 
87
    nsp = p->hipe.nsp;
 
88
    nsp_end = p->hipe.nstend - 1;
 
89
 
 
90
    nstkarity = p->hipe.narity - NR_ARG_REGS;
 
91
    if ((int)nstkarity < 0)
 
92
        nstkarity = 0;
 
93
 
 
94
    /* First RA not on stack. Dump current args first. */
 
95
    printf(" |%s|%s|\r\n", dashes, dashes);
 
96
    for(i = 0; i < nstkarity; ++i)
 
97
        print_slot(&nsp[i], 1);
 
98
    nsp += nstkarity;
 
99
 
 
100
    if (ra == (unsigned long)&nbif_stack_trap_ra)
 
101
        ra = (unsigned long)p->hipe.ngra;
 
102
    sdesc = hipe_find_sdesc(ra);
 
103
 
 
104
    for(;;) {   /* INV: nsp at bottom of frame described by sdesc */
 
105
        printf(" |%s|%s|\r\n", dashes, dashes);
 
106
        if (nsp >= nsp_end) {
 
107
            if (nsp == nsp_end)
 
108
                return;
 
109
            fprintf(stderr, "%s: passed end of stack\r\n", __FUNCTION__);
 
110
            break;
 
111
        }
 
112
        ra = nsp[sdesc_fsize(sdesc)];
 
113
        if (ra == (unsigned long)&nbif_stack_trap_ra)
 
114
            sdesc1 = hipe_find_sdesc((unsigned long)p->hipe.ngra);
 
115
        else
 
116
            sdesc1 = hipe_find_sdesc(ra);
 
117
        sdesc_size = sdesc_fsize(sdesc) + 1 + sdesc_arity(sdesc);
 
118
        i = 0;
 
119
        mask = sdesc->livebits[0];
 
120
        for(;;) {
 
121
            if (i == sdesc_fsize(sdesc)) {
 
122
                printf(" | 0x%0*lx | 0x%0*lx | ",
 
123
                       2*(int)sizeof(long), (unsigned long)&nsp[i],
 
124
                       2*(int)sizeof(long), ra);
 
125
                if (ra == (unsigned long)&nbif_stack_trap_ra)
 
126
                    printf("STACK TRAP, ORIG RA 0x%lx", (unsigned long)p->hipe.ngra);
 
127
                else
 
128
                    printf("NATIVE RA");
 
129
                if ((exnra = sdesc_exnra(sdesc1)) != 0)
 
130
                    printf(", EXNRA 0x%lx", exnra);
 
131
                printf("\r\n");
 
132
            } else {
 
133
                print_slot(&nsp[i], (mask & 1));
 
134
            }
 
135
            if (++i >= sdesc_size)
 
136
                break;
 
137
            if (i & 31)
 
138
                mask >>= 1;
 
139
            else
 
140
                mask = sdesc->livebits[i >> 5];
 
141
        }
 
142
        nsp += sdesc_size;
 
143
        sdesc = sdesc1;
 
144
    }
 
145
    abort();
 
146
}
 
147
 
 
148
/* XXX: x86's values, not yet tuned for anyone else */
 
149
#define MINSTACK        128
 
150
#define NSKIPFRAMES     4
 
151
 
 
152
void hipe_update_stack_trap(Process *p, const struct sdesc *sdesc)
 
153
{
 
154
    Eterm *nsp;
 
155
    Eterm *nsp_end;
 
156
    unsigned long ra;
 
157
    int n;
 
158
 
 
159
    nsp = p->hipe.nsp;
 
160
    nsp_end = p->hipe.nstend - 1;
 
161
    if ((unsigned long)((char*)nsp_end - (char*)nsp) < MINSTACK*sizeof(Eterm*)) {
 
162
        p->hipe.nstgraylim = NULL;
 
163
        return;
 
164
    }
 
165
    n = NSKIPFRAMES;
 
166
    for(;;) {
 
167
        nsp += sdesc_fsize(sdesc);
 
168
        if (nsp >= nsp_end) {
 
169
            p->hipe.nstgraylim = NULL;
 
170
            return;
 
171
        }
 
172
        ra = nsp[0];
 
173
        if (--n <= 0)
 
174
            break;
 
175
        nsp += 1 + sdesc_arity(sdesc);
 
176
        sdesc = hipe_find_sdesc(ra);
 
177
    }
 
178
    p->hipe.nstgraylim = nsp + 1 + sdesc_arity(sdesc);
 
179
    p->hipe.ngra = (void(*)(void))ra;
 
180
    nsp[0] = (unsigned long)&nbif_stack_trap_ra;
 
181
}
 
182
 
 
183
/*
 
184
 * hipe_handle_stack_trap() is called when the mutator returns to
 
185
 * nbif_stack_trap_ra, which marks the gray/white stack boundary frame.
 
186
 * The gray/white boundary is moved back one or more frames.
 
187
 *
 
188
 * The function head below is "interesting".
 
189
 */
 
190
void (*hipe_handle_stack_trap(Process *p))(void)
 
191
{
 
192
    void (*ngra)(void) = p->hipe.ngra;
 
193
    const struct sdesc *sdesc = hipe_find_sdesc((unsigned long)ngra);
 
194
    hipe_update_stack_trap(p, sdesc);
 
195
    return ngra;
 
196
}
 
197
 
 
198
/*
 
199
 * hipe_find_handler() is called from hipe_handle_exception() to locate
 
200
 * the current exception handler's PC and SP.
 
201
 * The native stack MUST contain a stack frame as it appears on
 
202
 * entry to a function (actuals, caller's frame, caller's return address).
 
203
 * p->hipe.narity MUST contain the arity (number of actuals).
 
204
 * On exit, p->hipe.ncallee is set to the handler's PC and p->hipe.nsp
 
205
 * is set to its SP (low address of its stack frame).
 
206
 */
 
207
void hipe_find_handler(Process *p)
 
208
{
 
209
    Eterm *nsp;
 
210
    Eterm *nsp_end;
 
211
    unsigned long ra;
 
212
    unsigned long exnra;
 
213
    unsigned int arity;
 
214
    const struct sdesc *sdesc;
 
215
 
 
216
    nsp = p->hipe.nsp;
 
217
    nsp_end = p->hipe.nstend;
 
218
    arity = p->hipe.narity - NR_ARG_REGS;
 
219
    if ((int)arity < 0)
 
220
        arity = 0;
 
221
 
 
222
    ra = (unsigned long)p->hipe.nra;
 
223
 
 
224
    while (nsp < nsp_end) {
 
225
        nsp += arity;           /* skip actuals */
 
226
        if (ra == (unsigned long)&nbif_stack_trap_ra)
 
227
            ra = (unsigned long)p->hipe.ngra;
 
228
        sdesc = hipe_find_sdesc(ra);
 
229
        if ((exnra = sdesc_exnra(sdesc)) != 0 &&
 
230
            (p->catches >= 0 ||
 
231
             exnra == (unsigned long)&nbif_fail)) {
 
232
            p->hipe.ncallee = (void(*)(void)) exnra;
 
233
            p->hipe.nsp = nsp;
 
234
            p->hipe.narity = 0;
 
235
            /* update the gray/white boundary if we threw past it */
 
236
            if (p->hipe.nstgraylim && nsp >= p->hipe.nstgraylim)
 
237
                hipe_update_stack_trap(p, sdesc);
 
238
            return;
 
239
        }
 
240
        nsp += sdesc_fsize(sdesc);      /* skip locals */
 
241
        arity = sdesc_arity(sdesc);
 
242
        ra = *nsp++;                    /* fetch & skip saved ra */
 
243
    }
 
244
    fprintf(stderr, "%s: no native CATCH found!\r\n", __FUNCTION__);
 
245
    abort();
 
246
}