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

« back to all changes in this revision

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

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

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
/*
2
2
 * %CopyrightBegin%
3
 
 * 
4
 
 * Copyright Ericsson AB 1996-2009. All Rights Reserved.
5
 
 * 
 
3
 *
 
4
 * Copyright Ericsson AB 1996-2011. All Rights Reserved.
 
5
 *
6
6
 * The contents of this file are subject to the Erlang Public License,
7
7
 * Version 1.1, (the "License"); you may not use this file except in
8
8
 * compliance with the License. You should have received a copy of the
9
9
 * Erlang Public License along with this software. If not, it can be
10
10
 * retrieved online at http://www.erlang.org/.
11
 
 * 
 
11
 *
12
12
 * Software distributed under the License is distributed on an "AS IS"
13
13
 * basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
 * the License for the specific language governing rights and limitations
15
15
 * under the License.
16
 
 * 
 
16
 *
17
17
 * %CopyrightEnd%
18
18
 */
19
19
 
37
37
MA_STACK_DECLARE(offset);
38
38
#endif
39
39
 
 
40
static void move_one_frag(Eterm** hpp, Eterm* src, Uint src_sz, ErlOffHeap*);
 
41
 
40
42
void
41
43
init_copy(void)
42
44
{
70
72
 * Return the "flat" size of the object.
71
73
 */
72
74
 
73
 
Uint
74
 
size_object(Eterm obj)
 
75
#if HALFWORD_HEAP
 
76
Uint size_object_rel(Eterm obj, Eterm* base)
 
77
#else
 
78
Uint size_object(Eterm obj)
 
79
#endif
75
80
{
76
81
    Uint sum = 0;
77
82
    Eterm* ptr;
82
87
        switch (primary_tag(obj)) {
83
88
        case TAG_PRIMARY_LIST:
84
89
            sum += 2;
85
 
            ptr = list_val(obj);
 
90
            ptr = list_val_rel(obj,base);
86
91
            obj = *ptr++;
87
92
            if (!IS_CONST(obj)) {
88
93
                ESTACK_PUSH(s, obj);
89
 
            }
 
94
            }       
90
95
            obj = *ptr;
91
96
            break;
92
97
        case TAG_PRIMARY_BOXED:
93
98
            {
94
 
                Eterm hdr = *boxed_val(obj);
 
99
                Eterm hdr = *boxed_val_rel(obj,base);
95
100
                ASSERT(is_header(hdr));
96
101
                switch (hdr & _TAG_HEADER_MASK) {
97
102
                case ARITYVAL_SUBTAG:
98
 
                    ptr = tuple_val(obj);
 
103
                    ptr = tuple_val_rel(obj,base);
99
104
                    arity = header_arity(hdr);
100
105
                    sum += arity + 1;
101
106
                    if (arity == 0) { /* Empty tuple -- unusual. */
102
 
                        goto size_common;
 
107
                        goto pop_next;
103
108
                    }
104
109
                    while (arity-- > 1) {
105
110
                        obj = *++ptr;
111
116
                    break;
112
117
                case FUN_SUBTAG:
113
118
                    {
114
 
                        Eterm* bptr = fun_val(obj);
 
119
                        Eterm* bptr = fun_val_rel(obj,base);
115
120
                        ErlFunThing* funp = (ErlFunThing *) bptr;
116
121
                        unsigned eterms = 1 /* creator */ + funp->num_free;
117
122
                        unsigned sz = thing_arityval(hdr);
118
 
 
119
123
                        sum += 1 /* header */ + sz + eterms;
120
124
                        bptr += 1 /* header */ + sz;
121
125
                        while (eterms-- > 1) {
135
139
                        Uint bitoffs;
136
140
                        Uint extra_bytes;
137
141
                        Eterm hdr;
138
 
                        ERTS_GET_REAL_BIN(obj, real_bin, offset, bitoffs, bitsize);
 
142
                        ERTS_GET_REAL_BIN_REL(obj, real_bin, offset, bitoffs, bitsize, base);
139
143
                        if ((bitsize + bitoffs) > 8) {
140
144
                            sum += ERL_SUB_BIN_SIZE;
141
145
                            extra_bytes = 2;
145
149
                        } else {
146
150
                            extra_bytes = 0;
147
151
                        }
148
 
                        hdr = *binary_val(real_bin);
 
152
                        hdr = *binary_val_rel(real_bin,base);
149
153
                        if (thing_subtag(hdr) == REFC_BINARY_SUBTAG) {
150
154
                            sum += PROC_BIN_SIZE;
151
155
                        } else {
152
 
                            sum += heap_bin_size(binary_size(obj)+extra_bytes);
 
156
                            sum += heap_bin_size(binary_size_rel(obj,base)+extra_bytes);
153
157
                        }
154
 
                        goto size_common;
 
158
                        goto pop_next;
155
159
                    }
156
160
                    break;
157
161
                case BIN_MATCHSTATE_SUBTAG:
159
163
                             "size_object: matchstate term not allowed");
160
164
                default:
161
165
                    sum += thing_arityval(hdr) + 1;
162
 
                    /* Fall through */
163
 
                size_common:
164
 
                    if (ESTACK_ISEMPTY(s)) {
165
 
                        DESTROY_ESTACK(s);
166
 
                        return sum;
167
 
                    }
168
 
                    obj = ESTACK_POP(s);
169
 
                    break;
 
166
                    goto pop_next;
170
167
                }
171
168
            }
172
169
            break;
173
170
        case TAG_PRIMARY_IMMED1:
 
171
        pop_next:
174
172
            if (ESTACK_ISEMPTY(s)) {
175
173
                DESTROY_ESTACK(s);
176
174
                return sum;
186
184
/*
187
185
 *  Copy a structure to a heap.
188
186
 */
189
 
Eterm
190
 
copy_struct(Eterm obj, Uint sz, Eterm** hpp, ErlOffHeap* off_heap)
 
187
#if HALFWORD_HEAP
 
188
Eterm copy_struct_rel(Eterm obj, Uint sz, Eterm** hpp, ErlOffHeap* off_heap,
 
189
                      Eterm* src_base, Eterm* dst_base)
 
190
#else
 
191
Eterm copy_struct(Eterm obj, Uint sz, Eterm** hpp, ErlOffHeap* off_heap)
 
192
#endif
191
193
{
192
194
    char* hstart;
193
195
    Uint hsize;
219
221
 
220
222
    /* Copy the object onto the heap */
221
223
    switch (primary_tag(obj)) {
222
 
    case TAG_PRIMARY_LIST: argp = &res; goto L_copy_list;
 
224
    case TAG_PRIMARY_LIST:
 
225
        argp = &res;
 
226
        objp = list_val_rel(obj,src_base);
 
227
        goto L_copy_list;
223
228
    case TAG_PRIMARY_BOXED: argp = &res; goto L_copy_boxed;
224
229
    default:
225
230
        erl_exit(ERTS_ABORT_EXIT,
236
241
            hp++;
237
242
            break;
238
243
        case TAG_PRIMARY_LIST:
239
 
            objp = list_val(obj);
 
244
            objp = list_val_rel(obj,src_base);
 
245
        #if !HALFWORD_HEAP || defined(DEBUG)
240
246
            if (in_area(objp,hstart,hsize)) {
 
247
                ASSERT(!HALFWORD_HEAP);
241
248
                hp++;
242
249
                break;
243
250
            }
 
251
        #endif
244
252
            argp = hp++;
245
253
            /* Fall through */
246
254
 
247
255
        L_copy_list:
248
256
            tailp = argp;
249
 
            while (is_list(obj)) {
250
 
                objp = list_val(obj);
 
257
            for (;;) {
251
258
                tp = tailp;
252
 
                elem = *objp;
 
259
                elem = CAR(objp);
253
260
                if (IS_CONST(elem)) {
254
 
                    *(hbot-2) = elem;
255
 
                    tailp = hbot-1;
256
261
                    hbot -= 2;
 
262
                    CAR(hbot) = elem;
 
263
                    tailp = &CDR(hbot);
257
264
                }
258
265
                else {
259
 
                    *htop = elem;
260
 
                    tailp = htop+1;
261
 
                    htop += 2;
262
 
                }
263
 
                *tp = make_list(tailp - 1);
264
 
                obj = *(objp+1);
 
266
                    CAR(htop) = elem;
 
267
                #if HALFWORD_HEAP
 
268
                    CDR(htop) = CDR(objp);
 
269
                    *tailp = make_list_rel(htop,dst_base);
 
270
                    htop += 2;
 
271
                    goto L_copy;
 
272
                #else
 
273
                    tailp = &CDR(htop);
 
274
                    htop += 2;
 
275
                #endif
 
276
                }
 
277
                ASSERT(!HALFWORD_HEAP || tp < hp || tp >= hbot);
 
278
                *tp = make_list_rel(tailp - 1, dst_base);
 
279
                obj = CDR(objp);
 
280
                if (!is_list(obj)) {
 
281
                    break;
 
282
                }
 
283
                objp = list_val_rel(obj,src_base);
265
284
            }
266
285
            switch (primary_tag(obj)) {
267
286
            case TAG_PRIMARY_IMMED1: *tailp = obj; goto L_copy;
273
292
            }
274
293
            
275
294
        case TAG_PRIMARY_BOXED:
276
 
            if (in_area(boxed_val(obj),hstart,hsize)) {
 
295
        #if !HALFWORD_HEAP || defined(DEBUG)
 
296
            if (in_area(boxed_val_rel(obj,src_base),hstart,hsize)) {
 
297
                ASSERT(!HALFWORD_HEAP);
277
298
                hp++;
278
299
                break;
279
300
            }
 
301
        #endif
280
302
            argp = hp++;
281
303
 
282
304
        L_copy_boxed:
283
 
            objp = boxed_val(obj);
 
305
            objp = boxed_val_rel(obj, src_base);
284
306
            hdr = *objp;
285
307
            switch (hdr & _TAG_HEADER_MASK) {
286
308
            case ARITYVAL_SUBTAG:
287
309
                {
288
310
                    int const_flag = 1; /* assume constant tuple */
289
311
                    i = arityval(hdr);
290
 
                    *argp = make_tuple(htop);
 
312
                    *argp = make_tuple_rel(htop, dst_base);
291
313
                    tp = htop;  /* tp is pointer to new arity value */
292
314
                    *htop++ = *objp++; /* copy arity value */
293
315
                    while (i--) {
316
338
                    while (i--)  {
317
339
                        *tp++ = *objp++;
318
340
                    }
319
 
                    *argp = make_binary(hbot);
 
341
                    *argp = make_binary_rel(hbot, dst_base);
320
342
                    pb = (ProcBin*) hbot;
321
343
                    erts_refc_inc(&pb->val->refc, 2);
322
 
                    pb->next = off_heap->mso;
 
344
                    pb->next = off_heap->first;
323
345
                    pb->flags = 0;
324
 
                    off_heap->mso = pb;
325
 
                    off_heap->overhead += pb->size / sizeof(Eterm);
 
346
                    off_heap->first = (struct erl_off_heap_header*) pb;
 
347
                    OH_OVERHEAD(off_heap, pb->size / sizeof(Eterm));
326
348
                }
327
349
                break;
328
350
            case SUB_BINARY_SUBTAG:
343
365
                        extra_bytes = 0;
344
366
                    } 
345
367
                    real_size = size+extra_bytes;
346
 
                    objp = binary_val(real_bin);
 
368
                    objp = binary_val_rel(real_bin,src_base);
347
369
                    if (thing_subtag(*objp) == HEAP_BINARY_SUBTAG) {
348
370
                        ErlHeapBin* from = (ErlHeapBin *) objp;
349
371
                        ErlHeapBin* to;
368
390
                        to->val = from->val;
369
391
                        erts_refc_inc(&to->val->refc, 2);
370
392
                        to->bytes = from->bytes + offset;
371
 
                        to->next = off_heap->mso;
 
393
                        to->next = off_heap->first;
372
394
                        to->flags = 0;
373
 
                        off_heap->mso = to;
374
 
                        off_heap->overhead += to->size / sizeof(Eterm);
 
395
                        off_heap->first = (struct erl_off_heap_header*) to;
 
396
                        OH_OVERHEAD(off_heap, to->size / sizeof(Eterm));
375
397
                    }
376
 
                    *argp = make_binary(hbot);
 
398
                    *argp = make_binary_rel(hbot, dst_base);
377
399
                    if (extra_bytes != 0) {
378
400
                        ErlSubBin* res;
379
401
                        hbot -= ERL_SUB_BIN_SIZE;
385
407
                        res->offs = 0;
386
408
                        res->is_writable = 0;
387
409
                        res->orig = *argp;
388
 
                        *argp = make_binary(hbot);
 
410
                        *argp = make_binary_rel(hbot, dst_base);
389
411
                    }
390
412
                    break;
391
413
                }
401
423
                    }
402
424
#ifndef HYBRID /* FIND ME! */
403
425
                    funp = (ErlFunThing *) tp;
404
 
                    funp->next = off_heap->funs;
405
 
                    off_heap->funs = funp;
 
426
                    funp->next = off_heap->first;
 
427
                    off_heap->first = (struct erl_off_heap_header*) funp;
406
428
                    erts_refc_inc(&funp->fe->refc, 2);
407
429
#endif
408
 
                    *argp = make_fun(tp);
 
430
                    *argp = make_fun_rel(tp, dst_base);
409
431
                }
410
432
                break;
411
433
            case EXTERNAL_PID_SUBTAG:
421
443
                    *htop++ = *objp++;
422
444
                  }
423
445
 
424
 
                  etp->next = off_heap->externals;
425
 
                  off_heap->externals = etp;
 
446
                  etp->next = off_heap->first;
 
447
                  off_heap->first = (struct erl_off_heap_header*)etp;
426
448
                  erts_refc_inc(&etp->node->refc, 2);
427
449
 
428
 
                  *argp = make_external(tp);
 
450
                  *argp = make_external_rel(tp, dst_base);
429
451
                }
430
452
                break;
431
453
            case BIN_MATCHSTATE_SUBTAG:
435
457
                i = thing_arityval(hdr)+1;
436
458
                hbot -= i;
437
459
                tp = hbot;
438
 
                *argp = make_boxed(hbot);
 
460
                *argp = make_boxed_rel(hbot, dst_base);
439
461
                while (i--) {
440
462
                    *tp++ = *objp++;
441
463
                }
655
677
                    *hp++ = *objp++;
656
678
                }
657
679
                erts_refc_inc(&pb->val->refc, 2);
658
 
                pb->next = erts_global_offheap.mso;
659
 
                erts_global_offheap.mso = pb;
660
 
                erts_global_offheap.overhead += pb->size / sizeof(Eterm);
 
680
                pb->next = erts_global_offheap.first;
 
681
                erts_global_offheap.first = pb;
 
682
                OH_OVERHEAD(off_heap, pb->size / sizeof(Eterm));
661
683
                continue;
662
684
            }
663
685
 
677
699
                while (i--) {
678
700
                    *hp++ = *objp++;
679
701
                }
680
 
#ifndef HYBRID // FIND ME!
681
 
                funp->next = erts_global_offheap.funs;
682
 
                erts_global_offheap.funs = funp;
 
702
#ifndef HYBRID /* FIND ME! */
 
703
                funp->next = erts_global_offheap.first;
 
704
                erts_global_offheap.first = funp;
683
705
                erts_refc_inc(&funp->fe->refc, 2);
684
706
#endif
685
707
                for (i = k; i < j; i++) {
723
745
                    *hp++ = *objp++;
724
746
                }
725
747
 
726
 
                etp->next = erts_global_offheap.externals;
727
 
                erts_global_offheap.externals = etp;
 
748
                etp->next = erts_global_offheap.first;
 
749
                erts_global_offheap.first = etp;
728
750
                erts_refc_inc(&etp->node->refc, 2);
729
751
                continue;
730
752
            }
780
802
                    to_bin->size = real_size;
781
803
                    to_bin->val = from_bin->val;
782
804
                    to_bin->bytes = from_bin->bytes + sub_offset;
783
 
                    to_bin->next = erts_global_offheap.mso;
784
 
                    erts_global_offheap.mso = to_bin;
785
 
                    erts_global_offheap.overhead += to_bin->size / sizeof(Eterm);
 
805
                    to_bin->next = erts_global_offheap.first;
 
806
                    erts_global_offheap.first = to_bin;
 
807
                    OH_OVERHEAD(&erts_global_offheap, to_bin->size / sizeof(Eterm));
786
808
                    res_binary=make_binary(to_bin);
787
809
                    hp += PROC_BIN_SIZE;
788
810
                }
