~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to erts/emulator/beam/external.c

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
/*
2
2
 * %CopyrightBegin%
3
 
 * 
4
 
 * Copyright Ericsson AB 1996-2009. All Rights Reserved.
5
 
 * 
 
3
 *
 
4
 * Copyright Ericsson AB 1996-2011. All Rights Reserved.
 
5
 *
6
6
 * The contents of this file are subject to the Erlang Public License,
7
7
 * Version 1.1, (the "License"); you may not use this file except in
8
8
 * compliance with the License. You should have received a copy of the
9
9
 * Erlang Public License along with this software. If not, it can be
10
10
 * retrieved online at http://www.erlang.org/.
11
 
 * 
 
11
 *
12
12
 * Software distributed under the License is distributed on an "AS IS"
13
13
 * basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
 * the License for the specific language governing rights and limitations
15
15
 * under the License.
16
 
 * 
 
16
 *
17
17
 * %CopyrightEnd%
18
18
 */
19
19
 
49
49
#define in_area(ptr,start,nbytes) ((Uint)((char*)(ptr) - (char*)(start)) < (nbytes))
50
50
 
51
51
#define MAX_STRING_LEN 0xffff
52
 
#define dec_set_creation(nodename,creat)                                \
53
 
  (((nodename) == erts_this_node->sysname && (creat) == ORIG_CREATION)  \
54
 
   ? erts_this_node->creation                                           \
55
 
   : (creat))
 
52
 
 
53
#define is_valid_creation(Cre) ((unsigned)(Cre) < MAX_CREATION || (Cre) == INTERNAL_CREATION)
56
54
 
57
55
#undef ERTS_DEBUG_USE_DIST_SEP
58
56
#ifdef DEBUG
65
63
#  endif
66
64
#endif
67
65
 
68
 
/*
69
 
 * For backward compatibility reasons, only encode integers that
70
 
 * fit in 28 bits (signed) using INTEGER_EXT.
 
66
/* Does Sint fit in Sint32?
71
67
 */
72
 
#define IS_SSMALL28(x) (((Uint) (((x) >> (28-1)) + 1)) < 2)
 
68
#define IS_SSMALL32(x) (((Uint) (((x) >> (32-1)) + 1)) < 2)
73
69
 
74
70
/*
75
71
 *   Valid creations for nodes are 1, 2, or 3. 0 can also be sent
85
81
 *
86
82
 */
87
83
 
88
 
static byte* enc_term(ErtsAtomCacheMap *, Eterm, byte*, Uint32);
 
84
static byte* enc_term(ErtsAtomCacheMap *, Eterm, byte*, Uint32, struct erl_off_heap_header** off_heap);
89
85
static Uint is_external_string(Eterm obj, int* p_is_string);
90
86
static byte* enc_atom(ErtsAtomCacheMap *, Eterm, byte*, Uint32);
91
87
static byte* enc_pid(ErtsAtomCacheMap *, Eterm, byte*, Uint32);
92
88
static byte* dec_term(ErtsDistExternal *, Eterm**, byte*, ErlOffHeap*, Eterm*);
93
89
static byte* dec_atom(ErtsDistExternal *, byte*, Eterm*);
94
90
static byte* dec_pid(ErtsDistExternal *, Eterm**, byte*, ErlOffHeap*, Eterm*);
95
 
static Sint decoded_size(byte *ep, byte* endp, int only_heap_bins);
 
91
static Sint decoded_size(byte *ep, byte* endp, int only_heap_bins, int internal_tags);
96
92
 
97
93
 
98
94
static Uint encode_size_struct2(ErtsAtomCacheMap *, Eterm, unsigned);
271
267
 
