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

« back to all changes in this revision

Viewing changes to erts/emulator/beam/utils.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
 
32
32
#include "erl_binary.h"
33
33
#include "erl_bits.h"
34
34
#include "packet_parser.h"
 
35
#include "erl_gc.h"
35
36
#define ERTS_WANT_DB_INTERNAL__
36
37
#include "erl_db.h"
37
38
#include "erl_threads.h"
47
48
#undef M_MMAP_THRESHOLD
48
49
#undef M_MMAP_MAX
49
50
 
50
 
#if !defined(ELIB_ALLOC_IS_CLIB) && defined(__GLIBC__) && defined(HAVE_MALLOC_H)
 
51
#if defined(__GLIBC__) && defined(HAVE_MALLOC_H)
51
52
#include <malloc.h>
52
53
#endif
53
54
 
54
 
#if defined(ELIB_ALLOC_IS_CLIB) || !defined(HAVE_MALLOPT)
 
55
#if !defined(HAVE_MALLOPT)
55
56
#undef  HAVE_MALLOPT
56
57
#define HAVE_MALLOPT 0
57
58
#endif
58
59
 
59
60
/* profile_scheduler mini message queue */
60
61
 
61
 
#ifdef ERTS_TIMER_THREAD
62
 
/* A timer thread is not welcomed with this lock violation work around.
63
 
 * - Bj�rn-Egil
64
 
 */
65
 
#error Timer thread may not be enabled due to lock violation.
66
 
#endif
67
 
 
68
62
typedef struct {
69
63
    Uint scheduler_id;
70
64
    Uint no_schedulers;
95
89
 
96
90
#endif
97
91
 
 
92
 
98
93
Eterm*
99
 
erts_heap_alloc(Process* p, Uint need)
 
94
erts_heap_alloc(Process* p, Uint need, Uint xtra)
100
95
{
101
96
    ErlHeapFragment* bp;
102
97
    Eterm* htop;
105
100
    Uint i;
106
101
#endif
107
102
 
108
 
    n = need;
 
103
#ifdef FORCE_HEAP_FRAGS
 
104
    if (p->space_verified && p->space_verified_from!=NULL
 
105
        && HEAP_TOP(p) >= p->space_verified_from
 
106
        && HEAP_TOP(p) + need <= p->space_verified_from + p->space_verified
 
107
        && HEAP_LIMIT(p) - HEAP_TOP(p) >= need) {
 
108
        
 
109
        Uint consumed = need + (HEAP_TOP(p) - p->space_verified_from);
 
110
        ASSERT(consumed <= p->space_verified);
 
111
        p->space_verified -= consumed;
 
112
        p->space_verified_from += consumed;
 
113
        HEAP_TOP(p) = p->space_verified_from;
 
114
        return HEAP_TOP(p) - need;
 
115
    }
 
116
    p->space_verified = 0;
 
117
    p->space_verified_from = NULL;
 
118
#endif /* FORCE_HEAP_FRAGS */
 
119
 
 
120
    n = need + xtra;
 
121
    bp = MBUF(p);
 
122
    if (bp != NULL && need <= (bp->alloc_size - bp->used_size)) {
 
123
        Eterm* ret = bp->mem + bp->used_size;
 
124
        bp->used_size += need;
 
125
        return ret;
 
126
    }
109
127
#ifdef DEBUG
110
128
    n++;
111
129
#endif
112
130
    bp = (ErlHeapFragment*)
113
 
        ERTS_HEAP_ALLOC(ERTS_ALC_T_HEAP_FRAG,
114
 
                        sizeof(ErlHeapFragment) + ((n-1)*sizeof(Eterm)));
 
131
        ERTS_HEAP_ALLOC(ERTS_ALC_T_HEAP_FRAG, ERTS_HEAP_FRAG_SIZE(n));
 
132
 
 
133
#if defined(DEBUG) || defined(CHECK_FOR_HOLES)
 
134
    for (i = 0; i < n; i++) {
 
135
        bp->mem[i] = ERTS_HOLE_MARKER;
 
136
    }
 
137
#endif
115
138
 
116
139
#ifdef DEBUG
117
140
    n--;
118
141
#endif
119
142
 
120
 
#if defined(DEBUG)
121
 
    for (i = 0; i <= n; i++) {
122
 
        bp->mem[i] = ERTS_HOLE_MARKER;
123
 
    }
124
 
#elif defined(CHECK_FOR_HOLES)
125
 
    for (i = 0; i < n; i++) {
126
 
        bp->mem[i] = ERTS_HOLE_MARKER;
127
 
    }
128
 
#endif
129
 
 
130
143
    /*
131
144
     * When we have created a heap fragment, we are no longer allowed
132
145
     * to store anything more on the heap. 
139
152
 
140
153
    bp->next = MBUF(p);
141
154
    MBUF(p) = bp;
142
 
    bp->size = n;
 
155
    bp->alloc_size = n;
 
156
    bp->used_size = need;
143
157
    MBUF_SIZE(p) += n;
144
 
    bp->off_heap.mso = NULL;
145
 
#ifndef HYBRID /* FIND ME! */
146
 
    bp->off_heap.funs = NULL;
147
 
#endif
148
 
    bp->off_heap.externals = NULL;
 
158
    bp->off_heap.first = NULL;
149
159
    bp->off_heap.overhead = 0;
150
 
 
151
160
    return bp->mem;
152
161
}
153
162
 
154
 
void erts_arith_shrink(Process* p, Eterm* hp)
155
 
{
156
 
#if defined(CHECK_FOR_HOLES)
157
 
    ErlHeapFragment* hf;
158
 
 
159
 
    /*
160
 
     * We must find the heap fragment that hp points into.
161
 
     * If we are unlucky, we might have to search through
162
 
     * a large part of the list. We'll hope that will not
163
 
     * happen too often.
164
 
     */
165
 
    for (hf = MBUF(p); hf != 0; hf = hf->next) {
166
 
        if (hp - hf->mem < (unsigned long)hf->size) {
167
 
            /*
168
 
             * We are not allowed to changed hf->size (because the
169
 
             * size must be correct when deallocating). Therefore,
170
 
             * clear out the uninitialized part of the heap fragment.
171
 
             */
172
 
            Eterm* to = hf->mem + hf->size;
173
 
            while (hp < to) {
174
 
                *hp++ = NIL;
175
 
            }
176
 
            break;
177
 
        }
178
 
    }
179
 
#endif
180
 
}
181
 
 
182
163
#ifdef CHECK_FOR_HOLES
183
164
Eterm*
184
165
erts_set_hole_marker(Eterm* ptr, Uint sz)
212
193
    *end = *start + new_size;
213
194
    *sp = *start + sp_offs;
214
195
}
 
196
/*
 
197
 * Helper function for the ESTACK macros defined in global.h.
 
198
 */
 
199
void
 
200
erl_grow_wstack(UWord** start, UWord** sp, UWord** end)
 
201
{
 
202
    Uint old_size = (*end - *start);
 
203
    Uint new_size = old_size * 2;
 
204
    Uint sp_offs = *sp - *start;
 
205
    if (new_size > 2 * DEF_ESTACK_SIZE) {
 
206
        *start = erts_realloc(ERTS_ALC_T_ESTACK, (void *) *start, new_size*sizeof(UWord));
 
207
    } else {
 
208
        UWord* new_ptr = erts_alloc(ERTS_ALC_T_ESTACK, new_size*sizeof(UWord));
 
209
        sys_memcpy(new_ptr, *start, old_size*sizeof(UWord));
 
210
        *start = new_ptr;
 
211
    }
 
212
    *end = *start + new_size;
 
213
    *sp = *start + sp_offs;
 
214
}
215
215
 
216
216
/* CTYPE macros */
217
217
 
362
362
    return res;
363
363
}
364
364
 
 
365
/*
 
366
 * Erts_bld_uword is more or less similar to erts_bld_uint, but a pointer
 
367
 * can safely be passed.
 
368
 */
 
369
 
 
370
Eterm
 
371
erts_bld_uword(Uint **hpp, Uint *szp, UWord uw)
 
