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

« back to all changes in this revision

Viewing changes to erts/emulator/hipe/hipe_amd64.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
#include <stddef.h>     /* offsetof() */
 
4
#ifdef HAVE_CONFIG_H
 
5
#include "config.h"
 
6
#endif
 
7
#include "global.h"
 
8
#include <sys/mman.h>
 
9
#include "error.h"
 
10
#include "bif.h"
 
11
#include "big.h"        /* term_to_Sint() */
 
12
 
 
13
#include "hipe_arch.h"
 
14
#include "hipe_bif0.h"
 
15
#include "hipe_native_bif.h"    /* nbif_callemu() */
 
16
 
 
17
#undef F_TIMO
 
18
#undef THE_NON_VALUE
 
19
#undef ERL_FUN_SIZE
 
20
#include "hipe_literals.h"
 
21
 
 
22
const Uint sse2_fnegate_mask[2] = {0x8000000000000000,0};
 
23
 
 
24
void hipe_patch_load_fe(Uint64 *address, Uint64 value)
 
25
{
 
26
    /* address points to an imm64 operand */
 
27
    *address = value;
 
28
    hipe_flush_icache_word(address);
 
29
}
 
30
 
 
31
int hipe_patch_insn(void *address, Uint64 value, Eterm type)
 
32
{
 
33
    switch (type) {
 
34
      case am_closure:
 
35
      case am_constant:
 
36
        *(Uint64*)address = value;
 
37
        break;
 
38
      case am_c_const:
 
39
      case am_atom:
 
40
        /* check that value fits in an unsigned imm32 */
 
41
        /* XXX: are we sure it's not really a signed imm32? */
 
42
        if ((Uint)(Uint32)value != value)
 
43
            return -1;
 
44
        *(Uint32*)address = (Uint32)value;
 
45
        break;
 
46
      default:
 
47
        return -1;
 
48
    }
 
49
    hipe_flush_icache_word(address);
 
50
    return 0;
 
51
}
 
52
 
 
53
int hipe_patch_call(void *callAddress, void *destAddress, void *trampoline)
 
54
{
 
55
    Sint rel32;
 
56
 
 
57
    if (trampoline)
 
58
        return -1;
 
59
    rel32 = (Sint)destAddress - (Sint)callAddress - 4;
 
60
    if ((Sint)(Sint32)rel32 != rel32)
 
61
        return -1;
 
62
    *(Uint32*)callAddress = (Uint32)rel32;
 
63
    hipe_flush_icache_word(callAddress);
 
64
    return 0;
 
65
}
 
66
 
 
67
/*
 
68
 * Memory allocator for executable code.
 
69
 *
 
70
 * This is required on AMD64 because some Linux kernels
 
71
 * (including 2.6.10-rc1 and newer www.kernel.org ones)
 
72
 * default to non-executable memory mappings, causing
 
73
 * ordinary malloc() memory to be non-executable.
 
74
 *
 
75
 * Implementing this properly also allows us to ensure that
 
76
 * executable code ends up in the low 2GB of the address space,
 
77
 * as required by HiPE/AMD64's small code model.
 
78
 */
 
79
static unsigned int code_bytes;
 
80
static char *code_next;
 
81
 
 
82
#if 0   /* change to non-zero to get allocation statistics at exit() */
 
83
static unsigned int total_mapped, nr_joins, nr_splits, total_alloc, nr_allocs, nr_large, total_lost;
 
84
static unsigned int atexit_done;
 
85
 
 
86
static void alloc_code_stats(void)
 
87
{
 
88
    printf("\r\nalloc_code_stats: %u bytes mapped, %u joins, %u splits, %u bytes allocated, %u average alloc, %u large allocs, %u bytes lost\r\n",
 
89
           total_mapped, nr_joins, nr_splits, total_alloc, nr_allocs ? total_alloc/nr_allocs : 0, nr_large, total_lost);
 
90
}
 
91
 
 
92
static void atexit_alloc_code_stats(void)
 
93
{
 
94
    if (!atexit_done) {
 
95
        atexit_done = 1;
 
96
        (void)atexit(alloc_code_stats);
 
97
    }
 
98
}
 
99
 
 
100
#define ALLOC_CODE_STATS(X)     do{X;}while(0)
 
101
#else
 
102
#define ALLOC_CODE_STATS(X)     do{}while(0)
 
