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

« back to all changes in this revision

Viewing changes to erts/emulator/hipe/hipe_sparc_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:
4
4
#include "config.h"
5
5
#endif
6
6
#include "global.h"
7
 
#include "beam_catches.h"
8
 
#include "hipe_bif0.h"          /* for hipe_find_sdesc() */
9
7
#include "hipe_stack.h"
10
8
#include "hipe_process.h"
11
9
 
12
 
 
13
 
#define SLOT_TYPE_VAL 0
14
 
#define SLOT_TYPE_RA  1
15
 
#define SLOT_TYPE_ARG 2
16
 
#define SLOT_TYPE_TRAP 3
17
 
 
18
10
extern void nbif_return(void);
 
11
extern void nbif_fail(void);
19
12
extern void nbif_stack_trap_ra(void);
20
13
 
21
14
/*
22
15
 * hipe_print_nstack() is called from hipe_bifs:show_nstack/1.
23
16
 */
24
 
static void print_slot(Process *p, Eterm *sp, unsigned int live, 
25
 
                       unsigned int type, unsigned long exnra)
 
17
static void print_slot(Eterm *sp, unsigned int live)
26
18
{
27
19
    Eterm val = *sp;
28
 
    switch (type) {
29
 
    case SLOT_TYPE_RA: /* RA */
30
 
      if ((unsigned long) val == (unsigned long)nbif_return) {
31
 
        printf(" | 0x%08lx | 0x%08lx | NATIVE RA", (long)sp, val);
32
 
        if( exnra != 0 )
33
 
          printf(", EXNRA 0x%08lx\n\r", exnra);      
34
 
        else
35
 
          printf(" !! MISSING CATCH !!\n\r");
36
 
 
37
 
        printf(" |    MODE    |   SWITCH   |");
38
 
 
39
 
      } else {
40
 
        printf(" | 0x%08lx | 0x%08lx | NATIVE RA", (long)sp, val);
41
 
        if( exnra != 0 )
42
 
          printf(", EXNRA 0x%08lx", exnra);      
43
 
      }
44
 
      break;
45
 
 
46
 
    case SLOT_TYPE_ARG:
47
 
      printf(" | 0x%08lx | 0x%08lx | ARG ", (long)sp, val);
48
 
      ldisplay(val, COUT, 30);
49
 
      break;
50
 
 
51
 
    case SLOT_TYPE_TRAP: /* RA */
52
 
      val = (unsigned long)p->hipe.ngra;
53
 
      if ((unsigned long) val == (unsigned long)nbif_return) {
54
 
        printf(" | 0x%08lx | 0x%08lx | TRAP RA", (long)sp, val);
55
 
        if( exnra != 0 )
56
 
          printf(", EXNRA 0x%08lx\n\r", exnra);      
57
 
        else
58
 
          printf(" !! MISSING CATCH !!\n\r");
59
 
 
60
 
        printf(" |    MODE    |   SWITCH   |");
61
 
 
62
 
      } else {
63
 
        printf(" | 0x%08lx | 0x%08lx | TRAP RA", (long)sp, val);
64
 
        if( exnra != 0 )
65
 
          printf(", EXNRA 0x%08lx", exnra);      
66
 
      }
67
 
      break;
68
 
 
69
 
    case SLOT_TYPE_VAL:
70
 
    default:
71
 
      printf(" | 0x%08lx | 0x%08lx | ", (long)sp, val);
72
 
      if( live )
73
 
        ldisplay(val, COUT, 30);
74
 
      else
75
 
        printf("DEAD");
76
 
      break;
77
 
    }
 
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);
78
25
    printf("\r\n");
79
26
}
80
27
 
84
31
    Eterm *nstart;
85
32
    const struct sdesc *sdesc;
86
33
    unsigned long ra;
 
34
    unsigned long exnra;
87
35
    unsigned int arity;
88
36
    unsigned int lsize;
89
37
    unsigned int i;
90
 
 
91
 
    nsp = p->hipe.nsp-1;
92
 
    nstart = p->hipe.nstack;
93
 
    ra = (unsigned long)p->hipe.nra; /* XXX: Temp solution to store RA here */