890
912
 *
891
913
 * NOTE: Assumes that term is a tuple (ptr is an untagged tuple ptr).
892
914
 */
893
 
Eterm
894
 
copy_shallow(Eterm* ptr, Uint sz, Eterm** hpp, ErlOffHeap* off_heap)
 
915
#if HALFWORD_HEAP
 
916
Eterm copy_shallow_rel(Eterm* ptr, Uint sz, Eterm** hpp, ErlOffHeap* off_heap,
 
917
                       Eterm* src_base)
 
918
#else
 
919
Eterm copy_shallow(Eterm* ptr, Uint sz, Eterm** hpp, ErlOffHeap* off_heap)
 
920
#endif
895
921
{
896
922
    Eterm* tp = ptr;
897
923
    Eterm* hp = *hpp;
898
 
    Sint offs = hp - tp;
 
924
    const Eterm res = make_tuple(hp);
 
925
#if HALFWORD_HEAP
 
926
    const Sint offs = COMPRESS_POINTER(hp - (tp - src_base));
 
927
#else
 
928
    const Sint offs = (hp - tp) * sizeof(Eterm);
 
929
#endif
899
930
 
900
931
    while (sz--) {
901
932
        Eterm val = *tp++;
906
937
            break;
907
938
        case TAG_PRIMARY_LIST:
908
939
        case TAG_PRIMARY_BOXED:
909
 
            *hp++ = offset_ptr(val, offs);
 
940
            *hp++ = byte_offset_ptr(val, offs);
910
941
            break;
911
942
        case TAG_PRIMARY_HEADER:
912
943
            *hp++ = val;
915
946
                break;
916
947
            case REFC_BINARY_SUBTAG:
917
948
                {
918
 
                    ProcBin* pb = (ProcBin *) (hp-1);
919
 
                    int tari = thing_arityval(val);
920
 
 
921
 
                    sz -= tari;
922
 
                    while (tari--) {
923
 
                        *hp++ = *tp++;
924
 
                    }
 
949
                    ProcBin* pb = (ProcBin *) (tp-1);
925
950
                    erts_refc_inc(&pb->val->refc, 2);
926
 
                    pb->next = off_heap->mso;
927
 
                    off_heap->mso = pb;
928
 
                    off_heap->overhead += pb->size / sizeof(Eterm);
 
951
                    OH_OVERHEAD(off_heap, pb->size / sizeof(Eterm));
929
952
                }
930
 
                break;
 
953
                goto off_heap_common;
 
954
 
931
955
            case FUN_SUBTAG:
932
956
                {
933
 
#ifndef HYBRID /* FIND ME! */
934
 
                    ErlFunThing* funp = (ErlFunThing *) (hp-1);
935
 
#endif
936
 
                    int tari = thing_arityval(val);
937
 
 
938
 
                    sz -= tari;
939
 
                    while (tari--) {
940
 
                        *hp++ = *tp++;
941
 
                    }
942
 
#ifndef HYBRID /* FIND ME! */
943
 
                    funp->next = off_heap->funs;
944
 
                    off_heap->funs = funp;
 
957
                    ErlFunThing* funp = (ErlFunThing *) (tp-1);
945
958
                    erts_refc_inc(&funp->fe->refc, 2);
946
 
#endif
947
959
                }
948
 
                break;
 
960
                goto off_heap_common;
 
961
 
949
962
            case EXTERNAL_PID_SUBTAG:
950
963
            case EXTERNAL_PORT_SUBTAG:
951
964
            case EXTERNAL_REF_SUBTAG:
952
965
                {
953
 
                    ExternalThing* etp = (ExternalThing *) (hp-1);
954
 
                    int tari = thing_arityval(val);
955
 
 
956
 
                    sz -= tari;
957
 
                    while (tari--) {
958
 
                        *hp++ = *tp++;
959
 
                    }
960
 
                    etp->next = off_heap->externals;
961
 
                    off_heap->externals = etp;
 
966
                    ExternalThing* etp = (ExternalThing *) (tp-1);
962
967
                    erts_refc_inc(&etp->node->refc, 2);
963
968
                }
 
969
            off_heap_common:
 
970
                {
 
971
                    struct erl_off_heap_header* ohh = (struct erl_off_heap_header*)(hp-1);
 
972
                    int tari = thing_arityval(val);
 
973
                    
 
974
                    sz -= tari;
 
975
                    while (tari--) {
 
976
                        *hp++ = *tp++;
 
977
                    }
 
978
                    ohh->next = off_heap->first;
 
979
                    off_heap->first = ohh;
 
980
                }
964
981
                break;
965
982
            default:
966
983
                {
967
984
                    int tari = header_arity(val);
968
 
 
 
985
    
969
986
                    sz -= tari;
970
987
                    while (tari--) {
971
988
                        *hp++ = *tp++;
977
994
        }
978
995
    }
979
996
    *hpp = hp;
980
 
    return make_tuple(ptr + offs); 
981
 
}
 
997
 
 
998
    return res;
 
999
}
 