103
#endif
 
104
 
 
105
/* FreeBSD 6.1 breakage */
 
106
#if !defined(MAP_ANONYMOUS) && defined(MAP_ANON)
 
107
#define MAP_ANONYMOUS MAP_ANON
 
108
#endif
 
109
 
 
110
static void morecore(unsigned int alloc_bytes)
 
111
{
 
112
    unsigned int map_bytes;
 
113
    char *map_hint, *map_start;
 
114
 
 
115
    /* Page-align the amount to allocate. */
 
116
    map_bytes = (alloc_bytes + 4095) & ~4095;
 
117
 
 
118
    /* Round up small allocations. */
 
119
    if (map_bytes < 1024*1024)
 
120
        map_bytes = 1024*1024;
 
121
    else
 
122
        ALLOC_CODE_STATS(++nr_large);
 
123
 
 
124
    /* Create a new memory mapping, ensuring it is executable
 
125
       and in the low 2GB of the address space. Also attempt
 
126
       to make it adjacent to the previous mapping. */
 
127
    map_hint = code_next + code_bytes;
 
128
#if !defined(MAP_32BIT)
 
129
    /* FreeBSD doesn't have MAP_32BIT, and it doesn't respect
 
130
       a plain map_hint (returns high mappings even though the
 
131
       hint refers to a free area), so we have to use both map_hint
 
132
       and MAP_FIXED to get addresses below the 2GB boundary.
 
133
       This is even worse than the Linux/ppc64 case.
 
134
       Similarly, Solaris 10 doesn't have MAP_32BIT,
 
135
       and it doesn't respect a plain map_hint. */
 
136
    if (!map_hint) /* first call */
 
137
        map_hint = (char*)(512*1024*1024); /* 0.5GB */
 
138
#endif
 
139
    if ((unsigned long)map_hint & 4095)
 
140
        abort();
 
141
    map_start = mmap(map_hint, map_bytes,
 
142
                     PROT_EXEC|PROT_READ|PROT_WRITE,
 
143
                     MAP_PRIVATE|MAP_ANONYMOUS
 
144
#if defined(MAP_32BIT)
 
145
                     |MAP_32BIT
 
146
#elif defined(__FreeBSD__) || defined(__sun__)
 
147
                     |MAP_FIXED
 
148
#endif
 
149
                     ,
 
150
                     -1, 0);
 
151
    ALLOC_CODE_STATS(fprintf(stderr, "%s: mmap(%p,%u,...) == %p\r\n", __FUNCTION__, map_hint, map_bytes, map_start));
 
152
#if !defined(MAP_32BIT)
 
153
    if (map_start != MAP_FAILED &&
 
154
        (((unsigned long)map_start + (map_bytes-1)) & ~0x7FFFFFFFUL)) {
 
155
        fprintf(stderr, "mmap with hint %p returned code memory %p\r\n", map_hint, map_start);
 
156
        abort();
 
157
    }
 
158
#endif
 
159
    if (map_start == MAP_FAILED) {
 
160
        perror("mmap");
 
161
        abort();
 
162
    }
 
163
    ALLOC_CODE_STATS(total_mapped += map_bytes);
 
164
 
 
165
    /* Merge adjacent mappings, so the trailing portion of the previous
 
166
       mapping isn't lost. In practice this is quite successful. */
 
167
    if (map_start == map_hint) {
 
168
        ALLOC_CODE_STATS(++nr_joins);
 
169
        code_bytes += map_bytes;
 
170
#if !defined(MAP_32BIT)
 
171
        if (!code_next) /* first call */
 
172
            code_next = map_start;
 
173
#endif
 
174
    } else {
 
175
        ALLOC_CODE_STATS(++nr_splits);
 
176
        ALLOC_CODE_STATS(total_lost += code_bytes);
 
177
        code_next = map_start;
 
178
        code_bytes = map_bytes;
 
179
    }
 
180
 
 
181
    ALLOC_CODE_STATS(atexit_alloc_code_stats());
 
182
}
 
183
 
 
184
static void *alloc_code(unsigned int alloc_bytes)
 