94
 
 
 
38
    static const char dashes[2*sizeof(long)+5] = {
 
39
        [0 ... 2*sizeof(long)+3] = '-'
 
40
    };
95
41
 
96
42
    printf(" |      NATIVE  STACK      |\r\n");
97
 
    printf(" |------------|------------|\r\n");
98
 
    printf(" | heap       | 0x%08lx |\r\n", (unsigned long)p->heap);
99
 
#ifndef SHARED_HEAP
100
 
    printf(" | high_water | 0x%08lx |\r\n", (unsigned long)p->high_water);
101
 
#endif
102
 
    printf(" | hend       | 0x%08lx |\r\n", (unsigned long)p->htop);
103
 
#ifndef SHARED_HEAP
104
 
    printf(" | old_heap   | 0x%08lx |\r\n", (unsigned long)p->old_heap);
105
 
    printf(" | old_hend   | 0x%08lx |\r\n", (unsigned long)p->old_hend);
106
 
#endif
107
 
    printf(" | nstack     | 0x%08lx |\r\n", (unsigned long)p->hipe.nstack);
108
 
    printf(" | nsp        | 0x%08lx |\r\n", (unsigned long)p->hipe.nsp);
109
 
    printf(" | nstend     | 0x%08lx |\r\n", (unsigned long)p->hipe.nstend);
110
 
    printf(" | nstblacklim| 0x%08lx |\r\n", (unsigned long)p->hipe.nstblacklim);
111
 
    printf(" | nstgraylim | 0x%08lx |\r\n", (unsigned long)p->hipe.nstgraylim);
112
 
    printf(" |------------|------------|\r\n");
113
 
    printf(" | Address    | Contents   |\r\n");
114
 
    printf(" |------------|------------|\r\n");
115
 
    if(!ra) return;
116
 
    if( ra == (unsigned long)nbif_stack_trap_ra ) {
117
 
      sdesc = hipe_find_sdesc((unsigned long)p->hipe.ngra);
118
 
    } else {
119
 
      sdesc = hipe_find_sdesc(ra);
120
 
    }
