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

« back to all changes in this revision

Viewing changes to erts/emulator/beam/erl_db_util.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 1998-2009. All Rights Reserved.
5
 
 * 
 
3
 *
 
4
 * Copyright Ericsson AB 1998-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
 
25
25
#ifdef HAVE_CONFIG_H
26
26
#  include "config.h"
27
27
#endif
28
 
 
29
28
#include "sys.h"
30
29
#include "erl_vm.h"
31
30
#include "global.h"
58
57
DBIF_TABLE_GUARD | DBIF_TABLE_BODY | DBIF_TRACE_GUARD | DBIF_TRACE_BODY
59
58
 
60
59
 
 
60
#define HEAP_XTRA 100
61
61
 
62
62
/*
63
63
** Some convenience macros for stacks (DMC == db_match_compile)
117
117
        erts_free(ERTS_ALC_T_DB_MC_STK, (Name).data);                   \
118
118
} while (0)
119
119
 
 
120
 
 
121
#define TermWords(t) (((t) / (sizeof(UWord)/sizeof(Eterm))) + !!((t) % (sizeof(UWord)/sizeof(Eterm))))
 
122
 
 
123
 
120
124
static ERTS_INLINE Process *
121
125
get_proc(Process *cp, Uint32 cp_locks, Eterm id, Uint32 id_locks)
122
126
{
226
230
    matchCall2,
227
231
    matchCall3,
228
232
    matchPushV,
 
233
#if HALFWORD_HEAP
 
234
    matchPushVGuard,    /* First guard-only variable reference */
 
235
#endif
 
236
    matchPushVResult, /* First variable reference in result, or (if HALFWORD)
 
237
                         in guard if also referenced in result */
229
238
    matchPushExpr, /* Push the whole expression we're matching ('$_') */
230
239
    matchPushArrayAsList, /* Only when parameter is an Array and 
231
240
                             not an erlang term  (DCOMP_TRACE) */
281
290
*/
282
291
DMC_DECLARE_STACK_TYPE(Eterm);
283
292
 
284
 
DMC_DECLARE_STACK_TYPE(Uint);
 
293
DMC_DECLARE_STACK_TYPE(UWord);
285
294
 
286
295
DMC_DECLARE_STACK_TYPE(unsigned);
287
296
 
289
298
** Data about the heap during compilation
290
299
*/
291
300
 
 
301
typedef struct DMCVariable {
 
302
    int is_bound;
 
303
    int is_in_body;
 
304
#if HALFWORD_HEAP
 
305
    int first_guard_label;  /* to maybe change from PushVGuard to PushVResult */
 
306
#endif
 
307
} DMCVariable;
 
308
 
292
309
typedef struct DMCHeap {
293
310
    int size;
294
 
    unsigned def[DMC_DEFAULT_SIZE];
295
 
    unsigned *data;
296
 
    int used;
 
311
    DMCVariable vars_def[DMC_DEFAULT_SIZE];
 
312
    DMCVariable* vars;
 
313
    int vars_used;
297
314
} DMCHeap;
298
315
 
299
316
/*
320
337
    Eterm *bodyexpr;
321
338
    int num_match;
322
339
    int current_match;
323
 
    int eheap_need;
324
340
    Uint cflags;
325
341
    int is_guard; /* 1 if in guard, 0 if in body */
326
342
    int special; /* 1 if the head in the match was a single expression */ 
343
359
 
344
360
#define ERTS_DEFAULT_MS_HEAP_SIZE 128
345
361
 
 
362
/* Runtime info about a $-variable
 
363
*/
 
364
typedef struct MatchVariable {
 
365
    Eterm term;
 
366
#ifdef DEBUG
 
367
    Process* proc;
 
368
    Eterm* base;
 
369
#endif
 
370
} MatchVariable;
 
371
 
346
372
typedef struct {
347
373
    Process process;
348
 
    Eterm *heap;
 
374
    union {
 
375
        Eterm* heap;
 
376
        MatchVariable* variables;   /* first on "heap" */
 
377
    }u;
349
378
    Eterm default_heap[ERTS_DEFAULT_MS_HEAP_SIZE];
350
379
} ErtsMatchPseudoProcess;
351
380
 