372
{
 
373
    Eterm res = THE_NON_VALUE;
 
374
    if (IS_USMALL(0, uw)) {
 
375
        if (hpp)
 
376
            res = make_small((Uint) uw);
 
377
    }
 
378
    else {
 
379
        if (szp)
 
380
            *szp += BIG_UWORD_HEAP_SIZE(uw);
 
381
        if (hpp) {
 
382
            res = uword_to_big(uw, *hpp);
 
383
            *hpp += BIG_UWORD_HEAP_SIZE(uw);
 
384
        }
 
385
    }
 
386
    return res;
 
387
}
 
388
 
 
389
 
365
390
Eterm
366
391
erts_bld_uint64(Uint **hpp, Uint *szp, Uint64 ui64)
367
392
{
372
397
    }
373
398
    else {
374
399
        if (szp)
375
 
            *szp = ERTS_UINT64_HEAP_SIZE(ui64);
 
400
            *szp += ERTS_UINT64_HEAP_SIZE(ui64);
376
401
        if (hpp)
377
402
            res = erts_uint64_to_big(ui64, hpp);
378
403
    }
389
414
    }
390
415
    else {
391
416
        if (szp)
392
 
            *szp = ERTS_SINT64_HEAP_SIZE(si64);
 
417
            *szp += ERTS_SINT64_HEAP_SIZE(si64);
393
418
        if (hpp)
394
419
            res = erts_sint64_to_big(si64, hpp);
395
420
    }
473
498
    if (hpp) {
474
499
        res = NIL;
475
500
        while (--i >= 0) {
476
 
            res = CONS(*hpp, make_small(str[i]), res);
 
501
            res = CONS(*hpp, make_small((byte) str[i]), res);
477
502
            *hpp += 2;
478
503
        }
479
504
    }
719
744
 
720
745
Uint32 make_hash(Eterm term_arg)
721
746
{
722
 
    DECLARE_ESTACK(stack);
 
747
    DECLARE_WSTACK(stack);
723
748
    Eterm term = term_arg;
724
749
    Eterm hash = 0;
725
750
    unsigned op;
778
803
            Uint y2 = y1 < 0 ? -(Uint)y1 : y1;
779
804
 
780
805
            UINT32_HASH_STEP(y2, FUNNY_NUMBER2);
781
 
#ifdef ARCH_64
 
806
#if defined(ARCH_64) && !HALFWORD_HEAP
782
807
            if (y2 >> 32)
783
808
                UINT32_HASH_STEP(y2 >> 32, FUNNY_NUMBER2);
784
809
#endif
795
820
        }
796
821
    case EXPORT_DEF:
797
822
        {
798
 
            Export* ep = (Export *) (export_val(term))[1];
 
823
            Export* ep = *((Export **) (export_val(term) + 1));
799
824
 
800
825
            hash = hash * FUNNY_NUMBER11 + ep->code[2];
801
826
            hash = hash*FUNNY_NUMBER1 + 
817
842
            hash = hash*FUNNY_NUMBER2 + funp->fe->old_uniq;
818
843
            if (num_free > 0) {
819
844
                if (num_free > 1) {
820
 
                    ESTACK_PUSH3(stack, (Eterm) &funp->env[1], (num_free-1), MAKE_HASH_FUN_OP);
 
845
                    WSTACK_PUSH3(stack, (UWord) &funp->env[1], (num_free-1), MAKE_HASH_FUN_OP);
821
846
                }
822
847
                term = funp->env[0];
823
848
                goto tail_recur;
845
870
        }
846
871
 
847
872
    case MAKE_HASH_CDR_PRE_OP:
848
 
        term = ESTACK_POP(stack);
 
873
        term = (Eterm) WSTACK_POP(stack);
849
874
        if (is_not_list(term)) {
850
 
            ESTACK_PUSH(stack, MAKE_HASH_CDR_POST_OP);
 
875
            WSTACK_PUSH(stack, (UWord) MAKE_HASH_CDR_POST_OP);
851
876
            goto tail_recur;
852
877
        }
853
878
        /* fall through */
862
887
                hash = hash*FUNNY_NUMBER2 + unsigned_val(*list);
863
888
                
864
889
                if (is_not_list(CDR(list))) {
865
 
                    ESTACK_PUSH(stack, MAKE_HASH_CDR_POST_OP);
 
890
                    WSTACK_PUSH(stack, MAKE_HASH_CDR_POST_OP);
866
891
                    term = CDR(list);
867
892
                    goto tail_recur;
868
893
                }               
869
894
                list = list_val(CDR(list));
870
895
            }
871
 
            ESTACK_PUSH2(stack, CDR(list), MAKE_HASH_CDR_PRE_OP);
 
896
            WSTACK_PUSH2(stack, CDR(list), MAKE_HASH_CDR_PRE_OP);
872
897
            term = CAR(list);
873
898
            goto tail_recur;
874
899
        }
896
921
            }
897
922
            d = BIG_DIGIT(ptr, k);
898
923
            k = sizeof(ErtsDigit);
899
 
#ifdef ARCH_64
 
924
#if defined(ARCH_64) && !HALFWORD_HEAP
900
925
            if (!(d >> 32))
901
926
                k /= 2;
902
927
#endif
912
937
            Eterm* ptr = tuple_val(term);
913
938
            Uint arity = arityval(*ptr);
914
939
 
915
 
            ESTACK_PUSH3(stack, arity, (Eterm)(ptr+1), arity);
 
940
            WSTACK_PUSH3(stack, (UWord) arity, (UWord)(ptr+1), (UWord) arity);
916
941
            op = MAKE_HASH_TUPLE_OP;        
917
942
        }/*fall through*/
918
943
    case MAKE_HASH_TUPLE_OP:
919
944
    case MAKE_HASH_FUN_OP:
920
945
        {
921
 
            Uint i = ESTACK_POP(stack);
922
 
            Eterm* ptr = (Eterm*) ESTACK_POP(stack);
 
946
            Uint i = (Uint) WSTACK_POP(stack);
 
947
            Eterm* ptr = (Eterm*) WSTACK_POP(stack);
923
948
            if (i != 0) {
924
949
                term = *ptr;
925
 
                ESTACK_PUSH3(stack, (Eterm)(ptr+1), i-1, op);
 
950
                WSTACK_PUSH3(stack, (UWord)(ptr+1), (UWord) i-1, (UWord) op);
926
951
                goto tail_recur;
927
952
            }
928
953
            if (op == MAKE_HASH_TUPLE_OP) {
929
 
                Uint32 arity = ESTACK_POP(stack);
 
954
                Uint32 arity = (Uint32) WSTACK_POP(stack);
930
955
                hash = hash*FUNNY_NUMBER9 + arity;
931
956
            }
932
957
            break;
936
961
        erl_exit(1, "Invalid tag in make_hash(0x%X,0x%X)\n", term, op);
937
962
        return 0;
938
963
      }
939
 
      if (ESTACK_ISEMPTY(stack)) break;
940
 
      op = ESTACK_POP(stack);
 
964
      if (WSTACK_ISEMPTY(stack)) break;
 
965
      op = WSTACK_POP(stack);
941
966
    }
942
 
    DESTROY_ESTACK(stack);
 
967
    DESTROY_WSTACK(stack);
943
968
    return hash;
944
969
 
945
970
#undef UINT32_HASH_STEP
1010
1035
make_hash2(Eterm term)
1011
1036
{
1012
1037
    Uint32 hash;
1013
 
    Eterm tmp_big[2];
 
1038
    DeclareTmpHeapNoproc(tmp_big,2);
1014
1039
 
1015
1040
/* (HCONST * {2, ..., 14}) mod 2^32 */
1016
1041
#define HCONST_2 0x3c6ef372UL
1049
1074
        } while(0)
1050
1075
 
1051
1076
#define IS_SSMALL28(x) (((Uint) (((x) >> (28-1)) + 1)) < 2)
1052
 
 
1053
1077
    /* Optimization. Simple cases before declaration of estack. */