121
 
 
122
 
    while( nsp > nstart  ) {
 
43
    printf(" |%s|%s|\r\n", dashes, dashes);
 
44
    printf(" | %*s | 0x%0*lx |\r\n",
 
45
           2+2*(int)sizeof(long), "heap",
 
46
           2*(int)sizeof(long), (unsigned long)p->heap);
 
47
    printf(" | %*s | 0x%0*lx |\r\n",
 
48
           2+2*(int)sizeof(long), "high_water",
 
49
           2*(int)sizeof(long), (unsigned long)p->high_water);
 
50
    printf(" | %*s | 0x%0*lx |\r\n",
 
51
           2+2*(int)sizeof(long), "hend",
 
52
           2*(int)sizeof(long), (unsigned long)p->htop);
 
53
    printf(" | %*s | 0x%0*lx |\r\n",
 
54
           2+2*(int)sizeof(long), "old_heap",
 
55
           2*(int)sizeof(long), (unsigned long)p->old_heap);
 
56
    printf(" | %*s | 0x%0*lx |\r\n",
 
57
           2+2*(int)sizeof(long), "old_hend",
 
58
           2*(int)sizeof(long), (unsigned long)p->old_hend);
 
59
    printf(" | %*s | 0x%0*lx |\r\n",
 
60
           2+2*(int)sizeof(long), "nstack",
 
61
           2*(int)sizeof(long), (unsigned long)p->hipe.nstack);
 
62
    printf(" | %*s | 0x%0*lx |\r\n",
 
63
           2+2*(int)sizeof(long), "nsp",
 
64
           2*(int)sizeof(long), (unsigned long)p->hipe.nsp);
 
65
    printf(" | %*s | 0x%0*lx |\r\n",
 
66
           2+2*(int)sizeof(long), "nstend",
 
67
           2*(int)sizeof(long), (unsigned long)p->hipe.nstend);
 
68
    printf(" | %*s| 0x%0*lx |\r\n",
 
69
           2+2*(int)sizeof(long)+1, "nstblacklim",
 
70
           2*(int)sizeof(long), (unsigned long)p->hipe.nstblacklim);
 
71
    printf(" | %*s | 0x%0*lx |\r\n",
 
72
           2+2*(int)sizeof(long), "nstgraylim",
 
73
           2*(int)sizeof(long), (unsigned long)p->hipe.nstgraylim);
 
74
    printf(" |%s|%s|\r\n", dashes, dashes);
 
75
    printf(" | %*s | %*s |\r\n",
 
76
           2+2*(int)sizeof(long), "Address",
 
77
           2+2*(int)sizeof(long), "Contents");
 
78
    printf(" |%s|%s|\r\n", dashes, dashes);
 
79
 
 
80
    ra = (unsigned long)p->hipe.nra;
 
81
    if (!ra)
 
82
        return;
 
83
    nsp = p->hipe.nsp-1;
 
84
    nstart = p->hipe.nstack;
 
85
 
 
86
    if (ra == (unsigned long)&nbif_stack_trap_ra)
 
87
        ra = (unsigned long)p->hipe.ngra;
 
88
    sdesc = hipe_find_sdesc(ra);
 
89
 
 
90
    while (nsp > nstart) {
123
91
        arity = sdesc_arity(sdesc);
124
92
        lsize = sdesc_fsize(sdesc)- 1;
125
93
        printf(" | LOCALS %3i : ARITY %4i | \r\n", lsize, arity);
126
 
 
127
94
        for(i = 0; i < lsize; i++)
128
 
            print_slot(p, &nsp[-i], sdesc->livebits[i>>5] & (1<<(i&31)),
129
 
                       SLOT_TYPE_VAL,0);
 
95
            print_slot(&nsp[-i], sdesc->livebits[i>>5] & (1<<(i&31)));
130
96
        nsp -= lsize;
131
97
        ra = nsp[0];
132
 
        if( ra == (unsigned long)nbif_stack_trap_ra ) {
 
98
        if (ra == (unsigned long)&nbif_stack_trap_ra)
133
99
            sdesc = hipe_find_sdesc((unsigned long)p->hipe.ngra);
134
 
            print_slot(p, nsp, 1, SLOT_TYPE_TRAP, sdesc_exnra(sdesc));
135
 
        } else {
136
 
          sdesc = hipe_find_sdesc(ra);
137
 
          print_slot(p, nsp, 1, SLOT_TYPE_RA, sdesc_exnra(sdesc));
138
 
        }
 
100
        else
 
101
            sdesc = hipe_find_sdesc(ra);
 
102
        printf(" | 0x%0*lx | 0x%0*lx | ",
 
103
               2*(int)sizeof(long), (unsigned long)&nsp[0],
 
104
               2*(int)sizeof(long), ra);
 
105
        if (ra == (unsigned long)&nbif_stack_trap_ra)
 
106
            printf("STACK TRAP, ORIG RA 0x%lx", (unsigned long)p->hipe.ngra);
 
107
        else if (ra == (unsigned long)&nbif_return)
 
108
            printf("MODE SWITCH");
 
109
        else
 
110
            printf("NATIVE RA");
 
111
        if ((exnra = sdesc_exnra(sdesc)) != 0)
 
112
            printf(", EXNRA 0x%lx", exnra);
 
113
        printf("\r\n");
139
114
        nsp -= 1;
140
115
        for(i = 0; i < arity; ++i)
141
 
            print_slot(p, &nsp[-i], 1, SLOT_TYPE_ARG,0);
 
116
            print_slot(&nsp[-i], 1);
142
117
        nsp -= arity;
143
 
 
144
118
        printf(" |------------|------------|\r\n");
145
 
 
146
119
    }
147
 
    /*   printf(" |------------|------------|\r\n"); */
148
120
}
149
121
 
150
 
 
151
122
#define MINSTACK        256
152
 
#define NSKIPFRAMES     32     
 
123
#define NSKIPFRAMES     32
153
124
 