1000
 
 
1001
/* Move all terms in heap fragments into heap. The terms must be guaranteed to 
 
1002
 * be contained within the fragments. The source terms are destructed with
 
1003
 * move markers.
 
1004
 * Typically used to copy a multi-fragmented message (from NIF).
 
1005
 */
 
1006
void move_multi_frags(Eterm** hpp, ErlOffHeap* off_heap, ErlHeapFragment* first,
 
1007
                      Eterm* refs, unsigned nrefs)
 
1008
{
 
1009
    ErlHeapFragment* bp;
 
1010
    Eterm* hp_start = *hpp;
 
1011
    Eterm* hp_end;
 
1012
    Eterm* hp;
 
1013
    unsigned i;
 
1014
 
 
1015
    for (bp=first; bp!=NULL; bp=bp->next) {
 
1016
        move_one_frag(hpp, bp->mem, bp->used_size, off_heap);
 
1017
        OH_OVERHEAD(off_heap, bp->off_heap.overhead);
 
1018
    }
 
1019
    hp_end = *hpp;
 
1020
    for (hp=hp_start; hp<hp_end; ++hp) {
 
1021
        Eterm* ptr;
 
1022
        Eterm val;
 
1023
        Eterm gval = *hp;
 
1024
        switch (primary_tag(gval)) {
 
1025
        case TAG_PRIMARY_BOXED:
 
1026
            ptr = boxed_val(gval);
 
1027
            val = *ptr;
 
1028
            if (IS_MOVED_BOXED(val)) {
 
1029
                ASSERT(is_boxed(val));
 
1030
                *hp = val;
 
1031
            }
 
1032
            break;
 
1033
        case TAG_PRIMARY_LIST:
 
1034
            ptr = list_val(gval);
 
1035
            val = *ptr;
 
1036
            if (IS_MOVED_CONS(val)) {
 
1037
                *hp = ptr[1];
 
1038
            }
 
1039
            break;
 
1040
        case TAG_PRIMARY_HEADER:
 
1041
            if (header_is_thing(gval)) {
 
1042
                hp += thing_arityval(gval);
 
1043
            }
 
1044
            break;
 
1045
        }
 
1046
    }
 
1047
    for (i=0; i<nrefs; ++i) {
 
1048
        refs[i] = follow_moved(refs[i]);
 
1049
    }
 
1050
}
 