1054
1078
    if (primary_tag(term) == TAG_PRIMARY_IMMED1) {
1055
1079
        switch (term & _TAG_IMMED1_MASK) {
1078
1102
    Eterm tmp;
1079
1103
    DECLARE_ESTACK(s);
1080
1104
 
 
1105
    UseTmpHeapNoproc(2);
1081
1106
    hash = 0;
1082
1107
    for (;;) {
1083
1108
        switch (primary_tag(term)) {
1131
1156
            break;
1132
1157
            case EXPORT_SUBTAG:
1133
1158
            {
1134
 
                Export* ep = (Export *) (export_val(term))[1];
 
1159
                Export* ep = *((Export **) (export_val(term) + 1));
1135
1160
 
1136
1161
                UINT32_HASH_2
1137
1162
                    (ep->code[2], 
1322
1347
        hash2_common:
1323
1348
            if (ESTACK_ISEMPTY(s)) {
1324
1349
                DESTROY_ESTACK(s);
 
1350
                UnUseTmpHeapNoproc(2);
1325
1351
                return hash;
1326
1352
            }
1327
1353
            term = ESTACK_POP(s);
1340
1366
Uint32 make_broken_hash(Eterm term)
1341
1367
{
1342
1368
    Uint32 hash = 0;
1343
 
    DECLARE_ESTACK(stack);
 
1369
    DECLARE_WSTACK(stack);
1344
1370
    unsigned op;
1345
1371
tail_recur:
1346
1372
    op = tag_val_def(term); 
1354
1380
            (atom_tab(atom_val(term))->slot.bucket.hvalue);
1355
1381
        break;
1356
1382
    case SMALL_DEF:
1357
 
#ifdef ARCH_64
 
1383
#if defined(ARCH_64) && !HALFWORD_HEAP
1358
1384
    {
1359
1385
        Sint y1 = signed_val(term);
1360
1386
        Uint y2 = y1 < 0 ? -(Uint)y1 : y1;
1407
1433
 
1408
1434
    case EXPORT_DEF:
1409
1435
        {
1410
 
            Export* ep = (Export *) (export_val(term))[1];
 
1436
            Export* ep = *((Export **) (export_val(term) + 1));
1411
1437
 
1412
1438
            hash = hash * FUNNY_NUMBER11 + ep->code[2];
1413
1439
            hash = hash*FUNNY_NUMBER1 + 
1429
1455
            hash = hash*FUNNY_NUMBER2 + funp->fe->old_uniq;
1430
1456
            if (num_free > 0) {
1431
1457
                if (num_free > 1) {
1432
 
                    ESTACK_PUSH3(stack, (Eterm) &funp->env[1], (num_free-1), MAKE_HASH_FUN_OP);
 
1458
                    WSTACK_PUSH3(stack, (UWord) &funp->env[1], (num_free-1), MAKE_HASH_FUN_OP);
1433
1459
                }
1434
1460
                term = funp->env[0];
1435
1461
                goto tail_recur;
1464
1490
        break;
1465
1491
 
1466
1492
    case MAKE_HASH_CDR_PRE_OP:
1467
 
        term = ESTACK_POP(stack);
 
1493
        term = (Eterm) WSTACK_POP(stack);
1468
1494
        if (is_not_list(term)) {
1469
 
            ESTACK_PUSH(stack, MAKE_HASH_CDR_POST_OP);
 
1495
            WSTACK_PUSH(stack, (UWord) MAKE_HASH_CDR_POST_OP);
1470
1496
            goto tail_recur;
1471
1497
        }
1472
1498
        /*fall through*/
1473
1499
    case LIST_DEF:
1474
1500
        {
1475
1501
            Eterm* list = list_val(term);
1476
 
            ESTACK_PUSH2(stack, CDR(list), MAKE_HASH_CDR_PRE_OP);
 
1502
            WSTACK_PUSH2(stack, (UWord) CDR(list),
 
1503
                         (UWord) MAKE_HASH_CDR_PRE_OP);
1477
1504
            term = CAR(list);
1478
1505
            goto tail_recur;
1479
1506
        }
1546
1573
            Eterm* ptr = tuple_val(term);
1547
1574
            Uint arity = arityval(*ptr);
1548
1575
 
1549
 
            ESTACK_PUSH3(stack, arity, (Eterm)(ptr+1), arity);
 
1576
            WSTACK_PUSH3(stack, (UWord) arity, (UWord) (ptr+1), (UWord) arity);
1550
1577
            op = MAKE_HASH_TUPLE_OP;
1551
1578
        }/*fall through*/ 
1552
1579
    case MAKE_HASH_TUPLE_OP:
1553
1580
    case MAKE_HASH_FUN_OP:
1554
1581
        {
1555
 
            Uint i = ESTACK_POP(stack);
1556
 
            Eterm* ptr = (Eterm*) ESTACK_POP(stack);
 
1582
            Uint i = (Uint) WSTACK_POP(stack);
 
1583
            Eterm* ptr = (Eterm*) WSTACK_POP(stack);
1557
1584
            if (i != 0) {
1558
1585
                term = *ptr;
1559
 
                ESTACK_PUSH3(stack, (Eterm)(ptr+1), i-1, op);
 
1586
                WSTACK_PUSH3(stack, (UWord)(ptr+1), (UWord) i-1, (UWord) op);
1560
1587
                goto tail_recur;
1561
1588
            }
1562
1589
            if (op == MAKE_HASH_TUPLE_OP) {
1563
 
                Uint32 arity = ESTACK_POP(stack);
 
1590
                Uint32 arity = (UWord) WSTACK_POP(stack);
1564
1591
                hash = hash*FUNNY_NUMBER9 + arity;
1565
1592
            }
1566
1593
            break;
1570
1597
        erl_exit(1, "Invalid tag in make_broken_hash\n");
1571
1598
        return 0;
1572
1599
      }
1573
 
      if (ESTACK_ISEMPTY(stack)) break;
1574
 
      op = ESTACK_POP(stack);
 
1600
      if (WSTACK_ISEMPTY(stack)) break;
 
1601
      op = (Uint) WSTACK_POP(stack);
1575
1602
    }
1576
1603
 
1577
 
    DESTROY_ESTACK(stack);
 
1604
    DESTROY_WSTACK(stack);
1578
1605
    return hash;
1579
1606
    
1580
1607
#undef MAKE_HASH_TUPLE_OP
1867
1894
    erts_free(ERTS_ALC_T_TMP_DSBUF, (void *) dsbufp);
1868
1895
}
1869
1896
 
1870
 
 
1871
1897
/* eq and cmp are written as separate functions a eq is a little faster */
1872
1898
 
1873
1899
/*
1874
1900
 * Test for equality of two terms.
1875
1901
 * Returns 0 if not equal, or a non-zero value otherwise.
1876
1902
 */
1877
 
 
 
1903
#if HALFWORD_HEAP
 
1904
int eq_rel(Eterm a, Eterm* a_base, Eterm b, Eterm* b_base)
 
1905
#else
1878
1906
int eq(Eterm a, Eterm b)
 
1907
#endif
1879
1908
{
1880
 
    DECLARE_ESTACK(stack);
 
1909
    DECLARE_WSTACK(stack);
1881
1910
    Sint sz;
1882
1911
    Eterm* aa;
1883
 
    Eterm* bb;  
 
1912
    Eterm* bb;
1884
1913
 
1885
1914
tailrecur:
1886
 
    if (a == b) goto pop_next; 
 
1915
    if (is_same(a, a_base, b, b_base)) goto pop_next;
1887
1916
tailrecur_ne:
1888
1917
 
1889
1918
    switch (primary_tag(a)) {
1890
1919
    case TAG_PRIMARY_LIST:
1891
1920
        if (is_list(b)) {
1892
 
            Eterm* aval = list_val(a);
1893
 
            Eterm* bval = list_val(b);
 
1921
            Eterm* aval = list_val_rel(a, a_base);
 
1922
            Eterm* bval = list_val_rel(b, b_base);
1894
1923
            while (1) {
1895
1924
                Eterm atmp = CAR(aval);
1896
1925
                Eterm btmp = CAR(bval);
1897
 
                if (atmp != btmp) {
1898
 
                    ESTACK_PUSH2(stack,CDR(bval),CDR(aval));
 
1926
                if (!is_same(atmp,a_base,btmp,b_base)) {
 
1927
                    WSTACK_PUSH2(stack,(UWord) CDR(bval),(UWord) CDR(aval));
1899
1928
                    a = atmp;
1900
1929
                    b = btmp;
1901
1930
                    goto tailrecur_ne;
1902
1931
                }
1903
1932
                atmp = CDR(aval);
1904
1933
                btmp = CDR(bval);
1905
 
                if (atmp == btmp) {
 
1934
                if (is_same(atmp,a_base,btmp,b_base)) {
1906
1935
                    goto pop_next;
1907
1936
                }
1908
1937
                if (is_not_list(atmp) || is_not_list(btmp)) {
1910
1939
                    b = btmp;
1911
1940
                    goto tailrecur_ne;
1912
1941
                }
1913
 
                aval = list_val(atmp);
1914
 
                bval = list_val(btmp);
 
1942
                aval = list_val_rel(atmp, a_base);
 
1943
                bval = list_val_rel(btmp, b_base);
1915
1944
            }
1916
1945
        }
1917
1946
        break; /* not equal */
1918
1947
 
1919
1948
    case TAG_PRIMARY_BOXED:
1920
1949
        {       
1921
 
            Eterm hdr = *boxed_val(a);
 
1950
            Eterm hdr = *boxed_val_rel(a,a_base);
1922
1951
            switch (hdr & _TAG_HEADER_MASK) {
1923
1952
            case ARITYVAL_SUBTAG:
1924
1953
                {
1925
 
                    aa = tuple_val(a);
1926
 
                    if (!is_boxed(b) || *boxed_val(b) != *aa)
 
1954
                    aa = tuple_val_rel(a, a_base);
 
1955
                    if (!is_boxed(b) || *boxed_val_rel(b,b_base) != *aa)
1927
1956
                        goto not_equal;
1928
 
                    bb = tuple_val(b);
 
1957
                    bb = tuple_val_rel(b,b_base);
1929
1958
                    if ((sz = arityval(*aa)) == 0) goto pop_next;
1930
1959
                    ++aa;
1931
1960
                    ++bb;
1944
1973
                    Uint a_bitoffs;
1945
1974
                    Uint b_bitoffs;
1946
1975
                    
1947
 
                    if (is_not_binary(b)) {
 
1976
                    if (!is_binary_rel(b,b_base)) {
1948
1977
                        goto not_equal;
1949
1978
                    }
1950
 
                    a_size = binary_size(a);
1951
 
                    b_size = binary_size(b); 
 
1979
                    a_size = binary_size_rel(a,a_base);
 
1980
                    b_size = binary_size_rel(b,b_base);
1952
1981
                    if (a_size != b_size) {
1953
1982
                        goto not_equal;
1954
1983
                    }
1955
 
                    ERTS_GET_BINARY_BYTES(a, a_ptr, a_bitoffs, a_bitsize);
1956
 
                    ERTS_GET_BINARY_BYTES(b, b_ptr, b_bitoffs, b_bitsize);
 
1984
                    ERTS_GET_BINARY_BYTES_REL(a, a_ptr, a_bitoffs, a_bitsize, a_base);
 
1985
                    ERTS_GET_BINARY_BYTES_REL(b, b_ptr, b_bitoffs, b_bitsize, b_base);
1957
1986
                    if ((a_bitsize | b_bitsize | a_bitoffs | b_bitoffs) == 0) {
1958
1987
                        if (sys_memcmp(a_ptr, b_ptr, a_size) == 0) goto pop_next;
1959
1988
                    } else if (a_bitsize == b_bitsize) {
1964
1993
                }
1965
1994
            case EXPORT_SUBTAG:
1966
1995
                {
1967
 
                    if (is_export(b)) {
1968
 
                        Export* a_exp = (Export *) (export_val(a))[1];
1969
 
                        Export* b_exp = (Export *) (export_val(b))[1];
 
1996
                    if (is_export_rel(b,b_base)) {
 
1997
                        Export* a_exp = *((Export **) (export_val_rel(a,a_base) + 1));
 
1998
                        Export* b_exp = *((Export **) (export_val_rel(b,b_base) + 1));
1970
1999
                        if (a_exp == b_exp) goto pop_next;
1971
2000
                    }
1972
2001
                    break; /* not equal */
1976
2005
                    ErlFunThing* f1;
1977
2006
                    ErlFunThing* f2;
1978
2007
  
1979
 
                    if (is_not_fun(b))
 
2008
                    if (!is_fun_rel(b,b_base))
1980
2009
                        goto not_equal;
1981
 
                    f1 = (ErlFunThing *) fun_val(a);
1982
 
                    f2 = (ErlFunThing *) fun_val(b);
 
2010
                    f1 = (ErlFunThing *) fun_val_rel(a,a_base);
 
2011
                    f2 = (ErlFunThing *) fun_val_rel(b,b_base);
1983
2012
                    if (f1->fe->module != f2->fe->module ||
1984
2013
                        f1->fe->old_index != f2->fe->old_index ||
1985
2014
                        f1->fe->old_uniq != f2->fe->old_uniq ||
1997
2026
                ExternalThing *ap;
1998
2027
                ExternalThing *bp;
1999
2028
 
2000
 
                if(is_not_external(b))
 
2029
                if(!is_external_rel(b,b_base))
2001
2030
                    goto not_equal;
2002
2031
 
2003
 
                ap = external_thing_ptr(a);
2004
 
                bp = external_thing_ptr(b);
 
2032
                ap = external_thing_ptr_rel(a,a_base);
 
2033
                bp = external_thing_ptr_rel(b,b_base);
2005
2034
 
2006
2035
                if(ap->header == bp->header && ap->node == bp->node) {
2007
 
                    ASSERT(1 == external_data_words(a));
2008
 
                    ASSERT(1 == external_data_words(b));
 
2036
                    ASSERT(1 == external_data_words_rel(a,a_base));
 
2037
                    ASSERT(1 == external_data_words_rel(b,b_base));
2009
2038
                    
2010
2039
                    if (ap->data.ui[0] == bp->data.ui[0]) goto pop_next;
2011
2040
                }
2023
2052
                Uint alen;
2024
2053
                Uint blen;
2025
2054
                Uint i;
2026
 
 
2027
 
                if(is_not_external_ref(b))
2028
 
                    goto not_equal;
2029
 
 
2030
 
                if(external_node(a) != external_node(b))
2031
 
                    goto not_equal;
2032
 
 
2033
 
                anum = external_ref_numbers(a);
2034
 
                bnum = external_ref_numbers(b);
2035
 
                alen = external_ref_no_of_numbers(a);
2036
 
                blen = external_ref_no_of_numbers(b);
 
2055
                ExternalThing* athing;
 
2056
                ExternalThing* bthing;
 
2057
 
 
2058
                if(!is_external_ref_rel(b,b_base))
 
2059
                    goto not_equal;
 
2060
 
 
2061
                athing = external_thing_ptr_rel(a,a_base);
 
2062
                bthing = external_thing_ptr_rel(b,b_base);
 
2063
 
 
2064
                if(athing->node != bthing->node)
 
2065
                    goto not_equal;
 
2066
 
 
2067
                anum = external_thing_ref_numbers(athing);
 
2068
                bnum = external_thing_ref_numbers(bthing);
 
2069
                alen = external_thing_ref_no_of_numbers(athing);
 
2070
                blen = external_thing_ref_no_of_numbers(bthing);
2037
2071
 
2038
2072
                goto ref_common;
2039
2073
            case REF_SUBTAG:
2040
 
  
2041
 
                    if (is_not_internal_ref(b))
 
2074
                    if (!is_internal_ref_rel(b,b_base))
2042
2075
                        goto not_equal;
2043
 
                    alen = internal_ref_no_of_numbers(a);
2044
 
                    blen = internal_ref_no_of_numbers(b);
2045
 
                    anum = internal_ref_numbers(a);
2046
 
                    bnum = internal_ref_numbers(b);
 
2076
 
 
2077
                    {
 
2078
                        RefThing* athing = ref_thing_ptr_rel(a,a_base);
 
2079
                        RefThing* bthing = ref_thing_ptr_rel(b,b_base);
 
2080
                        alen = internal_thing_ref_no_of_numbers(athing);
 
2081
                        blen = internal_thing_ref_no_of_numbers(bthing);
 
2082
                        anum = internal_thing_ref_numbers(athing);
 
2083
                        bnum = internal_thing_ref_numbers(bthing);
 
2084
                    }
2047
2085
 
2048
2086
            ref_common:
2049
2087
                    ASSERT(alen > 0 && blen > 0);
2088
2126
                {
2089
2127
                    int i;
2090
2128
  
2091
 
                    if (is_not_big(b))
 
2129
                    if (!is_big_rel(b,b_base))
2092
2130
                        goto not_equal;
2093
 
                    aa = big_val(a); /* get pointer to thing */
2094
 
                    bb = big_val(b);
 
2131
                    aa = big_val_rel(a,a_base);
 
2132
                    bb = big_val_rel(b,b_base);
2095
2133
                    if (*aa != *bb)
2096
2134
                        goto not_equal;
2097
2135
                    i = BIG_ARITY(aa);
2106
2144
                    FloatDef af;
2107
2145
                    FloatDef bf;
2108
2146
  
2109
 
                    if (is_float(b)) {
2110
 
                        GET_DOUBLE(a, af);
2111
 
                        GET_DOUBLE(b, bf);
 
2147
                    if (is_float_rel(b,b_base)) {
 
2148
                        GET_DOUBLE_REL(a, af, a_base);
 
2149
                        GET_DOUBLE_REL(b, bf, b_base);
2112
2150
                        if (af.fd == bf.fd) goto pop_next;
2113
2151
                    }
2114
2152
                    break; /* not equal */
2127
2165
        Eterm* bp = bb;
2128
2166
        Sint i = sz;
2129
2167
        for (;;) {
2130
 
            if (*ap != *bp) break;
 
2168
            if (!is_same(*ap,a_base,*bp,b_base)) break;
2131
2169
            if (--i == 0) goto pop_next;
2132
2170
            ++ap;
2133
2171
            ++bp;
2138
2176
            goto not_equal;
2139
2177
        }
2140
2178
        if (i > 1) { /* push the rest */
2141
 
            ESTACK_PUSH3(stack, i-1, (Eterm)(bp+1),
2142
 
                         ((Eterm)(ap+1)) | TAG_PRIMARY_HEADER);
 
2179
            WSTACK_PUSH3(stack, i-1, (UWord)(bp+1),
 
2180
                         ((UWord)(ap+1)) | TAG_PRIMARY_HEADER);
2143
2181
            /* We (ab)use TAG_PRIMARY_HEADER to recognize a term_array */
2144
2182
        }
2145
2183
        goto tailrecur_ne;
2146
2184
    }
2147
2185
   
2148
2186
pop_next:
2149
 
    if (!ESTACK_ISEMPTY(stack)) {
2150
 
        Eterm something  = ESTACK_POP(stack);   
2151
 
        if (primary_tag(something) == TAG_PRIMARY_HEADER) { /* a term_array */
 
2187
    if (!WSTACK_ISEMPTY(stack)) {
 
2188
        UWord something  = WSTACK_POP(stack);
 
2189
        if (primary_tag((Eterm) something) == TAG_PRIMARY_HEADER) { /* a term_array */
2152
2190
            aa = (Eterm*) something;
2153
 
            bb = (Eterm*) ESTACK_POP(stack);
2154
 
            sz = ESTACK_POP(stack);
 
2191
            bb = (Eterm*) WSTACK_POP(stack);
 
2192
            sz = WSTACK_POP(stack);
2155
2193
            goto term_array;
2156
2194
        }
2157
2195
        a = something;
2158
 
        b = ESTACK_POP(stack);
 
2196
        b = WSTACK_POP(stack);
2159
2197
        goto tailrecur;
2160
2198
    }
2161
2199
 
2162
 
    DESTROY_ESTACK(stack);
 
2200
    DESTROY_WSTACK(stack);
2163
2201
    return 1;
2164
2202
 
2165
2203
not_equal:
2166
 
    DESTROY_ESTACK(stack);
 
2204
    DESTROY_WSTACK(stack);
2167
2205
    return 0;
2168
2206
}
2169
2207
 
2216
2254
                    bb->name+3, bb->len-3);
2217
2255
}
2218
2256
 
 
2257
#if HALFWORD_HEAP
 
2258
Sint cmp_rel(Eterm a, Eterm* a_base, Eterm b, Eterm* b_base)
 
2259
#else
2219
2260
Sint cmp(Eterm a, Eterm b)
 
2261
#endif
2220
2262
{
2221
 
    DECLARE_ESTACK(stack);
 
2263
    DECLARE_WSTACK(stack);
2222
2264
    Eterm* aa;
2223
2265
    Eterm* bb;
2224
2266
    int i;
2250
2292
 
2251
2293
 
2252
2294
tailrecur:
2253
 
    if (a == b) {               /* Equal values or pointers. */
 
2295
    if (is_same(a,a_base,b,b_base)) {   /* Equal values or pointers. */
2254
2296
        goto pop_next;
2255
2297
    }
2256
2298
tailrecur_ne:
2276
2318
            if (is_internal_port(b)) {
2277
2319
                bnode = erts_this_node;
2278
2320
                bdata = internal_port_data(b);
2279
 
            } else if (is_external_port(b)) {
2280
 
                bnode = external_port_node(b);
2281
 
                bdata = external_port_data(b);
 
2321
            } else if (is_external_port_rel(b,b_base)) {
 
2322
                bnode = external_port_node_rel(b,b_base);
 
2323
                bdata = external_port_data_rel(b,b_base);
2282
2324
            } else {
2283
2325
                a_tag = PORT_DEF;
2284
2326
                goto mixed_types;
2294
2336
            if (is_internal_pid(b)) {
2295
2337
                bnode = erts_this_node;
2296
2338
                bdata = internal_pid_data(b);
2297
 
            } else if (is_external_pid(b)) {
2298
 
                bnode = external_pid_node(b);
2299
 
                bdata = external_pid_data(b);
 
2339
            } else if (is_external_pid_rel(b,b_base)) {
 
2340
                bnode = external_pid_node_rel(b,b_base);
 
2341
                bdata = external_pid_data_rel(b,b_base);
2300
2342
            } else {
2301
2343
                a_tag = PID_DEF;
2302
2344
                goto mixed_types;
2329
2371
            a_tag = LIST_DEF;
2330
2372
            goto mixed_types;
2331
2373
        }
2332
 
        aa = list_val(a);
2333
 
        bb = list_val(b);
 
2374
        aa = list_val_rel(a,a_base);
 
2375
        bb = list_val_rel(b,b_base);
2334
2376
        while (1) {
2335
2377
            Eterm atmp = CAR(aa);
2336
2378
            Eterm btmp = CAR(bb);
2337
 
            if (atmp != btmp) {
2338
 
                ESTACK_PUSH2(stack,CDR(bb),CDR(aa));
 
2379
            if (!is_same(atmp,a_base,btmp,b_base)) {
 
2380
                WSTACK_PUSH2(stack,(UWord) CDR(bb),(UWord) CDR(aa));
2339
2381
                a = atmp;
2340
2382
                b = btmp;
2341
2383
                goto tailrecur_ne;
2342
2384
            }
2343
2385
            atmp = CDR(aa);
2344
2386
            btmp = CDR(bb);
2345
 
            if (atmp == btmp) {
 
2387
            if (is_same(atmp,a_base,btmp,b_base)) {
2346
2388
                goto pop_next;
2347
2389
            }
2348
2390
            if (is_not_list(atmp) || is_not_list(btmp)) {
2350
2392
                b = btmp;
2351
2393
                goto tailrecur_ne;
2352
2394
            }
2353
 
            aa = list_val(atmp);
2354
 
            bb = list_val(btmp);
 
2395
            aa = list_val_rel(atmp,a_base);
 
2396
            bb = list_val_rel(btmp,b_base);
2355
2397
        }
2356
2398
    case TAG_PRIMARY_BOXED:
2357
2399
        {
2358
 
            Eterm ahdr = *boxed_val(a);
 
2400
            Eterm ahdr = *boxed_val_rel(a,a_base);
2359
2401
            switch ((ahdr & _TAG_HEADER_MASK) >> _TAG_PRIMARY_SIZE) {
2360
2402
            case (_TAG_HEADER_ARITYVAL >> _TAG_PRIMARY_SIZE):
2361
 
                if (is_not_tuple(b)) {
 
2403
                if (!is_tuple_rel(b,b_base)) {
2362
2404
                    a_tag = TUPLE_DEF;
2363
2405
                    goto mixed_types;
2364
2406
                }
2365
 
                aa = tuple_val(a);
2366
 
                bb = tuple_val(b);
 
2407
                aa = tuple_val_rel(a,a_base);
 
2408
                bb = tuple_val_rel(b,b_base);
2367
2409
                /* compare the arities */
2368
2410
                i = arityval(ahdr);     /* get the arity*/
2369
2411
                if (i != arityval(*bb)) {
2377
2419
                goto term_array;
2378
2420
 
2379
2421
            case (_TAG_HEADER_FLOAT >> _TAG_PRIMARY_SIZE):
2380
 
                if (is_not_float(b)) {
 
2422
                if (!is_float_rel(b,b_base)) {
2381
2423
                    a_tag = FLOAT_DEF;
2382
2424
                    goto mixed_types;
2383
2425
                } else {
2384
2426
                    FloatDef af;
2385
2427
                    FloatDef bf; 
2386
2428
 
2387
 
                    GET_DOUBLE(a, af);
2388
 
                    GET_DOUBLE(b, bf);
 
2429
                    GET_DOUBLE_REL(a, af, a_base);
 
2430
                    GET_DOUBLE_REL(b, bf, b_base);
2389
2431
                    ON_CMP_GOTO(float_comp(af.fd, bf.fd));
2390
2432
                }
2391
2433
            case (_TAG_HEADER_POS_BIG >> _TAG_PRIMARY_SIZE):
2392
2434
            case (_TAG_HEADER_NEG_BIG >> _TAG_PRIMARY_SIZE):
2393
 
                if (is_not_big(b)) {
 
2435
                if (!is_big_rel(b,b_base)) {
2394
2436
                    a_tag = BIG_DEF;
2395
2437
                    goto mixed_types;
2396
2438
                }
2397
 
                ON_CMP_GOTO(big_comp(a, b));
 
2439
                ON_CMP_GOTO(big_comp(rterm2wterm(a,a_base), rterm2wterm(b,b_base)));
2398
2440
            case (_TAG_HEADER_EXPORT >> _TAG_PRIMARY_SIZE):
2399
 
                if (is_not_export(b)) {
 
2441
                if (!is_export_rel(b,b_base)) {
2400
2442
                    a_tag = EXPORT_DEF;
2401
2443
                    goto mixed_types;
2402
2444
                } else {
2403
 
                    Export* a_exp = (Export *) (export_val(a))[1];
2404
 
                    Export* b_exp = (Export *) (export_val(b))[1];
 
2445
                    Export* a_exp = *((Export **) (export_val_rel(a,a_base) + 1));
 
2446
                    Export* b_exp = *((Export **) (export_val_rel(b,b_base) + 1));
2405
2447
 
2406
2448
                    if ((j = cmp_atoms(a_exp->code[0], b_exp->code[0])) != 0) {
2407
2449
                        RETURN_NEQ(j);
2413
2455
                }
2414
2456
                break;
2415
2457
            case (_TAG_HEADER_FUN >> _TAG_PRIMARY_SIZE):
2416
 
                if (is_not_fun(b)) {
 
2458
                if (!is_fun_rel(b,b_base)) {
2417
2459
                    a_tag = FUN_DEF;
2418
2460
                    goto mixed_types;
2419
2461
                } else {
2420
 
                    ErlFunThing* f1 = (ErlFunThing *) fun_val(a);
2421
 
                    ErlFunThing* f2 = (ErlFunThing *) fun_val(b);
 
2462
                    ErlFunThing* f1 = (ErlFunThing *) fun_val_rel(a,a_base);
 
2463
                    ErlFunThing* f2 = (ErlFunThing *) fun_val_rel(b,b_base);
2422
2464
                    Sint diff;
2423
2465
 
2424
2466
                    diff = cmpbytes(atom_tab(atom_val(f1->fe->module))->name,
2450
2492
                if (is_internal_pid(b)) {
2451
2493
                    bnode = erts_this_node;
2452
2494
                    bdata = internal_pid_data(b);
2453
 
                } else if (is_external_pid(b)) {
2454
 
                    bnode = external_pid_node(b);
2455
 
                    bdata = external_pid_data(b);
 
2495
                } else if (is_external_pid_rel(b,b_base)) {
 
2496
                    bnode = external_pid_node_rel(b,b_base);
 
2497
                    bdata = external_pid_data_rel(b,b_base);
2456
2498
                } else {
2457
2499
                    a_tag = EXTERNAL_PID_DEF;
2458
2500
                    goto mixed_types;
2459
2501
                }
2460
 
                anode = external_pid_node(a);
2461
 
                adata = external_pid_data(a);
 
2502
                anode = external_pid_node_rel(a,a_base);
 
2503
                adata = external_pid_data_rel(a,a_base);
2462
2504
                goto pid_common;
2463
2505
            case (_TAG_HEADER_EXTERNAL_PORT >> _TAG_PRIMARY_SIZE):
2464
2506
                if (is_internal_port(b)) {
2465
2507
                    bnode = erts_this_node;
2466
2508
                    bdata = internal_port_data(b);
2467
 
                } else if (is_external_port(b)) {
2468
 
                    bnode = external_port_node(b);
2469
 
                    bdata = external_port_data(b);
 
2509
                } else if (is_external_port_rel(b,b_base)) {
 
2510
                    bnode = external_port_node_rel(b,b_base);
 
2511
                    bdata = external_port_data_rel(b,b_base);
2470
2512
                } else {
2471
2513
                    a_tag = EXTERNAL_PORT_DEF;
2472
2514
                    goto mixed_types;
2473
2515
                }
2474
 
                anode = external_port_node(a);
2475
 
                adata = external_port_data(a);
 
2516
                anode = external_port_node_rel(a,a_base);
 
2517
                adata = external_port_data_rel(a,a_base);
2476
2518
                goto port_common;
2477
2519
            case (_TAG_HEADER_REF >> _TAG_PRIMARY_SIZE):
2478
2520
                /*
2479
2521
                 * Note! When comparing refs we need to compare ref numbers
2480
2522
                 * (32-bit words), *not* ref data words.
2481
2523
                 */
 
2524
 
2482
2525
                
2483
 
                if (is_internal_ref(b)) {
 
2526
                if (is_internal_ref_rel(b,b_base)) {
 
2527
                    RefThing* bthing = ref_thing_ptr_rel(b,b_base);
2484
2528
                    bnode = erts_this_node;
2485
 
                    bnum = internal_ref_numbers(b);
2486
 
                    blen = internal_ref_no_of_numbers(b);
2487
 
                } else if(is_external_ref(b)) {
2488
 
                    bnode = external_ref_node(b);
2489
 
                    bnum = external_ref_numbers(b);
2490
 
                    blen = external_ref_no_of_numbers(b);
 
2529
                    bnum = internal_thing_ref_numbers(bthing);
 
2530
                    blen = internal_thing_ref_no_of_numbers(bthing);
 
2531
                } else if(is_external_ref_rel(b,b_base)) {
 
2532
                    ExternalThing* bthing = external_thing_ptr_rel(b,b_base);
 
2533
                    bnode = bthing->node;
 
2534
                    bnum = external_thing_ref_numbers(bthing);
 
2535
                    blen = external_thing_ref_no_of_numbers(bthing);
2491
2536
                } else {
2492
2537
                    a_tag = REF_DEF;
2493
2538
                    goto mixed_types;
2494
2539
                }
2495
 
                anode = erts_this_node;
2496
 
                anum = internal_ref_numbers(a);
2497
 
                alen = internal_ref_no_of_numbers(a);
 
2540
                {
 
2541
                    RefThing* athing = ref_thing_ptr_rel(a,a_base);
 
2542
                    anode = erts_this_node;
 
2543
                    anum = internal_thing_ref_numbers(athing);
 
2544
                    alen = internal_thing_ref_no_of_numbers(athing);
 
2545
                }
2498
2546
                
2499
2547
            ref_common:
2500
2548
                CMP_NODES(anode, bnode);
2523
2571
                        RETURN_NEQ((Sint32) (anum[i] - bnum[i]));
2524
2572
                goto pop_next;
2525
2573
            case (_TAG_HEADER_EXTERNAL_REF >> _TAG_PRIMARY_SIZE):
2526
 
                if (is_internal_ref(b)) {
 
2574
                if (is_internal_ref_rel(b,b_base)) {
 
2575
                    RefThing* bthing = ref_thing_ptr_rel(b,b_base);
2527
2576
                    bnode = erts_this_node;
2528
 
                    bnum = internal_ref_numbers(b);
2529
 
                    blen = internal_ref_no_of_numbers(b);
2530
 
                } else if (is_external_ref(b)) {
2531
 
                    bnode = external_ref_node(b);
2532
 
                    bnum = external_ref_numbers(b);
2533
 
                    blen = external_ref_no_of_numbers(b);
 
2577
                    bnum = internal_thing_ref_numbers(bthing);
 
2578
                    blen = internal_thing_ref_no_of_numbers(bthing);
 
2579
                } else if (is_external_ref_rel(b,b_base)) {
 
2580
                    ExternalThing* bthing = external_thing_ptr_rel(b,b_base);
 
2581
                    bnode = bthing->node;
 
2582
                    bnum = external_thing_ref_numbers(bthing);
 
2583
                    blen = external_thing_ref_no_of_numbers(bthing);
2534
2584
                } else {
2535
2585
                    a_tag = EXTERNAL_REF_DEF;
2536
2586
                    goto mixed_types;
2537
2587
                }
2538
 
                anode = external_ref_node(a);
2539
 
                anum = external_ref_numbers(a);
2540
 
                alen = external_ref_no_of_numbers(a);
 
2588
                {
 
2589
                    ExternalThing* athing = external_thing_ptr_rel(a,a_base);
 
2590
                    anode = athing->node;
 
2591
                    anum = external_thing_ref_numbers(athing);
 
2592
                    alen = external_thing_ref_no_of_numbers(athing);
 
2593
                }
2541
2594
                goto ref_common;
2542
2595
            default:
2543
2596
                /* Must be a binary */
2544
 
                ASSERT(is_binary(a));
2545
 
                if (is_not_binary(b)) {
 
2597
                ASSERT(is_binary_rel(a,a_base));
 
2598
                if (!is_binary_rel(b,b_base)) {
2546
2599
                    a_tag = BINARY_DEF;
2547
2600
                    goto mixed_types;
2548
2601
                } else {
2549
 
                    Uint a_size = binary_size(a);
2550
 
                    Uint b_size = binary_size(b);
 
2602
                    Uint a_size = binary_size_rel(a,a_base);
 
2603
                    Uint b_size = binary_size_rel(b,b_base);
2551
2604
                    Uint a_bitsize;
2552
2605
                    Uint b_bitsize;
2553
2606
                    Uint a_bitoffs;
2556
2609
                    int cmp;
2557
2610
                    byte* a_ptr;
2558
2611
                    byte* b_ptr;
2559
 
                    ERTS_GET_BINARY_BYTES(a, a_ptr, a_bitoffs, a_bitsize);
2560
 
                    ERTS_GET_BINARY_BYTES(b, b_ptr, b_bitoffs, b_bitsize);
 
2612
                    ERTS_GET_BINARY_BYTES_REL(a, a_ptr, a_bitoffs, a_bitsize, a_base);
 
2613
                    ERTS_GET_BINARY_BYTES_REL(b, b_ptr, b_bitoffs, b_bitsize, b_base);
2561
2614
                    if ((a_bitsize | b_bitsize | a_bitoffs | b_bitoffs) == 0) {
2562
2615
                        min_size = (a_size < b_size) ? a_size : b_size;
2563
2616
                        if ((cmp = sys_memcmp(a_ptr, b_ptr, min_size)) != 0) {
2584
2637
     */
2585
2638
 
2586
2639
 mixed_types:
2587
 
    b_tag = tag_val_def(b);
2588
2640
 
2589
2641
    {
2590
2642
        FloatDef f1, f2;
2591
2643
        Eterm big;
2592
 
        Eterm big_buf[2];
 
2644
#if HEAP_ON_C_STACK
 
2645
        Eterm big_buf[2]; /* If HEAP_ON_C_STACK */
 
2646
#else
 
2647
        Eterm *big_buf = erts_get_scheduler_data()->cmp_tmp_heap;
 
2648
#endif
 
2649
#if HALFWORD_HEAP
 
2650
        Wterm aw = is_immed(a) ? a : rterm2wterm(a,a_base);
 
2651
        Wterm bw = is_immed(b) ? b : rterm2wterm(b,b_base);
 
2652
#else
 
2653
        Eterm aw = a;
 
2654
        Eterm bw = b;
 
2655
#endif
 
2656
        b_tag = tag_val_def(bw);
2593
2657
 
2594
2658
        switch(_NUMBER_CODE(a_tag, b_tag)) {
2595
2659
        case SMALL_BIG:
2596
2660
            big = small_to_big(signed_val(a), big_buf);
2597
 
            j = big_comp(big, b);
 
2661
            j = big_comp(big, bw);
2598
2662
            break;
2599
2663
        case SMALL_FLOAT:
2600
2664
            f1.fd = signed_val(a);
2601
 
            GET_DOUBLE(b, f2);
 
2665
            GET_DOUBLE(bw, f2);
2602
2666
            j = float_comp(f1.fd, f2.fd);
2603
2667
            break;
2604
2668
        case BIG_SMALL:
2605
2669
            big = small_to_big(signed_val(b), big_buf);
2606
 
            j = big_comp(a, big);
 
2670
            j = big_comp(aw, big);
2607
2671
            break;
2608
2672
        case BIG_FLOAT:
2609
 
            if (big_to_double(a, &f1.fd) < 0) {
 
2673
            if (big_to_double(aw, &f1.fd) < 0) {
2610
2674
                j = big_sign(a) ? -1 : 1;
2611
2675
            } else {
2612
 
                GET_DOUBLE(b, f2);
 
2676
                GET_DOUBLE(bw, f2);
2613
2677
                j = float_comp(f1.fd, f2.fd);
2614
2678
            }
2615
2679
            break;
2616
2680
        case FLOAT_SMALL:
2617
 
            GET_DOUBLE(a, f1);
 
2681
            GET_DOUBLE(aw, f1);
2618
2682
            f2.fd = signed_val(b);
2619
2683
            j = float_comp(f1.fd, f2.fd);
2620
2684
            break;
2621
2685
        case FLOAT_BIG:
2622
 
            if (big_to_double(b, &f2.fd) < 0) {
 
2686
            if (big_to_double(bw, &f2.fd) < 0) {
2623
2687
                j = big_sign(b) ? 1 : -1;
2624
2688
            } else {
2625
 
                GET_DOUBLE(a, f1);
 
2689
                GET_DOUBLE(aw, f1);
2626
2690
                j = float_comp(f1.fd, f2.fd);
2627
2691
            }
2628
2692
            break;
2652
2716
                }
2653
2717
            } else {
2654
2718
                /* (ab)Use TAG_PRIMARY_HEADER to recognize a term_array */
2655
 
                ESTACK_PUSH3(stack, i, (Eterm)bb, (Eterm)aa | TAG_PRIMARY_HEADER);
 
2719
                WSTACK_PUSH3(stack, i, (UWord)bb, (UWord)aa | TAG_PRIMARY_HEADER);
2656
2720
                goto tailrecur_ne;
2657
2721
            }
2658
2722
        }
2662
2726
    goto tailrecur;    
2663
2727
   
2664
2728
pop_next:
2665
 
    if (!ESTACK_ISEMPTY(stack)) {
2666
 
        Eterm something = ESTACK_POP(stack);
2667
 
        if (primary_tag(something) == TAG_PRIMARY_HEADER) { /* a term_array */
 
2729
    if (!WSTACK_ISEMPTY(stack)) {
 
2730
        UWord something = WSTACK_POP(stack);
 
2731
        if (primary_tag((Eterm) something) == TAG_PRIMARY_HEADER) { /* a term_array */
2668
2732
            aa = (Eterm*) something;
2669
 
            bb = (Eterm*) ESTACK_POP(stack);
2670
 
            i = ESTACK_POP(stack);
 
2733
            bb = (Eterm*) WSTACK_POP(stack);
 
2734
            i = WSTACK_POP(stack);
2671
2735
            goto term_array;
2672
2736
        }
2673
 
        a = something;
2674
 
        b = ESTACK_POP(stack);
 
2737
        a = (Eterm) something;
 
2738
        b = (Eterm) WSTACK_POP(stack);
2675
2739
        goto tailrecur;
2676
2740
    }
2677
2741
 
2678
 
    DESTROY_ESTACK(stack);
 
2742
    DESTROY_WSTACK(stack);
2679
2743
    return 0;
2680
2744
 
2681
2745
not_equal:
2686
2750
}
2687
2751
 
2688
2752
 
2689
 
void
2690
 
erts_cleanup_externals(ExternalThing *etp)
2691
 
{
2692
 
    ExternalThing *tetp;
2693
 
 
2694
 
    tetp = etp;
2695
 
 
2696
 
    while(tetp) {
2697
 
        erts_deref_node_entry(tetp->node);
2698
 
        tetp = tetp->next;
2699
 
    }
2700
 
}
2701
 
 
2702
2753
Eterm
2703
 
store_external_or_ref_(Uint **hpp, ExternalThing **etpp, Eterm ns)
 
2754
store_external_or_ref_(Uint **hpp, ErlOffHeap* oh, Eterm ns)
2704
2755
{
2705
2756
    Uint i;
2706
2757
    Uint size;
2719
2770
 
2720
2771
        erts_refc_inc(&((ExternalThing *) to_hp)->node->refc, 2);
2721
2772
 
2722
 
        ((ExternalThing *) to_hp)->next = *etpp;
2723
 
        *etpp = (ExternalThing *) to_hp;
 
2773
        ((struct erl_off_heap_header*) to_hp)->next = oh->first;
 
2774
        oh->first = (struct erl_off_heap_header*) to_hp;
2724
2775
 
2725
2776
        return make_external(to_hp);
2726
2777
    }
2749
2800
    sz = NC_HEAP_SIZE(ns);
2750
2801
    ASSERT(sz > 0);
2751
2802
    hp = HAlloc(proc, sz);
2752
 
    return store_external_or_ref_(&hp, &MSO(proc).externals, ns);
 
2803
    return store_external_or_ref_(&hp, &MSO(proc), ns);
2753
2804
}
2754
2805
 
2755
2806
void bin_write(int to, void *to_arg, byte* buf, int sz)
3158
3209
 
3159
3210
    *timer_ref = res;
3160
3211
 
3161
 
    erl_set_timer(&res->timer.tm,
 
3212
    erts_set_timer(&res->timer.tm,
3162
3213
                  (ErlTimeoutProc) ptimer_timeout,
3163
3214
                  (ErlCancelProc) ptimer_cancelled,
3164
3215
                  (void*) res,
3172
3223
        ASSERT(*ptimer->timer.timer_ref == ptimer);
3173
3224
        *ptimer->timer.timer_ref = NULL;
3174
3225
        ptimer->timer.flags |= ERTS_PTMR_FLG_CANCELLED;
3175
 
        erl_cancel_timer(&ptimer->timer.tm);
 
3226
        erts_cancel_timer(&ptimer->timer.tm);
3176
3227
    }
3177
3228
}
3178
3229
 
3612
3663
}
3613
3664
 
3614
3665
 
3615
 
static ERTS_INLINE int
 
3666
static ERTS_INLINE erts_aint32_t
3616
3667
threads_not_under_control(void)
3617
3668
{
3618
 
    int res = system_block_state.threads_to_block;
 
3669
    erts_aint32_t res = system_block_state.threads_to_block;
3619
3670
 
3620
3671
    /* Waiting is always an allowed activity... */
3621
 
    res -= erts_smp_atomic_read(&erts_system_block_state.in_activity.wait);
 
3672
    res -= erts_smp_atomic32_read(&erts_system_block_state.in_activity.wait);
3622
3673
 
3623
3674
    if (system_block_state.allowed_activities & ERTS_BS_FLG_ALLOW_GC)
3624
 
        res -= erts_smp_atomic_read(&erts_system_block_state.in_activity.gc);
 
3675
        res -= erts_smp_atomic32_read(&erts_system_block_state.in_activity.gc);
3625
3676
 
3626
3677
    if (system_block_state.allowed_activities & ERTS_BS_FLG_ALLOW_IO)
3627
 
        res -= erts_smp_atomic_read(&erts_system_block_state.in_activity.io);
 
3678
        res -= erts_smp_atomic32_read(&erts_system_block_state.in_activity.io);
3628
3679
 
3629
3680
    if (res < 0) {
3630
3681
        ASSERT(0);
3684
3735
    }
3685
3736
    else {
3686
3737
 
3687
 
        erts_smp_atomic_inc(&erts_system_block_state.do_block);
 
3738
        erts_smp_atomic32_inc(&erts_system_block_state.do_block);
3688
3739
 
3689
3740
        /* Someone else might be waiting for us to block... */
3690
3741
        if (do_block) {
3736
3787
 
3737
3788
    another_blocker = erts_smp_pending_system_block();
3738
3789
    system_block_state.emergency = 1;
3739
 
    erts_smp_atomic_inc(&erts_system_block_state.do_block);
 
3790
    erts_smp_atomic32_inc(&erts_system_block_state.do_block);
3740
3791
 
3741
3792
    if (another_blocker) {
3742
3793
        if (is_blocker()) {
3743
 
            erts_smp_atomic_dec(&erts_system_block_state.do_block);
 
3794
            erts_smp_atomic32_dec(&erts_system_block_state.do_block);
3744
3795
            res = 0;
3745
3796
            goto done;
3746
3797
        }
3797
3848
    if (system_block_state.recursive_block)
3798
3849
        system_block_state.recursive_block--;
3799
3850
    else {
3800
 
        do_block = erts_smp_atomic_dectest(&erts_system_block_state.do_block);
 
3851
        do_block = erts_smp_atomic32_dectest(&erts_system_block_state.do_block);
3801
3852
        system_block_state.have_blocker = 0;
3802
3853
        if (is_blockable_thread())
3803
3854
            system_block_state.threads_to_block++;
3932
3983
 
3933
3984
    /* Global state... */
3934
3985
 
3935
 
    erts_smp_atomic_init(&erts_system_block_state.do_block, 0L);
3936
 
    erts_smp_atomic_init(&erts_system_block_state.in_activity.wait, 0L);
3937
 
    erts_smp_atomic_init(&erts_system_block_state.in_activity.gc, 0L);
3938
 
    erts_smp_atomic_init(&erts_system_block_state.in_activity.io, 0L);
 
3986
    erts_smp_atomic32_init(&erts_system_block_state.do_block, 0);
 
3987
    erts_smp_atomic32_init(&erts_system_block_state.in_activity.wait, 0);
 
3988
    erts_smp_atomic32_init(&erts_system_block_state.in_activity.gc, 0);
 
3989
    erts_smp_atomic32_init(&erts_system_block_state.in_activity.io, 0);
3939
3990
 
3940
3991
    /* Make sure blockable threads unregister when exiting... */
3941
3992
    erts_smp_install_exit_handler(erts_unregister_blockable_thread);
3992
4043
    return res;
3993
4044
}
3994
4045
 
 
4046
/*
 
4047
 * To be used to silence unused result warnings, but do not abuse it.
 
4048
 */
 
4049
void erts_silence_warn_unused_result(long unused)
 
4050
{
 
4051
 
 
4052
}
 
4053
 
3995
4054
#ifdef DEBUG
3996
4055
/*
3997
4056
 * Handy functions when using a debugger - don't use in the code!