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

« back to all changes in this revision

Viewing changes to erts/emulator/hipe/hipe_bif0.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:
18
18
#include "erl_db.h"
19
19
#include "hash.h"
20
20
#include "erl_bits.h"
 
21
#include "erl_binary.h"
21
22
#ifdef HIPE
 
23
#include <stddef.h>     /* offsetof() */
 
24
#include "hipe_arch.h"
 
25
#include "hipe_stack.h"
22
26
#include "hipe_mode_switch.h"
23
27
#include "hipe_native_bif.h"
24
28
#include "hipe_bif0.h"
32
36
 
33
37
#define BeamOpCode(Op)  ((Uint)BeamOp(Op))
34
38
 
35
 
/* check if an address is unsafe for a 32-bit load or store */
36
 
#if defined(__i386__)
37
 
#define is_unsafe_32(address)   0
38
 
#else
39
 
#define is_unsafe_32(address)   ((unsigned long)(address) & 3)
40
 
#endif
41
 
 
42
 
static int term_to_Sint(Eterm term, Sint *sp)
43
 
{
44
 
    if( is_small(term) ) {
45
 
        *sp = signed_val(term);
46
 
        return 1;
47
 
    } else if (is_big(term) && big_fits_in_sint32(term) ) {
48
 
        *sp = big_to_sint32(term);
49
 
        return 1;
50
 
    } else
51
 
        return 0;
52
 
}
53
 
 
54
 
static Eterm Sint32_to_term(Sint32 x, Process *p)
55
 
{
56
 
    if( MY_IS_SSMALL(x) ) {
57
 
        return make_small(x);
58
 
    } else {
59
 
        Eterm *hp = HAlloc(p, BIG_NEED_SIZE(2));
60
 
        return small_to_big(x, hp);
61
 
    }
 
39
int term_to_Sint32(Eterm term, Sint *sp)
 
40
{
 
41
    Sint val;
 
42
 
 
43
    if( !term_to_Sint(term, &val) )
 
44
        return 0;
 
45
    if( (Sint)(Sint32)val != val )
 
46
        return 0;
 
47
    *sp = val;
 
48
    return 1;
62
49
}
63
50
 
64
51
static Eterm Uint_to_term(Uint x, Process *p)
71
58
    }
72
59
}
73
60
 
74
 
static void *term_to_address(Eterm arg)
 
61
void *term_to_address(Eterm arg)
75
62
{
76
63
    Uint u;
77
64
    return term_to_Uint(arg, &u) ? (void*)u : NULL;
78
65
}
79
66
 
80
 
static Eterm address_to_term(void *address, Process *p)
 
67
Eterm address_to_term(const void *address, Process *p)
81
68
{
82
69
    return Uint_to_term((Uint)address, p);
83
70
}
85
72
/*
86
73
 * BIFs for reading and writing memory. Used internally by HiPE.
87
74
 */
 
75
#if 0 /* XXX: unused */
88
76
BIF_RETTYPE hipe_bifs_read_u8_1(BIF_ALIST_1)
89
77
{
90
78
    unsigned char *address = term_to_address(BIF_ARG_1);
92
80
        BIF_ERROR(BIF_P, BADARG);
93
81
    BIF_RET(make_small(*address));
94
82
}
95
 
 
96
 
BIF_RETTYPE hipe_bifs_read_s32_1(BIF_ALIST_1)
97
 
{
98
 
    Sint32 *address = term_to_address(BIF_ARG_1);
99
 
    if( !address || is_unsafe_32(address) )
100
 
        BIF_ERROR(BIF_P, BADARG);
101
 
    BIF_RET(Sint32_to_term(*address, BIF_P));
102
 
}
103
 
 
 
83
#endif
 
84
 
 
85
#if 0 /* XXX: unused */
104
86
BIF_RETTYPE hipe_bifs_read_u32_1(BIF_ALIST_1)
105
87
{
106
 
    Uint *address = term_to_address(BIF_ARG_1);
107
 
    if( !address || is_unsafe_32(address) )
 
88
    Uint32 *address = term_to_address(BIF_ARG_1);
 
89
    if( !address || !hipe_word32_address_ok(address) )
108
90
        BIF_ERROR(BIF_P, BADARG);
109
91
    BIF_RET(Uint_to_term(*address, BIF_P));
110
92
}
 
93
#endif
111
94
 
112
95
BIF_RETTYPE hipe_bifs_write_u8_2(BIF_ALIST_2)
113
96
{
120
103
    BIF_RET(NIL);
121
104
}
122
105
 
 
106
#if 0 /* XXX: unused */
123
107
BIF_RETTYPE hipe_bifs_write_s32_2(BIF_ALIST_2)
124
108
{
125
109
    Sint32 *address;
126
110
    Sint value;
127
111
 
128
112
    address = term_to_address(BIF_ARG_1);
129
 
    if( !address || is_unsafe_32(address) )
 
113
    if( !address || !hipe_word32_address_ok(address) )
130
114
        BIF_ERROR(BIF_P, BADARG);
131
 
    if( !term_to_Sint(BIF_ARG_2, &value) )
 
115
    if( !term_to_Sint32(BIF_ARG_2, &value) )
132
116
        BIF_ERROR(BIF_P, BADARG);
133
117
    *address = value;
134
118
    BIF_RET(NIL);
135
119
}
 
120
#endif
136
121
 
137
122
BIF_RETTYPE hipe_bifs_write_u32_2(BIF_ALIST_2)
138
123
{
139
 
    Uint *address;
 
124
    Uint32 *address;
140
125
    Uint value;
141
126
 
142
127
    address = term_to_address(BIF_ARG_1);
143
 
    if( !address || is_unsafe_32(address) )
 
128
    if( !address || !hipe_word32_address_ok(address) )
144
129
        BIF_ERROR(BIF_P, BADARG);
145
130
    if( !term_to_Uint(BIF_ARG_2, &value) )
146
131
        BIF_ERROR(BIF_P, BADARG);
 
132
    if( (Uint)(Uint32)value != value )
 
133
        BIF_ERROR(BIF_P, BADARG);
147
134
    *address = value;
148
 
#if defined(__sparc__)
149
 
    asm volatile("flush %0"
150
 
                 : /* no outputs */
151
 
                 : "r"(address)
152
 
                 : "memory");
153
 
#endif
154
 
 
 
135
    hipe_flush_icache_word(address);
 
136
    BIF_RET(NIL);
 
137
}
 
138
 
 
139
/*
 
140
 * BIFs for mutable bytearrays.
 
141
 */
 
142
BIF_RETTYPE hipe_bifs_bytearray_2(BIF_ALIST_2)
 
143
{
 
144
    Sint nelts;
 
145
    Eterm bin;
 
146
 
 
147
    if (is_not_small(BIF_ARG_1) ||
 
148
        (nelts = signed_val(BIF_ARG_1)) < 0 ||
 
149
        !is_byte(BIF_ARG_2))
 
150
        BIF_ERROR(BIF_P, BADARG);
 
151
    bin = new_binary(BIF_P, NULL, nelts);
 
152
    memset(binary_bytes(bin), unsigned_val(BIF_ARG_2), nelts);
 
153
    BIF_RET(bin);
 
154
}
 
155
 
 
156
static inline unsigned char *bytearray_lvalue(Eterm bin, Eterm idx)
 
157
{
 
158
    Sint i;
 
159
    unsigned char *bytes;
 
160
    Uint bitoffs;
 
161
    Uint bitsize;
 
162
 
 
163
    if (is_not_binary(bin) ||
 
164
        is_not_small(idx) ||
 
165
        (i = unsigned_val(idx)) >= binary_size(bin))
 
166
        return NULL;
 
167
    ERTS_GET_BINARY_BYTES(bin, bytes, bitoffs, bitsize);
 
168
    ASSERT(bitoffs == 0);
 
169
    ASSERT(bitsize == 0);
 
170
    return bytes + i;
 
171
}
 
172
 
 
173
BIF_RETTYPE hipe_bifs_bytearray_sub_2(BIF_ALIST_2)
 
174
{
 
175
    unsigned char *bytep;
 
176
 
 
177
    bytep = bytearray_lvalue(BIF_ARG_1, BIF_ARG_2);
 
178
    if (!bytep)
 
179
        BIF_ERROR(BIF_P, BADARG);
 
180
    BIF_RET(make_small(*bytep));
 
181
}
 
182
 
 
183
BIF_RETTYPE hipe_bifs_bytearray_update_3(BIF_ALIST_3)
 
184
{
 
185
    unsigned char *bytep;
 
186
 
 
187
    bytep = bytearray_lvalue(BIF_ARG_1, BIF_ARG_2);
 
188
    if (!bytep || !is_byte(BIF_ARG_3))
 
189
        BIF_ERROR(BIF_P, BADARG);
 
190
    *bytep = unsigned_val(BIF_ARG_3);
155
191
    BIF_RET(NIL);
156
192
}
157
193
 