359
388
static ERTS_INLINE void
360
389
cleanup_match_pseudo_process(ErtsMatchPseudoProcess *mpsp, int keep_heap)
361
390
{
362
 
    if (mpsp->process.mbuf
363
 
        || mpsp->process.off_heap.mso
364
 
#ifndef HYBRID /* FIND ME! */
365
 
        || mpsp->process.off_heap.funs
366
 
#endif
367
 
        || mpsp->process.off_heap.externals) {
 
391
    if (mpsp->process.mbuf || mpsp->process.off_heap.first) {
368
392
        erts_cleanup_empty_process(&mpsp->process);
369
393
    }
370
394
#ifdef DEBUG
373
397
    }
374
398
#endif
375
399
    if (!keep_heap) {
376
 
        if (mpsp->heap != &mpsp->default_heap[0]) {
 
400
        if (mpsp->u.heap != mpsp->default_heap) {
377
401
            /* Have to be done *after* call to erts_cleanup_empty_process() */
378
 
            erts_free(ERTS_ALC_T_DB_MS_RUN_HEAP, (void *) mpsp->heap);
379
 
            mpsp->heap = &mpsp->default_heap[0];
 
402
            erts_free(ERTS_ALC_T_DB_MS_RUN_HEAP, (void *) mpsp->u.heap);
 
403
            mpsp->u.heap = mpsp->default_heap;
380
404
        }
381
405
#ifdef DEBUG
382
406
        else {
383
407
            int i;
384
408
            for (i = 0; i < ERTS_DEFAULT_MS_HEAP_SIZE; i++) {
385
 
#ifdef ARCH_64
 
409
#if defined(ARCH_64) && !HALFWORD_HEAP
386
410
                mpsp->default_heap[i] = (Eterm) 0xdeadbeefdeadbeef;
387
411
#else
388
412
                mpsp->default_heap[i] = (Eterm) 0xdeadbeef;
400
424
    mpsp = (ErtsMatchPseudoProcess *)erts_alloc(ERTS_ALC_T_DB_MS_PSDO_PROC,
401
425
                                                sizeof(ErtsMatchPseudoProcess));
402
426
    erts_init_empty_process(&mpsp->process);
403
 
    mpsp->heap = &mpsp->default_heap[0];
 
427
    mpsp->u.heap = mpsp->default_heap;
404
428
    return mpsp;
405
429
}
406
430
 
424
448
    mpsp = match_pseudo_process;
425
449
    cleanup_match_pseudo_process(mpsp, 0);
426
450
#endif
427
 
    if (heap_size > ERTS_DEFAULT_MS_HEAP_SIZE)
428
 
        mpsp->heap = (Eterm *) erts_alloc(ERTS_ALC_T_DB_MS_RUN_HEAP,
429
 
                                          heap_size*sizeof(Uint));
 
451
    if (heap_size > ERTS_DEFAULT_MS_HEAP_SIZE*sizeof(Eterm)) {
 
452
        mpsp->u.heap = (Eterm*) erts_alloc(ERTS_ALC_T_DB_MS_RUN_HEAP, heap_size);
 
453
    }
430
454
    else {
431
 
        ASSERT(mpsp->heap == &mpsp->default_heap[0]);
 
455
        ASSERT(mpsp->u.heap == mpsp->default_heap);
432
456
    }
433
457
    return mpsp;
434
458
}
469
493
 
470
494
static erts_smp_atomic_t trace_control_word;
471
495
 
472
 
 
473
 
Eterm
474
 
erts_ets_copy_object(Eterm obj, Process* to)
475
 
{
476
 
    Uint size = size_object(obj);
477
 
    Eterm* hp = HAlloc(to, size);
478
 
    Eterm res;
479
 
 
480
 
    res = copy_struct(obj, size, &hp, &MSO(to));
481
 
#ifdef DEBUG
482
 
    if (eq(obj, res) == 0) {
483
 
        erl_exit(1, "copy not equal to source\n");
484
 
    }
485
 
#endif
486
 
    return res;
487
 
}
488
 
 
489
496
/* This needs to be here, before the bif table... */
490
497
 
491
498
static Eterm db_set_trace_control_word_fake_1(Process *p, Eterm val);
830
837
static Eterm my_copy_struct(Eterm t, Eterm **hp, ErlOffHeap* off_heap);
831
838
 
832
839
/* Guard compilation */
833
 
static void do_emit_constant(DMCContext *context, DMC_STACK_TYPE(Uint) *text,
 
840
static void do_emit_constant(DMCContext *context, DMC_STACK_TYPE(UWord) *text,
834
841
                             Eterm t);
835
842
static DMCRet dmc_list(DMCContext *context,
836
843
                       DMCHeap *heap,
837
 
                       DMC_STACK_TYPE(Uint) *text,
 
844
                       DMC_STACK_TYPE(UWord) *text,
838
845
                       Eterm t,
839
846
                       int *constant);
840
847
static DMCRet dmc_tuple(DMCContext *context,
841
848
                       DMCHeap *heap,
842
 
                       DMC_STACK_TYPE(Uint) *text,
 
849
                       DMC_STACK_TYPE(UWord) *text,
843
850
                       Eterm t,
844
851
                       int *constant);
845
852
static DMCRet dmc_variable(DMCContext *context,
846
853
                           DMCHeap *heap,
847
 
                           DMC_STACK_TYPE(Uint) *text,
 
854
                           DMC_STACK_TYPE(UWord) *text,
848
855
                           Eterm t,
849
856
                           int *constant);
850
857
static DMCRet dmc_fun(DMCContext *context,
851
858
                      DMCHeap *heap,
852
 
                      DMC_STACK_TYPE(Uint) *text,
 
859
                      DMC_STACK_TYPE(UWord) *text,
853
860
                      Eterm t,
854
861
                      int *constant);
855
862
static DMCRet dmc_expr(DMCContext *context,
856
863
                       DMCHeap *heap,
857
 
                       DMC_STACK_TYPE(Uint) *text,
 
864
                       DMC_STACK_TYPE(UWord) *text,
858
865
                       Eterm t,
859
866
                       int *constant);
860
867
static DMCRet compile_guard_expr(DMCContext *context,
861
868
                                    DMCHeap *heap,
862
 
                                    DMC_STACK_TYPE(Uint) *text,
 
869
                                    DMC_STACK_TYPE(UWord) *text,
863
870
                                    Eterm t);
864
871
/* match expression subroutine */
865
872
static DMCRet dmc_one_term(DMCContext *context, 
866
873
                           DMCHeap *heap,
867
874
                           DMC_STACK_TYPE(Eterm) *stack,
868
 
                           DMC_STACK_TYPE(Uint) *text,
 
875
                           DMC_STACK_TYPE(UWord) *text,
869
876
                           Eterm c);
870
877
 
871
878
 
872
879
#ifdef DMC_DEBUG
873
880
static int test_disassemble_next = 0;
874
 
static void db_match_dis(Binary *prog);
 
881
void db_match_dis(Binary *prog);
875
882
#define TRACE erts_fprintf(stderr,"Trace: %s:%d\n",__FILE__,__LINE__)
876
 
#define FENCE_PATTERN_SIZE 1
 
883
#define FENCE_PATTERN_SIZE (1*sizeof(Uint))
877
884
#define FENCE_PATTERN 0xDEADBEEFUL
878
885
#else
879
886
#define TRACE /* Nothing */
891
898
 
892
899
static Eterm seq_trace_fake(Process *p, Eterm arg1);
893
900
 
 
901
static void db_free_tmp_uncompressed(DbTerm* obj);
 
902
 
894
903
 
895
904
/*
896
905
** Interface routines.
915
924
    if (val != ((Uint32)val))
916
925
        BIF_ERROR(p, BADARG);
917
926
    
918
 
    old_tcw = (Uint32) erts_smp_atomic_xchg(&trace_control_word, (long) val);
 
927
    old_tcw = (Uint32) erts_smp_atomic_xchg(&trace_control_word, (erts_aint_t) val);
919
928
    BIF_RET(erts_make_integer((Uint) old_tcw, p));
920
929
}
921
930
 
1179
1188
}
1180
1189
    
1181
1190
Eterm erts_match_set_run(Process *p, Binary *mpsp, 
1182
 
                         Eterm *args, int num_args, 
 
1191
                         Eterm *args, int num_args,
 
1192
                         enum erts_pam_run_flags in_flags,
1183
1193
                         Uint32 *return_flags) 
1184
1194
{
1185
1195
    Eterm ret;
1186
1196
 
1187
 
    ret = db_prog_match(p, mpsp,
1188
 
                        (Eterm) args, 
1189
 
                        num_args, return_flags);
 
1197
    ret = db_prog_match(p, mpsp, NIL, NULL, args, num_args,
 
1198
                        in_flags, return_flags);
1190
1199
#if defined(HARDDEBUG)
1191
1200
    if (is_non_value(ret)) {
1192
1201
        erts_fprintf(stderr, "Failed\n");
1204
1213
     */
1205
1214
}
1206
1215
 
 
1216
static Eterm erts_match_set_run_ets(Process *p, Binary *mpsp,
 
1217
                                    Eterm args, int num_args,
 
1218
                                    Uint32 *return_flags)
 
1219
{
 
1220
    Eterm ret;
 
1221
 
 
1222
    ret = db_prog_match(p, mpsp, args, NULL, NULL, num_args,
 
1223
                        ERTS_PAM_CONTIGUOUS_TUPLE | ERTS_PAM_COPY_RESULT,
 
1224
                        return_flags);
 
1225
#if defined(HARDDEBUG)
 
1226
    if (is_non_value(ret)) {
 
1227
        erts_fprintf(stderr, "Failed\n");
 
1228
    } else {
 
1229
        erts_fprintf(stderr, "Returning : %T\n", ret);
 
1230
    }
 
1231
#endif
 
1232
    return ret;
 
1233
    /* Returns
 
1234
     *   THE_NON_VALUE if no match
 
1235
     *   am_false      if {message,false} has been called,
 
1236
     *   am_true       if {message,_} has not been called or
 
1237
     *                 if {message,true} has been called,
 
1238
     *   Msg           if {message,Msg} has been called.
 
1239
     */
 
1240
}
 
1241
 
1207
1242
/*
1208
1243
** API Used by other erl_db modules.
1209
1244
*/
1245
1280
{
1246
1281
    DMCHeap heap;
1247
1282
    DMC_STACK_TYPE(Eterm) stack;
1248
 
    DMC_STACK_TYPE(Uint) text;
 
1283
    DMC_STACK_TYPE(UWord) text;
1249
1284
    DMCContext context;
1250
1285
    MatchProg *ret = NULL;
1251
1286
    Eterm t;
1254
1289
    int structure_checked;
1255
1290
    DMCRet res;
1256
1291
    int current_try_label;
1257
 
    Uint max_eheap_need;
1258
1292
    Binary *bp = NULL;
1259
1293
    unsigned clause_start;
1260
1294
 
1267
1301
    context.matchexpr = matchexpr;
1268
1302
    context.guardexpr = guards;
1269
1303
    context.bodyexpr = body;
1270
 
    context.eheap_need = 0;
1271
1304
    context.err_info = err_info;
1272
1305
    context.cflags = flags;
1273
1306
 
1274
1307
    heap.size = DMC_DEFAULT_SIZE;
1275
 
    heap.data = heap.def;
 
1308
    heap.vars = heap.vars_def;
1276
1309
 
1277
1310
    /*
1278
1311
    ** Compile the match expression
1279
1312
    */
1280
1313
restart:
1281
 
    heap.used = 0;
1282
 
    max_eheap_need = 0;
 
1314
    heap.vars_used = 0;
1283
1315
    for (context.current_match = 0; 
1284
1316
         context.current_match < num_progs; 
1285
1317
         ++context.current_match) { /* This loop is long, 
1286
1318
                                       too long */
1287
 
        memset(heap.data, 0, heap.size * sizeof(*heap.data));
 
1319
        memset(heap.vars, 0, heap.size * sizeof(*heap.vars));
1288
1320
        t = context.matchexpr[context.current_match];
1289
1321
        context.stack_used = 0;
1290
 
        context.eheap_need = 0;
1291
1322
        structure_checked = 0;
1292
1323
        if (context.current_match < num_progs - 1) {
1293
1324
            DMC_PUSH(text,matchTryMeElse);
1380
1411
    
1381
1412
        /* 
1382
1413
        ** There is one single top variable in the match expression
1383
 
        ** iff the text is tho Uint's and the single instruction 
 
1414
        ** iff the text is two Uint's and the single instruction
1384
1415
        ** is 'matchBind' or it is only a skip.
1385
1416
        */
1386
1417
        context.special = 
1459
1490
        if (current_try_label >= 0) {
1460
1491
            DMC_POKE(text, current_try_label, DMC_STACK_NUM(text));
1461
1492
        }
1462
 
        /* So, how much eheap did this part of the match program need? */
1463
 
        if (context.eheap_need > max_eheap_need) {
1464
 
            max_eheap_need = context.eheap_need;
1465
 
        }
1466
1493
    } /* for (context.current_match = 0 ...) */
1467
1494
 
1468
1495
 
1491
1518
    ** A special case is when the match expression is a single binding 
1492
1519
    ** (i.e '$1'), then the field single_variable is set to 1.
1493
1520
    */
1494
 
    bp = erts_create_magic_binary(((sizeof(MatchProg) - sizeof(Uint)) +
1495
 
                                   (DMC_STACK_NUM(text) * sizeof(Uint))),
 
1521
    bp = erts_create_magic_binary(((sizeof(MatchProg) - sizeof(UWord)) +
 
1522
                                   (DMC_STACK_NUM(text) * sizeof(UWord))),
1496
1523
                                  erts_db_match_prog_destructor);
1497
1524
    ret = Binary2MatchProg(bp);
1498
1525
    ret->saved_program_buf = NULL;
1499
1526
    ret->saved_program = NIL;
1500
1527
    ret->term_save = context.save;
1501
 
    ret->num_bindings = heap.used;
 
1528
    ret->num_bindings = heap.vars_used;
1502
1529
    ret->single_variable = context.special;
1503
1530
    sys_memcpy(ret->text, DMC_STACK_DATA(text), 
1504
 
               DMC_STACK_NUM(text) * sizeof(Uint));
1505
 
    ret->heap_size = ((heap.used * sizeof(Eterm)) +
1506
 
                      (max_eheap_need * sizeof(Eterm)) +
1507
 
                      (context.stack_need * sizeof(Eterm *)) +
1508
 
                      (3 * (FENCE_PATTERN_SIZE * sizeof(Eterm *))));
1509
 
    ret->eheap_offset = heap.used + FENCE_PATTERN_SIZE;
1510
 
    ret->stack_offset = ret->eheap_offset + max_eheap_need + FENCE_PATTERN_SIZE;
 
1531
               DMC_STACK_NUM(text) * sizeof(UWord));
 
1532
    ret->stack_offset = heap.vars_used*sizeof(MatchVariable) + FENCE_PATTERN_SIZE;
 
1533
    ret->heap_size = ret->stack_offset + context.stack_need * sizeof(Eterm*) + FENCE_PATTERN_SIZE;
 
1534
 
1511
1535
#ifdef DMC_DEBUG
1512
1536
    ret->prog_end = ret->text + DMC_STACK_NUM(text);
1513
1537
#endif
1517
1541
     */  
1518
1542
    context.save = NULL;
1519
1543
error: /* Here is were we land when compilation failed. */
1520
 
    while (context.save != NULL) {
1521
 
        ErlHeapFragment *ll = context.save->next;
 
1544
    if (context.save != NULL) {
1522
1545
        free_message_buffer(context.save);
1523
 
        context.save = ll;
 
1546
        context.save = NULL;
1524
1547
    }
1525
1548
    DMC_FREE(stack);
1526
1549
    DMC_FREE(text);
1527
1550
    if (context.copy != NULL) 
1528
1551
        free_message_buffer(context.copy);
1529
 
    if (heap.data != heap.def)
1530
 
        erts_free(ERTS_ALC_T_DB_MS_CMPL_HEAP, (void *) heap.data);
 
1552
    if (heap.vars != heap.vars_def)
 
1553
        erts_free(ERTS_ALC_T_DB_MS_CMPL_HEAP, (void *) heap.vars);
1531
1554
    return bp;
1532
1555
}
1533
1556
 
1537
1560
void erts_db_match_prog_destructor(Binary *bprog)
1538
1561
{
1539
1562
    MatchProg *prog;
1540
 
    ErlHeapFragment *tmp, *ll;
1541
1563
    if (bprog == NULL)
1542
1564
        return;
1543
1565
    prog = Binary2MatchProg(bprog);
1544
 
    tmp = prog->term_save; 
1545
 
    while (tmp != NULL) {
1546
 
        ll = tmp->next;
1547
 
        free_message_buffer(tmp);
1548
 
        tmp = ll;
 
1566
    if (prog->term_save != NULL) {
 
1567
        free_message_buffer(prog->term_save); 
1549
1568
    }
1550
1569
    if (prog->saved_program_buf != NULL)
1551
1570
        free_message_buffer(prog->saved_program_buf);
1576
1595
*/
1577
1596
static Eterm dpm_array_to_list(Process *psp, Eterm *arr, int arity)
1578
1597
{
1579
 
    Eterm *hp = HAlloc(psp, arity * 2);
 
1598
    Eterm *hp = HAllocX(psp, arity * 2, HEAP_XTRA);
1580
1599
    Eterm ret = NIL;
1581
1600
    while (--arity >= 0) {
1582
1601
        ret = CONS(hp, arr[arity], ret);
1584
1603
    }
1585
1604
    return ret;
1586
1605
}
 
1606
 
 
1607
 
 
1608
#if HALFWORD_HEAP
 
1609
struct heap_checkpoint_t
 
1610
{
 
1611
    Process *p;
 
1612
    Eterm* htop;
 
1613
    ErlHeapFragment* mbuf;
 
1614
    unsigned used_size;
 
1615
    ErlOffHeap off_heap;
 
1616
};
 
1617
 
 
1618
static void heap_checkpoint_init(Process* p, struct heap_checkpoint_t* hcp)
 
1619
{
 
1620
    hcp->p = p;
 
1621
    hcp->htop = HEAP_TOP(p);
 
1622
    hcp->mbuf = MBUF(p);
 
1623
    hcp->used_size = hcp->mbuf ? hcp->mbuf->used_size : 0;
 
1624
    hcp->off_heap = MSO(p);
 
1625
}
 
1626
 
 
1627
static void heap_checkpoint_revert(struct heap_checkpoint_t* hcp)
 
1628
{
 
1629
    struct erl_off_heap_header* oh = MSO(hcp->p).first;
 
1630
 
 
1631
    if (oh != hcp->off_heap.first) {
 
1632
        ASSERT(oh != NULL);
 
1633
        if (hcp->off_heap.first) {
 
1634
            while (oh->next != hcp->off_heap.first) {
 
1635
                oh = oh->next;
 
1636
            }
 
1637
            oh->next = NULL;
 
1638
        }
 
1639
        erts_cleanup_offheap(&MSO(hcp->p));
 
1640
        MSO(hcp->p) = hcp->off_heap;
 
1641
    }
 
1642
    if (MBUF(hcp->p) != hcp->mbuf) {
 
1643
        ErlHeapFragment* hf = MBUF(hcp->p);
 
1644
        ASSERT(hf != NULL);
 
1645
        if (hcp->mbuf) {
 
1646
            while (hf->next != hcp->mbuf) {
 
1647
                hf = hf->next;
 
1648
            }
 
1649
            hf->next = NULL;
 
1650
        }
 
1651
        free_message_buffer(MBUF(hcp->p));
 
1652
        MBUF(hcp->p) = hcp->mbuf;
 
1653
    }
 
1654
    if (hcp->mbuf != NULL && hcp->mbuf->used_size != hcp->used_size) {
 
1655
        hcp->mbuf->used_size = hcp->used_size;
 
1656
    }
 
1657
    HEAP_TOP(hcp->p) = hcp->htop;
 
1658
}
 
1659
#endif /* HALFWORD_HEAP */
 
1660
 
 
1661
static ERTS_INLINE Eterm copy_object_rel(Process* p, Eterm term, Eterm* base)
 
1662
{
 
1663
    if (!is_immed(term)) {
 
1664
        Uint sz = size_object_rel(term, base);
 
1665
        Eterm* top = HAllocX(p, sz, HEAP_XTRA);
 
1666
        return copy_struct_rel(term, sz, &top, &MSO(p), base, NULL);
 
1667
    }
 
1668
    return term;
 
1669
}
 
1670
 
 
1671
 
1587
1672
/*
1588
1673
** Execution of the match program, this is Pam.
1589
1674
** May return THE_NON_VALUE, which is a bailout.
1590
 
** the para meter 'arity' is only used if 'term' is actually an array,
 
1675
** the parameter 'arity' is only used if 'term' is actually an array,
1591
1676
** i.e. 'DCOMP_TRACE' was specified 
1592
1677
*/
1593
 
Eterm db_prog_match(Process *c_p, Binary *bprog, Eterm term, 
 
1678
Eterm db_prog_match(Process *c_p, Binary *bprog,
 
1679
                    Eterm term, Eterm* base,
 
1680
                    Eterm *termp,
1594
1681
                    int arity,
 
1682
                    enum erts_pam_run_flags in_flags,
1595
1683
                    Uint32 *return_flags)
1596
1684
{
1597
1685
    MatchProg *prog = Binary2MatchProg(bprog);
1600
1688
    Eterm t;
1601
1689
    Eterm **sp;
1602
1690
    Eterm *esp;
1603
 
    Eterm *hp;
1604
 
    Uint *pc = prog->text;
 
1691
    MatchVariable* variables;
 
1692
    BeamInstr *cp;
 
1693
    UWord *pc = prog->text;
1605
1694
    Eterm *ehp;
1606
1695
    Eterm ret;
1607
1696
    Uint n = 0; /* To avoid warning. */
1609
1698
    unsigned do_catch;
1610
1699
    ErtsMatchPseudoProcess *mpsp;
1611
1700
    Process *psp;
 
1701
    Process* build_proc;
1612
1702
    Process *tmpp;
1613
1703
    Process *current_scheduled;
1614
1704
    ErtsSchedulerData *esdp;
1615
1705
    Eterm (*bif)(Process*, ...);
1616
1706
    int fail_label;
1617
1707
    int atomic_trace;
 
1708
#if HALFWORD_HEAP
 
1709
    struct heap_checkpoint_t c_p_checkpoint = {};
 
1710
#endif
1618
1711
#ifdef DMC_DEBUG
1619
 
    unsigned long *heap_fence;
1620
 
    unsigned long *eheap_fence;
1621
 
    unsigned long *stack_fence;
 
1712
    Uint *heap_fence;
 
1713
    Uint *stack_fence;
1622
1714
    Uint save_op;
1623
1715
#endif /* DMC_DEBUG */
1624
1716
 
 
1717
    ASSERT(base==NULL || HALFWORD_HEAP);
 
1718
 
1625
1719
    mpsp = get_match_pseudo_process(c_p, prog->heap_size);
1626
1720
    psp = &mpsp->process;
1627
1721
 
1631
1725
    esdp = ERTS_GET_SCHEDULER_DATA_FROM_PROC(c_p);
1632
1726
    ASSERT(esdp != NULL);
1633
1727
    current_scheduled = esdp->current_process;
1634
 
    esdp->current_process = psp;
1635
1728
    /* SMP: psp->scheduler_data is set by get_match_pseudo_process */
1636
1729
 
1637
1730
    atomic_trace = 0;
1654
1747
 
1655
1748
#ifdef DMC_DEBUG
1656
1749
    save_op = 0;
1657
 
    heap_fence =  (unsigned long *) mpsp->heap + prog->eheap_offset - 1;
1658
 
    eheap_fence = (unsigned long *) mpsp->heap + prog->stack_offset - 1;
1659
 
    stack_fence = (unsigned long *) mpsp->heap + prog->heap_size - 1;
 
1750
    heap_fence = (Eterm*)((char*) mpsp->u.heap + prog->stack_offset) - 1;
 
1751
    stack_fence = (Eterm*)((char*) mpsp->u.heap + prog->heap_size) - 1;
1660
1752
    *heap_fence = FENCE_PATTERN;
1661
 
    *eheap_fence = FENCE_PATTERN;
1662
1753
    *stack_fence = FENCE_PATTERN;
1663
1754
#endif /* DMC_DEBUG */
1664
1755
 
1672
1763
 
1673
1764
    *return_flags = 0U;
1674
1765
 
 
1766
    variables = mpsp->u.variables;
 
1767
#if HALFWORD_HEAP
 
1768
    c_p_checkpoint.p = NULL;
 
1769
#endif
 
1770
 
1675
1771
restart:
1676
1772
    ep = &term;
1677
 
    esp = mpsp->heap + prog->stack_offset;
 
1773
    esp = (Eterm*)((char*)mpsp->u.heap + prog->stack_offset);
1678
1774
    sp = (Eterm **) esp;
1679
 
    hp = mpsp->heap;
1680
 
    ehp = mpsp->heap + prog->eheap_offset;
1681
1775
    ret = am_true;
1682
1776
    do_catch = 0;
1683
1777
    fail_label = -1;
 
1778
    build_proc = psp;
 
1779
    esdp->current_process = psp;
 
1780
    ASSERT_HALFWORD(!c_p_checkpoint.p);
 
1781
 
 
1782
#ifdef DEBUG
 
1783
    ASSERT(variables == mpsp->u.variables);
 
1784
    for (i=0; i<prog->num_bindings; i++) {
 
1785
        variables[i].term = THE_NON_VALUE;
 
1786
        variables[i].proc = NULL;
 
1787
        variables[i].base = base;
 
1788
    }
 
1789
#endif
1684
1790
 
1685
1791
    for (;;) {
1686
 
#ifdef DMC_DEBUG
 
1792
 
 
1793
    #ifdef DMC_DEBUG
1687
1794
        if (*heap_fence != FENCE_PATTERN) {
1688
1795
            erl_exit(1, "Heap fence overwritten in db_prog_match after op "
1689
1796
                     "0x%08x, overwritten with 0x%08x.", save_op, *heap_fence);
1690
1797
        }
1691
 
        if (*eheap_fence != FENCE_PATTERN) {
1692
 
            erl_exit(1, "Eheap fence overwritten in db_prog_match after op "
1693
 
                     "0x%08x, overwritten with 0x%08x.", save_op, 
1694
 
                     *eheap_fence);
1695
 
        }
1696
1798
        if (*stack_fence != FENCE_PATTERN) {
1697
1799
            erl_exit(1, "Stack fence overwritten in db_prog_match after op "
1698
1800
                     "0x%08x, overwritten with 0x%08x.", save_op, 
1699
1801
                     *stack_fence);
1700
1802
        }
1701
1803
        save_op = *pc;
1702
 
#endif
 
1804
    #endif
1703
1805
        switch (*pc++) {
1704
1806
        case matchTryMeElse:
 
1807
            ASSERT(fail_label == -1);
1705
1808
            fail_label = *pc++;
1706
1809
            break;
1707
1810
        case matchArray: /* only when DCOMP_TRACE, is always first
1709
1812
            n = *pc++;
1710
1813
            if ((int) n != arity)
1711
1814
                FAIL();
1712
 
            ep = (Eterm *) *ep;
 
1815
            ep = termp;
1713
1816
            break;
1714
1817
        case matchArrayBind: /* When the array size is unknown. */
 
1818
            ASSERT(termp);
1715
1819
            n = *pc++;
1716
 
            hp[n] = dpm_array_to_list(psp, (Eterm *) term, arity);
 
1820
            variables[n].term = dpm_array_to_list(psp, termp, arity);
1717
1821
            break;
1718
1822
        case matchTuple: /* *ep is a tuple of arity n */
1719
 
            if (!is_tuple(*ep))
 
1823
            if (!is_tuple_rel(*ep,base))
1720
1824
                FAIL();
1721
 
            ep = tuple_val(*ep);
 
1825
            ep = tuple_val_rel(*ep,base);
1722
1826
            n = *pc++;
1723
1827
            if (arityval(*ep) != n)
1724
1828
                FAIL();
1726
1830
            break;
1727
1831
        case matchPushT: /* *ep is a tuple of arity n, 
1728
1832
                            push ptr to first element */
1729
 
            if (!is_tuple(*ep))
 
1833
            if (!is_tuple_rel(*ep,base))
1730
1834
                FAIL();
1731
 
            tp = tuple_val(*ep);
 
1835
            tp = tuple_val_rel(*ep,base);
1732
1836
            n = *pc++;
1733
1837
            if (arityval(*tp) != n)
1734
1838
                FAIL();
1738
1842
        case matchList:
1739
1843
            if (!is_list(*ep))
1740
1844
                FAIL();
1741
 
            ep = list_val(*ep);
 
1845
            ep = list_val_rel(*ep,base);
1742
1846
            break;
1743
1847
        case matchPushL:
1744
1848
            if (!is_list(*ep))
1745
1849
                FAIL();
1746
 
            *sp++ = list_val(*ep);
 
1850
            *sp++ = list_val_rel(*ep,base);
1747
1851
            ++ep;
1748
1852
            break;
1749
1853
        case matchPop:
1751
1855
            break;
1752
1856
        case matchBind:
1753
1857
            n = *pc++;
1754
 
            hp[n] = *ep++;
 
1858
            variables[n].term = *ep++;
1755
1859
            break;
1756
1860
        case matchCmp:
1757
1861
            n = *pc++;
1758
 
            if (!eq(hp[n],*ep))
 
1862
            if (!eq_rel(variables[n].term, base, *ep, base))
1759
1863
                FAIL();
1760
1864
            ++ep;
1761
1865
            break;
1762
1866
        case matchEqBin:
1763
1867
            t = (Eterm) *pc++;
1764
 
            if (!eq(*ep,t))
 
1868
            if (!eq_rel(t,NULL,*ep,base))
1765
1869
                FAIL();
1766
1870
            ++ep;
1767
1871
            break;
1768
1872
        case matchEqFloat:
1769
 
            if (!is_float(*ep))
1770
 
                FAIL();
1771
 
            if (memcmp(float_val(*ep) + 1, pc, sizeof(double)))
1772
 
                FAIL();
1773
 
            pc += 2;
1774
 
            ++ep;
1775
 
            break;
1776
 
        case matchEqRef:
1777
 
            if (!is_ref(*ep))
1778
 
                FAIL();
1779
 
            if (!eq(*ep, make_internal_ref(pc)))
1780
 
                FAIL();
1781
 
            i = thing_arityval(*pc);
1782
 
            pc += i+1;
1783
 
            ++ep;
1784
 
            break;
 
1873
            if (!is_float_rel(*ep,base))
 
1874
                FAIL();
 
1875
            if (memcmp(float_val_rel(*ep,base) + 1, pc, sizeof(double)))
 
1876
                FAIL();
 
1877
            pc += TermWords(2);
 
1878
            ++ep;
 
1879
            break;
 
1880
        case matchEqRef: {
 
1881
            Eterm* epc = (Eterm*)pc;
 
1882
            if (!is_ref_rel(*ep,base))
 
1883
                FAIL();
 
1884
            if (!eq_rel(make_internal_ref_rel(epc, epc), epc, *ep, base)) {
 
1885
                FAIL();
 
1886
            }
 
1887
            i = thing_arityval(*epc);
 
1888
            pc += TermWords(i+1);
 
1889
            ++ep;
 
1890
            break;
 
1891
        }
1785
1892
        case matchEqBig:
1786
 
            if (!is_big(*ep))
1787
 
                FAIL();
1788
 
            tp = big_val(*ep);
1789
 
            if (*tp != *pc)
1790
 
                FAIL();
1791
 
            i = BIG_ARITY(pc);
1792
 
            while(i--)
1793
 
                if (*++tp != *++pc)
 
1893
            if (!is_big_rel(*ep,base))
 
1894
                FAIL();
 
1895
            tp = big_val_rel(*ep,base);
 
1896
            {
 
1897
                Eterm *epc = (Eterm *) pc;
 
1898
                if (*tp != *epc)
1794
1899
                    FAIL();
1795
 
            ++pc;
 
1900
                i = BIG_ARITY(epc);
 
1901
                pc += TermWords(i+1);
 
1902
                while(i--) {
 
1903
                    if (*++tp != *++epc) {
 
1904
                        FAIL();
 
1905
                    }
 
1906
                }
 
1907
            }
1796
1908
            ++ep;
1797
1909
            break;
1798
1910
        case matchEq:
1799
 
            t = (Eterm) *pc++; 
 
1911
            t = (Eterm) *pc++;
 
1912
            ASSERT(is_immed(t));
1800
1913
            if (t != *ep++)
1801
1914
                FAIL();
1802
1915
            break;
1804
1917
            ++ep;
1805
1918
            break;
1806
1919
        /* 
1807
 
         * Here comes guard instructions 
 
1920
         * Here comes guard & body instructions
1808
1921
         */
1809
1922
        case matchPushC: /* Push constant */
1810
 
            *esp++ = *pc++;
 
1923
            if ((in_flags & ERTS_PAM_COPY_RESULT)
 
1924
                && do_catch && !is_immed(*pc)) {
 
1925
                *esp++ = copy_object(*pc++, c_p);
 
1926
            }
 
1927
            else {
 
1928
                *esp++ = *pc++;
 
1929
            }
1811
1930
            break;
1812
1931
        case matchConsA:
1813
 
            ehp[1] = *--esp;
1814
 
            ehp[0] = esp[-1];
 
1932
            ehp = HAllocX(build_proc, 2, HEAP_XTRA);
 
1933
            CDR(ehp) = *--esp;
 
1934
            CAR(ehp) = esp[-1];
1815
1935
            esp[-1] = make_list(ehp);
1816
 
            ehp += 2;
1817
1936
            break;
1818
1937
        case matchConsB:
1819
 
            ehp[0] = *--esp;
1820
 
            ehp[1] = esp[-1];
 
1938
            ehp = HAllocX(build_proc, 2, HEAP_XTRA);
 
1939
            CAR(ehp) = *--esp;
 
1940
            CDR(ehp) = esp[-1];
1821
1941
            esp[-1] = make_list(ehp);
1822
 
            ehp += 2;
1823
1942
            break;
1824
1943
        case matchMkTuple:
1825
1944
            n = *pc++;
 
1945
            ehp = HAllocX(build_proc, n+1, HEAP_XTRA);
1826
1946
            t = make_tuple(ehp);
1827
1947
            *ehp++ = make_arityval(n);
1828
1948
            while (n--) {
1832
1952
            break;
1833
1953
        case matchCall0:
1834
1954
            bif = (Eterm (*)(Process*, ...)) *pc++;
1835
 
            t = (*bif)(psp);
 
1955
            t = (*bif)(build_proc);
1836
1956
            if (is_non_value(t)) {
1837
1957
                if (do_catch)
1838
1958
                    t = FAIL_TERM;
1843
1963
            break;
1844
1964
        case matchCall1:
1845
1965
            bif = (Eterm (*)(Process*, ...)) *pc++;
1846
 
            t = (*bif)(psp, esp[-1]);
 
1966
            t = (*bif)(build_proc, esp[-1]);
1847
1967
            if (is_non_value(t)) {
1848
1968
                if (do_catch)
1849
1969
                    t = FAIL_TERM;
1854
1974
            break;
1855
1975
        case matchCall2:
1856
1976
            bif = (Eterm (*)(Process*, ...)) *pc++;
1857
 
            t = (*bif)(psp, esp[-1], esp[-2]);
 
1977
            t = (*bif)(build_proc, esp[-1], esp[-2]);
1858
1978
            if (is_non_value(t)) {
1859
1979
                if (do_catch)
1860
1980
                    t = FAIL_TERM;
1866
1986
            break;
1867
1987
        case matchCall3:
1868
1988
            bif = (Eterm (*)(Process*, ...)) *pc++;
1869
 
            t = (*bif)(psp, esp[-1], esp[-2], esp[-3]);
 
1989
            t = (*bif)(build_proc, esp[-1], esp[-2], esp[-3]);
1870
1990
            if (is_non_value(t)) {
1871
1991
                if (do_catch)
1872
1992
                    t = FAIL_TERM;
1876
1996
            esp -= 2;
1877
1997
            esp[-1] = t;
1878
1998
            break;
 
1999
 
 
2000
        #if HALFWORD_HEAP
 
2001
        case matchPushVGuard:
 
2002
            if (!base) goto case_matchPushV;
 
2003
            /* Build NULL-based copy on pseudo heap for easy disposal */
 
2004
            n = *pc++;
 
2005
            ASSERT(is_value(variables[n].term));
 
2006
            ASSERT(!variables[n].proc);
 
2007
            variables[n].term = copy_object_rel(psp, variables[n].term, base);
 
2008
            *esp++ = variables[n].term;
 
2009
            #ifdef DEBUG
 
2010
            variables[n].proc = psp;
 
2011
            variables[n].base = NULL;
 
2012
            #endif
 
2013
            break;
 
2014
        #endif
 
2015
        case matchPushVResult:
 
2016
            if (!(in_flags & ERTS_PAM_COPY_RESULT)) goto case_matchPushV;
 
2017
 
 
2018
            /* Build (NULL-based) copy on callers heap */
 
2019
        #if HALFWORD_HEAP
 
2020
            if (!do_catch && !c_p_checkpoint.p) {
 
2021
                heap_checkpoint_init(c_p, &c_p_checkpoint);
 
2022
            }
 
2023
        #endif
 
2024
            n = *pc++;
 
2025
            ASSERT(is_value(variables[n].term));
 
2026
            ASSERT(!variables[n].proc);
 
2027
            variables[n].term = copy_object_rel(c_p, variables[n].term, base);
 
2028
            *esp++ = variables[n].term;
 
2029
            #ifdef DEBUG
 
2030
            variables[n].proc = c_p;
 
2031
            variables[n].base = NULL;
 
2032
            #endif
 
2033
            break;
1879
2034
        case matchPushV:
1880
 
            *esp++ = hp[*pc++];
 
2035
        case_matchPushV:
 
2036
            n = *pc++;
 
2037
            ASSERT(is_value(variables[n].term));
 
2038
            ASSERT(!variables[n].base);
 
2039
            *esp++ = variables[n].term;
1881
2040
            break;
1882
2041
        case matchPushExpr:
1883
 
            *esp++ = term;
 
2042
            if (in_flags & ERTS_PAM_COPY_RESULT) {
 
2043
                Uint sz;
 
2044
                Eterm* top;
 
2045
                sz = size_object_rel(term, base);
 
2046
                top = HAllocX(build_proc, sz, HEAP_XTRA);
 
2047
                if (in_flags & ERTS_PAM_CONTIGUOUS_TUPLE) {
 
2048
                    ASSERT(is_tuple_rel(term,base));
 
2049
                    *esp++ = copy_shallow_rel(tuple_val_rel(term,base), sz,
 
2050
                                              &top, &MSO(build_proc), base);
 
2051
                }
 
2052
                else {
 
2053
                    *esp++ = copy_struct_rel(term, sz, &top, &MSO(build_proc),
 
2054
                                             base, NULL);
 
2055
                }
 
2056
            }
 
2057
            else {
 
2058
                *esp = term;
 
2059
            }
1884
2060
            break;
1885
2061
        case matchPushArrayAsList:
 
2062
            ASSERT_HALFWORD(base == NULL);
1886
2063
            n = arity; /* Only happens when 'term' is an array */
1887
 
            tp = (Eterm *) term;
 
2064
            tp = termp;
 
2065
            ehp = HAllocX(build_proc, n*2, HEAP_XTRA);
1888
2066
            *esp++  = make_list(ehp);
1889
2067
            while (n--) {
1890
2068
                *ehp++ = *tp++;
1897
2075
            break;
1898
2076
        case matchPushArrayAsListU:
1899
2077
            /* This instruction is NOT efficient. */
1900
 
            *esp++  = dpm_array_to_list(psp, (Eterm *) term, arity); 
 
2078
            ASSERT_HALFWORD(base == NULL);
 
2079
            *esp++  = dpm_array_to_list(build_proc, termp, arity);
1901
2080
            break;
1902
2081
        case matchTrue:
1903
2082
            if (*--esp != am_true)
1983
2162
        case matchProcessDump: {
1984
2163
            erts_dsprintf_buf_t *dsbufp = erts_create_tmp_dsbuf(0);
1985
2164
            print_process_info(ERTS_PRINT_DSBUF, (void *) dsbufp, c_p);
1986
 
            *esp++ = new_binary(psp, (byte *)dsbufp->str, (int)dsbufp->str_len);
 
2165
            *esp++ = new_binary(build_proc, (byte *)dsbufp->str,
 
2166
                                dsbufp->str_len);
1987
2167
            erts_destroy_tmp_dsbuf(dsbufp);
1988
2168
            break;
1989
2169
        }
2027
2207
            if (SEQ_TRACE_TOKEN(c_p) == NIL) 
2028
2208
                *esp++ = NIL;
2029
2209
            else {
 
2210
                Eterm sender = SEQ_TRACE_TOKEN_SENDER(c_p);
 
2211
                Uint sender_sz = is_immed(sender) ? 0 : size_object(sender);
 
2212
                ehp = HAllocX(build_proc, 6 + sender_sz, HEAP_XTRA);
 
2213
                if (sender_sz) {
 
2214
                    sender = copy_struct(sender, sender_sz, &ehp, &MSO(build_proc));
 
2215
                }
2030
2216
                *esp++ = make_tuple(ehp);
2031
2217
                ehp[0] = make_arityval(5);
2032
2218
                ehp[1] = SEQ_TRACE_TOKEN_FLAGS(c_p);
2033
2219
                ehp[2] = SEQ_TRACE_TOKEN_LABEL(c_p);
2034
2220
                ehp[3] = SEQ_TRACE_TOKEN_SERIAL(c_p);
2035
 
                ehp[4] = SEQ_TRACE_TOKEN_SENDER(c_p);
 
2221
                ehp[4] = sender;
2036
2222
                ehp[5] = SEQ_TRACE_TOKEN_LASTCNT(c_p);
2037
2223
                ASSERT(SEQ_TRACE_TOKEN_ARITY(c_p) == 5);
2038
2224
                ASSERT(is_immed(ehp[1]));
2039
2225
                ASSERT(is_immed(ehp[2]));
2040
2226
                ASSERT(is_immed(ehp[3]));
2041
2227
                ASSERT(is_immed(ehp[5]));
2042
 
                if(!is_immed(ehp[4])) {
2043
 
                    Eterm *sender = &ehp[4];
2044
 
                    ehp += 6;
2045
 
                    *sender = copy_struct(*sender,
2046
 
                                          size_object(*sender),
2047
 
                                          &ehp,
2048
 
                                          &MSO(psp));
2049
 
                }
2050
 
                else
2051
 
                    ehp += 6;
2052
 
 
2053
2228
            } 
2054
2229
            break;
2055
2230
        case matchEnableTrace:
2095
2270
            }
2096
2271
            break;
2097
2272
        case matchCaller:
2098
 
            if (!(c_p->cp) || !(hp = find_function_from_pc(c_p->cp))) {
 
2273
            if (!(c_p->cp) || !(cp = find_function_from_pc(c_p->cp))) {
2099
2274
                *esp++ = am_undefined;
2100
2275
            } else {
 
2276
                ehp = HAllocX(build_proc, 4, HEAP_XTRA);
2101
2277
                *esp++ = make_tuple(ehp);
2102
 
                ehp[0] = make_arityval(3);
2103
 
                ehp[1] = hp[0];
2104
 
                ehp[2] = hp[1];
2105
 
                ehp[3] = make_small(hp[2]);
2106
 
                ehp += 4;
2107
 
            }
2108
 
            break;
 
2278
                ehp[0] = make_arityval(3);
 
2279
                ehp[1] = cp[0];
 
2280
                ehp[2] = cp[1];
 
2281
                ehp[3] = make_small((Uint) cp[2]);
 
2282
            }
 
2283
            break;
2109
2284
        case matchSilent:
2110
2285
            --esp;
2111
2286
            if (*esp == am_true) {
2180
2355
                }
2181
2356
            }
2182
2357
            break;
2183
 
        case matchCatch:
 
2358
        case matchCatch:  /* Match success, now build result */
2184
2359
            do_catch = 1;
 
2360
            if (in_flags & ERTS_PAM_COPY_RESULT) {
 
2361
                build_proc = c_p;
 
2362
                esdp->current_process = c_p;
 
2363
            }
2185
2364
            break;
2186
2365
        case matchHalt:
2187
2366
            goto success;
2190
2369
        }
2191
2370
    }
2192
2371
fail:
 
2372
#if HALFWORD_HEAP
 
2373
    if (c_p_checkpoint.p) {
 
2374
        /* Dispose garbage built by guards on caller heap */
 
2375
        heap_checkpoint_revert(&c_p_checkpoint);
 
2376
        c_p_checkpoint.p = NULL;
 
2377
    }
 
2378
#endif
2193
2379
    *return_flags = 0U;
2194
 
    if (fail_label >= 0) { /* We failed during a "TryMeElse", 
2195
 
                              lets restart, with the next match 
 
2380
    if (fail_label >= 0) { /* We failed during a "TryMeElse",
 
2381
                              lets restart, with the next match
2196
2382
                              program */
2197
2383
        pc = (prog->text) + fail_label;
2198
2384
        cleanup_match_pseudo_process(mpsp, 1);
2206
2392
        erl_exit(1, "Heap fence overwritten in db_prog_match after op "
2207
2393
                 "0x%08x, overwritten with 0x%08x.", save_op, *heap_fence);
2208
2394
    }
2209
 
    if (*eheap_fence != FENCE_PATTERN) {
2210
 
        erl_exit(1, "Eheap fence overwritten in db_prog_match after op "
2211
 
                 "0x%08x, overwritten with 0x%08x.", save_op, 
2212
 
                 *eheap_fence);
2213
 
    }
2214
2395
    if (*stack_fence != FENCE_PATTERN) {
2215
2396
        erl_exit(1, "Stack fence overwritten in db_prog_match after op "
2216
2397
                 "0x%08x, overwritten with 0x%08x.", save_op, 
2221
2402
    esdp->current_process = current_scheduled;
2222
2403
 
2223
2404
    END_ATOMIC_TRACE(c_p);
 
2405
 
2224
2406
    return ret;
2225
2407
#undef FAIL
2226
2408
#undef FAIL_TERM
2232
2414
/*
2233
2415
 * Convert a match program to a "magic" binary to return up to erlang
2234
2416
 */
2235
 
Eterm db_make_mp_binary(Process *p, Binary *mp, Eterm **hpp) {
 
2417
Eterm db_make_mp_binary(Process *p, Binary *mp, Eterm **hpp)
 
2418
{
2236
2419
    return erts_mk_magic_binary_term(hpp, &MSO(p), mp);
2237
2420
}
2238
2421
 
2298
2481
** Store bignum in *hpp and increase *hpp accordingly.
2299
2482
** *hpp is assumed to be large enough to hold the result.
2300
2483
*/
2301
 
Eterm db_add_counter(Eterm** hpp, Eterm counter, Eterm incr)
 
2484
Eterm db_add_counter(Eterm** hpp, Wterm counter, Eterm incr)
2302
2485
{
2303
 
    Eterm big_tmp[2];
 
2486
    DeclareTmpHeapNoproc(big_tmp,2);
2304
2487
    Eterm res;
2305
2488
    Sint ires;
2306
 
    Eterm arg1;
2307
 
    Eterm arg2;
 
2489
    Wterm arg1;
 
2490
    Wterm arg2;
2308
2491
 
2309
2492
    if (is_both_small(counter,incr)) {
2310
2493
        ires = signed_val(counter) + signed_val(incr);
2318
2501
        }
2319
2502
    }
2320
2503
    else {
 
2504
        UseTmpHeapNoproc(2);
2321
2505
        switch(NUMBER_CODE(counter, incr)) {
2322
2506
        case SMALL_BIG:
2323
2507
            arg1 = small_to_big(signed_val(counter), big_tmp);
2332
2516
            arg2 = counter;
2333
2517
            break;
2334
2518
        default:
 
2519
            UnUseTmpHeapNoproc(2);
2335
2520
            return THE_NON_VALUE;
2336
2521
        }
2337
2522
        res = big_plus(arg1, arg2, *hpp);
2338
2523
        if (is_big(res)) {
2339
2524
            *hpp += BIG_NEED_SIZE(big_size(res));
2340
2525
        }
 
2526
        UnUseTmpHeapNoproc(2);
2341
2527
        return res;
2342
2528
    }
2343
2529
}
2344
2530
 
 
2531
/* Must be called to read elements after db_lookup_dbterm.
 
2532
** Will decompress if needed.
 
2533
** HEALFWORD_HEAP:
 
2534
**      Will convert from relative to Wterm format if needed.
 
2535
**      (but only on top level, tuples and lists will still contain rterms)
 
2536
*/
 
2537
Wterm db_do_read_element(DbUpdateHandle* handle, Sint position)
 
2538
{
 
2539
    Eterm elem = handle->dbterm->tpl[position];
 
2540
    if (!is_header(elem)) {
 
2541
#if HALFWORD_HEAP
 
2542
        if (!is_immed(elem)
 
2543
            && !handle->tb->common.compress
 
2544
            && !(handle->abs_vec && handle->abs_vec[position])) {
 
2545
            return rterm2wterm(elem, handle->dbterm->tpl);
 
2546
        }
 
2547
#endif
 
2548
        return elem;
 
2549
    }
 
2550
 
 
2551
    ASSERT(((DbTableCommon*)handle->tb)->compress);
 
2552
    ASSERT(!handle->mustResize);
 
2553
    handle->dbterm = db_alloc_tmp_uncompressed(&handle->tb->common,
 
2554
                                               handle->dbterm);
 
2555
    handle->mustResize = 1;
 
2556
    return handle->dbterm->tpl[position];
 
2557
}
 
2558
 
2345
2559
/*
2346
2560
** Update one element:
2347
2561
** handle:   Initialized by db_lookup_dbterm()
2358
2572
    Eterm* oldp;
2359
2573
    Uint newval_sz;
2360
2574
    Uint oldval_sz;
 
2575
#if HALFWORD_HEAP
 
2576
    Eterm* old_base;
 
2577
#endif
2361
2578
 
2362
2579
    if (is_both_immed(newval,oldval)) {
2363
2580
        handle->dbterm->tpl[position] = newval;
 
2581
    #ifdef DEBUG_CLONE
 
2582
        if (handle->dbterm->debug_clone) {
 
2583
            handle->dbterm->debug_clone[position] = newval;
 
2584
        }
 
2585
    #endif
2364
2586
        return;
2365
2587
    }
2366
 
    else if (!handle->mustResize && is_boxed(newval)) {
2367
 
        newp = boxed_val(newval);
2368
 
        switch (*newp & _TAG_HEADER_MASK) {
2369
 
        case _TAG_HEADER_POS_BIG:
2370
 
        case _TAG_HEADER_NEG_BIG:
2371
 
        case _TAG_HEADER_FLOAT:
2372
 
        case _TAG_HEADER_HEAP_BIN:          
2373
 
            newval_sz = header_arity(*newp) + 1;            
2374
 
            if (is_boxed(oldval)) {
2375
 
                oldp = boxed_val(oldval);
2376
 
                switch (*oldp & _TAG_HEADER_MASK) {
 
2588
    if (!handle->mustResize) {
 
2589
        if (handle->tb->common.compress) {
 
2590
            handle->dbterm = db_alloc_tmp_uncompressed(&handle->tb->common,
 
2591
                                                       handle->dbterm);
 
2592
            handle->mustResize = 1;
 
2593
            oldval = handle->dbterm->tpl[position];
 
2594
        #if HALFWORD_HEAP
 
2595
            old_base = NULL;
 
2596
        #endif
 
2597
        }
 
2598
        else {
 
2599
        #if HALFWORD_HEAP
 
2600
            ASSERT(!handle->abs_vec);
 
2601
            old_base = handle->dbterm->tpl;
 
2602
        #endif
 
2603
            if (is_boxed(newval)) {
 
2604
                newp = boxed_val(newval);
 
2605
                switch (*newp & _TAG_HEADER_MASK) {
2377
2606
                case _TAG_HEADER_POS_BIG:
2378
2607
                case _TAG_HEADER_NEG_BIG:
2379
2608
                case _TAG_HEADER_FLOAT:
2380
2609
                case _TAG_HEADER_HEAP_BIN:
2381
 
                    oldval_sz = header_arity(*oldp) + 1;
2382
 
                    if (oldval_sz == newval_sz) {
2383
 
                        /* "self contained" terms of same size, do memcpy */
2384
 
                        sys_memcpy(oldp, newp, newval_sz*sizeof(Eterm));                        
2385
 
                        return;
 
2610
                    newval_sz = header_arity(*newp) + 1;
 
2611
                    if (is_boxed(oldval)) {
 
2612
                        oldp = boxed_val_rel(oldval,old_base);
 
2613
                        switch (*oldp & _TAG_HEADER_MASK) {
 
2614
                        case _TAG_HEADER_POS_BIG:
 
2615
                        case _TAG_HEADER_NEG_BIG:
 
2616
                        case _TAG_HEADER_FLOAT:
 
2617
                        case _TAG_HEADER_HEAP_BIN:
 
2618
                            oldval_sz = header_arity(*oldp) + 1;
 
2619
                            if (oldval_sz == newval_sz) {
 
2620
                                /* "self contained" terms of same size, do memcpy */
 
2621
                                    sys_memcpy(oldp, newp, newval_sz*sizeof(Eterm));
 
2622
                                return;
 
2623
                            }
 
2624
                            goto both_size_set;
 
2625
                        }
2386
2626
                    }
2387
 
                    goto both_size_set;
 
2627
                    goto new_size_set;
2388
2628
                }
2389
2629
            }
2390
 
            goto new_size_set;
2391
2630
        }
2392
2631
    }
 
2632
#if HALFWORD_HEAP
 
2633
    else {
 
2634
        old_base = (handle->tb->common.compress
 
2635
                    || (handle->abs_vec && handle->abs_vec[position])) ?
 
2636
            NULL : handle->dbterm->tpl;
 
2637
    }
 
2638
#endif
2393
2639
    /* Not possible for simple memcpy or dbterm is already non-contiguous, */
2394
2640
    /* need to realloc... */
2395
2641
 
2396
2642
    newval_sz = is_immed(newval) ? 0 : size_object(newval);
2397
2643
new_size_set:
2398
 
        
2399
 
    oldval_sz = is_immed(oldval) ? 0 : size_object(oldval);
 
2644
 
 
2645
    oldval_sz = is_immed(oldval) ? 0 : size_object_rel(oldval,old_base);
2400
2646
both_size_set:
2401
2647
 
2402
2648
    handle->new_size = handle->new_size - oldval_sz + newval_sz;
2403
2649
 
2404
 
    /* write new value in old dbterm, finalize will make a flat copy */ 
 
2650
    /* write new value in old dbterm, finalize will make a flat copy */
2405
2651
    handle->dbterm->tpl[position] = newval;
2406
2652
    handle->mustResize = 1;
2407
 
}
2408
 
 
 
2653
 
 
2654
#if HALFWORD_HEAP
 
2655
    if (old_base && newval_sz > 0) {
 
2656
        ASSERT(!handle->tb->common.compress);
 
2657
        if (!handle->abs_vec) {
 
2658
            int i = header_arity(handle->dbterm->tpl[0]);
 
2659
            handle->abs_vec = erts_alloc(ERTS_ALC_T_TMP, (i+1)*sizeof(char));
 
2660
            sys_memset(handle->abs_vec, 0, i+1);
 
2661
            /* abs_vec[0] not used */
 
2662
        }
 
2663
        handle->abs_vec[position] = 1;
 
2664
    }
 
2665
#endif
 
2666
}
 
2667
 
 
2668
static ERTS_INLINE byte* db_realloc_term(DbTableCommon* tb, void* old,
 
2669
                                         Uint old_sz, Uint new_sz, Uint offset)
 
2670
{
 
2671
    byte* ret;
 
2672
    if (erts_ets_realloc_always_moves) {
 
2673
        ret = erts_db_alloc(ERTS_ALC_T_DB_TERM, (DbTable*)tb, new_sz);
 
2674
        sys_memcpy(ret, old, offset);
 
2675
        erts_db_free(ERTS_ALC_T_DB_TERM, (DbTable*)tb, old, old_sz);
 
2676
    } else {
 
2677
        ret = erts_db_realloc(ERTS_ALC_T_DB_TERM, (DbTable*)tb,
 
2678
                              old, old_sz, new_sz);
 
2679
    }
 
2680
    return ret;
 
2681
}
 
2682
 
 
2683
/* Allocated size of a compressed dbterm
 
2684
*/
 
2685
static ERTS_INLINE Uint db_alloced_size_comp(DbTerm* obj)
 
2686
{
 
2687
    return obj->tpl[arityval(*obj->tpl) + 1];
 
2688
}
 
2689
 
 
2690
void db_free_term(DbTable *tb, void* basep, Uint offset)
 
2691
{
 
2692
    DbTerm* db = (DbTerm*) ((byte*)basep + offset);
 
2693
    Uint size;
 
2694
    if (tb->common.compress) {
 
2695
        db_cleanup_offheap_comp(db);
 
2696
        size = db_alloced_size_comp(db);
 
2697
    }
 
2698
    else {
 
2699
        ErlOffHeap tmp_oh;
 
2700
        tmp_oh.first = db->first_oh;
 
2701
        erts_cleanup_offheap(&tmp_oh);
 
2702
        size = offset + offsetof(DbTerm,tpl) + db->size*sizeof(Eterm);
 
2703
    }
 
2704
    erts_db_free(ERTS_ALC_T_DB_TERM, tb, basep, size);
 
2705
}
 
2706
 
 
2707
static ERTS_INLINE Uint align_up(Uint value, Uint pow2)
 
2708
{
 
2709
    ASSERT((pow2 & (pow2-1)) == 0);
 
2710
    return (value + (pow2-1)) & ~(pow2-1);
 
2711
}
 
2712
 
 
2713
/* Compressed size of an uncompressed term
 
2714
*/
 
2715
static Uint db_size_dbterm_comp(DbTableCommon* tb, Eterm obj)
 
2716
{
 
2717
    Eterm* tpl = tuple_val(obj);
 
2718
    int i;
 
2719
    Uint size = sizeof(DbTerm)
 
2720
        + arityval(*tpl) * sizeof(Eterm)
 
2721
        + sizeof(Uint); /* "alloc_size" */
 
2722
 
 
2723
    for (i = arityval(*tpl); i>0; i--) {
 
2724
        if (i != tb->keypos && is_not_immed(tpl[i])) {
 
2725
            size += erts_encode_ext_size_ets(tpl[i]);
 
2726
        }
 
2727
    }
 
2728
    size += size_object(tpl[tb->keypos]) * sizeof(Eterm);
 
2729
    return align_up(size, sizeof(Uint));
 
2730
}
 
2731
 
 
2732
/* Conversion between top tuple element and pointer to compressed data
 
2733
*/
 
2734
static ERTS_INLINE Eterm ext2elem(Eterm* tpl, byte* ext)
 
2735
{
 
2736
    return (((Uint)(ext - (byte*)tpl)) << _TAG_PRIMARY_SIZE) | TAG_PRIMARY_HEADER;
 
2737
}
 
2738
static ERTS_INLINE byte* elem2ext(Eterm* tpl, Uint ix)
 
2739
{
 
2740
    ASSERT(is_header(tpl[ix]));
 
2741
    return (byte*)tpl + (tpl[ix] >> _TAG_PRIMARY_SIZE);
 
2742
}
 
2743
 
 
2744
static void* copy_to_comp(DbTableCommon* tb, Eterm obj, DbTerm* dest,
 
2745
                          Uint alloc_size)
 
2746
{
 
2747
    ErlOffHeap tmp_offheap;
 
2748
    Eterm* src = tuple_val(obj);
 
2749
    Eterm* tpl = dest->tpl;
 
2750
    Eterm key = src[tb->keypos];
 
2751
    int arity = arityval(src[0]);
 
2752
    union {
 
2753
        Eterm* ep;
 
2754
        byte* cp;
 
2755
        UWord ui;
 
2756
    }top;
 
2757
    int i;
 
2758
 
 
2759
    top.ep = tpl+ 1 + arity + 1;
 
2760
    tpl[0] = src[0];
 
2761
    tpl[arity + 1] = alloc_size;
 
2762
 
 
2763
    tmp_offheap.first = NULL;
 
2764
    tpl[tb->keypos] = copy_struct_rel(key, size_object(key), &top.ep, &tmp_offheap, NULL, tpl);
 
2765
    dest->first_oh = tmp_offheap.first;
 
2766
    for (i=1; i<=arity; i++) {
 
2767
        if (i != tb->keypos) {
 
2768
            if (is_immed(src[i])) {
 
2769
                tpl[i] = src[i];
 
2770
            }
 
2771
            else {
 
2772
                tpl[i] = ext2elem(tpl, top.cp);
 
2773
                top.cp = erts_encode_ext_ets(src[i], top.cp, &dest->first_oh);
 
2774
            }
 
2775
        }
 
2776
    }
 
2777
 
 
2778
#ifdef DEBUG_CLONE
 
2779
    {
 
2780
        Eterm* dbg_top = erts_alloc(ERTS_ALC_T_DB_TERM, dest->size * sizeof(Eterm));
 
2781
        dest->debug_clone = dbg_top;
 
2782
        tmp_offheap.first = dest->first_oh;
 
2783
        copy_struct_rel(obj, dest->size, &dbg_top, &tmp_offheap, NULL, dbg_top);
 
2784
        dest->first_oh = tmp_offheap.first;
 
2785
        ASSERT(dbg_top == dest->debug_clone + dest->size);
 
2786
    }
 
2787
#endif
 
2788
    return top.cp;
 
2789
}
2409
2790
 
2410
2791
/*
2411
2792
** Copy the object into a possibly new DbTerm, 
2412
2793
** offset is the offset of the DbTerm from the start
2413
 
** of the sysAllocaed structure, The possibly realloced and copied
 
2794
** of the allocated structure, The possibly realloced and copied
2414
2795
** structure is returned. Make sure (((char *) old) - offset) is a 
2415
2796
** pointer to a ERTS_ALC_T_DB_TERM allocated data area.
2416
2797
*/
2417
 
void* db_get_term(DbTableCommon *tb, DbTerm* old, Uint offset, Eterm obj)
 
2798
void* db_store_term(DbTableCommon *tb, DbTerm* old, Uint offset, Eterm obj)
2418
2799
{
 
2800
    byte* basep;
 
2801
    DbTerm* newp;
 
2802
    Eterm* top;
2419
2803
    int size = size_object(obj);
2420
 
    void *structp = ((char*) old) - offset;
2421
 
    DbTerm* p;
2422
 
    Eterm copy;
2423
 
    Eterm *top;
 
2804
    ErlOffHeap tmp_offheap;
2424
2805
 
2425
2806
    if (old != 0) {
2426
 
        erts_cleanup_offheap(&old->off_heap);
 
2807
        basep = ((byte*) old) - offset;
 
2808
        tmp_offheap.first  = old->first_oh;
 
2809
        erts_cleanup_offheap(&tmp_offheap);
 
2810
        old->first_oh = tmp_offheap.first;
2427
2811
        if (size == old->size) {
2428
 
            p = old;
2429
 
        } else {
 
2812
            newp = old;
 
2813
        }
 
2814
        else {
2430
2815
            Uint new_sz = offset + sizeof(DbTerm) + sizeof(Eterm)*(size-1);
2431
2816
            Uint old_sz = offset + sizeof(DbTerm) + sizeof(Eterm)*(old->size-1);
2432
2817
 
2433
 
            if (erts_ets_realloc_always_moves) {
2434
 
                void *nstructp = erts_db_alloc(ERTS_ALC_T_DB_TERM,
2435
 
                                               (DbTable *) tb,
2436
 
                                               new_sz);
2437
 
                memcpy(nstructp,structp,offset);
2438
 
                erts_db_free(ERTS_ALC_T_DB_TERM,
2439
 
                             (DbTable *) tb,
2440
 
                             structp,
2441
 
                             old_sz);
2442
 
                structp = nstructp;
2443
 
            } else {
2444
 
                structp = erts_db_realloc(ERTS_ALC_T_DB_TERM,
2445
 
                                          (DbTable *) tb,
2446
 
                                          structp,
2447
 
                                          old_sz,
2448
 
                                          new_sz);
2449
 
            }
2450
 
            p = (DbTerm*) ((void *)(((char *) structp) + offset));
2451
 
        }
2452
 
    }
2453
 
    else {
2454
 
        structp = erts_db_alloc(ERTS_ALC_T_DB_TERM,
2455
 
                                (DbTable *) tb,
2456
 
                                (offset
2457
 
                                 + sizeof(DbTerm)
2458
 
                                 + sizeof(Eterm)*(size-1)));
2459
 
        p = (DbTerm*) ((void *)(((char *) structp) + offset));
2460
 
    }
2461
 
    p->size = size;
2462
 
    p->off_heap.mso = NULL;
2463
 
    p->off_heap.externals = NULL;
2464
 
#ifndef HYBRID /* FIND ME! */
2465
 
    p->off_heap.funs = NULL;
2466
 
#endif
2467
 
    p->off_heap.overhead = 0;
2468
 
 
2469
 
    top = DBTERM_BUF(p);
2470
 
    copy = copy_struct(obj, size, &top, &p->off_heap);
2471
 
    DBTERM_SET_TPL(p,tuple_val(copy));
2472
 
 
2473
 
    return structp;
2474
 
}
2475
 
 
2476
 
 
2477
 
void db_free_term_data(DbTerm* p)
2478
 
{
2479
 
    erts_cleanup_offheap(&p->off_heap);
2480
 
}
2481
 
 
 
2818
            basep = db_realloc_term(tb, basep, old_sz, new_sz, offset);
 
2819
            newp = (DbTerm*) (basep + offset);
 
2820
        }
 
2821
    }
 
2822
    else {
 
2823
        basep = erts_db_alloc(ERTS_ALC_T_DB_TERM, (DbTable *)tb,
 
2824
                              (offset + sizeof(DbTerm) + sizeof(Eterm)*(size-1)));
 
2825
        newp = (DbTerm*) (basep + offset);
 
2826
    }
 
2827
    newp->size = size;
 
2828
    top = newp->tpl;
 
2829
    tmp_offheap.first  = NULL;
 
2830
    copy_struct_rel(obj, size, &top, &tmp_offheap, NULL, top);
 
2831
    newp->first_oh = tmp_offheap.first;
 
2832
#ifdef DEBUG_CLONE
 
2833
    newp->debug_clone = NULL;
 
2834
#endif
 
2835
    return basep;
 
2836
}
 
2837
 
 
2838
 
 
2839
void* db_store_term_comp(DbTableCommon *tb, DbTerm* old, Uint offset, Eterm obj)
 
2840
{
 
2841
    Uint new_sz = offset + db_size_dbterm_comp(tb, obj);
 
2842
    byte* basep;
 
2843
    DbTerm* newp;
 
2844
    byte* top;
 
2845
 
 
2846
    ASSERT(tb->compress);
 
2847
    if (old != 0) {
 
2848
        Uint old_sz = db_alloced_size_comp(old);
 
2849
        db_cleanup_offheap_comp(old);
 
2850
 
 
2851
        basep = ((byte*) old) - offset;
 
2852
        if (new_sz == old_sz) {
 
2853
            newp = old;
 
2854
        }
 
2855
        else {
 
2856
            basep = db_realloc_term(tb, basep, old_sz, new_sz, offset);
 
2857
            newp = (DbTerm*) (basep + offset);
 
2858
        }
 
2859
    }
 
2860
    else {
 
2861
        basep = erts_db_alloc(ERTS_ALC_T_DB_TERM, (DbTable*)tb, new_sz);
 
2862
        newp = (DbTerm*) (basep + offset);
 
2863
    }
 
2864
 
 
2865
    newp->size = size_object(obj);
 
2866
    top = copy_to_comp(tb, obj, newp, new_sz);
 
2867
    ASSERT(top <= basep + new_sz);
 
2868
 
 
2869
    /* ToDo: Maybe realloc if ((basep+new_sz) - top) > WASTED_SPACE_LIMIT */
 
2870
 
 
2871
    return basep;
 
2872
}
 
2873
 
 
2874
 
 
2875
void db_finalize_resize(DbUpdateHandle* handle, Uint offset)
 
2876
{
 
2877
    DbTable* tbl = handle->tb;
 
2878
    DbTerm* newDbTerm;
 
2879
    Uint alloc_sz = offset +
 
2880
        (tbl->common.compress ?
 
2881
         db_size_dbterm_comp(&tbl->common, make_tuple(handle->dbterm->tpl)) :
 
2882
         sizeof(DbTerm)+sizeof(Eterm)*(handle->new_size-1));
 
2883
    byte* newp = erts_db_alloc(ERTS_ALC_T_DB_TERM, tbl, alloc_sz);
 
2884
    byte* oldp = *(handle->bp);
 
2885
 
 
2886
    sys_memcpy(newp, oldp, offset);  /* copy only hash/tree header */
 
2887
    *(handle->bp) = newp;
 
2888
    newDbTerm = (DbTerm*) (newp + offset);
 
2889
    newDbTerm->size = handle->new_size;
 
2890
#ifdef DEBUG_CLONE
 
2891
    newDbTerm->debug_clone = NULL;
 
2892
#endif
 
2893
 
 
2894
    /* make a flat copy */
 
2895
 
 
2896
    if (tbl->common.compress) {
 
2897
        copy_to_comp(&tbl->common, make_tuple(handle->dbterm->tpl),
 
2898
                     newDbTerm, alloc_sz);
 
2899
        db_free_tmp_uncompressed(handle->dbterm);
 
2900
    }
 
2901
    else {
 
2902
        ErlOffHeap tmp_offheap;
 
2903
        Eterm* tpl = handle->dbterm->tpl;
 
2904
        Eterm* top = newDbTerm->tpl;
 
2905
 
 
2906
        tmp_offheap.first = NULL;
 
2907
 
 
2908
    #if HALFWORD_HEAP
 
2909
        if (handle->abs_vec) {
 
2910
            int i, arity = header_arity(handle->dbterm->tpl[0]);
 
2911
 
 
2912
            top[0] = tpl[0];
 
2913
            top += arity + 1;
 
2914
            for (i=1; i<=arity; i++) {
 
2915
                Eterm* src_base = handle->abs_vec[i] ? NULL : tpl;
 
2916
 
 
2917
                newDbTerm->tpl[i] = copy_struct_rel(tpl[i],
 
2918
                                                    size_object_rel(tpl[i],src_base),
 
2919
                                                    &top, &tmp_offheap, src_base,
 
2920
                                                    newDbTerm->tpl);
 
2921
            }
 
2922
            newDbTerm->first_oh = tmp_offheap.first;
 
2923
            ASSERT((byte*)top <= (newp + alloc_sz));
 
2924
            erts_free(ERTS_ALC_T_TMP, handle->abs_vec);
 
2925
        }
 
2926
        else
 
2927
    #endif /* HALFWORD_HEAP */
 
2928
        {
 
2929
            copy_struct_rel(make_tuple_rel(tpl,tpl), handle->new_size, &top,
 
2930
                            &tmp_offheap, tpl, top);
 
2931
            newDbTerm->first_oh = tmp_offheap.first;
 
2932
            ASSERT((byte*)top == (newp + alloc_sz));
 
2933
        }
 
2934
    }
 
2935
}
 
2936
 
 
2937
Eterm db_copy_from_comp(DbTableCommon* tb, DbTerm* bp, Eterm** hpp,
 
2938
                             ErlOffHeap* off_heap)
 
2939
{
 
2940
    Eterm* hp = *hpp;
 
2941
    int i, arity = arityval(bp->tpl[0]);
 
2942
 
 
2943
    hp[0] = bp->tpl[0];
 
2944
    *hpp += arity + 1;
 
2945
 
 
2946
    hp[tb->keypos] = copy_struct_rel(bp->tpl[tb->keypos],
 
2947
                                     size_object_rel(bp->tpl[tb->keypos], bp->tpl),
 
2948
                                     hpp, off_heap, bp->tpl, NULL);
 
2949
    for (i=arity; i>0; i--) {
 
2950
        if (i != tb->keypos) {
 
2951
            if (is_immed(bp->tpl[i])) {
 
2952
                hp[i] = bp->tpl[i];
 
2953
            }
 
2954
            else {
 
2955
                hp[i] = erts_decode_ext_ets(hpp, off_heap,
 
2956
                                            elem2ext(bp->tpl, i));
 
2957
            }
 
2958
        }
 
2959
    }
 
2960
    ASSERT((*hpp - hp) <= bp->size);
 
2961
#ifdef DEBUG_CLONE
 
2962
    ASSERT(eq_rel(make_tuple(hp),make_tuple(bp->debug_clone),bp->debug_clone));
 
2963
#endif
 
2964
    return make_tuple(hp);
 
2965
}
 
2966
 
 
2967
Eterm db_copy_element_from_ets(DbTableCommon* tb, Process* p,
 
2968
                               DbTerm* obj, Uint pos,
 
2969
                               Eterm** hpp, Uint extra)
 
2970
{
 
2971
    if (is_immed(obj->tpl[pos])) {
 
2972
        *hpp = HAlloc(p, extra);
 
2973
        return obj->tpl[pos];
 
2974
    }
 
2975
    if (tb->compress && pos != tb->keypos) {
 
2976
        byte* ext = elem2ext(obj->tpl, pos);
 
2977
        Sint sz = erts_decode_ext_size_ets(ext, db_alloced_size_comp(obj)) + extra;
 
2978
        Eterm* hp = HAlloc(p, sz);
 
2979
        Eterm* endp = hp + sz;
 
2980
        Eterm copy = erts_decode_ext_ets(&hp, &MSO(p), ext);
 
2981
        *hpp = hp;
 
2982
        hp += extra;
 
2983
        HRelease(p, endp, hp);
 
2984
#ifdef DEBUG_CLONE
 
2985
        ASSERT(eq_rel(copy, obj->debug_clone[pos], obj->debug_clone));
 
2986
#endif
 
2987
        return copy;
 
2988
    }
 
2989
    else {
 
2990
        Uint sz = size_object_rel(obj->tpl[pos], obj->tpl);
 
2991
        *hpp = HAlloc(p, sz + extra);
 
2992
        return copy_struct_rel(obj->tpl[pos], sz, hpp, &MSO(p), obj->tpl, NULL);
 
2993
    }
 
2994
}
 
2995
 
 
2996
 
 
2997
/* Our own "cleanup_offheap"
 
2998
 * as refc-binaries may be unaligned in compressed terms
 
2999
*/
 
3000
void db_cleanup_offheap_comp(DbTerm* obj)
 
3001
{
 
3002
    union erl_off_heap_ptr u;
 
3003
    ProcBin tmp;
 
3004
 
 
3005
    for (u.hdr = obj->first_oh; u.hdr; u.hdr = u.hdr->next) {
 
3006
        if ((UWord)u.voidp % sizeof(Uint) != 0) { /* unaligned ptr */
 
3007
            sys_memcpy(&tmp, u.voidp, sizeof(tmp));
 
3008
            /* Warning, must pass (void*)-variable to memcpy. Otherwise it will
 
3009
               cause Bus error on Sparc due to false compile time assumptions
 
3010
               about word aligned memory (type cast is not enough) */
 
3011
            u.pb = &tmp;
 
3012
        }
 
3013
        switch (thing_subtag(u.hdr->thing_word)) {
 
3014
        case REFC_BINARY_SUBTAG:
 
3015
            if (erts_refc_dectest(&u.pb->val->refc, 0) == 0) {
 
3016
                erts_bin_free(u.pb->val);
 
3017
            }
 
3018
            break;
 
3019
        case FUN_SUBTAG:
 
3020
            ASSERT(u.pb != &tmp);
 
3021
            if (erts_refc_dectest(&u.fun->fe->refc, 0) == 0) {
 
3022
                erts_erase_fun_entry(u.fun->fe);
 
3023
            }
 
3024
            break;
 
3025
        default:
 
3026
            ASSERT(is_external_header(u.hdr->thing_word));
 
3027
            ASSERT(u.pb != &tmp);
 
3028
            erts_deref_node_entry(u.ext->node);
 
3029
            break;
 
3030
        }
 
3031
    }
 
3032
#ifdef DEBUG_CLONE
 
3033
    if (obj->debug_clone != NULL) {
 
3034
        erts_free(ERTS_ALC_T_DB_TERM, obj->debug_clone);
 
3035
        obj->debug_clone = NULL;
 
3036
    }
 
3037
#endif
 
3038
}
 
3039
 
 
3040
int db_eq_comp(DbTableCommon* tb, Eterm a, DbTerm* b)
 
3041
{
 
3042
    ErlOffHeap tmp_offheap;
 
3043
    Eterm* allocp;
 
3044
    Eterm* hp;
 
3045
    Eterm tmp_b;
 
3046
    int is_eq;
 
3047
 
 
3048
    ASSERT(tb->compress);
 
3049
    hp = allocp = erts_alloc(ERTS_ALC_T_TMP, b->size*sizeof(Eterm));
 
3050
    tmp_offheap.first = NULL;
 
3051
    tmp_b = db_copy_from_comp(tb, b, &hp, &tmp_offheap);
 
3052
    is_eq = eq(a,tmp_b);
 
3053
    erts_cleanup_offheap(&tmp_offheap);
 
3054
    erts_free(ERTS_ALC_T_TMP, allocp);
 
3055
    return is_eq;
 
3056
}
2482
3057
 
2483
3058
/*
2484
3059
** Check if object represents a "match" variable 
2606
3181
static DMCRet dmc_one_term(DMCContext *context, 
2607
3182
                           DMCHeap *heap,
2608
3183
                           DMC_STACK_TYPE(Eterm) *stack,
2609
 
                           DMC_STACK_TYPE(Uint) *text,
 
3184
                           DMC_STACK_TYPE(UWord) *text,
2610
3185
                           Eterm c)
2611
3186
{
2612
3187
    Sint n;
2624
3199
                ** Ouch, big integer in match variable.
2625
3200
                */
2626
3201
                Eterm *save_hp;
2627
 
                ASSERT(heap->data == heap->def);
 
3202
                ASSERT(heap->vars == heap->vars_def);
2628
3203
                sz = sz2 = sz3 = 0;
2629
3204
                for (j = 0; j < context->num_match; ++j) {
2630
3205
                    sz += size_object(context->matchexpr[j]);
2662
3237
                       may be atoms that changed */
2663
3238
                    context->matchexpr[j] = context->copy->mem[j];
2664
3239
                }
2665
 
                heap->data = erts_alloc(ERTS_ALC_T_DB_MS_CMPL_HEAP,
2666
 
                                        heap->size*sizeof(unsigned));
2667
 
                sys_memset(heap->data, 0, 
2668
 
                           heap->size * sizeof(unsigned));
 
3240
                heap->vars = erts_alloc(ERTS_ALC_T_DB_MS_CMPL_HEAP,
 
3241
                                        heap->size*sizeof(DMCVariable));
 
3242
                sys_memset(heap->vars, 0, heap->size * sizeof(DMCVariable));
2669
3243
                DMC_CLEAR(*stack);
2670
3244
                /*DMC_PUSH(*stack,NIL);*/
2671
3245
                DMC_CLEAR(*text);
2672
3246
                return retRestart;
2673
3247
            }
2674
 
            if (heap->data[n]) { /* already bound ? */
 
3248
            if (heap->vars[n].is_bound) {
2675
3249
                DMC_PUSH(*text,matchCmp);
2676
3250
                DMC_PUSH(*text,n);
2677
3251
            } else { /* Not bound, bind! */
2678
 
                if (n >= heap->used)
2679
 
                    heap->used = n + 1;
 
3252
                if (n >= heap->vars_used)
 
3253
                    heap->vars_used = n + 1;
2680
3254
                DMC_PUSH(*text,matchBind);
2681
3255
                DMC_PUSH(*text,n);
2682
 
                heap->data[n] = 1;
 
3256
                heap->vars[n].is_bound = 1;
2683
3257
            }
2684
3258
        } else if (c == am_Underscore) {
2685
3259
            DMC_PUSH(*text, matchSkip);
2704
3278
            DMC_PUSH(*stack, c);
2705
3279
            break;
2706
3280
        case (_TAG_HEADER_REF >> _TAG_PRIMARY_SIZE):
2707
 
            n = thing_arityval(*internal_ref_val(c));
 
3281
        {
 
3282
            Eterm* ref_val = internal_ref_val(c);
2708
3283
            DMC_PUSH(*text, matchEqRef);
2709
 
            DMC_PUSH(*text, *internal_ref_val(c));
2710
 
            for (i = 1; i <= n; ++i) {
2711
 
                DMC_PUSH(*text, (Uint) internal_ref_val(c)[i]);
2712
 
            }
 
3284
#if HALFWORD_HEAP
 
3285
            {
 
3286
                union {
 
3287
                    UWord u;
 
3288
                    Uint t[2];
 
3289
                } fiddle;
 
3290
                ASSERT(thing_arityval(ref_val[0]) == 3);
 
3291
                fiddle.t[0] = ref_val[0];
 
3292
                fiddle.t[1] = ref_val[1];
 
3293
                DMC_PUSH(*text, fiddle.u);
 
3294
                fiddle.t[0] = ref_val[2];
 
3295
                fiddle.t[1] = ref_val[3];
 
3296
                DMC_PUSH(*text, fiddle.u);
 
3297
            }
 
3298
#else
 
3299
            n = thing_arityval(ref_val[0]);
 
3300
            for (i = 0; i <= n; ++i) {
 
3301
                DMC_PUSH(*text, ref_val[i]);
 
3302
            }
 
3303
#endif
2713
3304
            break;
 
3305
        }
2714
3306
        case (_TAG_HEADER_POS_BIG >> _TAG_PRIMARY_SIZE):
2715
3307
        case (_TAG_HEADER_NEG_BIG >> _TAG_PRIMARY_SIZE):
2716
 
            n = thing_arityval(*big_val(c));
 
3308
        {
 
3309
            Eterm* bval = big_val(c);
 
3310
            n = thing_arityval(bval[0]);
2717
3311
            DMC_PUSH(*text, matchEqBig);
2718
 
            DMC_PUSH(*text, *big_val(c));
2719
 
            for (i = 1; i <= n; ++i) {
2720
 
                DMC_PUSH(*text, (Uint) big_val(c)[i]);
2721
 
            }
 
3312
#if HALFWORD_HEAP
 
3313
            {
 
3314
                union {
 
3315
                    UWord u;
 
3316
                    Uint t[2];
 
3317
                } fiddle;
 
3318
                ASSERT(n >= 1);
 
3319
                fiddle.t[0] = bval[0];
 
3320
                fiddle.t[1] = bval[1];
 
3321
                DMC_PUSH(*text, fiddle.u);
 
3322
                for (i = 2; i <= n; ++i) {
 
3323
                    fiddle.t[0] = bval[i];
 
3324
                    if (++i <= n) {
 
3325
                        fiddle.t[1] = bval[i];
 
3326
                    } else {
 
3327
                        fiddle.t[1] = (Uint) 0;
 
3328
                    }
 
3329
                    DMC_PUSH(*text, fiddle.u);
 
3330
                }
 
3331
            }
 
3332
#else
 
3333
            for (i = 0; i <= n; ++i) {
 
3334
                DMC_PUSH(*text, (Uint) bval[i]);
 
3335
            }
 
3336
#endif
2722
3337
            break;
 
3338
        }
2723
3339
        case (_TAG_HEADER_FLOAT >> _TAG_PRIMARY_SIZE):
2724
3340
            DMC_PUSH(*text,matchEqFloat);
 
3341
#if HALFWORD_HEAP
 
3342
            {
 
3343
                union {
 
3344
                    UWord u;
 
3345
                    Uint t[2];
 
3346
                } fiddle;
 
3347
                fiddle.t[0] = float_val(c)[1];
 
3348
                fiddle.t[1] = float_val(c)[2];
 
3349
                DMC_PUSH(*text, fiddle.u);
 
3350
            }
 
3351
#else
2725
3352
            DMC_PUSH(*text, (Uint) float_val(c)[1]);
2726
 
            /* XXX: this reads and pushes random junk on ARCH_64 */
 
3353
#ifdef ARCH_64
 
3354
            DMC_PUSH(*text, (Uint) 0);
 
3355
#else
2727
3356
            DMC_PUSH(*text, (Uint) float_val(c)[2]);
 
3357
#endif
 
3358
#endif
2728
3359
            break;
2729
3360
        default: /* BINARY, FUN, VECTOR, or EXTERNAL */
2730
3361
            /*
2753
3384
** Match guard compilation
2754
3385
*/
2755
3386
 
2756
 
static void do_emit_constant(DMCContext *context, DMC_STACK_TYPE(Uint) *text,
 
3387
static void do_emit_constant(DMCContext *context, DMC_STACK_TYPE(UWord) *text,
2757
3388
                             Eterm t) 
2758
3389
{
2759
3390
        int sz;
2807
3438
 
2808
3439
static DMCRet dmc_list(DMCContext *context,
2809
3440
                       DMCHeap *heap,
2810
 
                       DMC_STACK_TYPE(Uint) *text,
 
3441
                       DMC_STACK_TYPE(UWord) *text,
2811
3442
                       Eterm t,
2812
3443
                       int *constant)
2813
3444
{
2837
3468
        DMC_PUSH(*text, matchConsB);
2838
3469
    }
2839
3470
    --context->stack_used; /* Two objects on stack becomes one */
2840
 
    context->eheap_need += 2;
2841
3471
    return retOk;
2842
3472
}
2843
3473
 
2844
3474
static DMCRet dmc_tuple(DMCContext *context,
2845
3475
                       DMCHeap *heap,
2846
 
                       DMC_STACK_TYPE(Uint) *text,
 
3476
                       DMC_STACK_TYPE(UWord) *text,
2847
3477
                       Eterm t,
2848
3478
                       int *constant)
2849
3479
{
2850
 
    DMC_STACK_TYPE(Uint) instr_save;
 
3480
    DMC_STACK_TYPE(UWord) instr_save;
2851
3481
    int all_constant = 1;
2852
3482
    int textpos = DMC_STACK_NUM(*text);
2853
3483
    Eterm *p = tuple_val(t);
2896
3526
    DMC_PUSH(*text, matchMkTuple);
2897
3527
    DMC_PUSH(*text, nelems);
2898
3528
    context->stack_used -= (nelems - 1);
2899
 
    context->eheap_need += (nelems + 1);
2900
3529
    *constant = 0;
2901
3530
    return retOk;
2902
3531
}
2903
3532
 
2904
3533
static DMCRet dmc_whole_expression(DMCContext *context,
2905
3534
                                   DMCHeap *heap,
2906
 
                                   DMC_STACK_TYPE(Uint) *text,
 
3535
                                   DMC_STACK_TYPE(UWord) *text,
2907
3536
                                   Eterm t,
2908
3537
                                   int *constant)
2909
3538
{
2914
3543
        } else { 
2915
3544
            ASSERT(is_tuple(context->matchexpr
2916
3545
                            [context->current_match]));
2917
 
            context->eheap_need += 
2918
 
                arityval(*(tuple_val(context->matchexpr
2919
 
                                     [context->current_match]))) * 2;
2920
3546
            DMC_PUSH(*text, matchPushArrayAsList);
2921
3547
        }
2922
3548
    } else {
2929
3555
    return retOk;
2930
3556
}
2931
3557
 
 
3558
/* Figure out which PushV instruction to use.
 
3559
*/
 
3560
static void dmc_add_pushv_variant(DMCContext *context, DMCHeap *heap,
 
3561
                                  DMC_STACK_TYPE(UWord) *text, Uint n)
 
3562
{
 
3563
    DMCVariable* v = &heap->vars[n];
 
3564
    MatchOps instr = matchPushV;
 
3565
 
 
3566
    ASSERT(n < heap->vars_used && v->is_bound);
 
3567
    if (context->is_guard) {
 
3568
        #if HALFWORD_HEAP
 
3569
        if (!v->first_guard_label) {
 
3570
            v->first_guard_label = DMC_STACK_NUM(*text);
 
3571
            ASSERT(v->first_guard_label);
 
3572
            instr = matchPushVGuard; /* may be changed to PushVResult below */
 
3573
        }
 
3574
        #endif
 
3575
    }
 
3576
    else { /* body */
 
3577
        #if HALFWORD_HEAP
 
3578
        if (v->first_guard_label) {
 
3579
            /* Avoid double-copy, copy to result heap at first encounter in guard */
 
3580
            DMC_POKE(*text, v->first_guard_label, matchPushVResult);
 
3581
            v->is_in_body = 1;
 
3582
        }
 
3583
        #endif
 
3584
        if (!v->is_in_body) {
 
3585
            instr = matchPushVResult;
 
3586
            v->is_in_body = 1;
 
3587
        }
 
3588
    }
 
3589
    DMC_PUSH(*text, instr);
 
3590
    DMC_PUSH(*text, n);
 
3591
}
 
3592
 
2932
3593
static DMCRet dmc_variable(DMCContext *context,
2933
3594
                           DMCHeap *heap,
2934
 
                           DMC_STACK_TYPE(Uint) *text,
 
3595
                           DMC_STACK_TYPE(UWord) *text,
2935
3596
                           Eterm t,
2936
3597
                           int *constant)
2937
3598
{
2938
3599
    Uint n = db_is_variable(t);
2939
 
    ASSERT(n >= 0);
2940
 
    if (n >= heap->used) 
2941
 
        RETURN_VAR_ERROR("Variable $%d is unbound.", n, context, *constant);
2942
 
    if (heap->data[n] == 0U)
2943
 
        RETURN_VAR_ERROR("Variable $%d is unbound.", n, context, *constant);
2944
 
    DMC_PUSH(*text, matchPushV);
2945
 
    DMC_PUSH(*text, n);
 
3600
 
 
3601
    if (n >= heap->vars_used || !heap->vars[n].is_bound) {
 
3602
        RETURN_VAR_ERROR("Variable $%d is unbound.", n, context, *constant);
 
3603
    }
 
3604
 
 
3605
    dmc_add_pushv_variant(context, heap, text, n);
 
3606
 
2946
3607
    ++context->stack_used;
2947
3608
    if (context->stack_used > context->stack_need)
2948
3609
        context->stack_need = context->stack_used;
2952
3613
 
2953
3614
static DMCRet dmc_all_bindings(DMCContext *context,
2954
3615
                               DMCHeap *heap,
2955
 
                               DMC_STACK_TYPE(Uint) *text,
 
3616
                               DMC_STACK_TYPE(UWord) *text,
2956
3617
                               Eterm t,
2957
3618
                               int *constant)
2958
3619
{
2961
3622
 
2962
3623
    DMC_PUSH(*text, matchPushC);
2963
3624
    DMC_PUSH(*text, NIL);
2964
 
    for (i = heap->used - 1; i >= 0; --i) { 
2965
 
        if (heap->data[i]) {
2966
 
            DMC_PUSH(*text, matchPushV);
2967
 
            DMC_PUSH(*text, i);
 
3625
    for (i = heap->vars_used - 1; i >= 0; --i) {
 
3626
        if (heap->vars[i].is_bound) {
 
3627
            dmc_add_pushv_variant(context, heap, text, i);
2968
3628
            DMC_PUSH(*text, matchConsB);
2969
3629
            heap_used += 2;
2970
3630
        }
2972
3632
    ++context->stack_used;
2973
3633
    if ((context->stack_used + 1) > context->stack_need)
2974
3634
        context->stack_need = (context->stack_used + 1);
2975
 
    context->eheap_need += heap_used;
2976
3635
    *constant = 0;
2977
3636
    return retOk;
2978
3637
}
2979
3638
 
2980
3639
static DMCRet dmc_const(DMCContext *context,
2981
3640
                       DMCHeap *heap,
2982
 
                       DMC_STACK_TYPE(Uint) *text,
 
3641
                       DMC_STACK_TYPE(UWord) *text,
2983
3642
                       Eterm t,
2984
3643
                       int *constant)
2985
3644
{
2996
3655
 
2997
3656
static DMCRet dmc_and(DMCContext *context,
2998
3657
                      DMCHeap *heap,
2999
 
                      DMC_STACK_TYPE(Uint) *text,
 
3658
                      DMC_STACK_TYPE(UWord) *text,
3000
3659
                      Eterm t,
3001
3660
                      int *constant)
3002
3661
{
3025
3684
 
3026
3685
static DMCRet dmc_or(DMCContext *context,
3027
3686
                     DMCHeap *heap,
3028
 
                     DMC_STACK_TYPE(Uint) *text,
 
3687
                     DMC_STACK_TYPE(UWord) *text,
3029
3688
                     Eterm t,
3030
3689
                     int *constant)
3031
3690
{
3055
3714
 
3056
3715
static DMCRet dmc_andalso(DMCContext *context,
3057
3716
                          DMCHeap *heap,
3058
 
                          DMC_STACK_TYPE(Uint) *text,
 
3717
                          DMC_STACK_TYPE(UWord) *text,
3059
3718
                          Eterm t,
3060
3719
                          int *constant)
3061
3720
{
3104
3763
 
3105
3764
static DMCRet dmc_orelse(DMCContext *context,
3106
3765
                         DMCHeap *heap,
3107
 
                         DMC_STACK_TYPE(Uint) *text,
 
3766
                         DMC_STACK_TYPE(UWord) *text,
3108
3767
                         Eterm t,
3109
3768
                         int *constant)
3110
3769
{
3152
3811
 
3153
3812
static DMCRet dmc_message(DMCContext *context,
3154
3813
                          DMCHeap *heap,
3155
 
                          DMC_STACK_TYPE(Uint) *text,
 
3814
                          DMC_STACK_TYPE(UWord) *text,
3156
3815
                          Eterm t,
3157
3816
                          int *constant)
3158
3817
{
3194
3853
 
3195
3854
static DMCRet dmc_self(DMCContext *context,
3196
3855
                     DMCHeap *heap,
3197
 
                     DMC_STACK_TYPE(Uint) *text,
 
3856
                     DMC_STACK_TYPE(UWord) *text,
3198
3857
                     Eterm t,
3199
3858
                     int *constant)
3200
3859
{
3214
3873
 
3215
3874
static DMCRet dmc_return_trace(DMCContext *context,
3216
3875
                               DMCHeap *heap,
3217
 
                               DMC_STACK_TYPE(Uint) *text,
 
3876
                               DMC_STACK_TYPE(UWord) *text,
3218
3877
                               Eterm t,
3219
3878
                               int *constant)
3220
3879
{
3244
3903
 
3245
3904
static DMCRet dmc_exception_trace(DMCContext *context,
3246
3905
                               DMCHeap *heap,
3247
 
                               DMC_STACK_TYPE(Uint) *text,
 
3906
                               DMC_STACK_TYPE(UWord) *text,
3248
3907
                               Eterm t,
3249
3908
                               int *constant)
3250
3909
{
3276
3935
 
3277
3936
static DMCRet dmc_is_seq_trace(DMCContext *context,
3278
3937
                               DMCHeap *heap,
3279
 
                               DMC_STACK_TYPE(Uint) *text,
 
3938
                               DMC_STACK_TYPE(UWord) *text,
3280
3939
                               Eterm t,
3281
3940
                               int *constant)
3282
3941
{
3302
3961
 
3303
3962
static DMCRet dmc_set_seq_token(DMCContext *context,
3304
3963
                                DMCHeap *heap,
3305
 
                                DMC_STACK_TYPE(Uint) *text,
 
3964
                                DMC_STACK_TYPE(UWord) *text,
3306
3965
                                Eterm t,
3307
3966
                                int *constant)
3308
3967
{
3351
4010
 
3352
4011
static DMCRet dmc_get_seq_token(DMCContext *context,
3353
4012
                                DMCHeap *heap,
3354
 
                                DMC_STACK_TYPE(Uint) *text,
 
4013
                                DMC_STACK_TYPE(UWord) *text,
3355
4014
                                Eterm t,
3356
4015
                                int *constant)
3357
4016
{
3375
4034
 
3376
4035
    *constant = 0;
3377
4036
    DMC_PUSH(*text, matchGetSeqToken);
3378
 
    context->eheap_need += (6 /* A 5-tuple is built */
3379
 
                            + EXTERNAL_THING_HEAD_SIZE + 2 /* Sender can
3380
 
                                                              be an external
3381
 
                                                              pid */);
3382
4037
    if (++context->stack_used > context->stack_need)
3383
4038
        context->stack_need = context->stack_used;
3384
4039
    return retOk;
3388
4043
 
3389
4044
static DMCRet dmc_display(DMCContext *context,
3390
4045
                          DMCHeap *heap,
3391
 
                          DMC_STACK_TYPE(Uint) *text,
 
4046
                          DMC_STACK_TYPE(UWord) *text,
3392
4047
                          Eterm t,
3393
4048
                          int *constant)
3394
4049
{
3428
4083
 
3429
4084
static DMCRet dmc_process_dump(DMCContext *context,
3430
4085
                               DMCHeap *heap,
3431
 
                               DMC_STACK_TYPE(Uint) *text,
 
4086
                               DMC_STACK_TYPE(UWord) *text,
3432
4087
                               Eterm t,
3433
4088
                               int *constant)
3434
4089
{
3458
4113
 
3459
4114
static DMCRet dmc_enable_trace(DMCContext *context,
3460
4115
                               DMCHeap *heap,
3461
 
                               DMC_STACK_TYPE(Uint) *text,
 
4116
                               DMC_STACK_TYPE(UWord) *text,
3462
4117
                               Eterm t,
3463
4118
                               int *constant)
3464
4119
{
3518
4173
 
3519
4174
static DMCRet dmc_disable_trace(DMCContext *context,
3520
4175
                                DMCHeap *heap,
3521
 
                                DMC_STACK_TYPE(Uint) *text,
 
4176
                                DMC_STACK_TYPE(UWord) *text,
3522
4177
                                Eterm t,
3523
4178
                                int *constant)
3524
4179
{
3578
4233
 
3579
4234
static DMCRet dmc_trace(DMCContext *context,
3580
4235
                        DMCHeap *heap,
3581
 
                        DMC_STACK_TYPE(Uint) *text,
 
4236
                        DMC_STACK_TYPE(UWord) *text,
3582
4237
                        Eterm t,
3583
4238
                        int *constant)
3584
4239
{
3652
4307
 
3653
4308
static DMCRet dmc_caller(DMCContext *context,
3654
4309
                         DMCHeap *heap,
3655
 
                         DMC_STACK_TYPE(Uint) *text,
 
4310
                         DMC_STACK_TYPE(UWord) *text,
3656
4311
                         Eterm t,
3657
4312
                         int *constant)
3658
4313
{
3675
4330
    }
3676
4331
    *constant = 0;
3677
4332
    DMC_PUSH(*text, matchCaller); /* Creates binary */
3678
 
    context->eheap_need += 4;     /* A 3-tuple is built */
3679
4333
    if (++context->stack_used > context->stack_need)
3680
4334
        context->stack_need = context->stack_used;
3681
4335
    return retOk;
3685
4339
  
3686
4340
static DMCRet dmc_silent(DMCContext *context,
3687
4341
                         DMCHeap *heap,
3688
 
                         DMC_STACK_TYPE(Uint) *text,
 
4342
                         DMC_STACK_TYPE(UWord) *text,
3689
4343
                         Eterm t,
3690
4344
                         int *constant)
3691
4345
{
3727
4381
 
3728
4382
static DMCRet dmc_fun(DMCContext *context,
3729
4383
                       DMCHeap *heap,
3730
 
                       DMC_STACK_TYPE(Uint) *text,
 
4384
                       DMC_STACK_TYPE(UWord) *text,
3731
4385
                       Eterm t,
3732
4386
                       int *constant)
3733
4387
{
3844
4498
        erl_exit(1,"ets:match() internal error, "
3845
4499
                 "guard with more than 3 arguments.");
3846
4500
    }
3847
 
    DMC_PUSH(*text, (Uint) b->biff);
 
4501
    DMC_PUSH(*text, (UWord) b->biff);
3848
4502
    context->stack_used -= (((int) a) - 2);
3849
4503
    if (context->stack_used > context->stack_need)
3850
4504
        context->stack_need = context->stack_used;
3853
4507
 
3854
4508
static DMCRet dmc_expr(DMCContext *context,
3855
4509
                       DMCHeap *heap,
3856
 
                       DMC_STACK_TYPE(Uint) *text,
 
4510
                       DMC_STACK_TYPE(UWord) *text,
3857
4511
                       Eterm t,
3858
4512
                       int *constant)
3859
4513
{
3916
4570
    
3917
4571
static DMCRet compile_guard_expr(DMCContext *context,
3918
4572
                                 DMCHeap *heap,
3919
 
                                 DMC_STACK_TYPE(Uint) *text,
 
4573
                                 DMC_STACK_TYPE(UWord) *text,
3920
4574
                                 Eterm l)
3921
4575
{
3922
4576
    DMCRet ret;
4031
4685
    DMC_INIT_STACK(heap);
4032
4686
 
4033
4687
    p = expr->mem;
4034
 
    i = expr->size;
 
4688
    i = expr->used_size;
4035
4689
    while (i--) {
4036
4690
        if (is_thing(*p)) {
4037
4691
            a = thing_arityval(*p);
4060
4714
    }
4061
4715
 
4062
4716
    p = expr->mem;
4063
 
    i = expr->size;
 
4717
    i = expr->used_size;
4064
4718
    while (i--) {
4065
4719
        if (is_thing(*p)) {
4066
4720
            a = thing_arityval(*p);
4230
4884
    Eterm l;
4231
4885
    Uint32 ret_flags;
4232
4886
    Uint sz;
4233
 
    Eterm *save_cp;
 
4887
    BeamInstr *save_cp;
4234
4888
 
4235
4889
    if (trace && !(is_list(against) || against == NIL)) {
4236
4890
        return THE_NON_VALUE;
4271
4925
                ++n;
4272
4926
                l = CDR(list_val(l));
4273
4927
            }
 
4928
            save_cp = p->cp;
 
4929
            p->cp = NULL;
 
4930
            res = erts_match_set_run(p, mps, arr, n,
 
4931
                                     ERTS_PAM_COPY_RESULT, &ret_flags);
 
4932
            p->cp = save_cp;
4274
4933
        } else {
4275
4934
            n = 0;
4276
 
            arr = (Eterm *) against;
 
4935
            arr = NULL;
 
4936
            res = erts_match_set_run_ets(p, mps, against, n, &ret_flags);
4277
4937
        }
4278
4938
        
4279
4939
        /* We are in the context of a BIF, 
4280
4940
           {caller} should return 'undefined' */
4281
 
        save_cp = p->cp;
4282
 
        p->cp = NULL;
4283
 
        res = erts_match_set_run(p, mps, arr, n, &ret_flags);
4284
 
        p->cp = save_cp;
4285
4941
        if (is_non_value(res)) {
4286
4942
            res = am_false;
4287
4943
        }
4288
 
        sz = size_object(res);
 
4944
        sz = 0;
4289
4945
        if (ret_flags & MATCH_SET_EXCEPTION_TRACE) sz += 2;
4290
4946
        if (ret_flags & MATCH_SET_RETURN_TRACE) sz += 2;
4291
4947
        hp = HAlloc(p, 5 + sz);
4292
 
        res = copy_struct(res, sz, &hp, &MSO(p));
4293
4948
        flg = NIL;
4294
4949
        if (ret_flags & MATCH_SET_EXCEPTION_TRACE) {
4295
4950
            flg = CONS(hp, am_exception_trace, flg);
4316
4971
    }
4317
4972
    return result;
4318
4973
}
4319
 
    
 
4974
 
 
4975
DbTerm* db_alloc_tmp_uncompressed(DbTableCommon* tb, DbTerm* org)
 
4976
{
 
4977
    ErlOffHeap tmp_offheap;
 
4978
    DbTerm* res = erts_alloc(ERTS_ALC_T_TMP,
 
4979
                             sizeof(DbTerm) + org->size*sizeof(Eterm));
 
4980
    Eterm* hp = res->tpl;
 
4981
    tmp_offheap.first = NULL;
 
4982
    db_copy_from_comp(tb, org, &hp, &tmp_offheap);
 
4983
    res->first_oh = tmp_offheap.first;
 
4984
    res->size = org->size;
 
4985
#ifdef DEBUG_CLONE
 
4986
    res->debug_clone = NULL;
 
4987
#endif
 
4988
    return res;
 
4989
}
 
4990
 
 
4991
void db_free_tmp_uncompressed(DbTerm* obj)
 
4992
{
 
4993
    ErlOffHeap off_heap;
 
4994
    off_heap.first = obj->first_oh;
 
4995
    erts_cleanup_offheap(&off_heap);
 
4996
#ifdef DEBUG_CLONE
 
4997
    ASSERT(obj->debug_clone == NULL);
 
4998
#endif
 
4999
    erts_free(ERTS_ALC_T_TMP, obj);
 
5000
}
 
5001
 
 
5002
Eterm db_match_dbterm(DbTableCommon* tb, Process* c_p, Binary* bprog,
 
5003
                             int all, DbTerm* obj, Eterm** hpp, Uint extra)
 
5004
{
 
5005
    Uint32 dummy;
 
5006
    Eterm* base;
 
5007
    Eterm res;
 
5008
 
 
5009
    if (tb->compress) {
 
5010
        obj = db_alloc_tmp_uncompressed(tb, obj);
 
5011
        base = NULL;
 
5012
    }
 
5013
    else base = HALFWORD_HEAP ? obj->tpl : NULL;
 
5014
 
 
5015
    res = db_prog_match(c_p, bprog, make_tuple_rel(obj->tpl,base), base, NULL, 0,
 
5016
                        ERTS_PAM_COPY_RESULT|ERTS_PAM_CONTIGUOUS_TUPLE, &dummy);
 
5017
 
 
5018
    if (is_value(res) && hpp!=NULL) {
 
5019
        *hpp = HAlloc(c_p, extra);
 
5020
    }
 
5021
 
 
5022
    if (tb->compress) {
 
5023
        db_free_tmp_uncompressed(obj);
 
5024
    }
 
5025
    return res;
 
5026
}
 
5027
 
 
5028
 
4320
5029
#ifdef DMC_DEBUG
 
5030
 
4321
5031
/*
4322
5032
** Disassemble match program
4323
5033
*/
4324
 
static void db_match_dis(Binary *bp)
 
5034
void db_match_dis(Binary *bp)
4325
5035
{
4326
5036
    MatchProg *prog = Binary2MatchProg(bp);
4327
 
    Uint *t = prog->text;
 
5037
    UWord *t = prog->text;
4328
5038
    Uint n;
4329
5039
    Eterm p;
4330
5040
    int first;
4390
5100
            break;
4391
5101
        case matchEqRef:
4392
5102
            ++t;
4393
 
            n = thing_arityval(*t);
4394
 
            ++t;
4395
 
            erts_printf("EqRef\t(%d) {", (int) n);
4396
 
            first = 1;
4397
 
            while (n--) {
4398
 
                if (first)
4399
 
                    first = 0;
4400
 
                else
4401
 
                    erts_printf(", ");
4402
 
#ifdef ARCH_64
4403
 
                erts_printf("0x%016bpx", *t);
 
5103
            {
 
5104
                RefThing *rt = (RefThing *) t;
 
5105
                int ri;
 
5106
                n = thing_arityval(rt->header);
 
5107
                erts_printf("EqRef\t(%d) {", (int) n);
 
5108
                first = 1;
 
5109
                for (ri = 0; ri < n; ++ri) {
 
5110
                    if (first)
 
5111
                        first = 0;
 
5112
                    else
 
5113
                        erts_printf(", ");
 
5114
#if defined(ARCH_64) && !HALFWORD_HEAP
 
5115
                    erts_printf("0x%016bpx", rt->data.ui[ri]);
4404
5116
#else
4405
 
                erts_printf("0x%08bpx", *t);
 
5117
                    erts_printf("0x%08bpx", rt->data.ui[ri]);
4406
5118
#endif
4407
 
                ++t;
 
5119
                }
4408
5120
            }
 
5121
            t += TermWords(REF_THING_SIZE);
4409
5122
            erts_printf("}\n");
4410
5123
            break;
4411
5124
        case matchEqBig:
4412
5125
            ++t;
4413
5126
            n = thing_arityval(*t);
4414
 
            ++t;
4415
 
            erts_printf("EqBig\t(%d) {", (int) n);
4416
 
            first = 1;
4417
 
            while (n--) {
4418
 
                if (first)
4419
 
                    first = 0;
4420
 
                else
4421
 
                    erts_printf(", ");
4422
 
#ifdef ARCH_64
4423
 
                erts_printf("0x%016bpx", *t);
 
5127
            {
 
5128
                Eterm *et = (Eterm *) t;
 
5129
                t += TermWords(n+1);
 
5130
                erts_printf("EqBig\t(%d) {", (int) n);
 
5131
                first = 1;
 
5132
                ++n;
 
5133
                while (n--) {
 
5134
                    if (first)
 
5135
                        first = 0;
 
5136
                    else
 
5137
                        erts_printf(", ");
 
5138
#if defined(ARCH_64) && !HALFWORD_HEAP
 
5139
                    erts_printf("0x%016bpx", *et);
4424
5140
#else
4425
 
                erts_printf("0x%08bpx", *t);
 
5141
                    erts_printf("0x%08bpx", *et);
4426
5142
#endif
4427
 
                ++t;
 
5143
                ++et;
 
5144
                }
4428
5145
            }
4429
5146
            erts_printf("}\n");
4430
5147
            break;
4432
5149
            ++t;
4433
5150
            {
4434
5151
                double num;
4435
 
                memcpy(&num,t, 2 * sizeof(*t));
4436
 
                t += 2;
 
5152
                memcpy(&num,t,sizeof(double));
 
5153
                t += TermWords(2);
4437
5154
                erts_printf("EqFloat\t%f\n", num);
4438
5155
            }
4439
5156
            break;
4529
5246
            ++t;
4530
5247
            erts_printf("PushV\t%bpu\n", n);
4531
5248
            break;
 
5249
    #if HALFWORD_HEAP
 
5250
        case matchPushVGuard:
 
5251
            n = (Uint) *++t;
 
5252
            ++t;
 
5253
            erts_printf("PushVGuard\t%bpu\n", n);
 
5254
            break;
 
5255
    #endif
 
5256
        case matchPushVResult:
 
5257
            n = (Uint) *++t;
 
5258
            ++t;
 
5259
            erts_printf("PushVResult\t%bpu\n", n);
 
5260
            break;
4532
5261
        case matchTrue:
4533
5262
            ++t;
4534
5263
            erts_printf("True\n");
4639
5368
    erts_printf("}\n");
4640
5369
    erts_printf("num_bindings: %d\n", prog->num_bindings);
4641
5370
    erts_printf("heap_size: %bpu\n", prog->heap_size);
4642
 
    erts_printf("eheap_offset: %bpu\n", prog->eheap_offset);
4643
5371
    erts_printf("stack_offset: %bpu\n", prog->stack_offset);
4644
5372
    erts_printf("text: 0x%08x\n", (unsigned long) prog->text);
4645
5373
    erts_printf("stack_size: %d (words)\n", prog->heap_size-prog->stack_offset);