272
268
byte *erts_encode_ext_dist_header_setup(byte *ctl_ext, ErtsAtomCacheMap *acmp)
273
269
{
274
 
#ifndef ARCH_32
275
 
#if ATOM_LIMIT >= (1UL << 32)
276
 
#error "ATOM_LIMIT too large for interal atom cache update instructions. New instructions needed."
277
 
#endif
278
 
#endif
 
270
    /* Maximum number of atom must be less than the maximum of a 32 bits
 
271
       unsigned integer. Check is done in erl_init.c, erl_start function. */
279
272
    if (!acmp)
280
273
        return ctl_ext;
281
274
    else {
466
459
        + 1 /* VERSION_MAGIC */;
467
460
}
468
461
 
 
462
Uint erts_encode_ext_size_ets(Eterm term)
 
463
{
 
464
    return encode_size_struct2(NULL, term, TERM_TO_BINARY_DFLAGS|DFLAGS_INTERNAL_TAGS);
 
465
}
 
466
 
 
467
 
469
468
void erts_encode_dist_ext(Eterm term, byte **ext, Uint32 flags, ErtsAtomCacheMap *acmp)
470
469
{
471
470
    byte *ep = *ext;
473
472
    if (!(flags & DFLAG_DIST_HDR_ATOM_CACHE))
474
473
#endif
475
474
        *ep++ = VERSION_MAGIC;
476
 
    ep = enc_term(acmp, term, ep, flags);
 
475
    ep = enc_term(acmp, term, ep, flags, NULL);
477
476
    if (!ep)
478
477
        erl_exit(ERTS_ABORT_EXIT,
479
478
                 "%s:%d:erts_encode_dist_ext(): Internal data structure error\n",
485
484
{
486
485
    byte *ep = *ext;
487
486
    *ep++ = VERSION_MAGIC;
488
 
    ep = enc_term(NULL, term, ep, TERM_TO_BINARY_DFLAGS);
 
487
    ep = enc_term(NULL, term, ep, TERM_TO_BINARY_DFLAGS, NULL);
489
488
    if (!ep)
490
489
        erl_exit(ERTS_ABORT_EXIT,
491
490
                 "%s:%d:erts_encode_ext(): Internal data structure error\n",
493
492
    *ext = ep;
494
493
}
495
494
 
 
495
byte* erts_encode_ext_ets(Eterm term, byte *ep, struct erl_off_heap_header** off_heap)
 
496
{
 
497
    return enc_term(NULL, term, ep, TERM_TO_BINARY_DFLAGS|DFLAGS_INTERNAL_TAGS,
 
498
                    off_heap);
 
499
}
 
500
 
496
501
ErtsDistExternal *
497
502
erts_make_dist_ext_copy(ErtsDistExternal *edep, Uint xsize)
498
503
{
507
512
    ASSERT(edep->ext_endp >= edep->extp);
508
513
    ext_sz = edep->ext_endp - edep->extp;
509
514
 
510
 
    align_sz = ERTS_WORD_ALIGN_PAD_SZ(dist_ext_sz + ext_sz);
 
515
    align_sz = ERTS_EXTRA_DATA_ALIGN_SZ(dist_ext_sz + ext_sz);
511
516
 
512
517
    new_edep = erts_alloc(ERTS_ALC_T_EXT_TERM_DATA,
513
518
                          dist_ext_sz + ext_sz + align_sz + xsize);
818
823
            goto fail;
819
824
        ep = edep->extp+1;
820
825
    }
821
 
    res = decoded_size(ep, edep->ext_endp, no_refc_bins);
 
826
    res = decoded_size(ep, edep->ext_endp, no_refc_bins, 0);
822
827
    if (res >= 0)
823
828
        return res;
824
829
 fail:
830
835
{
831
836
    if (size == 0 || *ext != VERSION_MAGIC)
832
837
        return -1;
833
 
    return decoded_size(ext+1, ext+size, no_refc_bins);
834
 
}
 
838
    return decoded_size(ext+1, ext+size, no_refc_bins, 0);
 
839
}
 
840
 
 
841
Sint erts_decode_ext_size_ets(byte *ext, Uint size)
 
842
{
 
843
    Sint sz = decoded_size(ext, ext+size, 0, 1);
 
844
    ASSERT(sz >= 0);
 
845
    return sz;
 
846
}
 
847
 
835
848
 
836
849
/*
837
850
** hpp is set to either a &p->htop or
892
905
    return obj;
893
906
}
894
907
 
895
 
 
 
908
Eterm erts_decode_ext_ets(Eterm **hpp, ErlOffHeap *off_heap, byte *ext)
 
909
{
 
910
    Eterm obj;
 
911
    ext = dec_term(NULL, hpp, ext, off_heap, &obj);
 
912
    ASSERT(ext);
 
913
    return obj;
 
914
}
896
915
 
897
916
/**********************************************************************/
898
917
 
969
988
    return erts_term_to_binary(p, Term, 0, TERM_TO_BINARY_DFLAGS);
970
989
}
971
990
 
 
991
 
972
992
Eterm
973
993
term_to_binary_2(Process* p, Eterm Term, Eterm Flags)
974
994
{
1013
1033
    return erts_term_to_binary(p, Term, level, flags);
1014
1034
}
1015
1035
 
 
1036
static uLongf binary2term_uncomp_size(byte* data, Sint size)
 
1037
{
 
1038
    z_stream stream;
 
1039
    int err;
 
1040
    const uInt chunk_size = 64*1024;  /* Ask tmp-alloc about a suitable size? */
 
1041
    void* tmp_buf = erts_alloc(ERTS_ALC_T_TMP, chunk_size);
 
1042
    uLongf uncomp_size = 0;
 
1043
 
 
1044
    stream.next_in = (Bytef*)data;
 
1045
    stream.avail_in = (uInt)size;
 
1046
    stream.next_out = tmp_buf;
 
1047
    stream.avail_out = (uInt)chunk_size;
 
1048
 
 
1049
    erl_zlib_alloc_init(&stream);
 
1050
 
 
1051
    err = inflateInit(&stream);
 
1052
    if (err == Z_OK) {
 
1053
        do {
 
1054
            stream.next_out = tmp_buf;
 
1055
            stream.avail_out = chunk_size;         
 
1056
            err = inflate(&stream, Z_NO_FLUSH);
 
1057
            uncomp_size += chunk_size - stream.avail_out;
 
1058
        }while (err == Z_OK);
 
1059
        inflateEnd(&stream);
 
1060
    }
 
1061
    erts_free(ERTS_ALC_T_TMP, tmp_buf);
 
1062
    return err == Z_STREAM_END ? uncomp_size : 0;
 
1063
}
 
1064
 
1016
1065
static ERTS_INLINE Sint
1017
1066
binary2term_prepare(ErtsBinary2TermState *state, byte *data, Sint data_size)
1018
1067
{
1036
1085
        state->extp = bytes;
1037
1086
    }
1038
1087
    else  {
1039
 
        uLongf dest_len = get_int32(bytes+1);
1040
 
        state->extp = erts_alloc(ERTS_ALC_T_TMP, dest_len);
 
1088
        uLongf dest_len = (Uint32) get_int32(bytes+1);
 
1089
        bytes += 5;
 
1090
        size -= 5;      
 
1091
        if (dest_len > 32*1024*1024
 
1092
            || (state->extp = erts_alloc_fnf(ERTS_ALC_T_TMP, dest_len)) == NULL) {
 
1093
            if (dest_len != binary2term_uncomp_size(bytes, size)) {
 
1094
                goto error;
 
1095
            }
 
1096
            state->extp = erts_alloc(ERTS_ALC_T_TMP, dest_len);
 
1097
        }
1041
1098
        state->exttmp = 1;
1042
 
        if (erl_zlib_uncompress(state->extp, &dest_len, bytes+5, size-5) != Z_OK)
 
1099
        if (erl_zlib_uncompress(state->extp, &dest_len, bytes, size) != Z_OK)
1043
1100
            goto error;
1044
1101
        size = (Sint) dest_len;
1045
1102
    }
1046
 
    res = decoded_size(state->extp, state->extp + size, 0);
 
1103
    res = decoded_size(state->extp, state->extp + size, 0, 0);
1047
1104
    if (res < 0)
1048
1105
        goto error;
1049
1106
    return res;
1059
1116
}
1060
1117
 
1061
1118
static ERTS_INLINE Eterm
1062
 
binary2term_create(ErtsBinary2TermState *state, Eterm **hpp, ErlOffHeap *ohp)
 
1119
binary2term_create(ErtsDistExternal *edep, ErtsBinary2TermState *state, Eterm **hpp, ErlOffHeap *ohp)
1063
1120
{
1064
1121
    Eterm res;
1065
 
    if (!dec_term(NULL, hpp, state->extp, ohp, &res))
 
1122
    if (!dec_term(edep, hpp, state->extp, ohp, &res))
1066
1123
        res = THE_NON_VALUE;
1067
1124
    if (state->exttmp) {
1068
1125
        state->exttmp = 0;
1086
1143
Eterm
1087
1144
erts_binary2term_create(ErtsBinary2TermState *state, Eterm **hpp, ErlOffHeap *ohp)
1088
1145
{
1089
 
    return binary2term_create(state, hpp, ohp);
 
1146
    return binary2term_create(NULL,state, hpp, ohp);
1090
1147
}
1091
1148
 
1092
1149
BIF_RETTYPE binary_to_term_1(BIF_ALIST_1)
1114
1171
    hp = HAlloc(BIF_P, heap_size);
1115
1172
    endp = hp + heap_size;
1116
1173
 
1117
 
    res = binary2term_create(&b2ts, &hp, &MSO(BIF_P));
 
1174
    res = binary2term_create(NULL, &b2ts, &hp, &MSO(BIF_P));
 
1175
 
 
1176
    erts_free_aligned_binary_bytes(temp_alloc);
 
1177
 
 
1178
    if (hp > endp) {
 
1179
        erl_exit(1, ":%s, line %d: heap overrun by %d words(s)\n",
 
1180
                 __FILE__, __LINE__, hp-endp);
 
1181
    }
 
1182
 
 
1183
    HRelease(BIF_P, endp, hp);
 
1184
 
 
1185
    if (res == THE_NON_VALUE)
 
1186
        goto error;
 
1187
 
 
1188
    return res;
 
1189
}
 
1190
 
 
1191
BIF_RETTYPE binary_to_term_2(BIF_ALIST_2)
 
1192
{
 
1193
    Sint heap_size;
 
1194
    Eterm res;
 
1195
    Eterm opts;
 
1196
    Eterm opt;
 
1197
    Eterm* hp;
 
1198
    Eterm* endp;
 
1199
    Sint size;
 
1200
    byte* bytes;
 
1201
    byte* temp_alloc = NULL;
 
1202
    ErtsBinary2TermState b2ts;
 
1203
    ErtsDistExternal fakedep;
 
1204
 
 
1205
    fakedep.flags = 0;
 
1206
    opts = BIF_ARG_2;
 
1207
    while (is_list(opts)) {
 
1208
        opt = CAR(list_val(opts));
 
1209
        if (opt == am_safe) {
 
1210
            fakedep.flags |= ERTS_DIST_EXT_BTT_SAFE;
 
1211
        }
 
1212
        else {
 
1213
            goto error;
 
1214
        }
 
1215
        opts = CDR(list_val(opts));
 
1216
    }
 
1217
 
 
1218
    if (is_not_nil(opts))
 
1219
        goto error;
 
1220
 
 
1221
    if ((bytes = erts_get_aligned_binary_bytes(BIF_ARG_1, &temp_alloc)) == NULL) {
 
1222
    error:
 
1223
        erts_free_aligned_binary_bytes(temp_alloc);
 
1224
        BIF_ERROR(BIF_P, BADARG);
 
1225
    }
 
1226
    size = binary_size(BIF_ARG_1);
 
1227
 
 
1228
    heap_size = binary2term_prepare(&b2ts, bytes, size);
 
1229
    if (heap_size < 0)
 
1230
        goto error;
 
1231
 
 
1232
    hp = HAlloc(BIF_P, heap_size);
 
1233
    endp = hp + heap_size;
 
1234
 
 
1235
    res = binary2term_create(&fakedep, &b2ts, &hp, &MSO(BIF_P));
1118
1236
 
1119
1237
    erts_free_aligned_binary_bytes(temp_alloc);
1120
1238
 
1146
1264
Eterm
1147
1265
erts_term_to_binary(Process* p, Eterm Term, int level, Uint flags)
1148
1266
{
1149
 
    int size;
 
1267
    Uint size;
1150
1268
    Eterm bin;
1151
1269
    size_t real_size;
1152
1270
    byte* endp;
1163
1281
            bytes = erts_alloc(ERTS_ALC_T_TMP, size);
1164
1282
        }
1165
1283
 
1166
 
        if ((endp = enc_term(NULL, Term, bytes, flags))
 
1284
        if ((endp = enc_term(NULL, Term, bytes, flags, NULL))
1167
1285
            == NULL) {
1168
1286
            erl_exit(1, "%s, line %d: bad term: %x\n",
1169
1287
                     __FILE__, __LINE__, Term);
1208
1326
        bin = new_binary(p, (byte *)NULL, size);
1209
1327
        bytes = binary_bytes(bin);
1210
1328
        bytes[0] = VERSION_MAGIC;
1211
 
        if ((endp = enc_term(NULL, Term, bytes+1, flags))       
 
1329
        if ((endp = enc_term(NULL, Term, bytes+1, flags, NULL))
1212
1330
            == NULL) {
1213
1331
            erl_exit(1, "%s, line %d: bad term: %x\n",
1214
1332
                     __FILE__, __LINE__, Term);
1238
1356
 
1239
1357
    ASSERT(is_atom(atom));
1240
1358
 
 
1359
    if (dflags & DFLAGS_INTERNAL_TAGS) {
 
1360
        Uint aval = atom_val(atom);
 
1361
        ASSERT(aval < (1<<24));
 
1362
        if (aval >= (1 << 16)) {
 
1363
            *ep++ = ATOM_INTERNAL_REF3;
 
1364
            put_int24(aval, ep);
 
1365
            ep += 3;
 
1366
        }
 
1367
        else {
 
1368
            *ep++ = ATOM_INTERNAL_REF2;
 
1369
            put_int16(aval, ep);
 
1370
            ep += 2;
 
1371
        }
 
1372
        return ep;
 
1373
    }
1241
1374
    /*
1242
1375
     * term_to_binary/1,2 and the initial distribution message
1243
1376
     * don't use the cache.
1287
1420
    ep += 4;
1288
1421
    put_int32(os, ep);
1289
1422
    ep += 4;
1290
 
    *ep++ = pid_creation(pid);
 
1423
    *ep++ = (is_internal_pid(pid) && (dflags & DFLAGS_INTERNAL_TAGS)) ?
 
1424
        INTERNAL_CREATION : pid_creation(pid);
1291
1425
    return ep;
1292
1426
}
1293
1427
 
1300
1434
 
1301
1435
    switch (*ep++) {
1302
1436
    case ATOM_CACHE_REF:
1303
 
        if (!(edep->flags & ERTS_DIST_EXT_ATOM_TRANS_TAB))
 
1437
        if (!(edep && (edep->flags & ERTS_DIST_EXT_ATOM_TRANS_TAB)))
1304
1438
            goto error;
1305
1439
        n = get_int8(ep);
1306
1440
        ep++;
1312
1446
    case ATOM_EXT:
1313
1447
        len = get_int16(ep),
1314
1448
        ep += 2;
1315
 
        *objp = am_atom_put((char*)ep, len);
1316
 
        ep += len;
1317
 
        break;
 
1449
        goto dec_atom_common;
1318
1450
    case SMALL_ATOM_EXT:
1319
1451
        len = get_int8(ep);
1320
1452
        ep++;
1321
 
        *objp = am_atom_put((char*)ep, len);
 
1453
    dec_atom_common:
 
1454
        if (edep && (edep->flags & ERTS_DIST_EXT_BTT_SAFE)) {
 
1455
            if (!erts_atom_get((char*)ep, len, objp)) {
 
1456
                goto error;
 
1457
            }
 
1458
        } else {
 
1459
            *objp = am_atom_put((char*)ep, len);
 
1460
        }
1322
1461
        ep += len;
1323
1462
        break;
 
1463
    case ATOM_INTERNAL_REF2:
 
1464
        n = get_int16(ep);
 
1465
        ep += 2;
 
1466
        if (n >= atom_table_size()) {
 
1467
            goto error;
 
1468
        }
 
1469
        *objp = make_atom(n);
 
1470
        break;
 
1471
    case ATOM_INTERNAL_REF3:
 
1472
        n = get_int24(ep);
 
1473
        ep += 3;
 
1474
        if (n >= atom_table_size()) {
 
1475
            goto error;
 
1476
        }
 
1477
        *objp = make_atom(n);
 
1478
        break;
 
1479
 
1324
1480
    default:
1325
1481
    error:
1326
1482
        *objp = NIL;    /* Don't leave a hole in the heap */
1329
1485
    return ep;
1330
1486
}
1331
1487
 
 
1488
static ERTS_INLINE ErlNode* dec_get_node(Eterm sysname, Uint creation)
 
1489
{
 
1490
    switch (creation) {
 
1491
    case INTERNAL_CREATION:
 
1492
        return erts_this_node;
 
1493
    case ORIG_CREATION:
 
1494
        if (sysname == erts_this_node->sysname) {
 
1495
            creation = erts_this_node->creation;
 
1496
        }
 
1497
    }
 
1498
    return erts_find_or_insert_node(sysname,creation);
 
1499
}
 
1500
 
1332
1501
static byte*
1333
1502
dec_pid(ErtsDistExternal *edep, Eterm** hpp, byte* ep, ErlOffHeap* off_heap, Eterm* objp)
1334
1503
{
1352
1521
    ep += 4;
1353
1522
    if (ser > ERTS_MAX_PID_SERIAL)
1354
1523
        return NULL;
1355
 
    if ((cre = get_int8(ep)) >= MAX_CREATION)
1356
 
        return NULL;
 
1524
    cre = get_int8(ep);
1357
1525
    ep += 1;
1358
1526
 
 
1527
    if (!is_valid_creation(cre)) {
 
1528
        return NULL;
 
1529
    }
 
1530
    data = make_pid_data(ser, num);
 
1531
 
1359
1532
    /*
1360
1533
     * We are careful to create the node entry only after all
1361
1534
     * validity tests are done.
1362
1535
     */
1363
 
    cre = dec_set_creation(sysname,cre);
1364
 
    node = erts_find_or_insert_node(sysname,cre);
 
1536
    node = dec_get_node(sysname, cre);
1365
1537
 
1366
 
    data = make_pid_data(ser, num);
1367
1538
    if(node == erts_this_node) {
1368
1539
        *objp = make_internal_pid(data);
1369
1540
    } else {
1371
1542
        *hpp += EXTERNAL_THING_HEAD_SIZE + 1;
1372
1543
 
1373
1544
        etp->header = make_external_pid_header(1);
1374
 
        etp->next = off_heap->externals;
 
1545
        etp->next = off_heap->first;
1375
1546
        etp->node = node;
1376
1547
        etp->data.ui[0] = data;
1377
1548
 
1378
 
        off_heap->externals = etp;
 
1549
        off_heap->first = (struct erl_off_heap_header*) etp;
1379
1550
        *objp = make_external_pid(etp);
1380
1551
    }
1381
1552
    return ep;
1388
1559
#define ENC_LAST_ARRAY_ELEMENT ((Eterm) 3)
1389
1560
 
1390
1561
static byte*
1391
 
enc_term(ErtsAtomCacheMap *acmp, Eterm obj, byte* ep, Uint32 dflags)
 
1562
enc_term(ErtsAtomCacheMap *acmp, Eterm obj, byte* ep, Uint32 dflags,
 
1563
         struct erl_off_heap_header** off_heap)
1392
1564
{
1393
 
    DECLARE_ESTACK(s);
 
1565
    DECLARE_WSTACK(s);
1394
1566
    Uint n;
1395
1567
    Uint i;
1396
1568
    Uint j;
1397
1569
    Uint* ptr;
1398
1570
    Eterm val;
1399
1571
    FloatDef f;
 
1572
#if HALFWORD_HEAP
 
1573
    UWord wobj;
 
1574
#endif
 
1575
 
1400
1576
 
1401
1577
    goto L_jump_start;
1402
1578
 
1403
1579
 outer_loop:
1404
 
    while (!ESTACK_ISEMPTY(s)) {
1405
 
        obj = ESTACK_POP(s);
1406
 
        switch (val = ESTACK_POP(s)) {
 
1580
    while (!WSTACK_ISEMPTY(s)) {
 
1581
#if HALFWORD_HEAP
 
1582
        obj = (Eterm) (wobj = WSTACK_POP(s));
 
1583
#else
 
1584
        obj = WSTACK_POP(s);
 
1585
#endif
 
1586
        switch (val = WSTACK_POP(s)) {
1407
1587
        case ENC_TERM:
1408
1588
            break;
1409
1589
        case ENC_ONE_CONS:
1414
1594
 
1415
1595
                obj = CAR(cons);
1416
1596
                tl = CDR(cons);
1417
 
                ESTACK_PUSH(s, is_list(tl) ? ENC_ONE_CONS : ENC_TERM);
1418
 
                ESTACK_PUSH(s, tl);
 
1597
                WSTACK_PUSH(s, is_list(tl) ? ENC_ONE_CONS : ENC_TERM);
 
1598
                WSTACK_PUSH(s, tl);
1419
1599
            }
1420
1600
            break;
1421
1601
        case ENC_PATCH_FUN_SIZE:
1422
1602
            {
 
1603
#if HALFWORD_HEAP
 
1604
                byte* size_p = (byte *) wobj;
 
1605
#else
1423
1606
                byte* size_p = (byte *) obj;
1424
 
 
 
1607
#endif
1425
1608
                put_int32(ep - size_p, size_p);
1426
1609
            }
1427
1610
            goto outer_loop;
1428
1611
        case ENC_LAST_ARRAY_ELEMENT:
1429
1612
            {
 
1613
#if HALFWORD_HEAP
 
1614
                Eterm* ptr = (Eterm *) wobj;
 
1615
#else
1430
1616
                Eterm* ptr = (Eterm *) obj;
 
1617
#endif
1431
1618
                obj = *ptr;
1432
1619
            }
1433
1620
            break;
1434
1621
        default:                /* ENC_LAST_ARRAY_ELEMENT+1 and upwards */
1435
1622
            {
 
1623
#if HALFWORD_HEAP
 
1624
                Eterm* ptr = (Eterm *) wobj;
 
1625
#else
1436
1626
                Eterm* ptr = (Eterm *) obj;
 
1627
#endif
1437
1628
                obj = *ptr++;
1438
 
                ESTACK_PUSH(s, val-1);
1439
 
                ESTACK_PUSH(s, (Eterm) ptr);
 
1629
                WSTACK_PUSH(s, val-1);
 
1630
                WSTACK_PUSH(s, (UWord) ptr);
1440
1631
            }
1441
1632
            break;
1442
1633
        }
1453
1644
 
1454
1645
        case SMALL_DEF:
1455
1646
            {
 
1647
                /* From R14B we no longer restrict INTEGER_EXT to 28 bits,
 
1648
                 * as done earlier for backward compatibility reasons. */
1456
1649
                Sint val = signed_val(obj);
1457
1650
 
1458
1651
                if ((Uint)val < 256) {
1459
1652
                    *ep++ = SMALL_INTEGER_EXT;
1460
1653
                    put_int8(val, ep);
1461
1654
                    ep++;
1462
 
                } else if (sizeof(Sint) == 4 || IS_SSMALL28(val)) {
 
1655
                } else if (sizeof(Sint) == 4 || IS_SSMALL32(val)) {
1463
1656
                    *ep++ = INTEGER_EXT;
1464
1657
                    put_int32(val, ep);
1465
1658
                    ep += 4;
1466
1659
                } else {
1467
 
                    Eterm tmp_big[2];
1468
 
                    Eterm big = small_to_big(val, tmp_big);
 
1660
                    DeclareTmpHeapNoproc(tmp_big,2);
 
1661
                    Eterm big;
 
1662
                    UseTmpHeapNoproc(2);
 
1663
                    big = small_to_big(val, tmp_big);
1469
1664
                    *ep++ = SMALL_BIG_EXT;
1470
1665
                    n = big_bytes(big);
1471
1666
                    ASSERT(n < 256);
1473
1668
                    ep += 1;
1474
1669
                    *ep++ = big_sign(big);
1475
1670
                    ep = big_to_bytes(big, ep);
 
1671
                    UnUseTmpHeapNoproc(2);
1476
1672
                }
1477
1673
            }
1478
1674
            break;
1479
1675
 
1480
1676
        case BIG_DEF:
1481
 
            if ((n = big_bytes(obj)) < 256) {
1482
 
                *ep++ = SMALL_BIG_EXT;
1483
 
                put_int8(n, ep);
1484
 
                ep += 1;
1485
 
            }
1486
 
            else {
1487
 
                *ep++ = LARGE_BIG_EXT;
1488
 
                put_int32(n, ep);
1489
 
                ep += 4;
1490
 
            }
1491
 
            *ep++ = big_sign(obj);
1492
 
            ep = big_to_bytes(obj, ep);
 
1677
            {
 
1678
                int sign = big_sign(obj);
 
1679
                n = big_bytes(obj);
 
1680
                if (sizeof(Sint)==4 && n<=4) {
 
1681
                    Uint dig = big_digit(obj,0);                   
 
1682
                    Sint val = sign ? -dig : dig;
 
1683
                    if ((val<0) == sign) {
 
1684
                        *ep++ = INTEGER_EXT;
 
1685
                        put_int32(val, ep);
 
1686
                        ep += 4;
 
1687
                        break;
 
1688
                    }
 
1689
                }
 
1690
                if (n < 256) {
 
1691
                    *ep++ = SMALL_BIG_EXT;
 
1692
                    put_int8(n, ep);
 
1693
                    ep += 1;
 
1694
                }
 
1695
                else {
 
1696
                    *ep++ = LARGE_BIG_EXT;
 
1697
                    put_int32(n, ep);
 
1698
                    ep += 4;
 
1699
                }
 
1700
                *ep++ = sign;
 
1701
                ep = big_to_bytes(obj, ep);
 
1702
            }
1493
1703
            break;
1494
1704
 
1495
1705
        case PID_DEF:
1502
1712
            Uint32 *ref_num;
1503
1713
 
1504
1714
            ASSERT(dflags & DFLAG_EXTENDED_REFERENCES);
 
1715
 
1505
1716
            *ep++ = NEW_REFERENCE_EXT;
1506
1717
            i = ref_no_of_numbers(obj);
1507
1718
            put_int16(i, ep);
1508
1719
            ep += 2;
1509
1720
            ep = enc_atom(acmp,ref_node_name(obj),ep,dflags);
1510
 
            *ep++ = ref_creation(obj);
 
1721
            *ep++ = ((dflags & DFLAGS_INTERNAL_TAGS) && is_internal_ref(obj)) ?
 
1722
                INTERNAL_CREATION : ref_creation(obj);
1511
1723
            ref_num = ref_numbers(obj);
1512
1724
            for (j = 0; j < i; j++) {
1513
1725
                put_int32(ref_num[j], ep);
1523
1735
            j = port_number(obj);
1524
1736
            put_int32(j, ep);
1525
1737
            ep += 4;
1526
 
            *ep++ = port_creation(obj);
 
1738
            *ep++ = ((dflags & DFLAGS_INTERNAL_TAGS) && is_internal_port(obj)) ?
 
1739
                INTERNAL_CREATION : port_creation(obj);
1527
1740
            break;
1528
1741
 
1529
1742
        case LIST_DEF:
1563
1776
                ep += 4;
1564
1777
            }
1565
1778
            if (i > 0) {
1566
 
                ESTACK_PUSH(s, ENC_LAST_ARRAY_ELEMENT+i-1);
1567
 
                ESTACK_PUSH(s, (Eterm) ptr);
 
1779
                WSTACK_PUSH(s, ENC_LAST_ARRAY_ELEMENT+i-1);
 
1780
                WSTACK_PUSH(s, (UWord) ptr);
1568
1781
            }
1569
1782
            break;
1570
1783
 
1603
1816
                byte* bytes;
1604
1817
 
1605
1818
                ERTS_GET_BINARY_BYTES(obj, bytes, bitoffs, bitsize);
 
1819
                if (dflags & DFLAGS_INTERNAL_TAGS) {
 
1820
                    ProcBin* pb = (ProcBin*) binary_val(obj);
 
1821
                    Uint bytesize = pb->size;
 
1822
                    if (pb->thing_word == HEADER_SUB_BIN) {
 
1823
                        ErlSubBin* sub = (ErlSubBin*)pb;
 
1824
                        pb = (ProcBin*) binary_val(sub->orig);
 
1825
                        ASSERT(bytesize == sub->size);
 
1826
                        bytesize += (bitoffs + bitsize + 7) / 8;
 
1827
                    }
 
1828
                    if (pb->thing_word == HEADER_PROC_BIN
 
1829
                        && heap_bin_size(bytesize) > PROC_BIN_SIZE) {
 
1830
                        ProcBin tmp;
 
1831
                        if (bitoffs || bitsize) {
 
1832
                            *ep++ = BIT_BINARY_INTERNAL_REF;
 
1833
                            *ep++ = bitoffs;
 
1834
                            *ep++ = bitsize;
 
1835
                        }
 
1836
                        else {
 
1837
                            *ep++ = BINARY_INTERNAL_REF;
 
1838
                        }
 
1839
                        if (pb->flags) {
 
1840
                            erts_emasculate_writable_binary(pb);
 
1841
                        }
 
1842
                        erts_refc_inc(&pb->val->refc, 2);
 
1843
 
 
1844
                        sys_memcpy(&tmp, pb, sizeof(ProcBin));
 
1845
                        tmp.next = *off_heap;
 
1846
                        tmp.bytes = bytes;
 
1847
                        tmp.size = bytesize;
 
1848
                        sys_memcpy(ep, &tmp, sizeof(ProcBin));
 
1849
                        *off_heap = (struct erl_off_heap_header*) ep;
 
1850
                        ep += sizeof(ProcBin);
 
1851
                        break;
 
1852
                    }
 
1853
                }
1606
1854
                if (bitsize == 0) {
1607
1855
                    /* Plain old byte-sized binary. */
1608
1856
                    *ep++ = BINARY_EXT;
1638
1886
                    *ep++ = SMALL_INTEGER_EXT;
1639
1887
                    *ep++ = bitsize;
1640
1888
                }
1641
 
                break;
1642
1889
            }
 
1890
            break;
1643
1891
        case EXPORT_DEF:
1644
1892
            {
1645
 
                Export* exp = (Export *) (export_val(obj))[1];
 
1893
                Export* exp = *((Export **) (export_val(obj) + 1));
1646
1894
                if ((dflags & DFLAG_EXPORT_PTR_TAG) != 0) {
1647
1895
                    *ep++ = EXPORT_EXT;
1648
1896
                    ep = enc_atom(acmp, exp->code[0], ep, dflags);
1649
1897
                    ep = enc_atom(acmp, exp->code[1], ep, dflags);
1650
 
                    ep = enc_term(acmp, make_small(exp->code[2]), ep, dflags);
 
1898
                    ep = enc_term(acmp, make_small(exp->code[2]), ep, dflags, off_heap);
1651
1899
                } else {
1652
1900
                    /* Tag, arity */
1653
1901
                    *ep++ = SMALL_TUPLE_EXT;
1671
1919
                    int ei;
1672
1920
 
1673
1921
                    *ep++ = NEW_FUN_EXT;
1674
 
                    ESTACK_PUSH(s, ENC_PATCH_FUN_SIZE);
1675
 
                    ESTACK_PUSH(s, (Eterm) ep); /* Position for patching in size */
 
1922
                    WSTACK_PUSH(s, ENC_PATCH_FUN_SIZE);
 
1923
                    WSTACK_PUSH(s, (UWord) ep); /* Position for patching in size */
1676
1924
                    ep += 4;
1677
1925
                    *ep = funp->arity;
1678
1926
                    ep += 1;
1683
1931
                    put_int32(funp->num_free, ep);
1684
1932
                    ep += 4;
1685
1933
                    ep = enc_atom(acmp, funp->fe->module, ep, dflags);
1686
 
                    ep = enc_term(acmp, make_small(funp->fe->old_index), ep, dflags);
1687
 
                    ep = enc_term(acmp, make_small(funp->fe->old_uniq), ep, dflags);
 
1934
                    ep = enc_term(acmp, make_small(funp->fe->old_index), ep, dflags, off_heap);
 
1935
                    ep = enc_term(acmp, make_small(funp->fe->old_uniq), ep, dflags, off_heap);
1688
1936
                    ep = enc_pid(acmp, funp->creator, ep, dflags);
1689
1937
 
1690
1938
                fun_env:
1691
1939
                    for (ei = funp->num_free-1; ei > 0; ei--) {
1692
 
                        ESTACK_PUSH(s, ENC_TERM);
1693
 
                        ESTACK_PUSH(s, funp->env[ei]);
 
1940
                        WSTACK_PUSH(s, ENC_TERM);
 
1941
                        WSTACK_PUSH(s, (UWord) funp->env[ei]);
1694
1942
                    }
1695
1943
                    if (funp->num_free != 0) {
1696
1944
                        obj = funp->env[0];
1733
1981
            break;
1734
1982
        }
1735
1983
    }
1736
 
    DESTROY_ESTACK(s);
 
1984
    DESTROY_WSTACK(s);
1737
1985
    return ep;
1738
1986
}
1739
1987
 
1740
 
static Uint
 
1988
static
 
1989
Uint
1741
1990
is_external_string(Eterm list, int* p_is_string)
1742
1991
{
1743
1992
    Uint len = 0;
1775
2024
    return len;
1776
2025
}
1777
2026
 
 
2027
/* Assumes that the ones to undo are preluding the list. */ 
 
2028
static void
 
2029
undo_offheap_in_area(ErlOffHeap* off_heap, Eterm* start, Eterm* end)
 
2030
{
 
2031
    const Uint area_sz = (end - start) * sizeof(Eterm);
 
2032
    struct erl_off_heap_header* hdr;
 
2033
    struct erl_off_heap_header** hdr_nextp = NULL;
 
2034
 
 
2035
    for (hdr = off_heap->first; ; hdr=hdr->next) {
 
2036
        if (!in_area(hdr, start, area_sz)) {
 
2037
            if (hdr_nextp != NULL) {
 
2038
                *hdr_nextp = NULL;
 
2039
                erts_cleanup_offheap(off_heap);
 
2040
                off_heap->first = hdr;
 
2041
            }
 
2042
            break;
 
2043
        }
 
2044
        hdr_nextp = &hdr->next;
 
2045
    }    
 
2046
 
 
2047
    /* Assert that the ones to undo were indeed preluding the list. */ 
 
2048
#ifdef DEBUG
 
2049
    for (hdr = off_heap->first; hdr != NULL; hdr = hdr->next) {
 
2050
        ASSERT(!in_area(hdr, start, area_sz));
 
2051
    }    
 
2052
#endif /* DEBUG */
 
2053
}
 
2054
 
 
2055
/* Decode term from external format into *objp.
 
2056
** On failure return NULL and (R13B04) *hpp will be unchanged.
 
2057
*/
1778
2058
static byte*
1779
2059
dec_term(ErtsDistExternal *edep, Eterm** hpp, byte* ep, ErlOffHeap* off_heap, Eterm* objp)
1780
2060
{
 
2061
    Eterm* hp_saved = *hpp;
1781
2062
    int n;
1782
2063
    register Eterm* hp = *hpp;  /* Please don't take the address of hp */
1783
2064
    Eterm* next = objp;
1784
2065
 
1785
 
    *next = (Eterm) NULL;
 
2066
    *next = (Eterm) (UWord) NULL;
1786
2067
 
1787
2068
    while (next != NULL) {
1788
2069
        objp = next;
1789
 
        next = (Eterm *) (*objp);
 
2070
        next = (Eterm *) EXPAND_POINTER(*objp);
1790
2071
 
1791
2072
        switch (*ep++) {
1792
2073
        case INTEGER_EXT:
1794
2075
                Sint sn = get_int32(ep);
1795
2076
 
1796
2077
                ep += 4;
1797
 
#if defined(ARCH_64)
 
2078
#if defined(ARCH_64) && !HALFWORD_HEAP
1798
2079
                *objp = make_small(sn);
1799
2080
#else
1800
2081
                if (MY_IS_SSMALL(sn)) {
1864
2145
        case ATOM_EXT:
1865
2146
            n = get_int16(ep);
1866
2147
            ep += 2;
1867
 
            *objp = am_atom_put((char*)ep, n);
1868
 
            ep += n;
1869
 
            break;
 
2148
            goto dec_term_atom_common;
1870
2149
        case SMALL_ATOM_EXT:
1871
2150
            n = get_int8(ep);
1872
2151
            ep++;
1873
 
            *objp = am_atom_put((char*)ep, n);
 
2152
dec_term_atom_common:
 
2153
            if (edep && (edep->flags & ERTS_DIST_EXT_BTT_SAFE)) {
 
2154
                if (!erts_atom_get((char*)ep, n, objp)) {
 
2155
                    goto error;
 
2156
                }
 
2157
            } else {
 
2158
                *objp = am_atom_put((char*)ep, n);
 
2159
            }
1874
2160
            ep += n;
1875
2161
            break;
1876
2162
        case LARGE_TUPLE_EXT:
1886
2172
            hp += n;
1887
2173
            objp = hp - 1;
1888
2174
            while (n-- > 0) {
1889
 
                objp[0] = (Eterm) next;
 
2175
                objp[0] = (Eterm) COMPRESS_POINTER(next);
1890
2176
                next = objp;
1891
2177
                objp--;
1892
2178
            }
1904
2190
            *objp = make_list(hp);
1905
2191
            hp += 2*n;
1906
2192
            objp = hp - 2;
1907
 
            objp[0] = (Eterm) (objp+1);
1908
 
            objp[1] = (Eterm) next;
 
2193
            objp[0] = (Eterm) COMPRESS_POINTER((objp+1));
 
2194
            objp[1] = (Eterm) COMPRESS_POINTER(next);
1909
2195
            next = objp;
1910
2196
            objp -= 2;
1911
2197
            while (--n > 0) {
1912
 
                objp[0] = (Eterm) next;
 
2198
                objp[0] = (Eterm) COMPRESS_POINTER(next);
1913
2199
                objp[1] = make_list(objp + 2);
1914
2200
                next = objp;
1915
2201
                objp -= 2;
1973
2259
            ep = dec_pid(edep, hpp, ep, off_heap, objp);
1974
2260
            hp = *hpp;
1975
2261
            if (ep == NULL) {
1976
 
                return NULL;
 
2262
                goto error;
1977
2263
            }
1978
2264
            break;
1979
2265
        case PORT_EXT:
1990
2276
                    goto error;
1991
2277
                }
1992
2278
                ep += 4;
1993
 
                if ((cre = get_int8(ep)) >= MAX_CREATION) {
1994
 
                    goto error;
1995
 
                }
 
2279
                cre = get_int8(ep);
1996
2280
                ep++;
1997
 
                cre = dec_set_creation(sysname,cre);
1998
 
                node = erts_find_or_insert_node(sysname, cre);
 
2281
                if (!is_valid_creation(cre)) {
 
2282
                    goto error;
 
2283
                }
1999
2284
 
 
2285
                node = dec_get_node(sysname, cre);
2000
2286
                if(node == erts_this_node) {
2001
2287
                    *objp = make_internal_port(num);
2002
2288
                }
2005
2291
                    hp += EXTERNAL_THING_HEAD_SIZE + 1;
2006
2292
                    
2007
2293
                    etp->header = make_external_port_header(1);
2008
 
                    etp->next = off_heap->externals;
 
2294
                    etp->next = off_heap->first;
2009
2295
                    etp->node = node;
2010
2296
                    etp->data.ui[0] = num;
2011
2297
 
2012
 
                    off_heap->externals = etp;
 
2298
                    off_heap->first = (struct erl_off_heap_header*)etp;
2013
2299
                    *objp = make_external_port(etp);
2014
2300
                }
2015
2301
 
2033
2319
                    goto error;
2034
2320
                ep += 4;
2035
2321
 
2036
 
                if ((cre = get_int8(ep)) >= MAX_CREATION)
2037
 
                    goto error;
 
2322
                cre = get_int8(ep);
2038
2323
                ep += 1;
 
2324
                if (!is_valid_creation(cre)) {
 
2325
                    goto error;
 
2326
                }
2039
2327
                goto ref_ext_common;
2040
2328
 
2041
2329
            case NEW_REFERENCE_EXT:
2042
 
 
2043
2330
                ref_words = get_int16(ep);
2044
2331
                ep += 2;
2045
2332
 
2049
2336
                if ((ep = dec_atom(edep, ep, &sysname)) == NULL)
2050
2337
                    goto error;
2051
2338
 
2052
 
                if ((cre = get_int8(ep)) >= MAX_CREATION)
2053
 
                    goto error;
 
2339
                cre = get_int8(ep);
2054
2340
                ep += 1;
2055
 
 
 
2341
                if (!is_valid_creation(cre)) {
 
2342
                    goto error;
 
2343
                }
2056
2344
                r0 = get_int32(ep);
2057
2345
                ep += 4;
2058
2346
                if (r0 >= MAX_REFERENCE)
2060
2348
 
2061
2349
            ref_ext_common:
2062
2350
 
2063
 
                cre = dec_set_creation(sysname, cre);
2064
 
                node = erts_find_or_insert_node(sysname, cre);
 
2351
                node = dec_get_node(sysname, cre);
2065
2352
                if(node == erts_this_node) {
2066
2353
                    RefThing *rtp = (RefThing *) hp;
2067
 
                    hp += REF_THING_HEAD_SIZE;
2068
 
#ifdef ARCH_64
 
2354
                    ref_num = (Uint32 *) (hp + REF_THING_HEAD_SIZE);
 
2355
 
 
2356
#if defined(ARCH_64) && !HALFWORD_HEAP
 
2357
                    hp += REF_THING_HEAD_SIZE + ref_words/2 + 1;
2069
2358
                    rtp->header = make_ref_thing_header(ref_words/2 + 1);
2070
2359
#else
 
2360
                    hp += REF_THING_HEAD_SIZE + ref_words;
2071
2361
                    rtp->header = make_ref_thing_header(ref_words);
2072
2362
#endif
2073
2363
                    *objp = make_internal_ref(rtp);
2074
2364
                }
2075
2365
                else {
2076
2366
                    ExternalThing *etp = (ExternalThing *) hp;
2077
 
                    hp += EXTERNAL_THING_HEAD_SIZE;
2078
 
                    
2079
 
#ifdef ARCH_64
 
2367
#if defined(ARCH_64) && !HALFWORD_HEAP
 
2368
                    hp += EXTERNAL_THING_HEAD_SIZE + ref_words/2 + 1;
 
2369
#else
 
2370
                    hp += EXTERNAL_THING_HEAD_SIZE + ref_words;
 
2371
#endif
 
2372
 
 
2373
#if defined(ARCH_64) && !HALFWORD_HEAP
2080
2374
                    etp->header = make_external_ref_header(ref_words/2 + 1);
2081
2375
#else
2082
2376
                    etp->header = make_external_ref_header(ref_words);
2083
2377
#endif
2084
 
                    etp->next = off_heap->externals;
 
2378
                    etp->next = off_heap->first;
2085
2379
                    etp->node = node;
2086
2380
 
2087
 
                    off_heap->externals = etp;
 
2381
                    off_heap->first = (struct erl_off_heap_header*)etp;
2088
2382
                    *objp = make_external_ref(etp);
 
2383
                    ref_num = &(etp->data.ui32[0]);
2089
2384
                }
2090
2385
 
2091
 
                ref_num = (Uint32 *) hp;
2092
 
#ifdef ARCH_64
 
2386
#if defined(ARCH_64) && !HALFWORD_HEAP
2093
2387
                *(ref_num++) = ref_words /* 32-bit arity */;
2094
2388
#endif
2095
2389
                ref_num[0] = r0;
2097
2391
                    ref_num[i] = get_int32(ep);
2098
2392
                    ep += 4;
2099
2393
                }
2100
 
#ifdef ARCH_64
 
2394
#if defined(ARCH_64) && !HALFWORD_HEAP
2101
2395
                if ((1 + ref_words) % 2)
2102
2396
                    ref_num[ref_words] = 0;
2103
 
                hp += ref_words/2 + 1;
2104
 
#else
2105
 
                hp += ref_words;
2106
2397
#endif
2107
2398
                break;
2108
2399
            }
2130
2421
                    hp += PROC_BIN_SIZE;
2131
2422
                    pb->thing_word = HEADER_PROC_BIN;
2132
2423
                    pb->size = n;
2133
 
                    pb->next = off_heap->mso;
2134
 
                    off_heap->mso = pb;
 
2424
                    pb->next = off_heap->first;
 
2425
                    off_heap->first = (struct erl_off_heap_header*)pb;
2135
2426
                    pb->val = dbin;
2136
2427
                    pb->bytes = (byte*) dbin->orig_bytes;
2137
2428
                    pb->flags = 0;
2167
2458
                    pb = (ProcBin *) hp;
2168
2459
                    pb->thing_word = HEADER_PROC_BIN;
2169
2460
                    pb->size = n;
2170
 
                    pb->next = off_heap->mso;
2171
 
                    off_heap->mso = pb;
 
2461
                    pb->next = off_heap->first;
 
2462
                    off_heap->first = (struct erl_off_heap_header*)pb;
2172
2463
                    pb->val = dbin;
2173
2464
                    pb->bytes = (byte*) dbin->orig_bytes;
2174
2465
                    pb->flags = 0;
2209
2500
                ep = dec_term(edep, hpp, ep, off_heap, &temp);
2210
2501
                hp = *hpp;
2211
2502
                if (ep == NULL) {
2212
 
                    return NULL;
 
2503
                    goto error;
2213
2504
                }
2214
2505
                if (!is_small(temp)) {
2215
2506
                    goto error;
2218
2509
                if (arity < 0) {
2219
2510
                    goto error;
2220
2511
                }
 
2512
                if (edep && (edep->flags & ERTS_DIST_EXT_BTT_SAFE)) {
 
2513
                    if (!erts_find_export_entry(mod, name, arity))
 
2514
                        goto error;
 
2515
                }
2221
2516
                *objp = make_export(hp);
2222
2517
                *hp++ = HEADER_EXPORT;
 
2518
#if HALFWORD_HEAP
 
2519
                *((UWord *) (UWord) hp) =  (UWord) erts_export_get_or_make_stub(mod, name, arity);
 
2520
                hp += 2;
 
2521
#else
2223
2522
                *hp++ = (Eterm) erts_export_get_or_make_stub(mod, name, arity);
 
2523
#endif
2224
2524
                break;
2225
2525
            }
2226
2526
            break;
2235
2535
                Sint old_index;
2236
2536
                unsigned num_free;
2237
2537
                int i;
2238
 
                Eterm* temp_hp;
2239
 
                Eterm** hpp = &temp_hp;
2240
2538
                Eterm temp;
2241
2539
 
2242
2540
                ep += 4;        /* Skip total size in bytes */
2248
2546
                num_free = get_int32(ep);
2249
2547
                ep += 4;
2250
2548
                hp += ERL_FUN_SIZE;
2251
 
                if (num_free > 0) {
2252
 
                    /* Don't leave a hole in case we fail */
2253
 
                    *hp = make_pos_bignum_header(num_free-1);
2254
 
                }
2255
2549
                hp += num_free;
2256
 
                *hpp = hp;
2257
2550
                funp->thing_word = HEADER_FUN;
2258
2551
                funp->num_free = num_free;
2259
 
                funp->creator = NIL; /* Don't leave a hole in case we fail */
2260
2552
                *objp = make_fun(funp);
2261
2553
 
2262
2554
                /* Module */
2263
 
                if ((ep = dec_atom(edep, ep, &temp)) == NULL) {
 
2555
                if ((ep = dec_atom(edep, ep, &module)) == NULL) {
2264
2556
                    goto error;
2265
2557
                }
2266
 
                module = temp;
2267
 
 
 
2558
                *hpp = hp;
2268
2559
                /* Index */
2269
2560
                if ((ep = dec_term(edep, hpp, ep, off_heap, &temp)) == NULL) {
2270
2561
                    goto error;
2288
2579
                 * It is safe to link the fun into the fun list only when
2289
2580
                 * no more validity tests can fail.
2290
2581
                 */
2291
 
                funp->next = off_heap->funs;
2292
 
                off_heap->funs = funp;
 
2582
                funp->next = off_heap->first;
 
2583
                off_heap->first = (struct erl_off_heap_header*)funp;
2293
2584
#endif
2294
2585
 
2295
2586
                funp->fe = erts_put_fun_entry2(module, old_uniq, old_index,
2305
2596
 
2306
2597
                /* Environment */
2307
2598
                for (i = num_free-1; i >= 0; i--) {
2308
 
                    funp->env[i] = (Eterm) next;
 
2599
                    funp->env[i] = (Eterm) COMPRESS_POINTER(next);
2309
2600
                    next = funp->env + i;
2310
2601
                }
2311
2602
                /* Creator */
2312
 
                funp->creator = (Eterm) next;
 
2603
                funp->creator = (Eterm) COMPRESS_POINTER(next);
2313
2604
                next = &(funp->creator);
2314
2605
                break;
2315
2606
            }
2321
2612
                Sint old_index;
2322
2613
                unsigned num_free;
2323
2614
                int i;
2324
 
                Eterm* temp_hp;
2325
 
                Eterm** hpp = &temp_hp;
2326
2615
                Eterm temp;
2327
2616
 
2328
2617
                num_free = get_int32(ep);
2329
2618
                ep += 4;
2330
2619
                hp += ERL_FUN_SIZE;
2331
 
                if (num_free > 0) {
2332
 
                    /* Don't leave a hole in the heap in case we fail. */
2333
 
                    *hp = make_pos_bignum_header(num_free-1);
2334
 
                }
2335
2620
                hp += num_free;
2336
2621
                *hpp = hp;
2337
2622
                funp->thing_word = HEADER_FUN;
2339
2624
                *objp = make_fun(funp);
2340
2625
 
2341
2626
                /* Creator pid */
2342
 
                switch(*ep) {
2343
 
                case PID_EXT:
2344
 
                    ep = dec_pid(edep, hpp, ++ep, off_heap, &funp->creator);
2345
 
                    if (ep == NULL) {
2346
 
                        funp->creator = NIL; /* Don't leave a hole in the heap */
2347
 
                        goto error;
2348
 
                    }
2349
 
                    break;
2350
 
                default:
 
2627
                if (*ep != PID_EXT 
 
2628
                    || (ep = dec_pid(edep, hpp, ++ep, off_heap,
 
2629
                                     &funp->creator))==NULL) { 
2351
2630
                    goto error;
2352
2631
                }
2353
2632
 
2354
2633
                /* Module */
2355
 
                if ((ep = dec_atom(edep, ep, &temp)) == NULL) {
 
2634
                if ((ep = dec_atom(edep, ep, &module)) == NULL) {
2356
2635
                    goto error;
2357
2636
                }
2358
 
                module = temp;
2359
2637
 
2360
2638
                /* Index */
2361
2639
                if ((ep = dec_term(edep, hpp, ep, off_heap, &temp)) == NULL) {
2379
2657
                 * It is safe to link the fun into the fun list only when
2380
2658
                 * no more validity tests can fail.
2381
2659
                 */
2382
 
                funp->next = off_heap->funs;
2383
 
                off_heap->funs = funp;
 
2660
                funp->next = off_heap->first;
 
2661
                off_heap->first = (struct erl_off_heap_header*)funp;
2384
2662
#endif
2385
 
 
2386
2663
                old_uniq = unsigned_val(temp);
2387
2664
 
2388
2665
                funp->fe = erts_put_fun_entry(module, old_uniq, old_index);
2394
2671
 
2395
2672
                /* Environment */
2396
2673
                for (i = num_free-1; i >= 0; i--) {
2397
 
                    funp->env[i] = (Eterm) next;
 
2674
                    funp->env[i] = (Eterm) COMPRESS_POINTER(next);
2398
2675
                    next = funp->env + i;
2399
2676
                }
2400
2677
                break;
2401
2678
            }
 
2679
        case ATOM_INTERNAL_REF2:
 
2680
            n = get_int16(ep);
 
2681
            ep += 2;
 
2682
            if (n >= atom_table_size()) {
 
2683
                goto error;
 
2684
            }
 
2685
            *objp = make_atom(n);
 
2686
            break;
 
2687
        case ATOM_INTERNAL_REF3:
 
2688
            n = get_int24(ep);
 
2689
            ep += 3;
 
2690
            if (n >= atom_table_size()) {
 
2691
                goto error;
 
2692
            }
 
2693
            *objp = make_atom(n);
 
2694
            break;
 
2695
 
 
2696
        case BINARY_INTERNAL_REF:
 
2697
            {
 
2698
                ProcBin* pb = (ProcBin*) hp;
 
2699
                sys_memcpy(pb, ep, sizeof(ProcBin));
 
2700
                ep += sizeof(ProcBin);
 
2701
 
 
2702
                erts_refc_inc(&pb->val->refc, 1);
 
2703
                hp += PROC_BIN_SIZE;
 
2704
                pb->next = off_heap->first;
 
2705
                off_heap->first = (struct erl_off_heap_header*)pb;
 
2706
                pb->flags = 0;
 
2707
                *objp = make_binary(pb);
 
2708
                break;
 
2709
            }
 
2710
        case BIT_BINARY_INTERNAL_REF:
 
2711
            {
 
2712
                Sint bitoffs = *ep++;
 
2713
                Sint bitsize = *ep++;
 
2714
                ProcBin* pb = (ProcBin*) hp;
 
2715
                ErlSubBin* sub;
 
2716
                sys_memcpy(pb, ep, sizeof(ProcBin));
 
2717
                ep += sizeof(ProcBin);
 
2718
 
 
2719
                erts_refc_inc(&pb->val->refc, 1);
 
2720
                hp += PROC_BIN_SIZE;
 
2721
                pb->next = off_heap->first;
 
2722
                off_heap->first = (struct erl_off_heap_header*)pb;
 
2723
                pb->flags = 0;
 
2724
 
 
2725
                sub = (ErlSubBin*)hp;
 
2726
                sub->thing_word = HEADER_SUB_BIN;
 
2727
                sub->size = pb->size - (bitoffs + bitsize + 7)/8;
 
2728
                sub->offs = 0;
 
2729
                sub->bitoffs = bitoffs;
 
2730
                sub->bitsize = bitsize;
 
2731
                sub->is_writable = 0;
 
2732
                sub->orig = make_binary(pb);
 
2733
 
 
2734
                hp += ERL_SUB_BIN_SIZE;
 
2735
                *objp = make_binary(sub);
 
2736
                break;
 
2737
            }
 
2738
 
2402
2739
        default:
2403
2740
        error:
2404
 
            /*
2405
 
             * Be careful to return the updated heap pointer, to avoid
2406
 
             * that the caller wipes out binaries or other off-heap objects
2407
 
             * that may have been linked into the process.
 
2741
            /* UNDO:
 
2742
             * Must unlink all off-heap objects that may have been
 
2743
             * linked into the process. 
2408
2744
             */
2409
 
            *hpp = hp;
 
2745
            if (hp < *hpp) { /* Sometimes we used hp and sometimes *hpp */
 
2746
                hp = *hpp;   /* the largest must be the freshest */
 
2747
            }
 
2748
            undo_offheap_in_area(off_heap, hp_saved, hp);
 
2749
            *hpp = hp_saved;
2410
2750
            return NULL;
2411
2751
        }
2412
2752
    }
2422
2762
static Uint
2423
2763
encode_size_struct2(ErtsAtomCacheMap *acmp, Eterm obj, unsigned dflags)
2424
2764
{
2425
 
    DECLARE_ESTACK(s);
 
2765
    DECLARE_WSTACK(s);
2426
2766
    Uint m, i, arity;
2427
2767
    Uint result = 0;
 
2768
#if HALFWORD_HEAP
 
2769
    UWord wobj = 0;
 
2770
#endif
2428
2771
 
2429
2772
    goto L_jump_start;
2430
2773
 
2431
2774
 outer_loop:
2432
 
    while (!ESTACK_ISEMPTY(s)) {
2433
 
        obj = ESTACK_POP(s);
2434
 
 
 
2775
    while (!WSTACK_ISEMPTY(s)) {
 
2776
#if HALFWORD_HEAP
 
2777
        obj = (Eterm) (wobj = WSTACK_POP(s));
 
2778
#else
 
2779
        obj = WSTACK_POP(s);
 
2780
#endif
2435
2781
    handle_popped_obj:
2436
 
        if (is_CP(obj)) {
 
2782
        if (is_CP(obj)) { /* Does not look for CP, looks for "no tag" */
 
2783
#if HALFWORD_HEAP
 
2784
            Eterm* ptr = (Eterm *) wobj;
 
2785
#else
2437
2786
            Eterm* ptr = (Eterm *) obj;
2438
 
 
 
2787
#endif
2439
2788
            /*
2440
2789
             * Pointer into a tuple.
2441
2790
             */
2442
2791
            obj = *ptr--;
2443
2792
            if (!is_header(obj)) {
2444
 
                ESTACK_PUSH(s, (Eterm)ptr);
 
2793
                WSTACK_PUSH(s, (UWord)ptr);
2445
2794
            } else {
2446
2795
                /* Reached tuple header */
2447
2796
                ASSERT(header_is_arityval(obj));
2453
2802
 
2454
2803
            tl = CDR(cons);
2455
2804
            obj = CAR(cons);
2456
 
            ESTACK_PUSH(s, tl);
 
2805
            WSTACK_PUSH(s, tl);
2457
2806
        } else if (is_nil(obj)) {
2458
2807
            result++;
2459
2808
            goto outer_loop;
2469
2818
        case NIL_DEF:
2470
2819
            result++;
2471
2820
            break;
2472
 
        case ATOM_DEF: {
2473
 
            int alen = atom_tab(atom_val(obj))->len;
2474
 
            if ((MAX_ATOM_LENGTH <= 255 || alen <= 255)
2475
 
                && (dflags & DFLAG_SMALL_ATOM_TAGS)) {
2476
 
                /* Make sure a SMALL_ATOM_EXT fits: SMALL_ATOM_EXT l t1 t2... */
2477
 
                result += 1 + 1 + alen;
 
2821
        case ATOM_DEF:
 
2822
            if (dflags & DFLAGS_INTERNAL_TAGS) {
 
2823
                if (atom_val(obj) >= (1<<16)) {
 
2824
                    result += 1 + 3;
 
2825
                }
 
2826
                else {
 
2827
                    result += 1 + 2;
 
2828
                }
2478
2829
            }
2479
2830
            else {
2480
 
                /* Make sure an ATOM_EXT fits: ATOM_EXT l1 l0 t1 t2... */
2481
 
                result += 1 + 2 + alen;
 
2831
                int alen = atom_tab(atom_val(obj))->len;
 
2832
                if ((MAX_ATOM_LENGTH <= 255 || alen <= 255)
 
2833
                    && (dflags & DFLAG_SMALL_ATOM_TAGS)) {
 
2834
                    /* Make sure a SMALL_ATOM_EXT fits: SMALL_ATOM_EXT l t1 t2... */
 
2835
                        result += 1 + 1 + alen;
 
2836
                }
 
2837
                else {
 
2838
                    /* Make sure an ATOM_EXT fits: ATOM_EXT l1 l0 t1 t2... */
 
2839
                        result += 1 + 2 + alen;
 
2840
                }
 
2841
                insert_acache_map(acmp, obj);
2482
2842
            }
2483
 
            insert_acache_map(acmp, obj);
2484
2843
            break;
2485
 
        }
2486
2844
        case SMALL_DEF:
2487
2845
            {
2488
2846
                Sint val = signed_val(obj);
2489
2847
 
2490
2848
                if ((Uint)val < 256)
2491
2849
                    result += 1 + 1;            /* SMALL_INTEGER_EXT */
2492
 
                else if (sizeof(Sint) == 4 || IS_SSMALL28(val))
 
2850
                else if (sizeof(Sint) == 4 || IS_SSMALL32(val))
2493
2851
                    result += 1 + 4;            /* INTEGER_EXT */
2494
2852
                else {
2495
 
                    Eterm tmp_big[2];
 
2853
                    DeclareTmpHeapNoproc(tmp_big,2);
 
2854
                    UseTmpHeapNoproc(2);
2496
2855
                    i = big_bytes(small_to_big(val, tmp_big));
2497
2856
                    result += 1 + 1 + 1 + i;    /* SMALL_BIG_EXT */
 
2857
                    UnUseTmpHeapNoproc(2);
2498
2858
                }
2499
2859
            }
2500
2860
            break;
2501
2861
        case BIG_DEF:
2502
 
            if ((i = big_bytes(obj)) < 256)
 
2862
            i = big_bytes(obj);
 
2863
            if (sizeof(Sint)==4 && i <= 4 && (big_digit(obj,0)-big_sign(obj)) < (1<<31))
 
2864
                result += 1 + 4;          /* INTEGER_EXT */
 
2865
            else if (i < 256)
2503
2866
                result += 1 + 1 + 1 + i;  /* tag,size,sign,digits */
2504
2867
            else
2505
2868
                result += 1 + 4 + 1 + i;  /* tag,size,sign,digits */
2540
2903
                    result += 1 + 4;
2541
2904
                }
2542
2905
                ptr += arity;
 
2906
#if HALFWORD_HEAP
 
2907
                obj = (Eterm) (wobj = (UWord) ptr);
 
2908
#else
2543
2909
                obj = (Eterm) ptr;
 
2910
#endif
2544
2911
                goto handle_popped_obj;
2545
2912
            }
2546
2913
            break;
2552
2919
            }
2553
2920
            break;
2554
2921
        case BINARY_DEF:
 
2922
            if (dflags & DFLAGS_INTERNAL_TAGS) {
 
2923
                ProcBin* pb = (ProcBin*) binary_val(obj);
 
2924
                Uint sub_extra = 0;
 
2925
                Uint tot_bytes = pb->size;
 
2926
                if (pb->thing_word == HEADER_SUB_BIN) {
 
2927
                    ErlSubBin* sub = (ErlSubBin*) pb;
 
2928
                    pb = (ProcBin*) binary_val(sub->orig);
 
2929
                    sub_extra = 2;  /* bitoffs and bitsize */
 
2930
                    tot_bytes += (sub->bitoffs + sub->bitsize+ 7) / 8;
 
2931
                }
 
2932
                if (pb->thing_word == HEADER_PROC_BIN
 
2933
                    && heap_bin_size(tot_bytes) > PROC_BIN_SIZE) {
 
2934
 
 
2935
                    result += 1 + sub_extra + sizeof(ProcBin);
 
2936
                    break;
 
2937
                }
 
2938
            }
2555
2939
            result += 1 + 4 + binary_size(obj) +
2556
 
                5;                      /* For unaligned binary */
 
2940
                    5;                  /* For unaligned binary */
2557
2941
            break;
2558
2942
        case FUN_DEF:
2559
2943
            {
2582
2966
 
2583
2967
                    if (is_not_list(obj)) {
2584
2968
                        /* Push any non-list terms on the stack */
2585
 
                        ESTACK_PUSH(s, obj);
 
2969
                        WSTACK_PUSH(s, obj);
2586
2970
                    } else {
2587
2971
                        /* Lists must be handled specially. */
2588
2972
                        if ((m = is_string(obj)) && (m < MAX_STRING_LEN)) {
2589
2973
                            result += m + 2 + 1;
2590
2974
                        } else {
2591
2975
                            result += 5;
2592
 
                            ESTACK_PUSH(s, obj);
 
2976
                            WSTACK_PUSH(s, obj);
2593
2977
                        }
2594
2978
                    }
2595
2979
                }
2602
2986
 
2603
2987
        case EXPORT_DEF:
2604
2988
            {
2605
 
                Export* ep = (Export *) (export_val(obj))[1];
 
2989
                Export* ep = *((Export **) (export_val(obj) + 1));
 
2990
#if HALFWORD_HEAP
 
2991
                result += 2;
 
2992
#else
2606
2993
                result += 1;
 
2994
#endif
2607
2995
                result += encode_size_struct2(acmp, ep->code[0], dflags);
2608
2996
                result += encode_size_struct2(acmp, ep->code[1], dflags);
2609
2997
                result += encode_size_struct2(acmp, make_small(ep->code[2]), dflags);
2616
3004
        }
2617
3005
    }
2618
3006
 
2619
 
    DESTROY_ESTACK(s);
 
3007
    DESTROY_WSTACK(s);
2620
3008
    return result;
2621
3009
}
2622
3010
 
2623
3011
static Sint
2624
 
decoded_size(byte *ep, byte* endp, int no_refc_bins)
 
3012
decoded_size(byte *ep, byte* endp, int no_refc_bins, int internal_tags)
2625
3013
{
2626
3014
    int heap_size = 0;
2627
3015
    int terms;
2728
3116
                ep += 2;
2729
3117
                atom_extra_skip = 1 + 4*id_words;
2730
3118
                /* In case it is an external ref */
2731
 
#ifdef ARCH_64
 
3119
#if defined(ARCH_64) && !HALFWORD_HEAP
2732
3120
                heap_size += EXTERNAL_THING_HEAD_SIZE + id_words/2 + 1;
2733
3121
#else
2734
3122
                heap_size += EXTERNAL_THING_HEAD_SIZE + id_words;
2803
3191
            break;
2804
3192
        case EXPORT_EXT:
2805
3193
            terms += 3;
 
3194
#if HALFWORD_HEAP
 
3195
            heap_size += 3;
 
3196
#else
2806
3197
            heap_size += 2;
 
3198
#endif
2807
3199
            break;
2808
3200
        case NEW_FUN_EXT:
2809
3201
            {
2827
3219
                heap_size += ERL_FUN_SIZE + num_free;
2828
3220
                break;
2829
3221
            }
 
3222
        case ATOM_INTERNAL_REF2:
 
3223
            SKIP(2+atom_extra_skip);
 
3224
            atom_extra_skip = 0;
 
3225
            break;
 
3226
        case ATOM_INTERNAL_REF3:
 
3227
            SKIP(3+atom_extra_skip);
 
3228
            atom_extra_skip = 0;
 
3229
            break;
 
3230
 
 
3231
        case BINARY_INTERNAL_REF:
 
3232
            if (!internal_tags) {
 
3233
                return -1;
 
3234
            }
 
3235
            SKIP(sizeof(ProcBin));
 
3236
            heap_size += PROC_BIN_SIZE;
 
3237
            break;
 
3238
        case BIT_BINARY_INTERNAL_REF:
 
3239
            if (!internal_tags) {
 
3240
                return -1;
 
3241
            }
 
3242
            SKIP(2+sizeof(ProcBin));
 
3243
            heap_size += PROC_BIN_SIZE + ERL_SUB_BIN_SIZE;
 
3244
            break;
2830
3245
        default:
2831
3246
            return -1;
2832
3247
        }