177
213
BIF_RETTYPE hipe_bifs_array_2(BIF_ALIST_2)
178
214
{
179
215
    Eterm *hp;
180
 
    int nelts, i;
 
216
    Sint nelts, i;
181
217
 
182
218
    if( is_not_small(BIF_ARG_1) ||
183
219
        (nelts = signed_val(BIF_ARG_1)) < 0 ||
204
240
 
205
241
BIF_RETTYPE hipe_bifs_array_sub_2(BIF_ALIST_2)
206
242
{
207
 
    unsigned i;
 
243
    Uint i;
208
244
 
209
245
    if( is_not_small(BIF_ARG_2) ||
210
246
        is_not_array(BIF_ARG_1) ||
215
251
 
216
252
BIF_RETTYPE hipe_bifs_array_update_3(BIF_ALIST_3)
217
253
{
218
 
    unsigned i;
 
254
    Uint i;
219
255
 
220
256
    if( is_not_immed(BIF_ARG_3) ||
221
257
        is_not_small(BIF_ARG_2) ||
257
293
}
258
294
 
259
295
/*
260
 
 * Allocate memory for code.
261
 
 */
262
 
BIF_RETTYPE hipe_bifs_alloc_code_1(BIF_ALIST_1)
263
 
{
264
 
    Eterm *block;
265
 
 
266
 
    if( is_not_small(BIF_ARG_1) )
267
 
        BIF_ERROR(BIF_P, BADARG);
268
 
    block = (Eterm*) erts_alloc(ERTS_ALC_T_HIPE, unsigned_val(BIF_ARG_1));
 
296
 * Allocate memory and copy machine code to it.
 
297
 */
 
298
BIF_RETTYPE hipe_bifs_enter_code_2(BIF_ALIST_2)
 
299
{
 
300
    Uint nrbytes;
 
301
    void *bytes;
 
302
    void *address;
 
303
    Uint bitoffs;
 
304
    Uint bitsize;
 
305
    Eterm trampolines;
 
306
    Eterm *hp;
 
307
 
 
308
    if( is_not_binary(BIF_ARG_1) )
 
309
        BIF_ERROR(BIF_P, BADARG);
 
310
    nrbytes = binary_size(BIF_ARG_1);
 
311
    ERTS_GET_BINARY_BYTES(BIF_ARG_1, bytes, bitoffs, bitsize);
 
312
    ASSERT(bitoffs == 0);
 
313
    ASSERT(bitsize == 0);
 
314
    trampolines = NIL;
 
315
#ifdef HIPE_ALLOC_CODE
 
316
    address = HIPE_ALLOC_CODE(nrbytes, BIF_ARG_2, &trampolines, BIF_P);
 
317
    if( !address )
 
318
        BIF_ERROR(BIF_P, BADARG);
 
319
#else
 
320
    if( is_not_nil(BIF_ARG_2) )
 
321
        BIF_ERROR(BIF_P, BADARG);
 
322
    address = erts_alloc(ERTS_ALC_T_HIPE, nrbytes);
 
323
#endif
 
324
    memcpy(address, bytes, nrbytes);
 
325
    hipe_flush_icache_range(address, nrbytes);
 
326
    hp = HAlloc(BIF_P, 3);
 
327
    hp[0] = make_arityval(2);
 
328
    hp[1] = address_to_term(address, BIF_P);
 
329
    hp[2] = trampolines;
 
330
    BIF_RET(make_tuple(hp));
 
331
}
 
332
 
 
333
/*
 
334
 * Allocate memory for arbitrary non-Erlang data.
 
335
 */
 
336
BIF_RETTYPE hipe_bifs_alloc_data_2(BIF_ALIST_2)
 
337
{
 
338
    Uint align, nrbytes;
 
339
    void *block;
 
340
 
 
341
    if( is_not_small(BIF_ARG_1) || is_not_small(BIF_ARG_2) ||
 
342
        (align = unsigned_val(BIF_ARG_1),
 
343
         align != sizeof(long) && align != sizeof(double)) )
 
344
        BIF_ERROR(BIF_P, BADARG);
 
345
    nrbytes = unsigned_val(BIF_ARG_2);
 
346
    block = erts_alloc(ERTS_ALC_T_HIPE, nrbytes);
 
347
    if( (unsigned long)block & (align-1) )
 
348
        fprintf(stderr, "Yikes! erts_alloc() returned misaligned address %p\r\n", block);
269
349
    BIF_RET(address_to_term(block, BIF_P));
270
350
}
271
351
 
272
352
/*
273
 
 * hipe_bifs_alloc_constant_1 is like hipe_bifs_alloc_code_1, except it
274
 
 * returns memory suitable for storing constant Erlang values.
 
353
 * Memory area for constant Erlang terms.
275
354
 *
276
355
 * These constants must not be forwarded by the gc.
277
356
 * Therefore, the gc needs to be able to distinguish between
290
369
Eterm *hipe_constants_start = NULL;
291
370
Eterm *hipe_constants_next = NULL;
292
371
static unsigned constants_avail_words = 0;
293
 
#define CONSTANTS_BYTES (1024*4096)
 
372
#define CONSTANTS_BYTES (1536*1024*sizeof(Eterm))  /* 1.5 M words */
294
373
 
295
374
static Eterm *constants_alloc(unsigned nwords)
296
375
{
303
382
        hipe_constants_next = next;
304
383
        constants_avail_words = CONSTANTS_BYTES / sizeof(Eterm);
305
384
    }
306
 
    if( nwords > constants_avail_words )
307
 
        erl_exit(1, "out of constants pool memory\n");
 
385
    if( nwords > constants_avail_words ) {
 
386
        fprintf(stderr, "Native code constants pool depleted!\r\n");
 
387
        /* Must terminate immediately. erl_exit() seems to
 
388
           continue running some code which then SIGSEGVs. */
 
389
        exit(1);
 
390
    }
308
391
    constants_avail_words -= nwords;
309
392
    hipe_constants_next = next + nwords;
310
393
    return next;
311
394
}
312
395
 
313
 
BIF_RETTYPE hipe_bifs_alloc_constant_1(BIF_ALIST_1)
314
 
{
315
 
    unsigned nwords;
316
 
    Eterm *block;
317
 
 
318
 
    if( is_not_small(BIF_ARG_1) )
319
 
        BIF_ERROR(BIF_P, BADARG);
320
 
    nwords = unsigned_val(BIF_ARG_1);
321
 
    block = constants_alloc(nwords);
322
 
    BIF_RET(address_to_term(block, BIF_P));
323
 
}
324
 
 
325
 
BIF_RETTYPE hipe_bifs_term_size_1(BIF_ALIST_1)
326
 
{
327
 
    BIF_RET(make_small(size_object(BIF_ARG_1)));
328
 
}
329
 
 
330
 
BIF_RETTYPE hipe_bifs_copy_term_3(BIF_ALIST_3)
331
 
{
332
 
    Eterm size, *hp, res;
333
 
 
334
 
    hp = term_to_address(BIF_ARG_2);
335
 
    if( !hp || is_not_small(BIF_ARG_3) || is_immed(BIF_ARG_1) )
336
 
        BIF_ERROR(BIF_P, BADARG);
337
 
    size = unsigned_val(BIF_ARG_3);
338
 
 
339
 
    /* this only works as long as BIF_ARG_1 contains no binaries :-( */
340
 
    res = copy_struct(BIF_ARG_1, size, &hp, NULL);
341
 
 
342
 
    BIF_RET(address_to_term((void*)res, BIF_P));
343
 
}
 
396
BIF_RETTYPE hipe_bifs_constants_size_0(BIF_ALIST_0)
 
397
{
 
398
    BIF_RET(make_small(hipe_constants_next - hipe_constants_start));
 
399
}
 
400
 
 
401
/*
 
402
 * Merging constant Erlang terms.
 
403
 * Uses the constants pool and a hash table of all top-level
 
404
 * terms merged so far. (Sub-terms are not merged.)
 
405
 */
 
406
struct const_term {
 
407
    HashBucket bucket;
 
408
    Eterm val;          /* tagged pointer to mem[0] */
 
409
    Eterm mem[1];       /* variable size */
 
410
};
 
411
 
 
412
static Hash const_term_table;
 
413
static ErlOffHeap const_term_table_off_heap;
 
414
 
 
415
static HashValue const_term_hash(void *tmpl)
 
416
{
 
417
    return make_hash2((Eterm)tmpl);
 
418
}
 
419
 
 
420
static int const_term_cmp(void *tmpl, void *bucket)
 
421
{
 
422
    return !eq((Eterm)tmpl, ((struct const_term*)bucket)->val);
 
423
}
 
424
 
 
425
static void *const_term_alloc(void *tmpl)
 
426
{
 
427
    Eterm obj;
 
428
    Uint size;
 
429
    Eterm *hp;
 
430
    struct const_term *p;
 
431
 
 
432
    obj = (Eterm)tmpl;
 
433
    ASSERT(is_not_immed(obj));
 
434
    size = size_object(obj);
 
435
 
 
436
    p = (struct const_term*)constants_alloc(size + (offsetof(struct const_term, mem)/sizeof(Eterm)));
 
437
 
 
438
    /* I have absolutely no idea if having a private 'off_heap'
 
439
       works or not. _Some_ off_heap object is required for
 
440
       REFC_BINARY and FUN values, but _where_ it should be is
 
441
       a complete mystery to me. */
 
442
    hp = &p->mem[0];
 
443
    p->val = copy_struct(obj, size, &hp, &const_term_table_off_heap);
 
444
 
 
445
    return &p->bucket;
 
446
}
 
447
 
 
448
static void init_const_term_table(void)
 
449
{
 
450
    HashFunctions f;
 
451
    f.hash = (H_FUN) const_term_hash;
 
452
    f.cmp = (HCMP_FUN) const_term_cmp;
 
453
    f.alloc = (HALLOC_FUN) const_term_alloc;
 
454
    f.free = (HFREE_FUN) NULL;
 
455
    hash_init(ERTS_ALC_T_HIPE, &const_term_table, "const_term_table", 97, f);
 
456
}
 
457
 
 
458
BIF_RETTYPE hipe_bifs_merge_term_1(BIF_ALIST_1)
 
459
{
 
460
    static int init_done = 0;
 
461
    struct const_term *p;
 
462
    Eterm val;
 
463
 
 
464
    val = BIF_ARG_1;
 
465
    if( is_not_immed(val) ) {
 
466
        if( !init_done ) {
 
467
            init_const_term_table();
 
468
            init_done = 1;
 
469
        }
 
470
        p = (struct const_term*)hash_put(&const_term_table, (void*)val);
 
471
        val = p->val;
 
472
    }
 
473
    BIF_RET(val);
 
474
}
 
475
 
 
476
struct mfa {
 
477
    Eterm mod;
 
478
    Eterm fun;
 
479
    Uint  ari;
 
480
};
 
481
 
 
482
static int term_to_mfa(Eterm term, struct mfa *mfa)
 
483
{
 
484
    Eterm mod, fun, a;
 
485
    Uint ari;
 
486
 
 
487
    if (is_not_tuple(term))
 
488
        return 0;
 
489
    if (tuple_val(term)[0] != make_arityval(3))
 
490
        return 0;
 
491
    mod = tuple_val(term)[1];
 
492
    if (is_not_atom(mod))
 
493
        return 0;
 
494
    mfa->mod = mod;
 
495
    fun = tuple_val(term)[2];
 
496
    if (is_not_atom(fun))
 
497
        return 0;
 
498
    mfa->fun = fun;
 
499
    a = tuple_val(term)[3];
 
500
    if (is_not_small(a))
 
501
        return 0;
 
502
    ari = unsigned_val(a);
 
503
    if (ari > 255)
 
504
        return 0;
 
505
    mfa->ari = ari;
 
506
    return 1;
 
507
}
 
508
 
 
509
#ifdef DEBUG_LINKER
 
510
static void print_mfa(Eterm mod, Eterm fun, unsigned int ari)
 
511
{
 
512
    erts_printf("%T:%T/%u", mod, fun, ari);
 
513
}
 
514
#endif
344
515
 
345
516
/*
346
517
 * Convert {M,F,A} to pointer to first insn after initial func_info.
347
518
 */
348
 
Uint *hipe_bifs_find_pc_from_mfa(Eterm mfa)
 
519
static Uint *hipe_find_emu_address(Eterm mod, Eterm name, unsigned int arity)
349
520
{
350
 
    Eterm *tp;
351
521
    Module *modp;
352
 
    Eterm mod;
353
 
    Eterm name;
354
 
    int arity;
355
522
    Uint *code_base;
356
523
    int i, n;
357
524
 
358
 
    if( !is_tuple(mfa) )
359
 
        return NULL;
360
 
    tp = tuple_val(mfa);
361
 
    if( tp[0] != make_arityval(3) )
362
 
        return NULL;
363
 
    mod = tp[1];
364
 
    name = tp[2];
365
 
    if( !is_atom(mod) || !is_atom(name) || !is_small(tp[3]) )
366
 
        return NULL;
367
 
    arity = signed_val(tp[3]);
368
525
    modp = erts_get_module(mod);
369
526
    if( modp == NULL || (code_base = modp->code) == NULL )
370
527
        return NULL;
378
535
    return NULL;
379
536
}
380
537
 
 
538
Uint *hipe_bifs_find_pc_from_mfa(Eterm term)
 
539
{
 
540
    struct mfa mfa;
 
541
 
 
542
    if (!term_to_mfa(term, &mfa))
 
543
        return NULL;
 
544
    return hipe_find_emu_address(mfa.mod, mfa.fun, mfa.ari);
 
545
}
 
546
 
381
547
BIF_RETTYPE hipe_bifs_fun_to_address_1(BIF_ALIST_1)
382
548
{
383
549
    Eterm *pc = hipe_bifs_find_pc_from_mfa(BIF_ARG_1);
386
552
    BIF_RET(address_to_term(pc, BIF_P));
387
553
}
388
554
 
389
 
BIF_RETTYPE hipe_bifs_fun_to_address_3(BIF_ALIST_3)
390
 
{
391
 
  Export* export_entry;
392
 
 
393
 
  if( is_not_atom(BIF_ARG_1) ||
394
 
      is_not_atom(BIF_ARG_2) ||
395
 
      is_not_small(BIF_ARG_3) ||
396
 
      signed_val(BIF_ARG_3) < 0 )
397
 
    BIF_ERROR(BIF_P, BADARG);
398
 
 
399
 
  export_entry = erts_find_export_entry(BIF_ARG_1, BIF_ARG_2,
400
 
                                        signed_val(BIF_ARG_3));
401
 
  if( !export_entry )
402
 
      BIF_RET(am_false);
403
 
  BIF_RET(address_to_term(export_entry->address, BIF_P));
404
 
}
 
555
static void *hipe_get_emu_address(Eterm m, Eterm f, unsigned int arity, int is_remote)
 
556
{
 
557
    void *address = NULL;
 
558
    if (!is_remote)
 
559
        address = hipe_find_emu_address(m, f, arity);
 
560
    if( !address ) {
 
561
        /* if not found, stub it via the export entry */
 
562
        Export *export_entry = erts_export_get_or_make_stub(m, f, arity);
 
563
        address = export_entry->address;
 
564
    }
 
565
    return address;
 
566
}
 
567
 
 
568
#if 0 /* XXX: unused */
 
569
BIF_RETTYPE hipe_bifs_get_emu_address_1(BIF_ALIST_1)
 
570
{
 
571
    struct mfa mfa;
 
572
    void *address;
 
573
 
 
574
    if (!term_to_mfa(BIF_ARG_1, &mfa))
 
575
        BIF_ERROR(BIF_P, BADARG);
 
576
    address = hipe_get_emu_address(mfa.mod, mfa.fun, mfa.ari);
 
577
    BIF_RET(address_to_term(address, BIF_P));
 
578
}
 
579
#endif
405
580
 
406
581
BIF_RETTYPE hipe_bifs_set_native_address_3(BIF_ALIST_3)
407
582
{
408
583
    Eterm *pc;
409
584
    void *address;
410
585
    int is_closure;
 
586
    struct mfa mfa;
411
587
 
412
588
    switch( BIF_ARG_3 ) {
413
589
      case am_false:
423
599
    if( !address )
424
600
        BIF_ERROR(BIF_P, BADARG);
425
601
 
426
 
    pc = hipe_bifs_find_pc_from_mfa(BIF_ARG_1);
 
602
    /* The mfa is needed again later, otherwise we could
 
603
       simply have called hipe_bifs_find_pc_from_mfa(). */
 
604
    if (!term_to_mfa(BIF_ARG_1, &mfa))
 
605
        BIF_ERROR(BIF_P, BADARG);
 
606
    pc = hipe_find_emu_address(mfa.mod, mfa.fun, mfa.ari);
427
607
 
428
608
    if( pc ) {
 
609
        hipe_mfa_save_orig_beam_op(mfa.mod, mfa.fun, mfa.ari, pc);
429
610
#if HIPE
 
611
#ifdef DEBUG_LINKER
 
612
        printf("%s: ", __FUNCTION__);
 
613
        print_mfa(mfa.mod, mfa.fun, mfa.ari);
 
614
        printf(": planting call trap to %p at BEAM pc %p\r\n", address, pc);
 
615
#endif
430
616
        hipe_set_call_trap(pc, address, is_closure);
431
617
        BIF_RET(am_true);
432
618
#endif
433
619
    }
 
620
#ifdef DEBUG_LINKER
 
621
    printf("%s: ", __FUNCTION__);
 
622
    print_mfa(mfa.mod, mfa.fun, mfa.ari);
 
623
    printf(": no BEAM pc found\r\n");
 
624
#endif
434
625
    BIF_RET(am_false);
435
626
}
436
627
 
 
628
#if 0 /* XXX: unused */
437
629
/*
438
630
 * hipe_bifs_address_to_fun(Address)
439
 
 *    - Address is the address of the start of a JAM function's code
 
631
 *    - Address is the address of the start of a emu function's code
440
632
 *    - returns {Module, Function, Arity}
441
633
 */
442
634
BIF_RETTYPE hipe_bifs_address_to_fun_1(BIF_ALIST_1)
458
650
    hp[3] = make_small(funcinfo[2]);
459
651
    BIF_RET(make_tuple(hp));
460
652
}
461
 
 
462
 
/*
463
 
 * Native-code stack descriptor hash table.
464
 
 *
465
 
 * This uses a specialised version of BEAM's hash table code:
466
 
 * - hash table size is always a power of two
467
 
 *   permits replacing an expensive integer division operation
468
 
 *   with a cheap bitwise 'and' in the hash index calculation
469
 
 * - lookups assume the key is in the table
470
 
 *   permits removing NULL checks
471
 
 * - switched order of the hash bucket next and hvalue fields
472
 
 *   the hvalue field, which must always be checked, gets a zero
473
 
 *   structure offset, which is faster on some architectures;
474
 
 *   the next field is only referenced if hvalue didn't match
475
 
 * These changes yield a much more efficient lookup operation.
476
 
 */
477
 
struct hipe_sdesc_table hipe_sdesc_table;
478
 
 
479
 
static struct sdesc **alloc_bucket(unsigned int size)
480
 
{
481
 
    unsigned long nbytes = size * sizeof(struct sdesc*);
482
 
    struct sdesc **bucket = erts_alloc(ERTS_ALC_T_HIPE, nbytes);
483
 
    sys_memzero(bucket, nbytes);
484
 
    return bucket;
485
 
}
486
 
 
487
 
static void hipe_grow_sdesc_table(void)
488
 
{
489
 
    unsigned int old_size, new_size, new_mask;
490
 
    struct sdesc **old_bucket, **new_bucket;
491
 
    unsigned int i;
492
 
 
493
 
    old_size = 1 << hipe_sdesc_table.log2size;
494
 
    hipe_sdesc_table.log2size += 1;
495
 
    new_size = 1 << hipe_sdesc_table.log2size;
496
 
    new_mask = new_size - 1;
497
 
    hipe_sdesc_table.mask = new_mask;
498
 
    old_bucket = hipe_sdesc_table.bucket;
499
 
    new_bucket = alloc_bucket(new_size);
500
 
    hipe_sdesc_table.bucket = new_bucket;
501
 
    for(i = 0; i < old_size; ++i) {
502
 
        struct sdesc *b = old_bucket[i];
503
 
        while( b != NULL ) {
504
 
            struct sdesc *next = b->bucket.next;
505
 
            unsigned int j = (b->bucket.hvalue >> HIPE_RA_LSR_COUNT) & new_mask;
506
 
            b->bucket.next = new_bucket[j];
507
 
            new_bucket[j] = b;
508
 
            b = next;
509
 
        }
510
 
    }
511
 
    erts_free(ERTS_ALC_T_HIPE, old_bucket);
512
 
}
513
 
 
514
 
static struct sdesc *hipe_put_sdesc(struct sdesc *sdesc)
515
 
{
516
 
    unsigned long ra;
517
 
    unsigned int i;
518
 
    struct sdesc *chain;
519
 
    unsigned int size;
520
 
 
521
 
    ra = sdesc->bucket.hvalue;
522
 
    i = (ra >> HIPE_RA_LSR_COUNT) & hipe_sdesc_table.mask;
523
 
    chain = hipe_sdesc_table.bucket[i];
524
 
 
525
 
    for(; chain != NULL; chain = chain->bucket.next)
526
 
        if( chain->bucket.hvalue == ra )
527
 
            return chain;       /* collision! (shouldn't happen) */
528
 
 
529
 
    sdesc->bucket.next = hipe_sdesc_table.bucket[i];
530
 
    hipe_sdesc_table.bucket[i] = sdesc;
531
 
    hipe_sdesc_table.used += 1;
532
 
    size = 1 << hipe_sdesc_table.log2size;
533
 
    if( hipe_sdesc_table.used > (4*size)/5 )    /* rehash at 80% */
534
 
        hipe_grow_sdesc_table();
535
 
    return sdesc;
536
 
}
537
 
 
538
 
void hipe_init_sdesc_table(struct sdesc *sdesc)
539
 
{
540
 
    unsigned int log2size, size;
541
 
 
542
 
    log2size = 10;
543
 
    size = 1 << log2size;
544
 
    hipe_sdesc_table.log2size = log2size;
545
 
    hipe_sdesc_table.mask = size - 1;
546
 
    hipe_sdesc_table.used = 0;
547
 
    hipe_sdesc_table.bucket = alloc_bucket(size);
548
 
 
549
 
    hipe_put_sdesc(sdesc);
550
 
}
551
 
 
552
 
/* XXX: remove later when sparc is more debugged 
553
 
#ifdef __sparc__ 
554
 
const struct sdesc *hipe_find_sdesc(unsigned long ra)
555
 
{
556
 
    unsigned int i = (ra >> HIPE_RA_LSR_COUNT) & hipe_sdesc_table.mask;
557
 
    const struct sdesc *sdesc = hipe_sdesc_table.bucket[i];
558
 
    for(; sdesc; sdesc = sdesc->bucket.next)
559
 
        if( sdesc->bucket.hvalue == ra )
560
 
            return sdesc;
561
 
    fprintf(stderr, "%s: ra %#lx has no sdesc\r\n", __FUNCTION__, ra);
562
 
    abort();
563
 
}
564
 
  #endif */
565
 
 
566
 
/*
567
 
 * XXX: x86 and SPARC currently use the same stack descriptor
568
 
 * representation. If different representations are needed in
569
 
 * the future, this code has to be made target dependent.
570
 
 */
571
 
static struct sdesc *decode_sdesc(Eterm arg)
572
 
{
573
 
    Uint ra, exnra;
574
 
    Eterm *live;
575
 
    unsigned int fsize, arity, nlive, i, nslots, off;
576
 
    unsigned int livebitswords, sdescwords;
577
 
    void *p;
578
 
    struct sdesc *sdesc;
579
 
 
580
 
    if( is_not_tuple(arg) ||
581
 
        (tuple_val(arg))[0] != make_arityval(5) ||
582
 
        term_to_Uint((tuple_val(arg))[1], &ra) == 0 ||
583
 
        term_to_Uint((tuple_val(arg))[2], &exnra) == 0 ||
584
 
        is_not_small((tuple_val(arg))[3]) ||
585
 
        (fsize = unsigned_val((tuple_val(arg))[3])) > 65535 ||
586
 
        is_not_small((tuple_val(arg))[4]) ||
587
 
        (arity = unsigned_val((tuple_val(arg))[4])) > 255 ||
588
 
        is_not_tuple((tuple_val(arg))[5]) )
589
 
        return 0;
590
 
    /* Get tuple with live slots */
591
 
    live = tuple_val((tuple_val(arg))[5]) + 1;
592
 
    /* Get number of live slots */
593
 
    nlive = arityval(live[-1]);
594
 
    /* Calculate size of frame = locals + ra + arguments */
595
 
    nslots = fsize + 1 + arity;
596
 
    /* Check that only valid slots are given. */
597
 
    for(i = 0; i < nlive; ++i) {
598
 
        if( is_not_small(live[i]) ||
599
 
            (off = unsigned_val(live[i]), off >= nslots) ||
600
 
            off == fsize )
601
 
            return 0;
602
 
    }
603
 
 
604
 
    /* Calculate number of words for the live bitmap. */
605
 
    livebitswords = (fsize + arity + 1 + 31) / 32;
606
 
    /* Calculate number of words for the stack descriptor. */
607
 
    sdescwords = 3 + livebitswords + (exnra ? 1 : 0);
608
 
    p = erts_alloc(ERTS_ALC_T_HIPE, sdescwords*4);
609
 
    /* If we have an exception handler use the
610
 
       special sdesc_with_exnra structure. */
611
 
    if( exnra ) {
612
 
        struct sdesc_with_exnra *sdesc_we = p;
613
 
        sdesc_we->exnra = exnra;
614
 
        sdesc = &(sdesc_we->sdesc);
615
 
    } else
616
 
        sdesc = p;
617
 
 
618
 
    /* Initialise head of sdesc. */
619
 
    sdesc->bucket.next = 0;
620
 
    sdesc->bucket.hvalue = ra;
621
 
    sdesc->summary = (fsize << 9) | (exnra ? (1<<8) : 0) | arity;
622
 
    /* Clear all live-bits */
623
 
    for(i = 0; i < livebitswords; ++i)
624
 
        sdesc->livebits[i] = 0;
625
 
    /* Set live-bits given by caller. */
626
 
    for(i = 0; i < nlive; ++i) {
627
 
        off = unsigned_val(live[i]);
628
 
        sdesc->livebits[off / 32] |= (1 << (off & 31));
629
 
    }
630
 
    return sdesc;
631
 
}
 
653
#endif
632
654
 
633
655
BIF_RETTYPE hipe_bifs_enter_sdesc_1(BIF_ALIST_1)
634
656
{
635
657
    struct sdesc *sdesc;
636
658
 
637
 
    sdesc = decode_sdesc(BIF_ARG_1);
 
659
    sdesc = hipe_decode_sdesc(BIF_ARG_1);
638
660
    if( !sdesc ) {
639
661
        fprintf(stderr, "%s: bad sdesc!\r\n", __FUNCTION__);
640
662
        BIF_ERROR(BIF_P, BADARG);
654
676
    Eterm mod;
655
677
    Eterm fun;
656
678
    unsigned arity;
657
 
    void *address;
 
679
    const void *address;
658
680
};
659
681
 
660
682
static struct nbif nbifs[BIF_SIZE] = {
661
683
#define BIF_LIST(MOD,FUN,ARY,CFUN,IX)   \
662
 
        { {0,0}, MOD, FUN, ARY, nbif_##CFUN },
 
684
        { {0,0}, MOD, FUN, ARY, &nbif_##CFUN },
663
685
#include "erl_bif_list.h"
664
686
#undef BIF_LIST
665
687
};
698
720
        hash_put(&nbif_table, &nbifs[i]);
699
721
}
700
722
 
701
 
static void *nbif_address(Eterm mod, Eterm fun, unsigned arity)
 
723
static const void *nbif_address(Eterm mod, Eterm fun, unsigned arity)
702
724
{
703
725
    struct nbif tmpl;
704
726
    struct nbif *nbif;
716
738
 */
717
739
BIF_RETTYPE hipe_bifs_bif_address_3(BIF_ALIST_3)
718
740
{
719
 
    void *address;
 
741
    const void *address;
720
742
    static int init_done = 0;
721
743
 
722
744
    if( !init_done ) {
737
759
}
738
760
 
739
761
/*
 
762
 * Hash table mapping primops to their addresses.
 
763
 */
 
764
struct primop {
 
765
    HashBucket bucket;  /* bucket.hvalue == atom_val(name) */
 
766
    const void *address;
 
767
#if defined(__arm__)
 
768
    void *trampoline;
 
769
#endif
 
770
};
 
771
 
 
772
static struct primop primops[] = {
 
773
#define PRIMOP_LIST(ATOM,ADDRESS)       { {0,_unchecked_atom_val(ATOM)}, ADDRESS },
 
774
#include "hipe_primops.h"
 
775
#undef PRIMOP_LIST
 
776
};
 
777
 
 
778
static Hash primop_table;
 
779
 
 
780
static HashValue primop_hash(void *tmpl)
 
781
{
 
782
    return ((struct primop*)tmpl)->bucket.hvalue;       /* pre-initialised */
 
783
}
 
784
 
 
785
static int primop_cmp(void *tmpl, void *bucket)
 
786
{
 
787
    return 0;   /* hvalue matched so nothing further to do */
 
788
}
 
789
 
 
790
static void *primop_alloc(void *tmpl)
 
791
{
 
792
    return tmpl;        /* pre-allocated */
 
793
}
 
794
 
 
795
static void init_primop_table(void)
 
796
{
 
797
    HashFunctions f;
 
798
    int i;
 
799
    static int init_done = 0;
 
800
 
 
801
    if (init_done)
 
802
        return;
 
803
    init_done = 1;
 
804
 
 
805
    f.hash = (H_FUN) primop_hash;
 
806
    f.cmp = (HCMP_FUN) primop_cmp;
 
807
    f.alloc = (HALLOC_FUN) primop_alloc;
 
808
    f.free = NULL;
 
809
 
 
810
    hash_init(ERTS_ALC_T_HIPE, &primop_table, "primop_table", 50, f);
 
811
 
 
812
    for(i = 0; i < sizeof(primops)/sizeof(primops[0]); ++i)
 
813
        hash_put(&primop_table, &primops[i]);
 
814
}
 
815
 
 
816
static struct primop *primop_table_get(Eterm name)
 
817
{
 
818
    struct primop tmpl;
 
819
 
 
820
    init_primop_table();
 
821
    tmpl.bucket.hvalue = atom_val(name);
 
822
    return hash_get(&primop_table, &tmpl);
 
823
}
 
824
 
 
825
#if defined(__arm__)
 
826
static struct primop *primop_table_put(Eterm name)
 
827
{
 
828
    struct primop tmpl;
 
829
 
 
830
    init_primop_table();
 
831
    tmpl.bucket.hvalue = atom_val(name);
 
832
    return hash_put(&primop_table, &tmpl);
 
833
}
 
834
 
 
835
void *hipe_primop_get_trampoline(Eterm name)
 
836
{
 
837
    struct primop *primop = primop_table_get(name);
 
838
    return primop ? primop->trampoline : NULL;
 
839
}
 
840
 
 
841
void hipe_primop_set_trampoline(Eterm name, void *trampoline)
 
842
{
 
843
    struct primop *primop = primop_table_put(name);
 
844
    primop->trampoline = trampoline;
 
845
}
 
846
#endif
 
847
 
 
848
/*
740
849
 * hipe_bifs_primop_address(Atom) -> address or false
741
850
 */
742
851
BIF_RETTYPE hipe_bifs_primop_address_1(BIF_ALIST_1)
743
852
{
744
 
    void *res;
745
 
 
746
 
    switch( BIF_ARG_1 ) {
747
 
#define check_bif(Name,Address) case Name: res = Address; break
748
 
        check_bif(am_erl_fp_exception, (int*)&erl_fp_exception); /* ignore volatile */
749
 
        check_bif(am_erts_mb, &erts_mb);
750
 
        check_bif(am_erts_save_mb, &erts_save_mb);
751
 
 
752
 
        check_bif(am_callemu, nbif_callemu);
753
 
        check_bif(am_suspend_msg, nbif_suspend_msg);
754
 
        check_bif(am_suspend_msg_timeout, nbif_suspend_msg_timeout);
755
 
        check_bif(am_suspend_0, nbif_suspend_0);
756
 
 
757
 
        check_bif(am_Plus, nbif_add_2);
758
 
        check_bif(am_Minus, nbif_sub_2);
759
 
        check_bif(am_Times, nbif_mul_2);
760
 
        check_bif(am_Div, nbif_div_2);
761
 
        check_bif(am_div, nbif_intdiv_2);
762
 
        check_bif(am_rem, nbif_rem_2);
763
 
        check_bif(am_bsl, nbif_bsl_2);
764
 
        check_bif(am_bsr, nbif_bsr_2);
765
 
        check_bif(am_band, nbif_band_2);
766
 
        check_bif(am_bor, nbif_bor_2);
767
 
        check_bif(am_bxor, nbif_bxor_2);
768
 
        check_bif(am_bnot, nbif_bnot_1);
769
 
 
770
 
        check_bif(am_gc_1, nbif_gc_1);
771
 
        check_bif(am_get_msg, nbif_get_msg);
772
 
        check_bif(am_select_msg, nbif_select_msg);
773
 
        check_bif(am_mbox_empty, nbif_mbox_empty);
774
 
        check_bif(am_next_msg, nbif_next_msg);
775
 
        check_bif(am_set_timeout, nbif_set_timeout);
776
 
        check_bif(am_clear_timeout, nbif_clear_timeout);
777
 
 
778
 
        check_bif(am_bs_init, nbif_bs_init);
779
 
        check_bif(am_bs_final, nbif_bs_final);
780
 
        check_bif(am_bs_start_match, nbif_bs_start_match);
781
 
        check_bif(am_bs_get_integer, nbif_bs_get_integer);
782
 
        check_bif(am_bs_get_float, nbif_bs_get_float);
783
 
        check_bif(am_bs_get_binary, nbif_bs_get_binary);
784
 
        check_bif(am_bs_get_binary_all, nbif_bs_get_binary_all);
785
 
        check_bif(am_bs_skip_bits, nbif_bs_skip_bits);
786
 
        check_bif(am_bs_skip_bits_all, nbif_bs_skip_bits_all);
787
 
        check_bif(am_bs_test_tail, nbif_bs_test_tail);
788
 
        check_bif(am_bs_save, nbif_bs_save);
789
 
        check_bif(am_bs_restore, nbif_bs_restore);
790
 
        check_bif(am_bs_put_integer, nbif_bs_put_integer);
791
 
        check_bif(am_bs_put_binary, nbif_bs_put_binary);
792
 
        check_bif(am_bs_put_binary_all, nbif_bs_put_binary_all);
793
 
        check_bif(am_bs_put_float, nbif_bs_put_float);
794
 
        check_bif(am_bs_put_string, nbif_bs_put_string);
795
 
        check_bif(am_bs_get_matchbuffer, nbif_bs_get_matchbuffer);
796
 
        check_bif(am_bs_allocate, nbif_bs_allocate);
797
 
        check_bif(am_bs_put_big_integer, nbif_bs_put_big_integer);
798
 
        check_bif(am_bs_put_small_float, nbif_bs_put_small_float);
799
 
        
800
 
        check_bif(am_cmp_2, nbif_cmp_2);
801
 
        check_bif(am_op_exact_eqeq_2, nbif_eq_2);
802
 
 
803
 
        check_bif(am_conv_big_to_float, nbif_conv_big_to_float);
804
 
 
805
 
#ifdef __sparc__
806
 
        check_bif(am_inc_stack_0args_0, nbif_inc_stack_0args);
807
 
        check_bif(am_inc_stack_1args_0, nbif_inc_stack_1args);
808
 
        check_bif(am_inc_stack_2args_0, nbif_inc_stack_2args);
809
 
        check_bif(am_inc_stack_3args_0, nbif_inc_stack_3args);
810
 
        check_bif(am_inc_stack_4args_0, nbif_inc_stack_4args);
811
 
        check_bif(am_inc_stack_5args_0, nbif_inc_stack_5args);
812
 
        check_bif(am_inc_stack_6args_0, nbif_inc_stack_6args);
813
 
        check_bif(am_inc_stack_7args_0, nbif_inc_stack_7args);
814
 
        check_bif(am_inc_stack_8args_0, nbif_inc_stack_8args);
815
 
        check_bif(am_inc_stack_9args_0, nbif_inc_stack_9args);
816
 
        check_bif(am_inc_stack_10args_0, nbif_inc_stack_10args);
817
 
        check_bif(am_inc_stack_11args_0, nbif_inc_stack_11args);
818
 
        check_bif(am_inc_stack_12args_0, nbif_inc_stack_12args);
819
 
        check_bif(am_inc_stack_13args_0, nbif_inc_stack_13args);
820
 
        check_bif(am_inc_stack_14args_0, nbif_inc_stack_14args);
821
 
        check_bif(am_inc_stack_15args_0, nbif_inc_stack_15args);
822
 
        check_bif(am_inc_stack_16args_0, nbif_inc_stack_16args);
823
 
#endif
824
 
#ifdef __i386__
825
 
        check_bif(am_inc_stack_0, nbif_inc_stack_0);
826
 
        check_bif(am_handle_fp_exception, nbif_handle_fp_exception);
827
 
#endif
828
 
#undef check_bif
829
 
      default:
830
 
        BIF_RET(am_false);
831
 
    }
832
 
    BIF_RET(address_to_term(res, BIF_P));
 
853
    const struct primop *primop;
 
854
 
 
855
    if (is_not_atom(BIF_ARG_1))
 
856
        BIF_RET(am_false);
 
857
    primop = primop_table_get(BIF_ARG_1);
 
858
    if (!primop)
 
859
        BIF_RET(am_false);
 
860
    BIF_RET(address_to_term(primop->address, BIF_P));
833
861
}
834
862
 
 
863
#if 0 /* XXX: unused */
835
864
/*
836
865
 * hipe_bifs_gbif_address(F,A) -> address or false
837
866
 */
841
870
 
842
871
BIF_RETTYPE hipe_bifs_gbif_address_2(BIF_ALIST_2)
843
872
{
844
 
    unsigned arity;
 
873
    Uint arity;
845
874
    void *address;
846
875
 
847
876
    if( is_not_atom(BIF_ARG_1) || is_not_small(BIF_ARG_2) )
854
883
#undef GBIF_LIST
855
884
        printf("\r\n%s: guard BIF ", __FUNCTION__);
856
885
        fflush(stdout);
857
 
        print_atom(atom_val(BIF_ARG_1), COUT);
858
 
        printf("/%u isn't listed in hipe_gbif_list.h\r\n", arity);
 
886
        erts_printf("%T", BIF_ARG_1);
 
887
        printf("/%lu isn't listed in hipe_gbif_list.h\r\n", arity);
859
888
        BIF_RET(am_false);
860
889
    } while(0);
861
890
    BIF_RET(address_to_term(address, BIF_P));
862
891
}
 
892
#endif
863
893
 
864
894
BIF_RETTYPE hipe_bifs_atom_to_word_1(BIF_ALIST_1)
865
895
{
873
903
    BIF_RET(Uint_to_term(BIF_ARG_1, BIF_P));
874
904
}
875
905
 
876
 
BIF_RETTYPE hipe_bifs_emu_stub_3(BIF_ALIST_3)
877
 
{
878
 
  Export* export_entry;
879
 
 
880
 
  if( is_not_atom(BIF_ARG_1) ||
881
 
      is_not_atom(BIF_ARG_2) ||
882
 
      is_not_small(BIF_ARG_3) ||
883
 
      signed_val(BIF_ARG_3) < 0 )
884
 
    BIF_ERROR(BIF_P, BADARG);
885
 
 
886
 
  export_entry = erts_export_put(BIF_ARG_1, BIF_ARG_2, signed_val(BIF_ARG_3));
887
 
  BIF_RET(address_to_term(export_entry->address, BIF_P));
888
 
}
889
 
 
890
 
DbTable* code_tb = (DbTable*) NULL;
891
 
static void init_code_table(void)
892
 
{
893
 
    Uint32 status;
894
 
    int keypos;
895
 
    int cret;
896
 
 
897
 
    status = DB_NORMAL | DB_SET | DB_LHASH | DB_PROTECTED;
898
 
    keypos = 1;
899
 
 
900
 
    code_tb = (DbTable*) erts_alloc(ERTS_ALC_T_DB_TABLE, sizeof(DbTable));
901
 
    code_tb->common.status = status;
902
 
    code_tb->common.keypos = keypos;
903
 
    code_tb->common.nitems = 0;
904
 
    code_tb->common.memory = 0;
905
 
    cret = db_create_hash((Process *)NULL, &(code_tb->hash));
906
 
 
907
 
    if (cret != DB_ERROR_NONE) {
908
 
        printf("HiPE: Not enough mem for code table!\n");
909
 
        exit(1); /* TODO: Die gracefully */
910
 
    }
911
 
}
912
 
 
913
 
BIF_RETTYPE hipe_bifs_set_funinfo_1(BIF_ALIST_1)
914
 
{
915
 
    int cret;
916
 
    Eterm ret;
917
 
 
918
 
    if (code_tb == (DbTable*) NULL)
919
 
        init_code_table();
920
 
 
921
 
    if (is_not_tuple(BIF_ARG_1) ||
922
 
        (arityval(*tuple_val(BIF_ARG_1)) < code_tb->common.keypos)) {
923
 
        BIF_ERROR(BIF_P, BADARG);
924
 
    }
925
 
    cret = db_put_hash(BIF_P, &(code_tb->hash), BIF_ARG_1, &ret);
926
 
    switch (cret) {
927
 
    case DB_ERROR_NONE:
928
 
        BIF_RET(ret);
929
 
    case DB_ERROR_SYSRES:
930
 
        BIF_ERROR(BIF_P, SYSTEM_LIMIT);
931
 
    default:
932
 
        BIF_ERROR(BIF_P, BADARG);
933
 
    }
934
 
}
935
 
 
936
906
/* XXX: this is really a primop, not a BIF */
937
907
BIF_RETTYPE hipe_conv_big_to_float(BIF_ALIST_1)
938
908
{
946
916
    if( big_to_double(BIF_ARG_1, &f.fd) < 0 ) {
947
917
        BIF_ERROR(BIF_P, BADARG);
948
918
    }
949
 
    hp = HAlloc(BIF_P, 3);
 
919
    hp = HAlloc(BIF_P, FLOAT_SIZE_OBJECT);
950
920
    res = make_float(hp);
951
921
    PUT_DOUBLE(f, hp);
952
922
    BIF_RET(res);
953
923
}
954
924
 
955
 
BIF_RETTYPE hipe_bifs_get_funinfo_1(BIF_ALIST_1)
956
 
{
957
 
    int cret;
958
 
    Eterm ret;
959
 
 
960
 
    if (code_tb == (DbTable*) NULL)
961
 
        init_code_table();
962
 
 
963
 
    cret = db_get_hash(BIF_P, &(code_tb->hash), BIF_ARG_1, &ret);
964
 
    switch (cret) {
965
 
    case DB_ERROR_NONE:
966
 
        BIF_RET(ret);
967
 
    case DB_ERROR_SYSRES:
968
 
        BIF_ERROR(BIF_P, SYSTEM_LIMIT);
969
 
    default:
970
 
        BIF_ERROR(BIF_P, BADARG);
971
 
    }
972
 
}
973
 
 
 
925
#if 0 /* XXX: unused */
974
926
/*
975
927
  At least parts of this should be inlined in native code.
976
928
  The rest could be made a primop used by both the emulator and
1052
1004
    BIF_ERROR(BIF_P, BADARG);
1053
1005
  }
1054
1006
 
1055
 
#ifndef SHARED_HEAP
 
1007
#ifndef HYBRID /* FIND ME! */
1056
1008
  funp->next = MSO(BIF_P).funs;
1057
1009
  MSO(BIF_P).funs = funp;
1058
1010
#endif
1059
1011
 
1060
1012
  BIF_RET(make_fun(funp));
1061
1013
}
 
1014
#endif
1062
1015
 
1063
1016
BIF_RETTYPE hipe_bifs_make_fe_3(BIF_ALIST_3)
1064
1017
{
1107
1060
    char atom_buf[256];
1108
1061
 
1109
1062
    atom_buf[0] = '\0';
1110
 
    strncat(atom_buf, atom_tab(i)->name, atom_tab(i)->len);
 
1063
    strncat(atom_buf, (char*)atom_tab(i)->name, atom_tab(i)->len);
1111
1064
    printf("no fun entry for %s %ld:%ld\n", atom_buf, uniq, index);
1112
1065
    BIF_ERROR(BIF_P, BADARG);
1113
1066
  }
1114
1067
  fe->native_address = native_address;
 
1068
  if (erts_refc_dectest(&fe->refc, 0) == 0)
 
1069
      erts_erase_fun_entry(fe);
1115
1070
  BIF_RET(address_to_term((void *)fe, BIF_P));
1116
1071
}
1117
1072
 
1118
 
int hipe_patch_address(Uint *address, Eterm patchtype, Uint value)
 
1073
#if 0 /* XXX: unused */
 
1074
BIF_RETTYPE hipe_bifs_make_native_stub_2(BIF_ALIST_2)
 
1075
{
 
1076
    void *beamAddress;
 
1077
    Uint beamArity;
 
1078
    void *stubAddress;
 
1079
 
 
1080
    if( (beamAddress = term_to_address(BIF_ARG_1)) == 0 ||
 
1081
        is_not_small(BIF_ARG_2) ||
 
1082
        (beamArity = unsigned_val(BIF_ARG_2)) >= 256 )
 
1083
        BIF_ERROR(BIF_P, BADARG);
 
1084
    stubAddress = hipe_make_native_stub(beamAddress, beamArity);
 
1085
    BIF_RET(address_to_term(stubAddress, BIF_P));
 
1086
}
 
1087
#endif
 
1088
 
 
1089
/*
 
1090
 * MFA info hash table:
 
1091
 * - maps MFA to native code entry point
 
1092
 * - the MFAs it calls (refers_to)
 
1093
 * - the references to it (referred_from)
 
1094
 * - maps MFA to most recent trampoline [if powerpc or arm]
 
1095
 */
 
1096
struct hipe_mfa_info {
 
1097
    struct {
 
1098
        unsigned long hvalue;
 
1099
        struct hipe_mfa_info *next;
 
1100
    } bucket;
 
1101
    Eterm m;    /* atom */
 
1102
    Eterm f;    /* atom */
 
1103
    unsigned int a;
 
1104
    void *remote_address;
 
1105
    void *local_address;
 
1106
    Eterm *beam_code;
 
1107
    Uint orig_beam_op;
 
1108
    struct hipe_mfa_info_list *refers_to;
 
1109
    struct ref *referred_from;
 
1110
#if defined(__powerpc__) || defined(__ppc__) || defined(__powerpc64__) || defined(__arm__)
 
1111
    void *trampoline;
 
1112
#endif
 
1113
};
 
1114
 
 
1115
static struct {
 
1116
    unsigned int log2size;
 
1117
    unsigned int mask;          /* INV: mask == (1 << log2size)-1 */
 
1118
    unsigned int used;
 
1119
    struct hipe_mfa_info **bucket;
 
1120
} hipe_mfa_info_table;
 
1121
 
 
1122
#define HIPE_MFA_HASH(M,F,A)    ((M) * (F) + (A))
 
1123
 
 
1124
static struct hipe_mfa_info **hipe_mfa_info_table_alloc_bucket(unsigned int size)
 
1125
{
 
1126
    unsigned long nbytes = size * sizeof(struct hipe_mfa_info*);
 
1127
    struct hipe_mfa_info **bucket = erts_alloc(ERTS_ALC_T_HIPE, nbytes);
 
1128
    sys_memzero(bucket, nbytes);
 
1129
    return bucket;
 
1130
}
 
1131
 
 
1132
static void hipe_mfa_info_table_grow(void)
 
1133
{
 
1134
    unsigned int old_size, new_size, new_mask;
 
1135
    struct hipe_mfa_info **old_bucket, **new_bucket;
 
1136
    unsigned int i;
 
1137
 
 
1138
    old_size = 1 << hipe_mfa_info_table.log2size;
 
1139
    hipe_mfa_info_table.log2size += 1;
 
1140
    new_size = 1 << hipe_mfa_info_table.log2size;
 
1141
    new_mask = new_size - 1;
 
1142
    hipe_mfa_info_table.mask = new_mask;
 
1143
    old_bucket = hipe_mfa_info_table.bucket;
 
1144
    new_bucket = hipe_mfa_info_table_alloc_bucket(new_size);
 
1145
    hipe_mfa_info_table.bucket = new_bucket;
 
1146
    for(i = 0; i < old_size; ++i) {
 
1147
        struct hipe_mfa_info *b = old_bucket[i];
 
1148
        while( b != NULL ) {
 
1149
            struct hipe_mfa_info *next = b->bucket.next;
 
1150
            unsigned int j = b->bucket.hvalue & new_mask;
 
1151
            b->bucket.next = new_bucket[j];
 
1152
            new_bucket[j] = b;
 
1153
            b = next;
 
1154
        }
 
1155
    }
 
1156
    erts_free(ERTS_ALC_T_HIPE, old_bucket);
 
1157
}
 
1158
 
 
1159
static struct hipe_mfa_info *hipe_mfa_info_table_alloc(Eterm m, Eterm f, unsigned int arity)
 
1160
{
 
1161
    struct hipe_mfa_info *res;
 
1162
 
 
1163
    res = (struct hipe_mfa_info*)erts_alloc(ERTS_ALC_T_HIPE, sizeof(*res));
 
1164
    res->m = m;
 
1165
    res->f = f;
 
1166
    res->a = arity;
 
1167
    res->remote_address = NULL;
 
1168
    res->local_address = NULL;
 
1169
    res->beam_code = NULL;
 
1170
    res->orig_beam_op = 0;
 
1171
    res->refers_to = NULL;
 
1172
    res->referred_from = NULL;
 
1173
#if defined(__powerpc__) || defined(__ppc__) || defined(__powerpc64__) || defined(__arm__)
 
1174
    res->trampoline = NULL;
 
1175
#endif
 
1176
 
 
1177
    return res;
 
1178
}
 
1179
 
 
1180
void hipe_mfa_info_table_init(void)
 
1181
{
 
1182
    unsigned int log2size, size;
 
1183
 
 
1184
    log2size = 10;
 
1185
    size = 1 << log2size;
 
1186
    hipe_mfa_info_table.log2size = log2size;
 
1187
    hipe_mfa_info_table.mask = size - 1;
 
1188
    hipe_mfa_info_table.used = 0;
 
1189
    hipe_mfa_info_table.bucket = hipe_mfa_info_table_alloc_bucket(size);
 
1190
}
 
1191
 
 
1192
static inline struct hipe_mfa_info *hipe_mfa_info_table_get(Eterm m, Eterm f, unsigned int arity)
 
1193
{
 
1194
    unsigned long h;
 
1195
    unsigned int i;
 
1196
    struct hipe_mfa_info *p;
 
1197
 
 
1198
    h = HIPE_MFA_HASH(m, f, arity);
 
1199
    i = h & hipe_mfa_info_table.mask;
 
1200
    p = hipe_mfa_info_table.bucket[i];
 
1201
    for(; p; p = p->bucket.next)
 
1202
        /* XXX: do we want to compare p->bucket.hvalue as well? */
 
1203
        if (p->m == m && p->f == f && p->a == arity)
 
1204
            return p;
 
1205
    return NULL;
 
1206
}
 
1207
 
 
1208
#if 0 /* XXX: unused */
 
1209
void *hipe_mfa_find_na(Eterm m, Eterm f, unsigned int arity)
 
1210
{
 
1211
    const struct hipe_mfa_info *p;
 
1212
 
 
1213
    p = hipe_mfa_info_table_get(m, f, arity);
 
1214
    return p ? p->address : NULL;
 
1215
}
 
1216
#endif
 
1217
 
 
1218
static struct hipe_mfa_info *hipe_mfa_info_table_put(Eterm m, Eterm f, unsigned int arity)
 
1219
{
 
1220
    unsigned long h;
 
1221
    unsigned int i;
 
1222
    struct hipe_mfa_info *p;
 
1223
    unsigned int size;
 
1224
 
 
1225
    h = HIPE_MFA_HASH(m, f, arity);
 
1226
    i = h & hipe_mfa_info_table.mask;
 
1227
    p = hipe_mfa_info_table.bucket[i];
 
1228
    for(; p; p = p->bucket.next)
 
1229
        /* XXX: do we want to compare p->bucket.hvalue as well? */
 
1230
        if( p->m == m && p->f == f && p->a == arity )
 
1231
            return p;
 
1232
    p = hipe_mfa_info_table_alloc(m, f, arity);
 
1233
    p->bucket.hvalue = h;
 
1234
    p->bucket.next = hipe_mfa_info_table.bucket[i];
 
1235
    hipe_mfa_info_table.bucket[i] = p;
 
1236
    hipe_mfa_info_table.used += 1;
 
1237
    size = 1 << hipe_mfa_info_table.log2size;
 
1238
    if( hipe_mfa_info_table.used > (4*size/5) )         /* rehash at 80% */
 
1239
        hipe_mfa_info_table_grow();
 
1240
    return p;
 
1241
}
 
1242
 
 
1243
static void hipe_mfa_set_na(Eterm m, Eterm f, unsigned int arity, void *address, int is_exported)
 
1244
{
 
1245
    struct hipe_mfa_info *p = hipe_mfa_info_table_put(m, f, arity);
 
1246
#ifdef DEBUG_LINKER
 
1247
    printf("%s: ", __FUNCTION__);
 
1248
    print_mfa(m, f, arity);
 
1249
    printf(": changing address from %p to %p\r\n", p->local_address, address);
 
1250
#endif
 
1251
    p->local_address = address;
 
1252
    if (is_exported)
 
1253
        p->remote_address = address;
 
1254
}
 
1255
 
 
1256
#if defined(__powerpc__) || defined(__ppc__) || defined(__powerpc64__) || defined(__arm__)
 
1257
void *hipe_mfa_get_trampoline(Eterm m, Eterm f, unsigned int arity)
 
1258
{
 
1259
    struct hipe_mfa_info *p = hipe_mfa_info_table_put(m, f, arity);
 
1260
    return p->trampoline;
 
1261
}
 
1262
 
 
1263
void hipe_mfa_set_trampoline(Eterm m, Eterm f, unsigned int arity, void *trampoline)
 
1264
{
 
1265
    struct hipe_mfa_info *p = hipe_mfa_info_table_put(m, f, arity);
 
1266
    p->trampoline = trampoline;
 
1267
}
 
1268
#endif
 
1269
 
 
1270
BIF_RETTYPE hipe_bifs_set_funinfo_native_address_3(BIF_ALIST_3)
 
1271
{
 
1272
    struct mfa mfa;
 
1273
    void *address;
 
1274
    int is_exported;
 
1275
 
 
1276
    if (!term_to_mfa(BIF_ARG_1, &mfa))
 
1277
        BIF_ERROR(BIF_P, BADARG);
 
1278
    address = term_to_address(BIF_ARG_2);
 
1279
    if( !address )
 
1280
        BIF_ERROR(BIF_P, BADARG);
 
1281
    if (BIF_ARG_3 == am_true)
 
1282
        is_exported = 1;
 
1283
    else if (BIF_ARG_3 == am_false)
 
1284
        is_exported = 0;
 
1285
    else
 
1286
        BIF_ERROR(BIF_P, BADARG);
 
1287
    hipe_mfa_set_na(mfa.mod, mfa.fun, mfa.ari, address, is_exported);
 
1288
    BIF_RET(NIL);
 
1289
}
 
1290
 
 
1291
BIF_RETTYPE hipe_bifs_invalidate_funinfo_native_addresses_1(BIF_ALIST_1)
 
1292
{
 
1293
    Eterm lst;
 
1294
    struct mfa mfa;
 
1295
    struct hipe_mfa_info *p;
 
1296
 
 
1297
    lst = BIF_ARG_1;
 
1298
    while (is_list(lst)) {
 
1299
        if (!term_to_mfa(CAR(list_val(lst)), &mfa))
 
1300
            BIF_ERROR(BIF_P, BADARG);
 
1301
        lst = CDR(list_val(lst));
 
1302
        p = hipe_mfa_info_table_get(mfa.mod, mfa.fun, mfa.ari);
 
1303
        if (p) {
 
1304
            p->remote_address = NULL;
 
1305
            p->local_address = NULL;
 
1306
            if (p->beam_code) {
 
1307
#ifdef DEBUG_LINKER
 
1308
                printf("%s: ", __FUNCTION__);
 
1309
                print_mfa(mfa.mod, mfa.fun, mfa.ari);
 
1310
                printf(": removing call trap from BEAM pc %p (new op %#lx)\r\n",
 
1311
                       p->beam_code, p->orig_beam_op);
 
1312
#endif
 
1313
                p->beam_code[0] = p->orig_beam_op;
 
1314
                p->beam_code = NULL;
 
1315
                p->orig_beam_op = 0;
 
1316
            } else {
 
1317
#ifdef DEBUG_LINKER
 
1318
                printf("%s: ", __FUNCTION__);
 
1319
                print_mfa(mfa.mod, mfa.fun, mfa.ari);
 
1320
                printf(": no call trap to remove\r\n");
 
1321
#endif
 
1322
            }
 
1323
        }
 
1324
    }
 
1325
    if (is_not_nil(lst))
 
1326
        BIF_ERROR(BIF_P, BADARG);
 
1327
    BIF_RET(NIL);
 
1328
}
 
1329
 
 
1330
void hipe_mfa_save_orig_beam_op(Eterm mod, Eterm fun, unsigned int ari, Eterm *pc)
 
1331
{
 
1332
    Uint orig_beam_op;
 
1333
    struct hipe_mfa_info *p;
 
1334
 
 
1335
    orig_beam_op = pc[0];
 
1336
    if (orig_beam_op != BeamOpCode(op_hipe_trap_call_closure) &&
 
1337
        orig_beam_op != BeamOpCode(op_hipe_trap_call)) {
 
1338
        p = hipe_mfa_info_table_put(mod, fun, ari);
 
1339
#ifdef DEBUG_LINKER
 
1340
        printf("%s: ", __FUNCTION__);
 
1341
        print_mfa(mod, fun, ari);
 
1342
        printf(": saving orig op %#lx from BEAM pc %p\r\n", orig_beam_op, pc);
 
1343
#endif
 
1344
        p->beam_code = pc;
 
1345
        p->orig_beam_op = orig_beam_op;
 
1346
    } else {
 
1347
#ifdef DEBUG_LINKER
 
1348
        printf("%s: ", __FUNCTION__);
 
1349
        print_mfa(mod, fun, ari);
 
1350
        printf(": orig op %#lx already saved\r\n", orig_beam_op);
 
1351
#endif
 
1352
    }
 
1353
}
 
1354
 
 
1355
static void *hipe_make_stub(Eterm m, Eterm f, unsigned int arity, int is_remote)
 
1356
{
 
1357
    void *BEAMAddress;
 
1358
    void *StubAddress;
 
1359
 
 
1360
#if 0
 
1361
    if( is_not_atom(m) || is_not_atom(f) || arity > 255 )
 
1362
        return NULL;
 
1363
#endif
 
1364
    BEAMAddress = hipe_get_emu_address(m, f, arity, is_remote);
 
1365
    StubAddress = hipe_make_native_stub(BEAMAddress, arity);
 
1366
#if 0
 
1367
    hipe_mfa_set_na(m, f, arity, StubAddress);
 
1368
#endif
 
1369
    return StubAddress;
 
1370
}
 
1371
 
 
1372
static void *hipe_get_na_nofail(Eterm m, Eterm f, unsigned int a, int is_remote)
 
1373
{
 
1374
    struct hipe_mfa_info *p;
 
1375
    void *address;
 
1376
 
 
1377
    p = hipe_mfa_info_table_get(m, f, a);
 
1378
    if (p) {
 
1379
        /* find address, predicting for a runtime apply call */
 
1380
        address = p->remote_address;
 
1381
        if (!is_remote)
 
1382
            address = p->local_address;
 
1383
        if (address)
 
1384
            return address;
 
1385
 
 
1386
        /* bummer, install stub, checking if one already existed */
 
1387
        address = p->remote_address;
 
1388
        if (address)
 
1389
            return address;
 
1390
    } else {
 
1391
        p = hipe_mfa_info_table_put(m, f, a);
 
1392
    }
 
1393
    address = hipe_make_stub(m, f, a, is_remote);
 
1394
    /* XXX: how to tell if a BEAM MFA is exported or not? */
 
1395
    p->remote_address = address;
 
1396
    return address;
 
1397
}
 
1398
 
 
1399
/* used for apply/3 in hipe_mode_switch */
 
1400
void *hipe_get_remote_na(Eterm m, Eterm f, unsigned int a)
 
1401
{
 
1402
    if (is_not_atom(m) || is_not_atom(f) || a > 255)
 
1403
        return NULL;
 
1404
    return hipe_get_na_nofail(m, f, a, 1);
 
1405
}
 
1406
 
 
1407
/* primop, but called like a BIF for error handling purposes */
 
1408
BIF_RETTYPE hipe_find_na_or_make_stub(BIF_ALIST_3)
 
1409
{
 
1410
    Uint arity;
 
1411
    void *address;
 
1412
 
 
1413
    if( is_not_atom(BIF_ARG_1) || is_not_atom(BIF_ARG_2) )
 
1414
        BIF_ERROR(BIF_P, BADARG);
 
1415
    arity = unsigned_val(BIF_ARG_3); /* no error check */
 
1416
    address = hipe_get_na_nofail(BIF_ARG_1, BIF_ARG_2, arity, 1);
 
1417
    BIF_RET((Eterm)address);    /* semi-Ok */
 
1418
}
 
1419
 
 
1420
BIF_RETTYPE hipe_bifs_find_na_or_make_stub_2(BIF_ALIST_2)
 
1421
{
 
1422
    struct mfa mfa;
 
1423
    void *address;
 
1424
    int is_remote;
 
1425
 
 
1426
    if (!term_to_mfa(BIF_ARG_1, &mfa))
 
1427
        BIF_ERROR(BIF_P, BADARG);
 
1428
    if (BIF_ARG_2 == am_true)
 
1429
        is_remote = 1;
 
1430
    else if (BIF_ARG_2 == am_false)
 
1431
        is_remote = 0;
 
1432
    else
 
1433
        BIF_ERROR(BIF_P, BADARG);
 
1434
    address = hipe_get_na_nofail(mfa.mod, mfa.fun, mfa.ari, is_remote);
 
1435
    BIF_RET(address_to_term(address, BIF_P));
 
1436
}
 
1437
 
 
1438
/* primop, but called like a BIF for error handling purposes */
 
1439
BIF_RETTYPE hipe_nonclosure_address(BIF_ALIST_2)
 
1440
{
 
1441
    Eterm hdr, m, f;
 
1442
    void *address;
 
1443
 
 
1444
    if (!is_boxed(BIF_ARG_1))
 
1445
        goto badfun;
 
1446
    hdr = *boxed_val(BIF_ARG_1);
 
1447
    if (is_export_header(hdr)) {
 
1448
        Export *ep = (Export*)(export_val(BIF_ARG_1)[1]);
 
1449
        unsigned int actual_arity = ep->code[2];
 
1450
        if (actual_arity != BIF_ARG_2)
 
1451
            goto badfun;
 
1452
        m = ep->code[0];
 
1453
        f = ep->code[1];
 
1454
    } else if (hdr == make_arityval(2)) {
 
1455
        Eterm *tp = tuple_val(BIF_ARG_1);
 
1456
        m = tp[1];
 
1457
        f = tp[2];
 
1458
        if (is_not_atom(m) || is_not_atom(f))
 
1459
            goto badfun;
 
1460
        if (!erts_find_export_entry(m, f, BIF_ARG_2))
 
1461
            goto badfun;
 
1462
    } else
 
1463
        goto badfun;
 
1464
    address = hipe_get_na_nofail(m, f, BIF_ARG_2, 1);
 
1465
    BIF_RET((Eterm)address);
 
1466
 
 
1467
 badfun:
 
1468
    BIF_P->current = NULL;
 
1469
    BIF_P->fvalue = BIF_ARG_1;
 
1470
    BIF_ERROR(BIF_P, EXC_BADFUN);
 
1471
}
 
1472
 
 
1473
/*
 
1474
 * Patch Reference Handling.
 
1475
 */
 
1476
struct hipe_mfa_info_list {
 
1477
    struct hipe_mfa_info *mfa;
 
1478
    struct hipe_mfa_info_list *next;
 
1479
};
 
1480
 
 
1481
struct ref {
 
1482
    struct hipe_mfa_info *caller_mfa;
 
1483
    void *address;
 
1484
    void *trampoline;
 
1485
    unsigned int flags;
 
1486
    struct ref *next;
 
1487
};
 
1488
#define REF_FLAG_IS_LOAD_MFA            1       /* bit 0: 0 == call, 1 == load_mfa */
 
1489
#define REF_FLAG_IS_REMOTE              2       /* bit 1: 0 == local, 1 == remote */
 
1490
#define REF_FLAG_PENDING_REDIRECT       4       /* bit 2: 1 == pending redirect */
 
1491
#define REF_FLAG_PENDING_REMOVE         8       /* bit 3: 1 == pending remove */
 
1492
 
 
1493
/* add_ref(CalleeMFA, {CallerMFA,Address,'call'|'load_mfa',Trampoline,'remote'|'local'})
 
1494
 */
 
1495
BIF_RETTYPE hipe_bifs_add_ref_2(BIF_ALIST_2)
 
1496
{
 
1497
    struct mfa callee;
 
1498
    Eterm *tuple;
 
1499
    struct mfa caller;
 
1500
    void *address;
 
1501
    void *trampoline;
 
1502
    unsigned int flags;
 
1503
    struct hipe_mfa_info *callee_mfa;
 
1504
    struct hipe_mfa_info *caller_mfa;
 
1505
    struct hipe_mfa_info_list *refers_to;
 
1506
    struct ref *ref;
 
1507
 
 
1508
    if (!term_to_mfa(BIF_ARG_1, &callee))
 
1509
        goto badarg;
 
1510
    if (is_not_tuple(BIF_ARG_2))
 
1511
        goto badarg;
 
1512
    tuple = tuple_val(BIF_ARG_2);
 
1513
    if (tuple[0] != make_arityval(5))
 
1514
        goto badarg;
 
1515
    if (!term_to_mfa(tuple[1], &caller))
 
1516
        goto badarg;
 
1517
    address = term_to_address(tuple[2]);
 
1518
    if (!address)
 
1519
        goto badarg;
 
1520
    switch (tuple[3]) {
 
1521
      case am_call:
 
1522
        flags = 0;
 
1523
        break;
 
1524
      case am_load_mfa:
 
1525
        flags = REF_FLAG_IS_LOAD_MFA;
 
1526
        break;
 
1527
      default:
 
1528
        goto badarg;
 
1529
    }
 
1530
    if (is_nil(tuple[4]))
 
1531
        trampoline = NULL;
 
1532
    else {
 
1533
        trampoline = term_to_address(tuple[4]);
 
1534
        if (!trampoline)
 
1535
            goto badarg;
 
1536
    }
 
1537
    switch (tuple[5]) {
 
1538
      case am_local:
 
1539
        break;
 
1540
      case am_remote:
 
1541
        flags |= REF_FLAG_IS_REMOTE;
 
1542
        break;
 
1543
      default:
 
1544
        goto badarg;
 
1545
    }
 
1546
    callee_mfa = hipe_mfa_info_table_put(callee.mod, callee.fun, callee.ari);
 
1547
    caller_mfa = hipe_mfa_info_table_put(caller.mod, caller.fun, caller.ari);
 
1548
 
 
1549
    refers_to = erts_alloc(ERTS_ALC_T_HIPE, sizeof(*refers_to));
 
1550
    refers_to->mfa = callee_mfa;
 
1551
    refers_to->next = caller_mfa->refers_to;
 
1552
    caller_mfa->refers_to = refers_to;
 
1553
 
 
1554
    ref = erts_alloc(ERTS_ALC_T_HIPE, sizeof(*ref));
 
1555
    ref->caller_mfa = caller_mfa;
 
1556
    ref->address = address;
 
1557
    ref->trampoline = trampoline;
 
1558
    ref->flags = flags;
 
1559
    ref->next = callee_mfa->referred_from;
 
1560
    callee_mfa->referred_from = ref;
 
1561
 
 
1562
    BIF_RET(NIL);
 
1563
 
 
1564
 badarg:
 
1565
    BIF_ERROR(BIF_P, BADARG);   
 
1566
}
 
1567
 
 
1568
/* Given a CalleeMFA, mark each ref to it as pending-redirect.
 
1569
 * This ensures that remove_refs_from() won't remove them: any
 
1570
 * removal is instead done at the end of redirect_referred_from().
 
1571
 */
 
1572
BIF_RETTYPE hipe_bifs_mark_referred_from_1(BIF_ALIST_1) /* get_refs_from */
 
1573
{
 
1574
    struct mfa mfa;
 
1575
    const struct hipe_mfa_info *p;
 
1576
    struct ref *ref;
 
1577
 
 
1578
    if (!term_to_mfa(BIF_ARG_1, &mfa))
 
1579
        BIF_ERROR(BIF_P, BADARG);
 
1580
    p = hipe_mfa_info_table_get(mfa.mod, mfa.fun, mfa.ari);
 
1581
    if (p)
 
1582
        for(ref = p->referred_from; ref != NULL; ref = ref->next)
 
1583
            ref->flags |= REF_FLAG_PENDING_REDIRECT;
 
1584
    BIF_RET(NIL);
 
1585
}
 
1586
 
 
1587
BIF_RETTYPE hipe_bifs_remove_refs_from_1(BIF_ALIST_1)
 
1588
{
 
1589
    struct mfa mfa;
 
1590
    struct hipe_mfa_info *caller_mfa, *callee_mfa;
 
1591
    struct hipe_mfa_info_list *refers_to, *tmp_refers_to;
 
1592
    struct ref **prev, *ref;
 
1593
 
 
1594
    if (!term_to_mfa(BIF_ARG_1, &mfa))
 
1595
        BIF_ERROR(BIF_P, BADARG);
 
1596
    caller_mfa = hipe_mfa_info_table_get(mfa.mod, mfa.fun, mfa.ari);
 
1597
    if (caller_mfa) {
 
1598
        refers_to = caller_mfa->refers_to;
 
1599
        while (refers_to) {
 
1600
            callee_mfa = refers_to->mfa;
 
1601
            prev = &callee_mfa->referred_from;
 
1602
            ref = *prev;
 
1603
            while (ref) {
 
1604
                if (ref->caller_mfa == caller_mfa) {
 
1605
                    if (ref->flags & REF_FLAG_PENDING_REDIRECT) {
 
1606
                        ref->flags |= REF_FLAG_PENDING_REMOVE;
 
1607
                        prev = &ref->next;
 
1608
                        ref = ref->next;
 
1609
                    } else {
 
1610
                        struct ref *tmp = ref;
 
1611
                        ref = ref->next;
 
1612
                        *prev = ref;
 
1613
                        erts_free(ERTS_ALC_T_HIPE, tmp);
 
1614
                    }
 
1615
                } else {
 
1616
                    prev = &ref->next;
 
1617
                    ref = ref->next;
 
1618
                }
 
1619
            }
 
1620
            tmp_refers_to = refers_to;
 
1621
            refers_to = refers_to->next;
 
1622
            erts_free(ERTS_ALC_T_HIPE, tmp_refers_to);
 
1623
        }
 
1624
        caller_mfa->refers_to = NULL;
 
1625
    }
 
1626
    BIF_RET(NIL);
 
1627
}
 
1628
 
 
1629
/* redirect_referred_from(CalleeMFA)
 
1630
 * Redirect all pending-redirect refs in CalleeMFA's referred_from.
 
1631
 * Then remove any pending-redirect && pending-remove refs from CalleeMFA's referred_from.
 
1632
 */
 
1633
BIF_RETTYPE hipe_bifs_redirect_referred_from_1(BIF_ALIST_1)
 
1634
{
 
1635
    struct mfa mfa;
 
1636
    struct hipe_mfa_info *p;
 
1637
    struct ref **prev, *ref;
 
1638
    int is_remote, res;
 
1639
    void *new_address;
 
1640
 
 
1641
    if (!term_to_mfa(BIF_ARG_1, &mfa))
 
1642
        BIF_ERROR(BIF_P, BADARG);
 
1643
    p = hipe_mfa_info_table_get(mfa.mod, mfa.fun, mfa.ari);
 
1644
    if (p) {
 
1645
        prev = &p->referred_from;
 
1646
        ref = *prev;
 
1647
        while (ref) {
 
1648
            if (ref->flags & REF_FLAG_PENDING_REDIRECT) {
 
1649
                is_remote = ref->flags & REF_FLAG_IS_REMOTE;
 
1650
                new_address = hipe_get_na_nofail(p->m, p->f, p->a, is_remote);
 
1651
                if (ref->flags & REF_FLAG_IS_LOAD_MFA)
 
1652
                    res = hipe_patch_insn(ref->address, (Uint)new_address, am_load_mfa);
 
1653
                else
 
1654
                    res = hipe_patch_call(ref->address, new_address, ref->trampoline);
 
1655
                if (res)
 
1656
                    fprintf(stderr, "%s: patch failed\r\n", __FUNCTION__);
 
1657
                ref->flags &= ~REF_FLAG_PENDING_REDIRECT;
 
1658
                if (ref->flags & REF_FLAG_PENDING_REMOVE) {
 
1659
                    struct ref *tmp = ref;
 
1660
                    ref = ref->next;
 
1661
                    *prev = ref;
 
1662
                    erts_free(ERTS_ALC_T_HIPE, tmp);
 
1663
                } else {
 
1664
                    prev = &ref->next;
 
1665
                    ref = ref->next;
 
1666
                }
 
1667
            } else {
 
1668
                prev = &ref->next;
 
1669
                ref = ref->next;
 
1670
            }
 
1671
        }
 
1672
    }
 
1673
    BIF_RET(NIL);
 
1674
}
 
1675
 
 
1676
BIF_RETTYPE hipe_bifs_check_crc_1(BIF_ALIST_1)
 
1677
{
 
1678
    Uint crc;
 
1679
 
 
1680
    if (!term_to_Uint(BIF_ARG_1, &crc))
 
1681
        BIF_ERROR(BIF_P, BADARG);
 
1682
    if (crc == HIPE_SYSTEM_CRC)
 
1683
        BIF_RET(am_true);
 
1684
    BIF_RET(am_false);
 
1685
}
 
1686
 
 
1687
BIF_RETTYPE hipe_bifs_system_crc_1(BIF_ALIST_1)
 
1688
{
 
1689
    Uint crc;
 
1690
 
 
1691
    if (!term_to_Uint(BIF_ARG_1, &crc))
 
1692
        BIF_ERROR(BIF_P, BADARG);
 
1693
    crc ^= (HIPE_SYSTEM_CRC ^ HIPE_LITERALS_CRC);
 
1694
    BIF_RET(Uint_to_term(crc, BIF_P));
 
1695
}
 
1696
 
 
1697
BIF_RETTYPE hipe_bifs_get_rts_param_1(BIF_ALIST_1)
 
1698
{
 
1699
    unsigned int is_defined;
 
1700
    unsigned long value;
 
1701
 
 
1702
    if( is_not_small(BIF_ARG_1) )
 
1703
        BIF_ERROR(BIF_P, BADARG);
 
1704
    is_defined = 1;
 
1705
    value = 0;
 
1706
    switch( unsigned_val(BIF_ARG_1) ) {
 
1707
        RTS_PARAMS_CASES
 
1708
      default:
 
1709
        BIF_ERROR(BIF_P, BADARG);
 
1710
    }
 
1711
    if( !is_defined )
 
1712
        BIF_RET(NIL);
 
1713
    BIF_RET(Uint_to_term(value, BIF_P));
 
1714
}
 
1715
 
 
1716
void hipe_patch_address(Uint *address, Eterm patchtype, Uint value)
1119
1717
{
1120
1718
    switch( patchtype ) {
1121
 
#if defined(__i386__)
1122
 
      case am_address:
1123
 
        {       /* address points to a disp32 or imm32 operand */
1124
 
            *address = value;
1125
 
            return 1;
1126
 
        }
1127
 
#endif
1128
 
#if defined(__sparc__)
1129
 
      case am_sethi:
1130
 
        {        /* address points to a SETHI insn */
1131
 
            unsigned int high22 = value >> 10;
1132
 
            unsigned int sethi_insn = *address;
1133
 
            *address = (sethi_insn & 0xFFC00000) | high22;
1134
 
            /* Flush the I-cache. */
1135
 
            asm volatile("flush %0"
1136
 
                         : /* no outputs */
1137
 
                         : "r"(address)
1138
 
                         : "memory");
1139
 
            return 1;
1140
 
        }
1141
 
      case am_or:
1142
 
        {       /* address points to an OR reg,imm,reg insn */
1143
 
            unsigned int low10 = value & 0x3FF;
1144
 
            unsigned int or_insn = *address;
1145
 
            *address = (or_insn & 0xFFFFE000) | low10;
1146
 
            /* Flush the I-cache. */
1147
 
            asm volatile("flush %0"
1148
 
                         : /* no outputs */
1149
 
                         : "r"(address)
1150
 
                         : "memory");
1151
 
            return 1;
1152
 
        }
1153
 
#endif
 
1719
      case am_load_fe:
 
1720
        hipe_patch_load_fe(address, value);
 
1721
        return;
1154
1722
      default:
1155
 
        {
1156
 
            fprintf(stderr, "hipe_patch_address: unknown patchtype %#lx\r\n",
1157
 
                    patchtype);
1158
 
            return 0;
1159
 
        }
1160
 
    }
1161
 
}
1162
 
 
1163
 
BIF_RETTYPE hipe_bifs_check_crc_1(BIF_ALIST_1)
1164
 
{
1165
 
    Uint crc;
1166
 
 
1167
 
    term_to_Uint(BIF_ARG_1, &crc);
1168
 
    if( !crc )
1169
 
        BIF_ERROR(BIF_P, BADARG);
1170
 
    if( crc == HIPE_SYSTEM_CRC )
1171
 
        BIF_RET(am_true);
1172
 
    BIF_RET(am_false);
 
1723
        fprintf(stderr, "%s: unknown patchtype %#lx\r\n",
 
1724
                __FUNCTION__, patchtype);
 
1725
        return;
 
1726
    }
 
1727
}
 
1728
 
 
1729
struct modinfo {
 
1730
    HashBucket bucket;          /* bucket.hvalue == atom_val(the module name) */
 
1731
    unsigned int code_size;
 
1732
};
 
1733
 
 
1734
static Hash modinfo_table;
 
1735
 
 
1736
static HashValue modinfo_hash(void *tmpl)
 
1737
{
 
1738
    Eterm mod = (Eterm)tmpl;
 
1739
    return atom_val(mod);
 
1740
}
 
1741
 
 
1742
static int modinfo_cmp(void *tmpl, void *bucket)
 
1743
{
 
1744
    /* bucket->hvalue == modinfo_hash(tmpl), so just return 0 (match) */
 
1745
    return 0;
 
1746
}
 
1747
 
 
1748
static void *modinfo_alloc(void *tmpl)
 
1749
{
 
1750
    struct modinfo *p;
 
1751
 
 
1752
    p = (struct modinfo*)erts_alloc(ERTS_ALC_T_HIPE, sizeof(*p));
 
1753
    p->code_size = 0;
 
1754
    return &p->bucket;
 
1755
}
 
1756
 
 
1757
static void init_modinfo_table(void)
 
1758
{
 
1759
    HashFunctions f;
 
1760
    static int init_done = 0;
 
1761
 
 
1762
    if (init_done)
 
1763
        return;
 
1764
    init_done = 1;
 
1765
    f.hash = (H_FUN) modinfo_hash;
 
1766
    f.cmp = (HCMP_FUN) modinfo_cmp;
 
1767
    f.alloc = (HALLOC_FUN) modinfo_alloc;
 
1768
    f.free = (HFREE_FUN) NULL;
 
1769
    hash_init(ERTS_ALC_T_HIPE, &modinfo_table, "modinfo_table", 11, f);
 
1770
}
 
1771
 
 
1772
BIF_RETTYPE hipe_bifs_update_code_size_3(BIF_ALIST_3)
 
1773
{
 
1774
    struct modinfo *p;
 
1775
    Sint code_size;
 
1776
    
 
1777
    init_modinfo_table();
 
1778
 
 
1779
    if (is_not_atom(BIF_ARG_1) ||
 
1780
        is_not_small(BIF_ARG_3) ||
 
1781
        (code_size = signed_val(BIF_ARG_3)) < 0)
 
1782
        BIF_ERROR(BIF_P, BADARG);
 
1783
 
 
1784
    p = (struct modinfo*)hash_put(&modinfo_table, (void*)BIF_ARG_1);
 
1785
 
 
1786
    if (is_nil(BIF_ARG_2))      /* some MFAs, not whole module */
 
1787
        p->code_size += code_size;
 
1788
    else                        /* whole module */
 
1789
        p->code_size = code_size;
 
1790
    BIF_RET(NIL);
 
1791
}
 
1792
 
 
1793
BIF_RETTYPE hipe_bifs_code_size_1(BIF_ALIST_1)
 
1794
{
 
1795
    struct modinfo *p;
 
1796
    unsigned int code_size;
 
1797
 
 
1798
    init_modinfo_table();
 
1799
 
 
1800
    if (is_not_atom(BIF_ARG_1))
 
1801
        BIF_ERROR(BIF_P, BADARG);
 
1802
 
 
1803
    p = (struct modinfo*)hash_get(&modinfo_table, (void*)BIF_ARG_1);
 
1804
 
 
1805
    code_size = p ? p->code_size : 0;
 
1806
    BIF_RET(make_small(code_size));
 
1807
}
 
1808
 
 
1809
BIF_RETTYPE hipe_bifs_patch_insn_3(BIF_ALIST_3)
 
1810
{
 
1811
    Uint *address, value;
 
1812
 
 
1813
    address = term_to_address(BIF_ARG_1);
 
1814
    if (!address)
 
1815
        BIF_ERROR(BIF_P, BADARG);
 
1816
    if (!term_to_Uint(BIF_ARG_2, &value))
 
1817
        BIF_ERROR(BIF_P, BADARG);
 
1818
    if (hipe_patch_insn(address, value, BIF_ARG_3))
 
1819
        BIF_ERROR(BIF_P, BADARG);
 
1820
    BIF_RET(NIL);
 
1821
}
 
1822
 
 
1823
BIF_RETTYPE hipe_bifs_patch_call_3(BIF_ALIST_3)
 
1824
{
 
1825
    Uint *callAddress, *destAddress, *trampAddress;
 
1826
 
 
1827
    callAddress = term_to_address(BIF_ARG_1);
 
1828
    if (!callAddress)
 
1829
        BIF_ERROR(BIF_P, BADARG);
 
1830
    destAddress = term_to_address(BIF_ARG_2);
 
1831
    if (!destAddress)
 
1832
        BIF_ERROR(BIF_P, BADARG);
 
1833
    if (is_nil(BIF_ARG_3))
 
1834
        trampAddress = NULL;
 
1835
    else {
 
1836
        trampAddress = term_to_address(BIF_ARG_3);
 
1837
        if (!trampAddress)
 
1838
            BIF_ERROR(BIF_P, BADARG);
 
1839
    }
 
1840
    if (hipe_patch_call(callAddress, destAddress, trampAddress))
 
1841
        BIF_ERROR(BIF_P, BADARG);
 
1842
    BIF_RET(NIL);
1173
1843
}