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

« back to all changes in this revision

Viewing changes to erts/emulator/beam/beam_load.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:
35
35
#include "erl_binary.h"
36
36
 
37
37
#ifdef HIPE
 
38
#include "hipe_bif0.h"
38
39
#include "hipe_mode_switch.h"
39
 
#include "hipe_bif0.h"
 
40
#include "hipe_arch.h"
40
41
#endif
41
42
 
42
43
/* Imported from drv/gzio.c. Why not in any header file? */
78
79
    Uint patches;               /* Index (into code buffer) to first location
79
80
                                 * which must be patched with the value of this label.
80
81
                                 */
 
82
#ifdef ERTS_SMP
 
83
    Uint looprec_targeted;      /* Non-zero if this label is the target of a loop_rec
 
84
                                 * instruction.
 
85
                                 */
 
86
#endif
81
87
} Label;
82
88
 
83
89
/*
112
118
} GenOpBlock;
113
119
 
114
120
/*
115
 
 * This structure contains information for a imported function or BIF.
 
121
 * This structure contains information for an imported function or BIF.
116
122
 */
117
123
typedef struct {
118
124
    Eterm module;               /* Tagged atom for module. */
234
240
    int ci;                     /* Current index into loaded code. */
235
241
    Label* labels;
236
242
    Uint put_strings;           /* Linked list of put_string instructions. */
237
 
    Uint bs_put_strings;        /* Linked list of bs_put_string instructions. */
 
243
#if !defined(HEAP_FRAG_ELIM_TEST)
 
244
    Uint bs_put_strings;        /* Linked list of i_bs_put_string instructions. */
 
245
#endif
 
246
    Uint new_bs_put_strings;    /* Linked list of i_new_bs_put_string instructions. */
238
247
    Uint catches;               /* Linked list of catch_yf instructions. */
239
248
    unsigned loaded_size;       /* Final size of code when loaded. */
240
249
    byte mod_md5[16];           /* MD5 for module code. */
280
289
    /*
281
290
     * Bit syntax.
282
291
     */
 
292
    int new_instructions;       /* New instructions are currently used. */
283
293
 
284
 
    int generate_heap_bin;      /* Safe to generate a heap bin. */
 
294
    /*
 
295
     * Floating point.
 
296
     */
 
297
    int new_float_instructions; /* New allocation scheme for floating point. */
285
298
} LoaderState;
286
299
 
287
300
typedef struct {
415
428
  } while (0)
416
429
 
417
430
 
418
 
static int bin_load(Eterm group_leader, Eterm* modp, byte* bytes, int unloaded_size);
 
431
static int bin_load(Process *c_p, Uint32 c_p_locks,
 
432
                    Eterm group_leader, Eterm* modp, byte* bytes, int unloaded_size);
419
433
static void init_state(LoaderState* stp);
420
 
static int insert_new_code(Eterm group_leader, Eterm module,
 
434
static int insert_new_code(Process *c_p, Uint32 c_p_locks,
 
435
                           Eterm group_leader, Eterm module,
421
436
                           Eterm* code, Uint size, Uint catches);
422
437
static int scan_iff_file(LoaderState* stp, Uint* chunk_types,
423
438
                         Uint num_types, Uint num_mandatory);
439
454
                               GenOpArg Size, GenOpArg* Rest);
440
455
static GenOp* gen_func_info(LoaderState* stp, GenOpArg mod, GenOpArg Func,
441
456
                            GenOpArg arity, GenOpArg label);
 
457
#if defined(HEAP_FRAG_ELIM_TEST)
 
458
static GenOp*
 
459
gen_guard_bif(LoaderState* stp, GenOpArg Fail, GenOpArg Live, GenOpArg Bif,
 
460
              GenOpArg Src, GenOpArg Dst);
 
461
#endif
 
462
 
442
463
static int freeze_code(LoaderState* stp);
443
464
 
444
465
static void final_touch(LoaderState* stp);
503
524
}
504
525
 
505
526
int
506
 
erts_load_module(Eterm group_leader, /* Group leader or NIL if none. */
 
527
erts_load_module(Process *c_p,
 
528
                 Uint32 c_p_locks,
 
529
                 Eterm group_leader, /* Group leader or NIL if none. */
507
530
                 Eterm* modp,   /*
508
531
                                 * Module name as an atom (NIL to not check).
509
532
                                 * On return, contains the actual module name.
514
537
    ErlDrvBinary* bin;
515
538
    int result;
516
539
 
517
 
    if ((bin = (ErlDrvBinary *) gzinflate_buffer(code, size)) == NULL) {
518
 
        return -1;
 
540
    if (size >= 4 && code[0] == 'F' && code[1] == 'O' &&
 
541
        code[2] == 'R' && code[3] == '1') {
 
542
        /*
 
543
         * The BEAM module is not compressed.
 
544
         */
 
545
        result = bin_load(c_p, c_p_locks, group_leader, modp, code, size);
 
546
    } else {
 
547
        /*
 
548
         * The BEAM module is compressed (or possibly invalid/corrupted).
 
549
         */
 
550
        if ((bin = (ErlDrvBinary *) gzinflate_buffer((char*)code, size)) == NULL) {
 
551
            return -1;
 
552
        }
 
553
        result = bin_load(c_p, c_p_locks, group_leader, modp,
 
554
                          (byte*)bin->orig_bytes, bin->orig_size);
 
555
        driver_free_binary(bin);
519
556
    }
520
 
    result = bin_load(group_leader, modp, bin->orig_bytes, bin->orig_size);
521
 
    driver_free_binary(bin);
522
557
    return result;
523
558
}
524
559
 
525
560
 
526
561
static int
527
 
bin_load(Eterm group_leader, Eterm* modp, byte* bytes, int unloaded_size)
 
562
bin_load(Process *c_p, Uint32 c_p_locks,
 
563
         Eterm group_leader, Eterm* modp, byte* bytes, int unloaded_size)