185
{
 
186
    void *res;
 
187
 
 
188
    /* Align function entries. */
 
189
    alloc_bytes = (alloc_bytes + 3) & ~3;
 
190
 
 
191
    if (code_bytes < alloc_bytes)
 
192
        morecore(alloc_bytes);
 
193
    ALLOC_CODE_STATS(++nr_allocs);
 
194
    ALLOC_CODE_STATS(total_alloc += alloc_bytes);
 
195
    res = code_next;
 
196
    code_next += alloc_bytes;
 
197
    code_bytes -= alloc_bytes;
 
198
    return res;
 
199
}
 
200
 
 
201
void *hipe_alloc_code(Uint nrbytes, Eterm callees, Eterm *trampolines, Process *p)
 
202
{
 
203
    if (is_not_nil(callees))
 
204
        return NULL;
 
205
    *trampolines = NIL;
 
206
    return alloc_code(nrbytes);
 
207
}
 
208
 
 
209
/* called from hipe_bif0.c:hipe_bifs_make_native_stub_2()
 
210
   and hipe_bif0.c:hipe_make_stub() */
 
211
void *hipe_make_native_stub(void *beamAddress, unsigned int beamArity)
 
212
{
 
213
    /*
 
214
     * This creates a native code stub with the following contents:
 
215
     *
 
216
     * movq $Address, P_BEAM_IP(%ebp)  %% Actually two movl
 
217
     * movb $Arity, P_ARITY(%ebp)
 
218
     * jmp callemu
 
219
     *
 
220
     * The stub has variable size, depending on whether the P_BEAM_IP
 
221
     * and P_ARITY offsets fit in 8-bit signed displacements or not.
 
222
     * The rel32 offset in the final jmp depends on its actual location,
 
223
     * which also depends on the size of the previous instructions.
 
224
     * Arity is stored with a movb because (a) Bj�rn tells me arities
 
225
     * are <= 255, and (b) a movb is smaller and faster than a movl.
 
226
     */
 
227
    unsigned int codeSize;
 
228
    unsigned char *code, *codep;
 
229
    unsigned int callEmuOffset;
 
230
 
 
231
    codeSize =  /* 23, 26, 29, or 32 bytes */
 
232
      23 +      /* 23 when all offsets are 8-bit */
 
233
      (P_BEAM_IP >= 128 ? 3 : 0) +
 
234
      ((P_BEAM_IP + 4) >= 128 ? 3 : 0) +
 
235
      (P_ARITY >= 128 ? 3 : 0);
 
236
    codep = code = alloc_code(codeSize);
 
237
 
 
238
    /* movl $beamAddress, P_BEAM_IP(%ebp); 3 or 6 bytes, plus 4 */
 
239
    codep[0] = 0xc7;
 
240
#if P_BEAM_IP >= 128
 
241
    codep[1] = 0x85;    /* disp32[EBP] */
 
242
    codep[2] =  P_BEAM_IP        & 0xFF;
 
243
    codep[3] = (P_BEAM_IP >>  8) & 0xFF;
 
244
    codep[4] = (P_BEAM_IP >> 16) & 0xFF;
 
245
    codep[5] = (P_BEAM_IP >> 24) & 0xFF;
 
246
    codep += 6;
 
247
#else
 
248
    codep[1] = 0x45;    /* disp8[EBP] */
 
249
    codep[2] = P_BEAM_IP;
 
250
    codep += 3;
 
251
#endif
 
252
    codep[0] = ((unsigned long)beamAddress      ) & 0xFF;
 
253
    codep[1] = ((unsigned long)beamAddress >>  8) & 0xFF;
 
254
    codep[2] = ((unsigned long)beamAddress >> 16) & 0xFF;
 
255
    codep[3] = ((unsigned long)beamAddress >> 24) & 0xFF;
 
256
    codep += 4;
 
257
 
 
258
    /* movl (shl 32 $beamAddress), P_BEAM_IP+4(%ebp); 3 or 6 bytes, plus 4 */
 
259
    codep[0] = 0xc7;
 
260
#if P_BEAM_IP+4 >= 128
 
261
    codep[1] = 0x85;    /* disp32[EBP] */
 
262
    codep[2] =  (P_BEAM_IP+4)        & 0xFF;
 
263
    codep[3] = ((P_BEAM_IP+4) >>  8) & 0xFF;
 
264
    codep[4] = ((P_BEAM_IP+4) >> 16) & 0xFF;
 
265
    codep[5] = ((P_BEAM_IP+4) >> 24) & 0xFF;
 
266
    codep += 6;
 
267
#else
 
268
    codep[1] = 0x45;    /* disp8[EBP] */
 
269
    codep[2] =  (P_BEAM_IP+4);
 
270
    codep += 3;
 
271
#endif
 
272
    codep[0] = ((unsigned long)beamAddress >> 32) & 0xFF;
 
273
    codep[1] = ((unsigned long)beamAddress >> 40) & 0xFF;
 
274
    codep[2] = ((unsigned long)beamAddress >> 48) & 0xFF;
 
275
    codep[3] = ((unsigned long)beamAddress >> 56) & 0xFF;
 
276
    codep += 4;
 
277
 
 
278
    /* movb $beamArity, P_ARITY(%ebp); 3 or 6 bytes */
 
279
    codep[0] = 0xc6;
 
280
#if P_ARITY >= 128
 
281
    codep[1] = 0x85;    /* disp32[EBP] */
 
282
    codep[2] =  P_ARITY        & 0xFF;
 
283
    codep[3] = (P_ARITY >>  8) & 0xFF;
 
284
    codep[4] = (P_ARITY >> 16) & 0xFF;
 
285
    codep[5] = (P_ARITY >> 24) & 0xFF;
 
286
    codep += 6;
 
287
#else
 
288
    codep[1] = 0x45;    /* disp8[EBP] */
 
289
    codep[2] = P_ARITY;
 
290
    codep += 3;
 
291
#endif
 
292
    codep[0] = beamArity;
 
293
    codep += 1;
 
294
 
 
295
    /* jmp callemu; 5 bytes */
 
296
    callEmuOffset = (unsigned char*)nbif_callemu - (code + codeSize);
 
297
    codep[0] = 0xe9;
 
298
    codep[1] =  callEmuOffset        & 0xFF;
 
299
    codep[2] = (callEmuOffset >>  8) & 0xFF;
 
300
    codep[3] = (callEmuOffset >> 16) & 0xFF;
 
301
    codep[4] = (callEmuOffset >> 24) & 0xFF;
 
302
    codep += 5;
 
303
 
 
304
    ASSERT(codep == code + codeSize);
 
305
 
 
306
    /* I-cache flush? */
 
307
 
 
308
    return code;
 
309
}
 