154
125
void hipe_update_stack_trap(Process *p, const struct sdesc *sdesc)
155
126
{
160
131
 
161
132
    nsp = p->hipe.nsp-1;
162
133
    nstart = p->hipe.nstack;
163
 
 
164
 
    /* ASSERT that passed sdesc == real sdesc */
165
 
    /*    ra = (unsigned long)p->hipe.nra; *//* XXX: Temp solution to store RA here */
166
 
/*    if( ra == (unsigned long)nbif_stack_trap_ra ) 
167
 
      sdesc = hipe_find_sdesc((unsigned long)p->hipe.ngra);
168
 
    else 
169
 
      sdesc = hipe_find_sdesc(ra);
170
 
*/
171
 
 
172
 
    if( (char*)nsp - (char*)nstart < MINSTACK*sizeof(Eterm*) ) {
 
134
    if ((unsigned long)((char*)nsp - (char*)nstart) < MINSTACK*sizeof(Eterm*)) {
173
135
        p->hipe.nstgraylim = NULL;
174
136
        return;
175
137
    }
176
138
    n = NSKIPFRAMES;
177
 
 
178
139
    for(;;) {
179
140
        nsp -= sdesc_fsize(sdesc);
180
 
        if( nsp <= nstart ) {
 
141
        if (nsp <= nstart) {
181
142
            p->hipe.nstgraylim = NULL;
182
143
            return;
183
144
        }
184
145
        ra = nsp[1];
185
 
        if( --n <= 0 )
 
146
        if (--n <= 0)
186
147
            break;
187
148
        nsp -= sdesc_arity(sdesc);
188
 
        /* Can this ra be a stack_trap_ra ? */
189
149
        sdesc = hipe_find_sdesc(ra);
190
150
    }
191
151
    p->hipe.nstgraylim = nsp - sdesc_arity(sdesc);
192
152
    p->hipe.ngra = (void(*)(void))ra;
193
153
    nsp[1] = (unsigned long)nbif_stack_trap_ra;
194
 
 
195
154
}
196
155
 
197
156
/*
221
180
    Eterm *nsp;
222
181
    Eterm *nstart;
223
182
    unsigned long ra;
 
183
    unsigned long exnra;
224
184
    unsigned int arity;
225
 
    extern void nbif_fail(void);
226
 
    unsigned long exnra;
227
185
    const struct sdesc *sdesc;
228
186
 
229
187
    nsp = p->hipe.nsp;
230
188
    nstart = p->hipe.nstack;
231
189
 
232
 
    ra = (unsigned long)p->hipe.nra; /* XXX: Temp solution to store RA here */
 
190
    ra = (unsigned long)p->hipe.nra;
233
191
 
234
 
    while( nsp > nstart ) {
235
 
        if( ra == (unsigned long)nbif_stack_trap_ra )
 
192
    while (nsp > nstart) {
 
193
        if (ra == (unsigned long)&nbif_stack_trap_ra)
236
194
            ra = (unsigned long)p->hipe.ngra;
237
195
        sdesc = hipe_find_sdesc(ra);
238
 
        if( (exnra = sdesc_exnra(sdesc)) != 0 &&
 
196
        if ((exnra = sdesc_exnra(sdesc)) != 0 &&
239
197
            (p->catches >= 0 ||
240
 
             exnra == (unsigned long)nbif_fail) ) {
 
198
             exnra == (unsigned long)&nbif_fail)) {
241
199
            p->hipe.ncallee = (void(*)(void)) exnra;
242
200
            p->hipe.nsp = nsp;
243
201
            /* update the gray/white boundary if we threw past it */
244
 
            if( p->hipe.nstgraylim && nsp <= p->hipe.nstgraylim )
 
202
            if (p->hipe.nstgraylim && nsp <= p->hipe.nstgraylim)
245
203
              hipe_update_stack_trap(p, sdesc);
246
 
 
247
204
            return;
248
205
        }
249
206
        nsp -= sdesc_fsize(sdesc);
250
 
        ra = nsp[0];            
251
 
 
 
207
        ra = nsp[0];
252
208
        arity = sdesc_arity(sdesc);
253
209
        nsp -= arity;           /* skip actuals on stack */
254
210
    }
255
211
    fprintf(stderr, "%s: no native CATCH found!\r\n", __FUNCTION__);
256
 
    hipe_print_nstack(p);
257
212
    abort();
258
213
}
259
 
 
260