528
564
{
529
565
    LoaderState state;
530
566
    int rval = -1;
608
644
     * exported and imported functions.  This can't fail.
609
645
     */
610
646
    
611
 
    rval = insert_new_code(state.group_leader, state.module,
 
647
    rval = insert_new_code(c_p, c_p_locks, state.group_leader, state.module,
612
648
                           state.code, state.loaded_size, state.catches);
613
649
    if (rval < 0) {
614
650
        goto load_error;
675
711
    stp->lambdas_allocated = sizeof(stp->def_lambdas)/sizeof(Lambda);
676
712
    stp->lambdas = stp->def_lambdas;
677
713
    stp->lambda_error = NULL;
678
 
    stp->generate_heap_bin = 0;
 
714
    stp->new_float_instructions = 0;
679
715
}
680
716
 
681
717
static int
682
 
insert_new_code(Eterm group_leader, Eterm module, Eterm* code, Uint size, Uint catches)
 
718
insert_new_code(Process *c_p, Uint32 c_p_locks,
 
719
                Eterm group_leader, Eterm module, Eterm* code, Uint size, Uint catches)
683
720
{
684
721
    Module* modp;
685
722
    int rval;
686
723
    int i;
687
724
 
688
 
    if ((rval = beam_make_current_old(module)) < 0) {
689
 
        cerr_pos = 0;
690
 
        erl_printf(CBUF, "Module ");
691
 
        print_atom(atom_val(module), CBUF);
692
 
        erl_printf(CBUF, " must be purged before loading\n");
693
 
        send_error_to_logger(group_leader);
 
725
    if ((rval = beam_make_current_old(c_p, c_p_locks, module)) < 0) {
 
726
        erts_dsprintf_buf_t *dsbufp = erts_create_logger_dsbuf();
 
727
        erts_dsprintf(dsbufp,
 
728
                      "Module %T must be purged before loading\n",
 
729
                      module);
 
730
        erts_send_error_to_logger(group_leader, dsbufp);
694
731
        return rval;
695
732
    }
696
733
 
889
926
 
890
927
        GetByte(stp, n);
891
928
        GetString(stp, atom, n);
892
 
        stp->atom[i] = am_atom_put(atom, n);
 
929
        stp->atom[i] = am_atom_put((char*)atom, n);
893
930
    }
894
931
 
895
932
    /*
970
1007
static int
971
1008
read_export_table(LoaderState* stp)
972
1009
{
 
1010
    static struct {
 
1011
        Eterm mod;
 
1012
        Eterm func;
 
1013
        int arity;
 
1014
    } allow_redef[] = {
 
1015
        /* The BIFs that are allowed to be redefined by Erlang code */
 
1016
        {am_erlang,am_apply,2},
 
1017
        {am_erlang,am_apply,3},
 
1018
    };
973
1019
    int i;
974
1020
 
975
1021
    GetInt(stp, 4, stp->num_exps);
984
1030
    for (i = 0; i < stp->num_exps; i++) {
985
1031
        Uint n;
986
1032
        Uint value;
 
1033
        Eterm func;
 
1034
        Uint arity;
 
1035
        Export* e;
987
1036
 
988
1037
        GetInt(stp, 4, n);
989
 
        GetAtom(stp, n, stp->export[i].function);
990
 
        GetInt(stp, 4, n);
991
 
        if (n > MAX_REG) {
992
 
            LoadError2(stp, "export table entry %d: absurdly high arity %d", i, n);
 
1038
        GetAtom(stp, n, func);
 
1039
        stp->export[i].function = func;
 
1040
        GetInt(stp, 4, arity);
 
1041
        if (arity > MAX_REG) {
 
1042
            LoadError2(stp, "export table entry %d: absurdly high arity %d", i, arity);
993
1043
        }
994
 
        stp->export[i].arity = n;
 
1044
        stp->export[i].arity = arity;
995
1045
        GetInt(stp, 4, n);
996
1046
        if (n >= stp->num_labels) {
997
1047
            LoadError3(stp, "export table entry %d: invalid label %d (highest defined label is %d)", i, n, stp->num_labels);
1001
1051
            LoadError2(stp, "export table entry %d: label %d not resolved", i, n);
1002
1052
        }
1003
1053
        stp->export[i].address = stp->code + value;
 
1054
 
 
1055
        /*
 
1056
         * Check that we are not redefining a BIF (except the ones allowed to
 
1057
         * redefine).
 
1058
         */
 
1059
        if ((e = erts_find_export_entry(stp->module, func, arity)) != NULL) {
 
1060
            if (e->code[3] == (Uint) em_apply_bif) {
 
1061
                int j;
 
1062
 
 
1063
                for (j = 0; j < sizeof(allow_redef)/sizeof(allow_redef[0]); j++) {
 
1064
                    if (stp->module == allow_redef[j].mod &&
 
1065
                        func == allow_redef[j].func &&
 
1066
                        arity == allow_redef[j].arity) {
 
1067
                        break;
 
1068
                    }
 
1069
                }
 
1070
                if (j == sizeof(allow_redef)/sizeof(allow_redef[0])) {
 
1071
                    LoadError2(stp, "exported function %T/%d redefines BIF",
 
1072
                               func, arity);
 
1073
                }
 
1074
            }
 
1075
        }
1004
1076
    }
1005
1077
    return 1;
1006
1078
 
1103
1175
    for (i = 0; i < stp->num_labels; i++) {
1104
1176
        stp->labels[i].value = 0;
1105
1177
        stp->labels[i].patches = 0;
 
1178
#ifdef ERTS_SMP
 
1179
        stp->labels[i].looprec_targeted = 0;
 
1180
#endif
1106
1181
    }
1107
1182
 
1108
1183
    /*
1122
1197
    stp->code[MI_NUM_BREAKPOINTS] = 0;
1123
1198
 
1124
1199
    stp->put_strings = 0;
 
1200
#if !defined(HEAP_FRAG_ELIM_TEST)
1125
1201
    stp->bs_put_strings = 0;
 
1202
#endif
 
1203
    stp->new_bs_put_strings = 0;
1126
1204
    stp->catches = 0;
1127
1205
    return 1;
1128
1206
 
1231
1309
            switch (last_op->a[arg].type) {
1232
1310
            case TAG_i:
1233
1311
                if ((first & 0x08) == 0) {
1234
 
                    last_op->a[arg].val = make_small(first >> 4);
 
1312
                    last_op->a[arg].val = first >> 4;
1235
1313
                } else if ((first & 0x10) == 0) {
1236
1314
                    Uint w;
1237
1315
                    GetByte(stp, w);
1238
1316
                    ASSERT(first < 0x800);
1239
 
                    last_op->a[arg].val = make_small(((first >> 5) << 8) | w);
 
1317
                    last_op->a[arg].val = ((first >> 5) << 8) | w;
1240
1318
                } else {
1241
1319
                    int i = get_erlang_integer(stp, first, &(last_op->a[arg].val));
1242
1320
                    if (i < 0) {
1252
1330
                GetValue(stp, first, last_op->a[arg].val);
1253
1331
                if (last_op->a[arg].val == 0) {
1254
1332
                    last_op->a[arg].type = TAG_r;
 
1333
                } else if (last_op->a[arg].val >= MAX_REG) {
 
1334
                    LoadError1(stp, "invalid x register number: %u",
 
1335
                               last_op->a[arg].val);
1255
1336
                }
1256
1337
                break;
1257
1338
            case TAG_y:
1258
1339
                GetValue(stp, first, last_op->a[arg].val);
 
1340
                if (last_op->a[arg].val >= MAX_REG) {
 
1341
                    LoadError1(stp, "invalid y register number: %u",
 
1342
                               last_op->a[arg].val);
 
1343
                }
1259
1344
                last_op->a[arg].val += CP_SIZE;
1260
1345
                break;
1261
1346
            case TAG_a:
1333
1418
                        VerifyTag(stp, tag, TAG_u);
1334
1419
                        last_op->a[arg].type = TAG_l;
1335
1420
                        break;
 
1421
                    case 3:     /* Allocation list. */
 
1422
                        {
 
1423
                            Uint n;
 
1424
                            Uint type;
 
1425
                            Uint val;
 
1426
                            Uint words = 0;
 
1427
                            
 
1428
                            stp->new_float_instructions = 1;
 
1429
                            GetTagAndValue(stp, tag, n);
 
1430
                            VerifyTag(stp, tag, TAG_u);
 
1431
                            while (n-- > 0) {
 
1432
                                GetTagAndValue(stp, tag, type);
 
1433
                                VerifyTag(stp, tag, TAG_u);
 
1434
                                GetTagAndValue(stp, tag, val);
 
1435
                                VerifyTag(stp, tag, TAG_u);
 
1436
                                switch (type) {
 
1437
                                case 0: /* Heap words */
 
1438
                                    words += val;
 
1439
                                    break;
 
1440
                                case 1:
 
1441
                                    words += FLOAT_SIZE_OBJECT*val;
 
1442
                                    break;
 
1443
                                default:
 
1444
                                    LoadError1(stp, "alloc list: bad allocation descriptor %d", type);
 
1445
                                    break;
 
1446
                                }
 
1447
                            }
 
1448
                            last_op->a[arg].type = TAG_u;
 
1449
                            last_op->a[arg].val = words;
 
1450
                            break;
 
1451
                        }
1336
1452
                    default:
1337
1453
                        LoadError1(stp, "invalid extended tag %d", ext_tag);
1338
1454
                        break;
1347
1463
        }
1348
1464
#undef GetValue
1349
1465
 
 
1466
        ASSERT(arity == last_op->arity);
 
1467
 
1350
1468
    do_transform:
1351
1469
        if (stp->genop == NULL) {
1352
1470
            last_op_next = NULL;
1385
1503
        }
1386
1504
 
1387
1505
        /*
 
1506
         * Special error message instruction.
 
1507
         */
 
1508
        if (stp->genop->op == genop_too_old_compiler_0) {
 
1509
#if defined(HEAP_FRAG_ELIM_TEST)
 
1510
            LoadError0(stp, "please re-compile this module with an R11B compiler");
 
1511
#else
 
1512
            LoadError0(stp, "this module was compiled by an obsolete compiler (R5B/R6B); please re-compile it");
 
1513
#endif      
 
1514
        }
 
1515
 
 
1516
        /*
1388
1517
         * From the collected generic instruction, find the specific
1389
1518
         * instruction.
1390
1519
         */
1391
1520
 
1392
1521
        {
1393
 
            Uint mask[2] = {0, 0};
 
1522
            Uint mask[3] = {0, 0, 0};
1394
1523
 
1395
1524
            tmp_op = stp->genop;
1396
1525
            arity = gen_opc[tmp_op->op].arity;
1397
 
            ASSERT(arity <= 4);
 
1526
            ASSERT(arity <= 6);
1398
1527
            for (arg = 0; arg < arity; arg++) {
1399
1528
                mask[arg/2] |= (1 << (tmp_op->a[arg].type)) << ((arg%2)*16);
1400
1529
            }
1402
1531
            num_specific = gen_opc[tmp_op->op].num_specific;
1403
1532
            for (i = 0; i < num_specific; i++) {
1404
1533
                if (((opc[specific].mask[0] & mask[0]) == mask[0]) &&
1405
 
                    ((opc[specific].mask[1] & mask[1]) == mask[1])) {
 
1534
                    ((opc[specific].mask[1] & mask[1]) == mask[1]) &&
 
1535
                    ((opc[specific].mask[2] & mask[2]) == mask[2])) {
1406
1536
                    break;
1407
1537
                }
1408
1538
                specific++;
1475
1605
            case 'c':           /* Tagged constant */
1476
1606
                switch (tag) {
1477
1607
                case TAG_i:
1478
 
                    ASSERT(is_small(tmp_op->a[arg].val));
1479
 
                    code[ci++] = tmp_op->a[arg].val;
 
1608
                    code[ci++] = make_small(tmp_op->a[arg].val);
1480
1609
                    break;
1481
1610
                case TAG_a:
1482
1611
                    code[ci++] = tmp_op->a[arg].val;
1502
1631
                    code[ci++] = make_yreg(tmp_op->a[arg].val);
1503
1632
                    break;
1504
1633
                case TAG_i:
1505
 
                    ASSERT(is_small(tmp_op->a[arg].val));
1506
 
                    code[ci++] = tmp_op->a[arg].val;
 
1634
                    code[ci++] = make_small(tmp_op->a[arg].val);
1507
1635
                    break;
1508
1636
                case TAG_a:
1509
1637
                    code[ci++] = tmp_op->a[arg].val;
1623
1751
                break;
1624
1752
            case 'l':           /* Floating point register. */
1625
1753
                VerifyTag(stp, tag_to_letter[tag], *sign);
1626
 
                code[ci++] = tmp_op->a[arg].val * 2 * sizeof(Eterm);
 
1754
                code[ci++] = tmp_op->a[arg].val * sizeof(FloatDef);
1627
1755
                break;
1628
1756
            default:
1629
1757
                LoadError1(stp, "bad argument tag: %d", *sign);
1638
1766
 
1639
1767
        for ( ; arg < tmp_op->arity; arg++) {
1640
1768
            switch (tmp_op->a[arg].type) {
 
1769
            case TAG_i:
 
1770
                Need(1);
 
1771
                code[ci++] = make_small(tmp_op->a[arg].val);
 
1772
                break;
1641
1773
            case TAG_u:
1642
 
            case TAG_i:
1643
1774
            case TAG_a:
1644
1775
            case TAG_v:
1645
1776
                Need(1);
1666
1797
                ci++;
1667
1798
                break;
1668
1799
            case TAG_o:
 
1800
#ifdef ARCH_64
 
1801
                Need(1);
 
1802
                code[ci++] = tmp_op->a[arg].val;
 
1803
#else
1669
1804
                {
1670
1805
                    Eterm* fptr;
1671
1806
 
1673
1808
                    Need(2);
1674
1809
                    code[ci++] = *fptr++;
1675
1810
                    code[ci++] = *fptr++;
1676
 
                    break;
1677
1811
                }
 
1812
#endif
 
1813
                break;
1678
1814
            default:
1679
1815
                LoadError1(stp, "unsupported primitive type %d",
1680
1816
                           tmp_op->a[arg].type);
1698
1834
                case 'i':       /* Initialize packing accumulator. */
1699
1835
                    packed = code[--ci];
1700
1836
                    break;
1701
 
                case '0':       /* Shift 10 steps */
1702
 
                    packed = (packed << 10) | code[--ci];
1703
 
                    break;
1704
 
                case '2':       /* Shift 12 steps */
1705
 
                    packed = (packed << 12) | code[--ci];
 
1837
                case '0':       /* Tight shift */
 
1838
                    packed = (packed << BEAM_TIGHT_SHIFT) | code[--ci];
1706
1839
                    break;
1707
1840
                case '6':       /* Shift 16 steps */
1708
1841
                    packed = (packed << 16) | code[--ci];
1739
1872
                 */
1740
1873
                stp->function = code[ci-2];
1741
1874
                stp->arity = code[ci-1];
1742
 
 
1743
1875
                offset = MI_FUNCTIONS + function_number;
1744
1876
                code[offset] = stp->labels[last_label].patches;
1745
1877
                stp->labels[last_label].patches = offset;
1746
1878
                function_number++;
 
1879
                if (stp->arity >= MAX_ARG) {
 
1880
                    LoadError1(stp, "too many arguments: %d", stp->arity);
 
1881
                }
1747
1882
#ifdef DEBUG
1748
1883
                ASSERT(stp->labels[0].patches == 0); /* Should not be referenced. */
1749
1884
                for (i = 1; i < stp->num_labels; i++) {
1752
1887
#endif
1753
1888
            }
1754
1889
            break;
1755
 
 
1756
1890
        case op_put_string_IId:
1757
1891
            {
1758
1892
                /*
1781
1915
                stp->put_strings = ci - 4;
1782
1916
            }
1783
1917
            break;
1784
 
 
1785
 
        case op_bs_put_string_II:
 
1918
#if !defined(HEAP_FRAG_ELIM_TEST)
 
1919
        case op_i_bs_put_string_II:
1786
1920
            {
1787
1921
                /*
1788
1922
                 * At entry:
1789
1923
                 *
1790
 
                 * code[ci-3]   &&lb_bs_put_string_II
 
1924
                 * code[ci-3]   &&lb_i_bs_put_string_II
1791
1925
                 * code[ci-2]   length of string
1792
1926
                 * code[ci-1]   offset into string table
1793
1927
                 *
1796
1930
                 * the instruction field as a link field to link all put_string
1797
1931
                 * instructions into a single linked list.  At exit:
1798
1932
                 *
1799
 
                 * code[ci-3]   pointer to next bs_put_string instruction (or 0
 
1933
                 * code[ci-3]   pointer to next i_bs_put_string instruction (or 0
1800
1934
                 *              if this is the last)
1801
1935
                 */
1802
1936
                Uint offset = code[ci-1];
1809
1943
                stp->bs_put_strings = ci - 3;
1810
1944
            }
1811
1945
            break;
 
1946
#endif
 
1947
        case op_i_new_bs_put_string_II:
 
1948
            {
 
1949
                /*
 
1950
                 * At entry:
 
1951
                 *
 
1952
                 * code[ci-3]   &&lb_i_new_bs_put_string_II
 
1953
                 * code[ci-2]   length of string
 
1954
                 * code[ci-1]   offset into string table
 
1955
                 *
 
1956
                 * Since we don't know the address of the string table yet,
 
1957
                 * just check the offset and length for validity, and use
 
1958
                 * the instruction field as a link field to link all put_string
 
1959
                 * instructions into a single linked list.  At exit:
 
1960
                 *
 
1961
                 * code[ci-3]   pointer to next i_new_bs_put_string instruction (or 0
 
1962
                 *              if this is the last)
 
1963
                 */
 
1964
                Uint offset = code[ci-1];
 
1965
                Uint len = code[ci-2];
 
1966
                unsigned strtab_size = stp->chunks[STR_CHUNK].size;
 
1967
                if (offset > strtab_size || offset + len > strtab_size) {
 
1968
                    LoadError2(stp, "invalid string reference %d, size %d", offset, len);
 
1969
                }
 
1970
                code[ci-3] = stp->new_bs_put_strings;
 
1971
                stp->new_bs_put_strings = ci - 3;
 
1972
            }
 
1973
            break;
1812
1974
 
1813
1975
        case op_catch_yf:
1814
1976
            /* code[ci-3]       &&lb_catch_yf
1857
2019
#endif
1858
2020
 
1859
2021
/*
1860
 
 * Predicate that tests if a jump table can be used.
 
2022
 * Predicate that tests whether a jump table can be used.
1861
2023
 */
1862
2024
 
1863
2025
static int
1864
2026
use_jump_tab(LoaderState* stp, GenOpArg Size, GenOpArg* Rest)
1865
2027
{
1866
 
    int min, max;
1867
 
    int i;
 
2028
    Sint min, max;
 
2029
    Sint i;
1868
2030
 
1869
2031
    if (Size.val < 2 || Size.val % 2 != 0) {
1870
2032
        return 0;
1874
2036
       return early in latter case, before we access the values */
1875
2037
    if (Rest[0].type != TAG_i || Rest[1].type != TAG_f)
1876
2038
        return 0;
1877
 
    min = max = signed_val(Rest[0].val);
 
2039
    min = max = Rest[0].val;
1878
2040
    for (i = 2; i < Size.val; i += 2) {
1879
2041
        if (Rest[i].type != TAG_i || Rest[i+1].type != TAG_f) {
1880
2042
            return 0;
1881
2043
        }
1882
 
        if (signed_val(Rest[i].val) < min) {
1883
 
            min = signed_val(Rest[i].val);
1884
 
        } else if (max < signed_val(Rest[i].val)) {
1885
 
            max = signed_val(Rest[i].val);
 
2044
        if (Rest[i].val < min) {
 
2045
            min = Rest[i].val;
 
2046
        } else if (max < Rest[i].val) {
 
2047
            max = Rest[i].val;
1886
2048
        }
1887
2049
    }
1888
2050
 
1890
2052
}
1891
2053
 
1892
2054
/*
1893
 
 * Predicate to test if all values in a table are big numbers.
 
2055
 * Predicate to test whether all values in a table are big numbers.
1894
2056
 */
1895
2057
 
1896
2058
static int
1913
2075
 
1914
2076
 
1915
2077
/*
1916
 
 * Predicate to test if all values in a table have a fixed size.
 
2078
 * Predicate to test whether all values in a table have a fixed size.
1917
2079
 */
1918
2080
 
1919
2081
static int
1961
2123
    return 0;
1962
2124
}
1963
2125
 
1964
 
static int
1965
 
assign_heap_bin_flag(LoaderState* stp, GenOpArg Flags, GenOpArg Bits)
1966
 
{
1967
 
    stp->generate_heap_bin = (Flags.val & BSF_EXACT) != 0 &&
1968
 
        (Bits.val % 8) == 0 &&
1969
 
            Bits.val / 8 <= ERL_ONHEAP_BIN_LIMIT;
1970
 
    return 1;
1971
 
}
1972
 
 
1973
 
#define reset_heap_bin_flag(stp) (stp->generate_heap_bin = 0, 1)
1974
 
#define generate_heap_bin(stp) (stp->generate_heap_bin)
1975
 
 
1976
2126
/*
1977
2127
 * Generate an instruction for element/2.
1978
2128
 */
1996
2146
     * If safe, generate a faster instruction.
1997
2147
     */
1998
2148
 
1999
 
    if (Index.type == TAG_i && signed_val(Index.val) > 0 &&
 
2149
    if (Index.type == TAG_i && Index.val > 0 &&
2000
2150
        (Tuple.type == TAG_r || Tuple.type == TAG_x || Tuple.type == TAG_y)) {
2001
2151
        op->op = genop_i_fast_element_4;
2002
2152
        op->a[1].type = TAG_u;
2003
 
        op->a[1].val = signed_val(Index.val);
 
2153
        op->a[1].val = Index.val;
2004
2154
    }
2005
2155
 
2006
2156
    return op;
2011
2161
 */
2012
2162
 
2013
2163
static GenOp*
2014
 
gen_get_integer(LoaderState* stp, GenOpArg Fail, GenOpArg Size, GenOpArg Unit,
2015
 
                GenOpArg Flags, GenOpArg Dst)
 
2164
gen_get_integer2(LoaderState* stp, GenOpArg Fail, GenOpArg Ms, GenOpArg Live,
 
2165
                 GenOpArg Size, GenOpArg Unit,
 
2166
                 GenOpArg Flags, GenOpArg Dst)
2016
2167
{
2017
2168
    GenOp* op;
2018
2169
    NEW_GENOP(stp, op);
2019
2170
 
2020
2171
    NATIVE_ENDIAN(Flags);
2021
2172
    if (Size.type == TAG_i) {
2022
 
        if (Flags.val & BSF_ALIGNED && (Flags.val & BSF_SIGNED) == 0) {
2023
 
            Uint bits = signed_val(Size.val) * Unit.val;
2024
 
            if (bits == 8) {
2025
 
                op->op = genop_i_bs_get_integer8_2;
2026
 
                op->arity = 2;
 
2173
      if ((Flags.val & BSF_SIGNED) == 0) {
 
2174
        Uint bits = Size.val * Unit.val;
 
2175
        if (bits == 8) {
 
2176
          op->op = genop_i_bs_get_integer2_8_3;
 
2177
                op->arity = 3;
2027
2178
                op->a[0] = Fail;
2028
 
                op->a[1] = Dst;
 
2179
                op->a[1] = Ms;
 
2180
                op->a[2] = Dst;
2029
2181
            } else if (bits == 16 && (Flags.val & BSF_LITTLE) == 0) {
2030
 
                op->op = genop_i_bs_get_integer16_2;
2031
 
                op->arity = 2;
 
2182
                op->op = genop_i_bs_get_integer2_16_3;
 
2183
                op->arity = 3;
2032
2184
                op->a[0] = Fail;
2033
 
                op->a[1] = Dst;
 
2185
                op->a[1] = Ms;
 
2186
                op->a[2] = Dst;
2034
2187
            } else if (bits == 32 && (Flags.val & BSF_LITTLE) == 0) {
2035
 
                op->op = genop_i_bs_get_integer32_2;
2036
 
                op->arity = 2;
 
2188
                op->op = genop_i_bs_get_integer2_32_4;
 
2189
                op->arity = 4;
2037
2190
                op->a[0] = Fail;
2038
 
                op->a[1] = Dst;
 
2191
                op->a[1] = Ms;
 
2192
                op->a[2] = Live;
 
2193
                op->a[3] = Dst;
2039
2194
            } else {
2040
2195
                goto generic;
2041
2196
            }
2042
2197
        } else {
2043
2198
        generic:
2044
 
            op->op = genop_i_bs_get_integer_imm_4;
2045
 
            op->arity = 4;
 
2199
            op->op = genop_i_bs_get_integer_imm2_6;
 
2200
            op->arity = 6;
2046
2201
            op->a[0] = Fail;
2047
 
            op->a[1].type = TAG_u;
2048
 
            op->a[1].val = signed_val(Size.val) * Unit.val;
2049
 
            op->a[2] = Flags;
2050
 
            op->a[3] = Dst;
 
2202
            op->a[1] = Ms;
 
2203
            op->a[2] = Live;
 
2204
            op->a[3].type = TAG_u;
 
2205
            op->a[3].val = Size.val * Unit.val;
 
2206
            op->a[4] = Flags;
 
2207
            op->a[5] = Dst;
2051
2208
        }
2052
2209
    } else {
2053
 
        op->op = genop_i_bs_get_integer_4;
2054
 
        op->arity = 4;
 
2210
        op->op = genop_i_bs_get_integer2_6;
 
2211
        op->arity = 6;
2055
2212
        op->a[0] = Fail;
2056
 
        op->a[1] = Size;
2057
 
        op->a[2].type = TAG_u;
2058
 
        op->a[2].val = (Unit.val << 3) | Flags.val;
2059
 
        op->a[3] = Dst;
 
2213
        op->a[1] = Ms;
 
2214
        op->a[2] = Live;
 
2215
        op->a[3] = Size;
 
2216
        op->a[4].type = TAG_u;
 
2217
        op->a[4].val = (Unit.val << 3) | Flags.val;
 
2218
        op->a[5] = Dst;
2060
2219
    }
2061
2220
    op->next = NULL;
2062
2221
    return op;
2067
2226
 */
2068
2227
 
2069
2228
static GenOp*
2070
 
gen_get_binary(LoaderState* stp, GenOpArg Fail, GenOpArg Size, GenOpArg Unit,
 
2229
gen_get_binary2(LoaderState* stp, GenOpArg Fail, GenOpArg Ms, GenOpArg Live,
 
2230
                GenOpArg Size, GenOpArg Unit,
2071
2231
                GenOpArg Flags, GenOpArg Dst)
2072
2232
{
2073
2233
    GenOp* op;
2075
2235
 
2076
2236
    NATIVE_ENDIAN(Flags);
2077
2237
    if (Size.type == TAG_a && Size.val == am_all) {
2078
 
        op->op = genop_i_bs_get_binary_all_2;
2079
 
        op->arity = 2;
 
2238
        op->op = genop_i_bs_get_binary_all2_5;
 
2239
        op->arity = 5;
2080
2240
        op->a[0] = Fail;
2081
 
        op->a[1] = Dst;
 
2241
        op->a[1] = Ms;
 
2242
        op->a[2] = Live;        
 
2243
        op->a[3] = Unit;
 
2244
        op->a[4] = Dst;
2082
2245
    } else if (Size.type == TAG_i) {
2083
 
        op->op = genop_i_bs_get_binary_imm_4;
2084
 
        op->arity = 4;
 
2246
        op->op = genop_i_bs_get_binary_imm2_6;
 
2247
        op->arity = 6;
2085
2248
        op->a[0] = Fail;
2086
 
        op->a[1].type = TAG_u;
2087
 
        op->a[1].val = signed_val(Size.val) * Unit.val;
2088
 
        op->a[2] = Flags;
2089
 
        op->a[3] = Dst;
 
2249
        op->a[1] = Ms;
 
2250
        op->a[2] = Live;
 
2251
        op->a[3].type = TAG_u;
 
2252
        op->a[3].val = Size.val * Unit.val;
 
2253
        op->a[4] = Flags;
 
2254
        op->a[5] = Dst;
2090
2255
    } else {
2091
 
        op->op = genop_i_bs_get_binary_4;
2092
 
        op->arity = 4;
 
2256
        op->op = genop_i_bs_get_binary2_6;
 
2257
        op->arity = 6;
2093
2258
        op->a[0] = Fail;
2094
 
        op->a[1] = Size;
2095
 
        op->a[2].type = TAG_u;
2096
 
        op->a[2].val = (Unit.val << 3) | Flags.val;
2097
 
        op->a[3] = Dst;
 
2259
        op->a[1] = Ms;
 
2260
        op->a[2] = Live;
 
2261
        op->a[3] = Size;
 
2262
        op->a[4].type = TAG_u;
 
2263
        op->a[4].val = (Unit.val << 3) | Flags.val;
 
2264
        op->a[5] = Dst;
2098
2265
    }
2099
2266
    op->next = NULL;
2100
2267
    return op;
2101
2268
}
2102
2269
 
 
2270
/*
 
2271
 * Predicate to test whether a heap binary should be generated.
 
2272
 */
 
2273
 
 
2274
static int
 
2275
should_gen_heap_bin(LoaderState* stp, GenOpArg Src)
 
2276
{
 
2277
    return Src.val <= ERL_ONHEAP_BIN_LIMIT;
 
2278
}
 
2279
 
 
2280
#if !defined(HEAP_FRAG_ELIM_TEST)
 
2281
static int
 
2282
old_bs_instructions(LoaderState* stp)
 
2283
{
 
2284
    stp->new_instructions = 0;
 
2285
    return 1;
 
2286
}
 
2287
#endif
 
2288
 
 
2289
static int
 
2290
new_bs_instructions(LoaderState* stp)
 
2291
{
 
2292
    stp->new_instructions = 1;
 
2293
    return 1;
 
2294
}
 
2295
 
 
2296
#define query_new_instructions(stp) (stp->new_instructions)
 
2297
 
 
2298
#if defined(HEAP_FRAG_ELIM_TEST)
 
2299
# define NEW_OR_OLD(New,Old) New
 
2300
#else
 
2301
# define NEW_OR_OLD(New,Old) \
 
2302
  (stp->new_instructions ? New : Old)
 
2303
#endif
 
2304
 
 
2305
#define new_float_allocation(Stp) ((Stp)->new_float_instructions)
 
2306
 
2103
2307
static GenOp*
2104
2308
gen_put_binary(LoaderState* stp, GenOpArg Fail,GenOpArg Size,
2105
2309
               GenOpArg Unit, GenOpArg Flags, GenOpArg Src)
2109
2313
 
2110
2314
    NATIVE_ENDIAN(Flags);
2111
2315
    if (Size.type == TAG_a && Size.val == am_all) {
2112
 
        op->op = genop_i_bs_put_binary_all_2;
 
2316
        op->op = NEW_OR_OLD(genop_i_new_bs_put_binary_all_2,genop_i_bs_put_binary_all_2);
2113
2317
        op->arity = 2;
2114
2318
        op->a[0] = Fail;
2115
2319
        op->a[1] = Src;
2116
 
    } else if (Size.type == TAG_i) {
2117
 
        op->op = genop_i_bs_put_binary_imm_3;
 
2320
    } else if (Size.type == TAG_i && stp->new_instructions) {
 
2321
        op->op = genop_i_new_bs_put_binary_imm_3;
2118
2322
        op->arity = 3;
2119
2323
        op->a[0] = Fail;
2120
2324
        op->a[1].type = TAG_u;
2121
 
        op->a[1].val = signed_val(Size.val) * Unit.val;
 
2325
        op->a[1].val = Size.val * Unit.val;
2122
2326
        op->a[2] = Src;
2123
2327
    } else {
2124
 
        op->op = genop_i_bs_put_binary_4;
 
2328
        op->op = NEW_OR_OLD(genop_i_new_bs_put_binary_4,genop_i_bs_put_binary_4);
2125
2329
        op->arity = 4;
2126
2330
        op->a[0] = Fail;
2127
2331
        op->a[1] = Size;
2128
2332
        op->a[2].type = TAG_u;
2129
 
        op->a[2].val = (Unit.val << 3) | Flags.val;
 
2333
        op->a[2].val = (Unit.val << 3) | (Flags.val & 7);
2130
2334
        op->a[3] = Src;
2131
2335
    }
2132
2336
 
2142
2346
    NEW_GENOP(stp, op);
2143
2347
 
2144
2348
    NATIVE_ENDIAN(Flags);
2145
 
    if (Size.type == TAG_i && signed_val(Size.val) < 0) {
 
2349
    if (Size.type == TAG_i && Size.val < 0) {
2146
2350
        /* Negative size must fail */
2147
2351
        op->op = genop_badarg_1;
2148
2352
        op->arity = 1;
2149
2353
        op->a[0] = Fail;
2150
 
    } else if (Size.type == TAG_i) {
2151
 
        op->op = genop_i_bs_put_integer_imm_4;
 
2354
    } else if (Size.type == TAG_i && stp->new_instructions) {
 
2355
        op->op = genop_i_new_bs_put_integer_imm_4;
2152
2356
        op->arity = 4;
2153
2357
        op->a[0] = Fail;
2154
2358
        op->a[1].type = TAG_u;
2155
 
        op->a[1].val = signed_val(Size.val) * Unit.val;
2156
 
        op->a[2] = Flags;
 
2359
        op->a[1].val = Size.val * Unit.val;
 
2360
        op->a[2].type = Flags.type;
 
2361
        op->a[2].val = (Flags.val & 7);
2157
2362
        op->a[3] = Src;
2158
2363
    } else {
2159
 
        op->op = genop_i_bs_put_integer_4;
 
2364
        op->op = NEW_OR_OLD(genop_i_new_bs_put_integer_4,genop_i_bs_put_integer_4);
2160
2365
        op->arity = 4;
2161
2366
        op->a[0] = Fail;
2162
2367
        op->a[1] = Size;
2163
2368
        op->a[2].type = TAG_u;
2164
 
        op->a[2].val = (Unit.val << 3) | Flags.val;
 
2369
        op->a[2].val = (Unit.val << 3) | (Flags.val & 7);
2165
2370
        op->a[3] = Src;
2166
2371
    }
2167
2372
    op->next = NULL;
2176
2381
    NEW_GENOP(stp, op);
2177
2382
 
2178
2383
    NATIVE_ENDIAN(Flags);
2179
 
    if (Size.type == TAG_i) {
2180
 
        op->op = genop_i_bs_put_float_imm_4;
 
2384
    if (Size.type == TAG_i && stp->new_instructions) {
 
2385
        op->op = genop_i_new_bs_put_float_imm_4;
2181
2386
        op->arity = 4;
2182
2387
        op->a[0] = Fail;
2183
2388
        op->a[1].type = TAG_u;
2184
 
        op->a[1].val = signed_val(Size.val) * Unit.val;
 
2389
        op->a[1].val = Size.val * Unit.val;
2185
2390
        op->a[2] = Flags;
2186
2391
        op->a[3] = Src;
2187
2392
    } else {
2188
 
        op->op = genop_i_bs_put_float_4;
 
2393
        op->op = NEW_OR_OLD(genop_i_new_bs_put_float_4,genop_i_bs_put_float_4);
2189
2394
        op->arity = 4;
2190
2395
        op->a[0] = Fail;
2191
2396
        op->a[1] = Size;
2192
2397
        op->a[2].type = TAG_u;
2193
 
        op->a[2].val = (Unit.val << 3) | Flags.val;
 
2398
        op->a[2].val = (Unit.val << 3) | (Flags.val & 7);
2194
2399
        op->a[3] = Src;
2195
2400
    }
2196
2401
    op->next = NULL;
2202
2407
 */
2203
2408
 
2204
2409
static GenOp*
 
2410
gen_get_float2(LoaderState* stp, GenOpArg Fail, GenOpArg Ms, GenOpArg Live,
 
2411
                GenOpArg Size, GenOpArg Unit, GenOpArg Flags, GenOpArg Dst)
 
2412
{
 
2413
    GenOp* op;
 
2414
    NEW_GENOP(stp, op);
 
2415
 
 
2416
    NATIVE_ENDIAN(Flags);
 
2417
    op->op = genop_i_bs_get_float2_6;
 
2418
    op->arity = 6;
 
2419
    op->a[0] = Fail;
 
2420
    op->a[1] = Ms;
 
2421
    op->a[2] = Live;
 
2422
    op->a[3] = Size;
 
2423
    op->a[4].type = TAG_u;
 
2424
    op->a[4].val = (Unit.val << 3) | Flags.val;
 
2425
    op->a[5] = Dst;
 
2426
    op->next = NULL;
 
2427
    return op;
 
2428
}
 
2429
 
 
2430
/*
 
2431
 * Generate the fastest instruction for bs_skip_bits.
 
2432
 */
 
2433
 
 
2434
static GenOp*
 
2435
gen_skip_bits2(LoaderState* stp, GenOpArg Fail, GenOpArg Ms, 
 
2436
               GenOpArg Size, GenOpArg Unit, GenOpArg Flags)
 
2437
{
 
2438
    GenOp* op;
 
2439
 
 
2440
    NATIVE_ENDIAN(Flags);
 
2441
    NEW_GENOP(stp, op);
 
2442
    if (Size.type == TAG_a && Size.val == am_all) {
 
2443
        op->op = genop_i_bs_skip_bits_all2_3;
 
2444
        op->arity = 3;
 
2445
        op->a[0] = Fail;
 
2446
        op->a[1] = Ms; 
 
2447
        op->a[2] = Unit;
 
2448
    } else if (Size.type == TAG_i) {
 
2449
        op->op = genop_i_bs_skip_bits_imm2_3;
 
2450
        op->arity = 3;
 
2451
        op->a[0] = Fail;
 
2452
        op->a[1] = Ms; 
 
2453
        op->a[2].type = TAG_u;
 
2454
        op->a[2].val = Size.val * Unit.val;
 
2455
    } else {
 
2456
        op->op = genop_i_bs_skip_bits2_4;
 
2457
        op->arity = 4;
 
2458
        op->a[0] = Fail;
 
2459
        op->a[1] = Ms; 
 
2460
        op->a[2] = Size;
 
2461
        op->a[3] = Unit;
 
2462
    }
 
2463
    op->next = NULL;
 
2464
    return op;
 
2465
}
 
2466
 
 
2467
 
 
2468
#if !defined(HEAP_FRAG_ELIM_TEST)
 
2469
/*
 
2470
 * Old binary matching instructions - not allowed in the nofrag emulator.
 
2471
 */
 
2472
 
 
2473
static GenOp*
 
2474
gen_get_integer(LoaderState* stp, GenOpArg Fail, GenOpArg Size, GenOpArg Unit,
 
2475
                GenOpArg Flags, GenOpArg Dst)
 
2476
{
 
2477
    GenOp* op;
 
2478
    NEW_GENOP(stp, op);
 
2479
 
 
2480
    NATIVE_ENDIAN(Flags);
 
2481
    op->op = genop_i_bs_get_integer_4;
 
2482
    op->arity = 4;
 
2483
    op->a[0] = Fail;
 
2484
    op->a[1] = Size;
 
2485
    op->a[2].type = TAG_u;
 
2486
    op->a[2].val = (Unit.val << 3) | Flags.val;
 
2487
    op->a[3] = Dst;
 
2488
    op->next = NULL;
 
2489
    return op;
 
2490
}
 
2491
 
 
2492
static GenOp*
 
2493
gen_get_binary(LoaderState* stp, GenOpArg Fail, GenOpArg Size, GenOpArg Unit,
 
2494
                GenOpArg Flags, GenOpArg Dst)
 
2495
{
 
2496
    GenOp* op;
 
2497
    NEW_GENOP(stp, op);
 
2498
 
 
2499
    NATIVE_ENDIAN(Flags);
 
2500
    if (Size.type == TAG_a && Size.val == am_all) {
 
2501
        op->op = genop_i_bs_get_binary_all_2;
 
2502
        op->arity = 2;
 
2503
        op->a[0] = Fail;
 
2504
        op->a[1] = Dst;
 
2505
    } else if (Size.type == TAG_i) {
 
2506
        op->op = genop_i_bs_get_binary_imm_4;
 
2507
        op->arity = 4;
 
2508
        op->a[0] = Fail;
 
2509
        op->a[1].type = TAG_u;
 
2510
        op->a[1].val = Size.val * Unit.val;
 
2511
        op->a[2] = Flags;
 
2512
        op->a[3] = Dst;
 
2513
    } else {
 
2514
        op->op = genop_i_bs_get_binary_4;
 
2515
        op->arity = 4;
 
2516
        op->a[0] = Fail;
 
2517
        op->a[1] = Size;
 
2518
        op->a[2].type = TAG_u;
 
2519
        op->a[2].val = (Unit.val << 3) | Flags.val;
 
2520
        op->a[3] = Dst;
 
2521
    }
 
2522
    op->next = NULL;
 
2523
    return op;
 
2524
}
 
2525
 
 
2526
static GenOp*
2205
2527
gen_get_float(LoaderState* stp, GenOpArg Fail, GenOpArg Size, GenOpArg Unit,
2206
2528
              GenOpArg Flags, GenOpArg Dst)
2207
2529
{
2220
2542
    return op;
2221
2543
}
2222
2544
 
2223
 
/*
2224
 
 * Generate the fastest instruction for bs_skip_bits.
2225
 
 */
2226
 
 
2227
2545
static GenOp*
2228
2546
gen_skip_bits(LoaderState* stp, GenOpArg Fail, GenOpArg Size,
2229
2547
              GenOpArg Unit, GenOpArg Flags)
2233
2551
    NATIVE_ENDIAN(Flags);
2234
2552
    NEW_GENOP(stp, op);
2235
2553
    if (Size.type == TAG_a && Size.val == am_all) {
2236
 
        if (Flags.val & BSF_ALIGNED) {
2237
 
            op->op = genop_i_bs_skip_bits_all_aligned_0;
2238
 
            op->arity = 0;
2239
 
        } else {
2240
 
            op->op = genop_i_bs_skip_bits_all_1;
2241
 
            op->arity = 1;
2242
 
            op->a[0] = Fail;
2243
 
        }
 
2554
        op->op = genop_i_bs_skip_bits_all_1;
 
2555
        op->arity = 1;
 
2556
        op->a[0] = Fail;
2244
2557
    } else if (Size.type == TAG_i) {
2245
2558
        op->op = genop_i_bs_skip_bits_imm_2;
2246
2559
        op->arity = 2;
2247
2560
        op->a[0] = Fail;
2248
2561
        op->a[1].type = TAG_u;
2249
 
        op->a[1].val = signed_val(Size.val) * Unit.val;
 
2562
        op->a[1].val = Size.val * Unit.val;
2250
2563
    } else {
2251
2564
        op->op = genop_i_bs_skip_bits_3;
2252
2565
        op->arity = 3;
2258
2571
    return op;
2259
2572
}
2260
2573
 
 
2574
#endif
 
2575
 
 
2576
 
 
2577
static int
 
2578
smp(LoaderState* stp)
 
2579
{
 
2580
#ifdef ERTS_SMP
 
2581
    return 1;
 
2582
#else
 
2583
    return 0;
 
2584
#endif
 
2585
}
 
2586
 
 
2587
/*
 
2588
 * Mark this label.
 
2589
 */
 
2590
static int
 
2591
smp_mark_target_label(LoaderState* stp, GenOpArg L)
 
2592
{
 
2593
#ifdef ERTS_SMP
 
2594
    ASSERT(L.type == TAG_f);
 
2595
    stp->labels[L.val].looprec_targeted = 1;
 
2596
#endif
 
2597
    return 1;
 
2598
}
 
2599
 
 
2600
/*
 
2601
 * Test whether this label was targeted by a loop_rec/2 instruction.
 
2602
 */
 
2603
 
 
2604
static int
 
2605
smp_already_locked(LoaderState* stp, GenOpArg L)
 
2606
{
 
2607
#ifdef ERTS_SMP
 
2608
    ASSERT(L.type == TAG_u);
 
2609
    return stp->labels[L.val].looprec_targeted;
 
2610
#else
 
2611
    return 0;
 
2612
#endif
 
2613
}
 
2614
 
2261
2615
/*
2262
2616
 * Generate a timeout instruction for a literal timeout.
2263
2617
 */
2266
2620
gen_literal_timeout(LoaderState* stp, GenOpArg Fail, GenOpArg Time)
2267
2621
{
2268
2622
    GenOp* op;
2269
 
    int timeout;
 
2623
    Sint timeout;
2270
2624
 
2271
2625
    NEW_GENOP(stp, op);
2272
 
    op->op = genop_wait_timeout_2;
 
2626
    op->op = genop_i_wait_timeout_2;
2273
2627
    op->next = NULL;
2274
2628
    op->arity = 2;
2275
2629
    op->a[0] = Fail;
2276
2630
    op->a[1].type = TAG_u;
2277
2631
    
2278
 
    if (Time.type == TAG_i && (timeout = signed_val(Time.val)) >= 0) {
 
2632
    if (Time.type == TAG_i && (timeout = Time.val) >= 0 &&
 
2633
#ifdef ARCH_64
 
2634
        (timeout >> 32) == 0
 
2635
#else
 
2636
        1
 
2637
#endif
 
2638
        ) {
2279
2639
        op->a[1].val = timeout;
 
2640
#ifndef ARCH_64
2280
2641
    } else if (Time.type == TAG_w) {
2281
2642
        Eterm* bigp = stp->temp_heap + Time.val;
2282
2643
        if (thing_arityval(*bigp) > 1 || BIG_SIGN(bigp)) {
2283
2644
            op->op = genop_i_wait_error_0;
2284
2645
            op->arity = 0;
2285
2646
        } else {
2286
 
            ASSERT(sizeof(unsigned) == 4);
2287
 
            bigp++;
2288
 
            op->a[1].val = (((unsigned) (((unsigned short *)bigp)[1])) << 16) |
2289
 
                ((unsigned short *)bigp)[0];
 
2647
            (void) term_to_Uint(make_big(bigp), &op->a[1].val);
2290
2648
        }
 
2649
#endif
2291
2650
    } else {
2292
2651
        op->op = genop_i_wait_error_0;
2293
2652
        op->arity = 0;
2295
2654
    return op;
2296
2655
}
2297
2656
 
 
2657
static GenOp*
 
2658
gen_literal_timeout_locked(LoaderState* stp, GenOpArg Fail, GenOpArg Time)
 
2659
{
 
2660
    GenOp* op;
 
2661
    Sint timeout;
 
2662
 
 
2663
    NEW_GENOP(stp, op);
 
2664
    op->op = genop_i_wait_timeout_locked_2;
 
2665
    op->next = NULL;
 
2666
    op->arity = 2;
 
2667
    op->a[0] = Fail;
 
2668
    op->a[1].type = TAG_u;
 
2669
    
 
2670
    if (Time.type == TAG_i && (timeout = Time.val) >= 0 &&
 
2671
#ifdef ARCH_64
 
2672
        (timeout >> 32) == 0
 
2673
#else
 
2674
        1
 
2675
#endif
 
2676
        ) {
 
2677
        op->a[1].val = timeout;
 
2678
#ifndef ARCH_64
 
2679
    } else if (Time.type == TAG_w) {
 
2680
        Eterm* bigp = stp->temp_heap + Time.val;
 
2681
        if (thing_arityval(*bigp) > 1 || BIG_SIGN(bigp)) {
 
2682
            op->op = genop_i_wait_error_locked_0;
 
2683
            op->arity = 0;
 
2684
        } else {
 
2685
            (void) term_to_Uint(make_big(bigp), &op->a[1].val);
 
2686
        }
 
2687
#endif
 
2688
    } else {
 
2689
        op->op = genop_i_wait_error_locked_0;
 
2690
        op->arity = 0;
 
2691
    }
 
2692
    return op;
 
2693
}
 
2694
 
2298
2695
/*
2299
2696
 * Tag the list of values with tuple arity tags.
2300
2697
 */
2431
2828
static GenOp*
2432
2829
gen_jump_tab(LoaderState* stp, GenOpArg S, GenOpArg Fail, GenOpArg Size, GenOpArg* Rest)
2433
2830
{
2434
 
    int min, max;
2435
 
    int i;
2436
 
    int size;
2437
 
    int arity;
 
2831
    Sint min, max;
 
2832
    Sint i;
 
2833
    Sint size;
 
2834
    Sint arity;
2438
2835
    int fixed_args;
2439
2836
    GenOp* op;
2440
2837
 
2445
2842
     */
2446
2843
 
2447
2844
    ASSERT(Rest[0].type == TAG_i);
2448
 
    min = max = signed_val(Rest[0].val);
 
2845
    min = max = Rest[0].val;
2449
2846
    for (i = 2; i < Size.val; i += 2) {
2450
2847
        ASSERT(Rest[i].type == TAG_i && Rest[i+1].type == TAG_f);
2451
 
        if (signed_val(Rest[i].val) < min) {
2452
 
            min = signed_val(Rest[i].val);
2453
 
        } else if (max < signed_val(Rest[i].val)) {
2454
 
            max = signed_val(Rest[i].val);
 
2848
        if (Rest[i].val < min) {
 
2849
            min = Rest[i].val;
 
2850
        } else if (max < Rest[i].val) {
 
2851
            max = Rest[i].val;
2455
2852
        }
2456
2853
    }
2457
2854
    size = max - min + 1;
2489
2886
    }
2490
2887
    for (i = 0; i < Size.val; i += 2) {
2491
2888
        int index;
2492
 
        ASSERT(is_small(Rest[i].val));
2493
 
        index = fixed_args+signed_val(Rest[i].val)-min;
 
2889
        index = fixed_args+Rest[i].val-min;
2494
2890
        ASSERT(fixed_args <= index && index < arity);
2495
2891
        op->a[index] = Rest[i+1];
2496
2892
    }
2690
3086
    fi->next = op;
2691
3087
    op->next = NULL;
2692
3088
 
2693
 
    if (func.val == am_module_info && arity.val < 2) {
2694
 
        NEW_GENOP(stp, op->next);
2695
 
        op = op->next;
2696
 
        op->op = arity.val == 0 ? genop_i_module_info_0_0 :
2697
 
            genop_i_module_info_1_0;
2698
 
        op->arity = 1;
2699
 
        op->a[0] = mod;
2700
 
        op->next = NULL;
2701
 
    }
2702
 
    return fi;
2703
 
}
2704
 
 
2705
 
 
 
3089
    return fi;
 
3090
}
 
3091
 
 
3092
 
 
3093
static GenOp*
 
3094
gen_func_info_mi(LoaderState* stp, GenOpArg mod,
 
3095
                 GenOpArg arity, GenOpArg label)
 
3096
{
 
3097
    GenOp* fi;
 
3098
    GenOp* op;
 
3099
 
 
3100
    NEW_GENOP(stp, fi);
 
3101
    fi->op = genop_i_func_info_4;
 
3102
    fi->arity = 4;
 
3103
    fi->a[0].type = TAG_u;      /* untagged Zero */
 
3104
    fi->a[0].val = 0;
 
3105
    fi->a[1] = mod;
 
3106
    fi->a[2].type = TAG_a;
 
3107
    fi->a[2].val = am_module_info;
 
3108
    fi->a[3] = arity;
 
3109
 
 
3110
    NEW_GENOP(stp, op);
 
3111
    op->op = genop_label_1;
 
3112
    op->arity = 1;
 
3113
    op->a[0] = label;
 
3114
    
 
3115
    fi->next = op;
 
3116
    op->next = NULL;
 
3117
 
 
3118
    NEW_GENOP(stp, op->next);
 
3119
    op = op->next;
 
3120
    op->op = arity.val == 0 ? genop_i_module_info_0_0 :
 
3121
        genop_i_module_info_1_0;
 
3122
    op->arity = 1;
 
3123
    op->a[0] = mod;
 
3124
    op->next = NULL;
 
3125
    return fi;
 
3126
}
 
3127
 
 
3128
 
 
3129
#ifndef HEAP_FRAG_ELIM_TEST
2706
3130
static GenOp*
2707
3131
gen_make_fun(LoaderState* stp, GenOpArg lbl, GenOpArg uniq, GenOpArg num_free)
2708
3132
{
2744
3168
    stp->num_lambdas++;
2745
3169
    return op;
2746
3170
}
 
3171
#endif
2747
3172
 
2748
3173
static GenOp*
2749
3174
gen_make_fun2(LoaderState* stp, GenOpArg idx)
2769
3194
    return op;
2770
3195
}
2771
3196
 
 
3197
#if defined(HEAP_FRAG_ELIM_TEST)
 
3198
static GenOp*
 
3199
gen_guard_bif(LoaderState* stp, GenOpArg Fail, GenOpArg Live, GenOpArg Bif,
 
3200
              GenOpArg Src, GenOpArg Dst)
 
3201
{
 
3202
    GenOp* op;
 
3203
    BifFunction bf;
 
3204
 
 
3205
    NEW_GENOP(stp, op);
 
3206
    op->op = genop_i_gc_bif1_5;
 
3207
    op->arity = 5;
 
3208
    op->a[0] = Fail;
 
3209
    op->a[1].type = TAG_u;
 
3210
    bf = stp->import[Bif.val].bf;
 
3211
    if (bf == length_1) {
 
3212
        op->a[1].val = (Uint) (void *) erts_gc_length_1;
 
3213
    } else if (bf == size_1) {
 
3214
        op->a[1].val = (Uint) (void *) erts_gc_size_1;
 
3215
    } else if (bf == abs_1) {
 
3216
        op->a[1].val = (Uint) (void *) erts_gc_abs_1;
 
3217
    } else if (bf == float_1) {
 
3218
        op->a[1].val = (Uint) (void *) erts_gc_float_1;
 
3219
    } else if (bf == round_1) {
 
3220
        op->a[1].val = (Uint) (void *) erts_gc_round_1;
 
3221
    } else if (bf == trunc_1) {
 
3222
        op->a[1].val = (Uint) (void *) erts_gc_trunc_1;
 
3223
    } else {
 
3224
        abort();
 
3225
    }
 
3226
    op->a[2] = Src;
 
3227
    op->a[3] = Live;
 
3228
    op->a[4] = Dst;
 
3229
    op->next = NULL;
 
3230
    return op;
 
3231
}
 
3232
#endif
 
3233
 
2772
3234
 
2773
3235
/*
2774
3236
 * Freeze the code in memory, move the string table into place,
2859
3321
        index = next;
2860
3322
    }
2861
3323
 
 
3324
#if !defined(HEAP_FRAG_ELIM_TEST)
2862
3325
    /*
2863
 
     * Go through all bs_put_strings instructions, restore the pointer to
 
3326
     * Go through all i_bs_put_strings instructions, restore the pointer to
2864
3327
     * the instruction and convert string offsets to pointers (to the
2865
3328
     * FIRST character).
2866
3329
     */
2868
3331
    index = stp->bs_put_strings;
2869
3332
    while (index != 0) {
2870
3333
        Uint next = code[index];
2871
 
        code[index] = BeamOpCode(op_bs_put_string_II);
 
3334
        code[index] = BeamOpCode(op_i_bs_put_string_II);
 
3335
        code[index+2] = (Uint) (str_table + code[index+2]);
 
3336
        index = next;
 
3337
    }
 
3338
#endif
 
3339
 
 
3340
    /*
 
3341
     * Go through all i_new_bs_put_strings instructions, restore the pointer to
 
3342
     * the instruction and convert string offsets to pointers (to the
 
3343
     * FIRST character).
 
3344
     */
 
3345
 
 
3346
    index = stp->new_bs_put_strings;
 
3347
    while (index != 0) {
 
3348
        Uint next = code[index];
 
3349
        code[index] = BeamOpCode(op_i_new_bs_put_string_II);
2872
3350
        code[index+2] = (Uint) (str_table + code[index+2]);
2873
3351
        index = next;
2874
3352
    }
2978
3456
                /*
2979
3457
                 * We are hiding a pointer into older code.
2980
3458
                 */
2981
 
                fe->refc--;
 
3459
                erts_refc_dec(&fe->refc, 1);
2982
3460
            }
2983
3461
            fe->address = code_ptr;
2984
3462
#ifdef HIPE
3111
3589
            break;
3112
3590
 
3113
3591
#endif
 
3592
#if defined(TOP_is_not_bif)
 
3593
        case TOP_is_not_bif:
 
3594
            {
 
3595
                pc++;
 
3596
                
 
3597
                /*
 
3598
                 * In debug build, the type must be 'u'.
 
3599
                 */
 
3600
 
 
3601
                ASSERT(instr->a[ap].type == TAG_u);
 
3602
                if (instr->a[ap].type != TAG_u) {
 
3603
                    goto restart;
 
3604
                }
 
3605
                i = instr->a[ap].val;
 
3606
 
 
3607
                /*
 
3608
                 * erlang:apply/2,3 are strange. They exist as (dummy) BIFs
 
3609
                 * so that they are included in the export table before
 
3610
                 * the erlang module is loaded. They also exist in the erlang
 
3611
                 * module as functions. When used in code, a special Beam
 
3612
                 * instruction is used.
 
3613
                 * 
 
3614
                 * Below we specially recognize erlang:apply/2,3 as special.
 
3615
                 * This is necessary because after setting a trace pattern on
 
3616
                 * them, you cannot no longer see from the export entry that
 
3617
                 * they are special.
 
3618
                 */
 
3619
                if (i < st->num_imports) {
 
3620
                    if (st->import[i].bf != NULL ||
 
3621
                        (st->import[i].module == am_erlang &&
 
3622
                         st->import[i].function == am_apply &&
 
3623
                         (st->import[i].arity == 2 || st->import[i].arity == 3))) {
 
3624
                        goto restart;
 
3625
                    }
 
3626
                }
 
3627
            }
 
3628
            break;
 
3629
 
 
3630
#endif
3114
3631
#if defined(TOP_is_func)
3115
3632
        case TOP_is_func:
3116
3633
            {
3132
3649
            }
3133
3650
            break;
3134
3651
#endif
3135
 
        case TOP_set_var:
 
3652
        case TOP_set_var_next_arg:
3136
3653
            ASSERT(ap < instr->arity);
3137
3654
            i = *pc++;
3138
3655
            ASSERT(i < TE_MAX_VARS);
3139
3656
            var[i].type = instr->a[ap].type;
3140
3657
            var[i].val = instr->a[ap].val;
 
3658
            ap++;
3141
3659
            break;
3142
3660
 
3143
3661
#if defined(TOP_rest_args)
3144
3662
        case TOP_rest_args:
3145
 
            i = *pc++;
3146
 
            var = erts_alloc(ERTS_ALC_T_LOADER_TMP,
3147
 
                             instr->arity * sizeof(GenOpArg));
3148
 
            memcpy(var, def_vars, sizeof(def_vars));
3149
 
            while (i < instr->arity) {
3150
 
                var[i] = instr->a[i];
3151
 
                i++;
 
3663
            {
 
3664
                int n = *pc++;
 
3665
                var = erts_alloc(ERTS_ALC_T_LOADER_TMP,
 
3666
                                 instr->arity * sizeof(GenOpArg));
 
3667
                for (i = 0; i < n; i++) {
 
3668
                    var[i] = def_vars[i];
 
3669
                }
 
3670
                while (i < instr->arity) {
 
3671
                    var[i] = instr->a[i];
 
3672
                    i++;
 
3673
                }
3152
3674
            }
3153
3675
            break;
3154
3676
#endif
3274
3796
static void
3275
3797
load_printf(int line, LoaderState* context, char *fmt,...)
3276
3798
{
3277
 
    char sbuf[1024];
3278
 
    char error[1024];
3279
 
    char module_name[256];      /* Module name as string. */
 
3799
    erts_dsprintf_buf_t *dsbufp;
3280
3800
    va_list va;
3281
 
    char* ep = error;
3282
 
    Atom* ap;
3283
3801
 
3284
3802
    if (is_non_value(context->module)) {
3285
3803
        /* Suppressed by code:get_chunk/2 */
3286
3804
        return;
3287
3805
    }
3288
3806
 
 
3807
    dsbufp = erts_create_logger_dsbuf();
 
3808
 
 
3809
    erts_dsprintf(dsbufp, "%s(%d): Error loading ", __FILE__, line);
 
3810
 
 
3811
    if (is_atom(context->function))
 
3812
        erts_dsprintf(dsbufp, "function %T:%T/%d", context->module,
 
3813
                      context->function, context->arity);
 
3814
    else
 
3815
        erts_dsprintf(dsbufp, "module %T", context->module);
 
3816
 
 
3817
    if (context->genop)
 
3818
        erts_dsprintf(dsbufp, ": op %s", gen_opc[context->genop->op].name);
 
3819
 
 
3820
    if (context->specific_op != -1)
 
3821
        erts_dsprintf(dsbufp, ": %s", opc[context->specific_op].sign);
 
3822
    else if (context->genop) {
 
3823
        int i;
 
3824
        for (i = 0; i < context->genop->arity; i++)
 
3825
            erts_dsprintf(dsbufp, " %c",
 
3826
                          tag_to_letter[context->genop->a[i].type]);
 
3827
    }
 
3828
 
 
3829
    erts_dsprintf(dsbufp, ":\n  ");
 
3830
 
3289
3831
    va_start(va, fmt);
3290
 
    vsprintf(sbuf, fmt, va);
 
3832
    erts_vdsprintf(dsbufp, fmt, va);
3291
3833
    va_end(va);
3292
3834
 
3293
 
    sprintf(ep, "%s(%d): Error loading ", __FILE__, line);
3294
 
    ep += strlen(ep);
3295
 
 
3296
 
    /*
3297
 
     * Convert atom for module to a string.
3298
 
     */
3299
 
    ap = atom_tab(atom_val(context->module));
3300
 
    memcpy(module_name, ap->name, ap->len);
3301
 
    module_name[ap->len] = '\0';
3302
 
 
3303
 
    if (is_atom(context->function)) {
3304
 
        char function[256];
3305
 
 
3306
 
        ap = atom_tab(atom_val(context->function));
3307
 
        memcpy(function, ap->name, ap->len);
3308
 
        function[ap->len] = '\0';
3309
 
        sprintf(ep, "function %s:%s/%d", module_name, function, context->arity);
3310
 
    } else {
3311
 
        sprintf(ep, "module %s", module_name);
3312
 
    }
3313
 
    ep += strlen(ep);
3314
 
    if (context->genop) {
3315
 
        sprintf(ep, ": op %s", gen_opc[context->genop->op].name);
3316
 
    }
3317
 
    ep += strlen(ep);
3318
 
    if (context->specific_op != -1) {
3319
 
        sprintf(ep, ": %s", opc[context->specific_op].sign);
3320
 
    } else if (context->genop) {
3321
 
        int i;
3322
 
        for (i = 0; i < context->genop->arity; i++) {
3323
 
            sprintf(ep, " %c", tag_to_letter[context->genop->a[i].type]);
3324
 
            ep += strlen(ep);
3325
 
        }
3326
 
    }
3327
 
    ep += strlen(ep);
3328
 
    cerr_pos = 0;
3329
 
    sys_printf(CBUF, "%s:\n  %s\n", error, sbuf);
 
3835
    erts_dsprintf(dsbufp, "\n");
3330
3836
#ifdef DEBUG
3331
 
    sys_printf(CERR, "%s:\n  %s\n", error, sbuf);
 
3837
    erts_fprintf(stderr, "%s", dsbufp->str);
3332
3838
#endif
3333
 
    send_error_to_logger(context->group_leader);
 
3839
    erts_send_error_to_logger(context->group_leader, dsbufp);
3334
3840
}
3335
3841
 
3336
3842
 
3338
3844
get_int_val(LoaderState* stp, Uint len_code, Uint* result)
3339
3845
{
3340
3846
    Uint count;
3341
 
    int val;
 
3847
    Uint val;
3342
3848
 
3343
3849
    len_code >>= 5;
3344
3850
    ASSERT(len_code < 8);
3355
3861
        GetInt(stp, 4, *result);
3356
3862
    } else if (count <= 4) {
3357
3863
        GetInt(stp, count, val);
3358
 
        *result = (int) ((val << 8*(sizeof(val)-count)) >> 8*(sizeof(val)-count));
 
3864
        *result = ((val << 8*(sizeof(val)-count)) >> 8*(sizeof(val)-count));
3359
3865
    } else {
3360
3866
        LoadError1(stp, "too big integer; %d bytes\n", count);
3361
3867
    }
3370
3876
get_erlang_integer(LoaderState* stp, Uint len_code, Uint* result)
3371
3877
{
3372
3878
    Uint count;
3373
 
    int val;
 
3879
    Sint val;
3374
3880
    byte default_buf[128];
3375
3881
    byte* bigbuf = default_buf;
3376
3882
    byte* s;
3403
3909
    if (count <= sizeof(val)) {
3404
3910
        GetInt(stp, count, val);
3405
3911
 
3406
 
        val = (int) ((val << 8*(sizeof(val)-count)) >> 8*(sizeof(val)-count));
 
3912
        val = ((val << 8*(sizeof(val)-count)) >> 8*(sizeof(val)-count));
3407
3913
        if (IS_SSMALL(val)) {
3408
 
            *result = make_small(val);
 
3914
            *result = val;
3409
3915
            return TAG_i;
3410
3916
        } else {
3411
 
            hindex = TempAlloc(stp, 2);
 
3917
            hindex = TempAlloc(stp, BIG_UINT_HEAP_SIZE);
3412
3918
            (void) small_to_big(val, stp->temp_heap+hindex);
3413
3919
            *result = hindex;
3414
3920
            return TAG_w;
3469
3975
    arity = count/sizeof(Eterm);
3470
3976
    hindex = TempAlloc(stp, arity+1);
3471
3977
    hp = stp->temp_heap + hindex;
3472
 
    *hp++ = neg ? make_neg_bignum_header(arity) : make_pos_bignum_header(arity);
3473
 
    for (i = 0; i < arity; i++) {
3474
 
        byte* bp = bigbuf + sizeof(Eterm)*i;
3475
 
        ((unsigned short *)hp)[0] = bp[0] | (bp[1] << 8);
3476
 
        ((unsigned short *)hp)[1] = bp[2] | (bp[3] << 8);
3477
 
        if (sizeof(Eterm) == 8) {
3478
 
            ((unsigned short *)hp)[2] = bp[4] | (bp[5] << 8);
3479
 
            ((unsigned short *)hp)[3] = bp[6] | (bp[7] << 8);
3480
 
        }
3481
 
        hp++;
3482
 
    }
 
3978
    (void) bytes_to_big(bigbuf, count, neg, hp);
3483
3979
 
3484
3980
    if (bigbuf != default_buf) {
3485
3981
        erts_free(ERTS_ALC_T_LOADER_TMP, (void *) bigbuf);
3574
4070
    Eterm list = NIL;
3575
4071
    Eterm tup;
3576
4072
 
 
4073
    if (is_not_atom(module)) {
 
4074
        return THE_NON_VALUE;
 
4075
    }
 
4076
 
 
4077
    if (erts_get_module(module) == NULL) {
 
4078
        return THE_NON_VALUE;
 
4079
    }
 
4080
 
3577
4081
#define BUILD_INFO(What) \
3578
4082
    tup = erts_module_info_1(p, module, What); \
3579
4083
    hp = HAlloc(p, 5); \
3624
4128
    Module* modp;
3625
4129
    Eterm* code;
3626
4130
    int i;
3627
 
    Eterm* hp = NULL;
3628
 
    Eterm* hend = NULL;
 
4131
    Uint num_functions;
 
4132
    Eterm* hp;
3629
4133
    Eterm result = NIL;
3630
4134
 
3631
4135
    if (is_not_atom(mod)) {
3637
4141
        return THE_NON_VALUE;
3638
4142
    }
3639
4143
    code = modp->code;
3640
 
    for (i = code[MI_NUM_FUNCTIONS]-1; i >= 0 ; i--) {
 
4144
    num_functions = code[MI_NUM_FUNCTIONS];
 
4145
    hp = HAlloc(p, 5*num_functions);
 
4146
    for (i = num_functions-1; i >= 0 ; i--) {
3641
4147
        Eterm* func_info = (Eterm *) code[MI_FUNCTIONS+i];
3642
4148
        Eterm name = func_info[3];
3643
4149
        int arity = func_info[4];
3644
4150
        Eterm tuple;
3645
4151
 
3646
4152
        ASSERT(is_atom(name));
3647
 
        if (hp == hend) {
3648
 
            int need = 10 * 5;
3649
 
            hp = HAlloc(p, need);
3650
 
            hend = hp + need;
3651
 
        }
3652
4153
        tuple = TUPLE2(hp, name, make_small(arity));
3653
4154
        hp += 3;
3654
4155
        result = CONS(hp, tuple, result);
3670
4171
    Module* modp;
3671
4172
    Eterm* code;
3672
4173
    int i;
3673
 
    Eterm* hp = NULL;
3674
 
    Eterm* hend = NULL;
 
4174
    Eterm* hp;
 
4175
    Uint num_functions;
 
4176
    Uint need;
 
4177
    Eterm* hp_end;
3675
4178
    Eterm result = NIL;
3676
4179
 
3677
4180
    if (is_not_atom(mod)) {
3682
4185
    if (modp == NULL) {
3683
4186
        return THE_NON_VALUE;
3684
4187
    }
 
4188
 
3685
4189
    code = modp->code;
3686
 
    for (i = code[MI_NUM_FUNCTIONS]-1; i >= 0 ; i--) {
 
4190
    num_functions = code[MI_NUM_FUNCTIONS];
 
4191
    need = (6+BIG_UINT_HEAP_SIZE)*num_functions;
 
4192
    hp = HAlloc(p, need);
 
4193
    hp_end = hp + need;
 
4194
    for (i = num_functions-1; i >= 0 ; i--) {
3687
4195
        Eterm* func_info = (Eterm *) code[MI_FUNCTIONS+i];
3688
4196
        Eterm name = func_info[3];
3689
4197
        int arity = func_info[4];
3691
4199
 
3692
4200
        ASSERT(is_atom(name));
3693
4201
        if (func_info[1] != 0) {
3694
 
            Eterm addr = make_small_or_big(func_info[1], p);
3695
 
 
3696
 
            if (hp == hend) {
3697
 
                int need = 10 * 6;
3698
 
                hp = HAlloc(p, need);
3699
 
                hend = hp + need;
3700
 
            }
3701
 
            tuple = TUPLE3(hp, name, make_small(arity), addr);
3702
 
            hp += 4;
3703
 
            result = CONS(hp, tuple, result);
3704
 
            hp += 2;
 
4202
            Eterm addr = erts_bld_uint(&hp, NULL, func_info[1]);
 
4203
            tuple = erts_bld_tuple(&hp, NULL, 3, name, make_small(arity), addr);
 
4204
            result = erts_bld_cons(&hp, NULL, tuple, result);
3705
4205
        }
3706
4206
    }
 
4207
    HRelease(p, hp_end, hp);
3707
4208
    return result;
3708
4209
}
3709
4210
 
3719
4220
exported_from_module(Process* p, /* Process whose heap to use. */
3720
4221
                     Eterm mod) /* Tagged atom for module. */
3721
4222
{
3722
 
    Module* modp;
3723
 
    Eterm* code;
3724
4223
    int i;
3725
4224
    Eterm* hp = NULL;
3726
4225
    Eterm* hend = NULL;
3729
4228
    if (is_not_atom(mod)) {
3730
4229
        return THE_NON_VALUE;
3731
4230
    }
3732
 
    modp = erts_get_module(mod);
3733
 
    if (modp == NULL) {
3734
 
        return THE_NON_VALUE;
3735
 
    }
3736
 
    code = modp->code;
3737
 
    for (i = code[MI_NUM_FUNCTIONS]-1; i >= 0 ; i--) {
3738
 
        Eterm* func_info = (Eterm *) code[MI_FUNCTIONS+i];
3739
 
        Eterm name = func_info[3];
3740
 
        int arity = func_info[4];
3741
 
        Eterm tuple;
3742
 
 
3743
 
        if (erts_find_function(mod, name, arity) != NULL) {
3744
 
            ASSERT(is_atom(name));
 
4231
 
 
4232
    for (i = 0; i < export_list_size(); i++) {
 
4233
        Export* ep = export_list(i);
 
4234
        
 
4235
        if (ep->code[0] == mod) {
 
4236
            Eterm tuple;
 
4237
            
 
4238
            if (ep->address == ep->code+3 &&
 
4239
                ep->code[3] == (Eterm) em_call_error_handler) {
 
4240
                /* There is a call to the function, but it does not exist. */ 
 
4241
                continue;
 
4242
            }
 
4243
 
3745
4244
            if (hp == hend) {
3746
4245
                int need = 10 * 5;
3747
4246
                hp = HAlloc(p, need);
3748
4247
                hend = hp + need;
3749
4248
            }
3750
 
            tuple = TUPLE2(hp, name, make_small(arity));
 
4249
            tuple = TUPLE2(hp, ep->code[1], make_small(ep->code[2]));
3751
4250
            hp += 3;
3752
4251
            result = CONS(hp, tuple, result);
3753
4252
            hp += 2;
3754
4253
        }
3755
4254
    }
 
4255
    HRelease(p,hend,hp);
3756
4256
    return result;
3757
4257
}
3758
4258
 
3773
4273
    Eterm* hp;
3774
4274
    byte* ext;
3775
4275
    Eterm result = NIL;
3776
 
#ifdef DEBUG
3777
4276
    Eterm* end;
3778
 
#endif
3779
4277
 
3780
4278
    if (is_not_atom(mod) || (is_not_list(result) && is_not_nil(result))) {
3781
4279
        return THE_NON_VALUE;
3789
4287
    ext = (byte *) code[MI_ATTR_PTR];
3790
4288
    if (ext != NULL) {
3791
4289
        hp = HAlloc(p, code[MI_ATTR_SIZE_ON_HEAP]);
3792
 
#ifdef DEBUG
3793
4290
        end = hp + code[MI_ATTR_SIZE_ON_HEAP];
3794
 
#endif
3795
4291
        result = erts_from_external_format(NULL, &hp, &ext, &MSO(p));
3796
4292
        if (is_value(result)) {
3797
4293
            ASSERT(hp <= end);
3798
4294
        }
 
4295
        HRelease(p,end,hp);
3799
4296
    }
3800
4297
    return result;
3801
4298
}
3816
4313
    Eterm* hp;
3817
4314
    byte* ext;
3818
4315
    Eterm result = NIL;
3819
 
#ifdef DEBUG
3820
4316
    Eterm* end;
3821
 
#endif
3822
4317
 
3823
4318
    if (is_not_atom(mod) || (is_not_list(result) && is_not_nil(result))) {
3824
4319
        return THE_NON_VALUE;
3832
4327
    ext = (byte *) code[MI_COMPILE_PTR];
3833
4328
    if (ext != NULL) {
3834
4329
        hp = HAlloc(p, code[MI_COMPILE_SIZE_ON_HEAP]);
3835
 
#ifdef DEBUG
3836
4330
        end = hp + code[MI_COMPILE_SIZE_ON_HEAP];
3837
 
#endif
3838
4331
        result = erts_from_external_format(NULL, &hp, &ext, &MSO(p));
3839
4332
        if (is_value(result)) {
3840
4333
            ASSERT(hp <= end);
3841
4334
        }
 
4335
        HRelease(p,end,hp);
3842
4336
    }
3843
4337
    return result;
3844
4338
}
3893
4387
    Uint chunk = 0;
3894
4388
    ErlSubBin* sb;
3895
4389
    Uint offset;
 
4390
    Uint bitoffs;
 
4391
    Uint bitsize;
3896
4392
    byte* start;
3897
4393
    int i;
 
4394
    Eterm res;
 
4395
    Eterm real_bin;
 
4396
    byte* temp_alloc = NULL;
3898
4397
 
3899
 
    if (is_not_binary(Bin)) {
3900
 
        goto error;
 
4398
    if ((start = erts_get_aligned_binary_bytes(Bin, &temp_alloc)) == NULL) {
 
4399
    error:
 
4400
        erts_free_aligned_binary_bytes(temp_alloc);
 
4401
        BIF_ERROR(p, BADARG);
3901
4402
    }
3902
4403
    state.module = THE_NON_VALUE; /* Suppress diagnostiscs */
3903
4404
    state.file_name = "IFF header for Beam file";
3904
 
    GET_BINARY_BYTES(Bin, start);
3905
4405
    state.file_p = start;
3906
4406
    state.file_left = binary_size(Bin);
3907
4407
    for (i = 0; i < 4; i++) {
3921
4421
    if (is_not_nil(Chunk)) {
3922
4422
        goto error;
3923
4423
    }
3924
 
 
3925
4424
    if (!scan_iff_file(&state, &chunk, 1, 1)) {
 
4425
        erts_free_aligned_binary_bytes(temp_alloc);
3926
4426
        return am_undefined;
3927
4427
    }
3928
 
    sb = (ErlSubBin *) HAlloc(p, ERL_SUB_BIN_SIZE);
3929
 
    GET_REAL_BIN(Bin, sb->orig, offset);
3930
 
    sb->thing_word = HEADER_SUB_BIN;
3931
 
    sb->size = state.chunks[0].size;
3932
 
    sb->offs = offset + (state.chunks[0].start-start);
3933
 
    return make_binary(sb);
3934
 
 
3935
 
 error:
3936
 
    BIF_ERROR(p, BADARG);
 
4428
    ERTS_GET_REAL_BIN(Bin, real_bin, offset, bitoffs, bitsize);
 
4429
    if (bitoffs) {
 
4430
        res = new_binary(p, state.chunks[0].start, state.chunks[0].size);
 
4431
    } else {
 
4432
        sb = (ErlSubBin *) HAlloc(p, ERL_SUB_BIN_SIZE);
 
4433
        sb->thing_word = HEADER_SUB_BIN;
 
4434
        sb->orig = real_bin;
 
4435
        sb->size = state.chunks[0].size;
 
4436
        sb->bitsize = 0;
 
4437
        sb->bitoffs = 0;
 
4438
        sb->offs = offset + (state.chunks[0].start - start);
 
4439
        res = make_binary(sb);
 
4440
    }
 
4441
    erts_free_aligned_binary_bytes(temp_alloc);
 
4442
    return res;
3937
4443
}
3938
4444
 
3939
4445
/*
3944
4450
code_module_md5_1(Process* p, Eterm Bin)
3945
4451
{
3946
4452
    LoaderState state;
3947
 
    byte* start;
 
4453
    byte* temp_alloc = NULL;
3948
4454
 
3949
 
    if (is_not_binary(Bin)) {
 
4455
    if ((state.file_p = erts_get_aligned_binary_bytes(Bin, &temp_alloc)) == NULL) {
3950
4456
        BIF_ERROR(p, BADARG);
3951
4457
    }
3952
4458
    state.module = THE_NON_VALUE; /* Suppress diagnostiscs */
3953
4459
    state.file_name = "IFF header for Beam file";
3954
 
    GET_BINARY_BYTES(Bin, start);
3955
 
    state.file_p = start;
3956
4460
    state.file_left = binary_size(Bin);
3957
4461
 
3958
4462
    if (!scan_iff_file(&state, chunk_types, NUM_CHUNK_TYPES, NUM_MANDATORY)) {
3959
4463
        return am_undefined;
3960
4464
    }
 
4465
    erts_free_aligned_binary_bytes(temp_alloc);
3961
4466
    return new_binary(p, state.mod_md5, sizeof(state.mod_md5));
3962
4467
}
3963
4468
 
3971
4476
    fp[2] = mod;
3972
4477
    fp[3] = func;
3973
4478
    fp[4] = arity;
 
4479
#ifdef HIPE
 
4480
    if (native) {
 
4481
        fp[5] = BeamOpCode(op_move_return_nr);
 
4482
        hipe_mfa_save_orig_beam_op(mod, func, arity, fp+5);
 
4483
    }
 
4484
#endif
3974
4485
    fp[5] = OpCode;
3975
4486
    return fp + WORDS_PER_FUNCTION;
3976
4487
}
3977
4488
 
3978
 
static void
3979
 
stub_init_state(LoaderState* stp, Eterm Bin)
3980
 
{
3981
 
    byte* start;
3982
 
 
3983
 
    init_state(stp);
3984
 
    stp->file_name = "IFF header for Beam file";
3985
 
    GET_BINARY_BYTES(Bin, start);
3986
 
    stp->file_p = start;
3987
 
    stp->file_left = binary_size(Bin);
3988
 
}
3989
 
 
3990
4489
static byte*
3991
4490
stub_copy_info(LoaderState* stp,
3992
4491
               int chunk,       /* Chunk: ATTR_CHUNK or COMPILE_CHUNK */
4206
4705
 
4207
4706
    fe = erts_get_fun_entry(Mod, uniq, index);
4208
4707
    fe->native_address = (Uint *)native_address;
4209
 
 
 
4708
    erts_refc_dec(&fe->refc, 1);
4210
4709
 
4211
4710
    if (!patch(Addresses, (Uint) fe))
4212
4711
      return 0;
4225
4724
 */
4226
4725
 
4227
4726
Eterm
4228
 
code_make_stub_module_3(Process* p, Eterm Mod, Eterm Beam, Eterm Info)
 
4727
erts_make_stub_module(Process* p, Eterm Mod, Eterm Beam, Eterm Info)
4229
4728
{
4230
4729
    LoaderState state;
4231
4730
    Eterm Funcs;
4240
4739
    int code_size;
4241
4740
    int rval;
4242
4741
    int i;
 
4742
    byte* temp_alloc = NULL;
 
4743
    byte* bytes;
4243
4744
 
4244
4745
    if (is_not_atom(Mod)) {
4245
4746
        goto error;
4258
4759
        goto error;
4259
4760
    }
4260
4761
    n += 2;                     /* module_info/0 and module_info/1 */
 
4762
    if ((bytes = erts_get_aligned_binary_bytes(Beam, &temp_alloc)) == NULL) {
 
4763
        goto error;
 
4764
    }
4261
4765
 
4262
4766
    /*
4263
4767
     * Scan the Beam binary and read the interesting sections.
4264
4768
     */
4265
4769
 
4266
 
    stub_init_state(&state, Beam);
 
4770
    init_state(&state);
 
4771
    state.file_name = "IFF header for Beam file";
 
4772
    state.file_p = bytes;
 
4773
    state.file_left = binary_size(Beam);
4267
4774
    state.module = Mod;
4268
4775
    state.group_leader = p->group_leader;
4269
4776
    state.num_functions = n;
4407
4914
     * Insert the module in the module table.
4408
4915
     */
4409
4916
 
4410
 
    rval = insert_new_code(p->group_leader, Mod, code, code_size, BEAM_CATCHES_NIL);
 
4917
    rval = insert_new_code(p, 0, p->group_leader, Mod, code, code_size,
 
4918
                           BEAM_CATCHES_NIL);
4411
4919
    if (rval < 0) {
4412
4920
        goto error;
4413
4921
    }
4422
4930
        fp += WORDS_PER_FUNCTION;
4423
4931
    }
4424
4932
 
4425
 
    if (patch_funentries(Patchlist))
4426
 
      return Mod;
 
4933
    if (patch_funentries(Patchlist)) {
 
4934
        erts_free_aligned_binary_bytes(temp_alloc);
 
4935
        return Mod;
 
4936
    }
4427
4937
 
4428
4938
 error:
 
4939
    erts_free_aligned_binary_bytes(temp_alloc);
4429
4940
    if (code != NULL) {
4430
4941
        erts_free(ERTS_ALC_T_CODE, code);
4431
4942
    }