1051
 
 
1052
static void
 
1053
move_one_frag(Eterm** hpp, Eterm* src, Uint src_sz, ErlOffHeap* off_heap)
 
1054
{
 
1055
    Eterm* ptr = src;
 
1056
    Eterm* end = ptr + src_sz;
 
1057
    Eterm dummy_ref;
 
1058
    Eterm* hp = *hpp;
 
1059
 
 
1060
    while (ptr != end) {
 
1061
        Eterm val;
 
1062
        ASSERT(ptr < end);
 
1063
        val = *ptr;
 
1064
        ASSERT(val != ERTS_HOLE_MARKER);
 
1065
        if (is_header(val)) {
 
1066
            struct erl_off_heap_header* hdr = (struct erl_off_heap_header*)hp;
 
1067
            ASSERT(ptr + header_arity(val) < end);
 
1068
            MOVE_BOXED(ptr, val, hp, &dummy_ref);           
 
1069
            switch (val & _HEADER_SUBTAG_MASK) {
 
1070
            case REFC_BINARY_SUBTAG:
 
1071
            case FUN_SUBTAG:
 
1072
            case EXTERNAL_PID_SUBTAG:
 
1073
            case EXTERNAL_PORT_SUBTAG:
 
1074
            case EXTERNAL_REF_SUBTAG:
 
1075
                hdr->next = off_heap->first;
 
1076
                off_heap->first = hdr;
 
1077
                break;
 
1078
            }
 
1079
        }
 
1080
        else { /* must be a cons cell */
 
1081
            ASSERT(ptr+1 < end);
 
1082
            MOVE_CONS(ptr, val, hp, &dummy_ref);
 
1083
            ptr += 2;
 
1084
        }
 
1085
    }
 
1086
    *hpp = hp;
 
1087
}
 
1088