310
 
 
311
void hipe_arch_print_pcb(struct hipe_process_state *p)
 
312
{
 
313
#define U(n,x) \
 
314
    printf(" % 4d | %s | 0x%0*lx | %*s |\r\n", (int)offsetof(struct hipe_process_state,x), n, 2*(int)sizeof(long), (unsigned long)p->x, 2+2*(int)sizeof(long), "")
 
315
    U("ncsp       ", ncsp);
 
316
    U("narity     ", narity);
 
317
#undef U
 
318
}
 
319
 
 
320
/*
 
321
 * XXX: The following should really be moved to a generic hipe_bifs_64 file.
 
322
 */
 
323
 
 
324
#if 0 /* unused */
 
325
static int term_to_Sint64(Eterm term, Sint64 *sp)
 
326
{
 
327
    return term_to_Sint(term, sp);
 
328
}
 
329
 
 
330
BIF_RETTYPE hipe_bifs_write_s64_2(BIF_ALIST_2)
 
331
{
 
332
    Sint64 *address;
 
333
    Sint64 value;
 
334
 
 
335
    address = term_to_address(BIF_ARG_1);
 
336
    if( !address || !hipe_word64_address_ok(address) )
 
337
        BIF_ERROR(BIF_P, BADARG);
 
338
    if( !term_to_Sint64(BIF_ARG_2, &value) )
 
339
        BIF_ERROR(BIF_P, BADARG);
 
340
    *address = value;
 
341
    BIF_RET(NIL);
 
342
}
 
343
#endif
 
344
 
 
345
BIF_RETTYPE hipe_bifs_write_u64_2(BIF_ALIST_2)
 
346
{
 
347
    Uint64 *address;
 
348
    Uint64 value;
 
349
 
 
350
    address = term_to_address(BIF_ARG_1);
 
351
    if( !address || !hipe_word64_address_ok(address) )
 
352
        BIF_ERROR(BIF_P, BADARG);
 
353
    if( !term_to_Uint(BIF_ARG_2, &value) )
 
354
        BIF_ERROR(BIF_P, BADARG);
 
355
    *address = value;
 
356
    hipe_flush_icache_word(address);
 
357
    BIF_RET(NIL);
 
358
}