~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

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

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
/*
2
2
 * %CopyrightBegin%
3
3
 *
4
 
 * Copyright Ericsson AB 1996-2010. All Rights Reserved.
 
4
 * Copyright Ericsson AB 1996-2011. All Rights Reserved.
5
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
72
72
 * Return the "flat" size of the object.
73
73
 */
74
74
 
75
 
Uint
76
 
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
77
80
{
78
81
    Uint sum = 0;
79
82
    Eterm* ptr;
84
87
        switch (primary_tag(obj)) {
85
88
        case TAG_PRIMARY_LIST:
86
89
            sum += 2;
87
 
            ptr = list_val(obj);
 
90
            ptr = list_val_rel(obj,base);
88
91
            obj = *ptr++;
89
92
            if (!IS_CONST(obj)) {
90
93
                ESTACK_PUSH(s, obj);
93
96
            break;
94
97
        case TAG_PRIMARY_BOXED:
95
98
            {
96
 
                Eterm hdr = *boxed_val(obj);
 
99
                Eterm hdr = *boxed_val_rel(obj,base);
97
100
                ASSERT(is_header(hdr));
98
101
                switch (hdr & _TAG_HEADER_MASK) {
99
102
                case ARITYVAL_SUBTAG:
100
 
                    ptr = tuple_val(obj);
 
103
                    ptr = tuple_val_rel(obj,base);
101
104
                    arity = header_arity(hdr);
102
105
                    sum += arity + 1;
103
106
                    if (arity == 0) { /* Empty tuple -- unusual. */
113
116
                    break;
114
117
                case FUN_SUBTAG:
115
118
                    {
116
 
                        Eterm* bptr = fun_val(obj);
 
119
                        Eterm* bptr = fun_val_rel(obj,base);
117
120
                        ErlFunThing* funp = (ErlFunThing *) bptr;
118
121
                        unsigned eterms = 1 /* creator */ + funp->num_free;
119
122
                        unsigned sz = thing_arityval(hdr);
131
134
                case SUB_BINARY_SUBTAG:
132
135
                    {
133
136
                        Eterm real_bin;
134
 
                        Uint offset; /* Not used. */
 
137
                        ERTS_DECLARE_DUMMY(Uint offset); /* Not used. */
135
138
                        Uint bitsize;
136
139
                        Uint bitoffs;
137
140
                        Uint extra_bytes;
138
141
                        Eterm hdr;
139
 
                        ERTS_GET_REAL_BIN(obj, real_bin, offset, bitoffs, bitsize);
 
142
                        ERTS_GET_REAL_BIN_REL(obj, real_bin, offset, bitoffs, bitsize, base);
140
143
                        if ((bitsize + bitoffs) > 8) {
141
144
                            sum += ERL_SUB_BIN_SIZE;
142
145
                            extra_bytes = 2;
146
149
                        } else {
147
150
                            extra_bytes = 0;
148
151
                        }
149
 
                        hdr = *binary_val(real_bin);
 
152
                        hdr = *binary_val_rel(real_bin,base);
150
153
                        if (thing_subtag(hdr) == REFC_BINARY_SUBTAG) {
151
154
                            sum += PROC_BIN_SIZE;
152
155
                        } else {
153
 
                            sum += heap_bin_size(binary_size(obj)+extra_bytes);
 
156
                            sum += heap_bin_size(binary_size_rel(obj,base)+extra_bytes);
154
157
                        }
155
158
                        goto pop_next;
156
159
                    }
181
184
/*
182
185
 *  Copy a structure to a heap.
183
186
 */
184
 
Eterm
185
 
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
186
193
{
187
194
    char* hstart;
188
195
    Uint hsize;
214
221
 
215
222
    /* Copy the object onto the heap */
216
223
    switch (primary_tag(obj)) {
217
 
    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;
218
228
    case TAG_PRIMARY_BOXED: argp = &res; goto L_copy_boxed;
219
229
    default:
220
230
        erl_exit(ERTS_ABORT_EXIT,
231
241
            hp++;
232
242
            break;
233
243
        case TAG_PRIMARY_LIST:
234
 
            objp = list_val(obj);
 
244
            objp = list_val_rel(obj,src_base);
 
245
        #if !HALFWORD_HEAP || defined(DEBUG)
235
246
            if (in_area(objp,hstart,hsize)) {
 
247
                ASSERT(!HALFWORD_HEAP);
236
248
                hp++;
237
249
                break;
238
250
            }
 
251
        #endif
239
252
            argp = hp++;
240
253
            /* Fall through */
241
254
 
242
255
        L_copy_list:
243
256
            tailp = argp;
244
 
            while (is_list(obj)) {
245
 
                objp = list_val(obj);
 
257
            for (;;) {
246
258
                tp = tailp;
247
 
                elem = *objp;
 
259
                elem = CAR(objp);
248
260
                if (IS_CONST(elem)) {
249
 
                    *(hbot-2) = elem;
250
 
                    tailp = hbot-1;
251
261
                    hbot -= 2;
 
262
                    CAR(hbot) = elem;
 
263
                    tailp = &CDR(hbot);
252
264
                }
253
265
                else {
254
 
                    *htop = elem;
255
 
                    tailp = htop+1;
256
 
                    htop += 2;
257
 
                }
258
 
                *tp = make_list(tailp - 1);
259
 
                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);
260
284
            }
261
285
            switch (primary_tag(obj)) {
262
286
            case TAG_PRIMARY_IMMED1: *tailp = obj; goto L_copy;
268
292
            }
269
293
            
270
294
        case TAG_PRIMARY_BOXED:
271
 
            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);
272
298
                hp++;
273
299
                break;
274
300
            }
 
301
        #endif
275
302
            argp = hp++;
276
303
 
277
304
        L_copy_boxed:
278
 
            objp = boxed_val(obj);
 
305
            objp = boxed_val_rel(obj, src_base);
279
306
            hdr = *objp;
280
307
            switch (hdr & _TAG_HEADER_MASK) {
281
308
            case ARITYVAL_SUBTAG:
282
309
                {
283
310
                    int const_flag = 1; /* assume constant tuple */
284
311
                    i = arityval(hdr);
285
 
                    *argp = make_tuple(htop);
 
312
                    *argp = make_tuple_rel(htop, dst_base);
286
313
                    tp = htop;  /* tp is pointer to new arity value */
287
314
                    *htop++ = *objp++; /* copy arity value */
288
315
                    while (i--) {
311
338
                    while (i--)  {
312
339
                        *tp++ = *objp++;
313
340
                    }
314
 
                    *argp = make_binary(hbot);
 
341
                    *argp = make_binary_rel(hbot, dst_base);
315
342
                    pb = (ProcBin*) hbot;
316
343
                    erts_refc_inc(&pb->val->refc, 2);
317
344
                    pb->next = off_heap->first;
338
365
                        extra_bytes = 0;
339
366
                    } 
340
367
                    real_size = size+extra_bytes;
341
 
                    objp = binary_val(real_bin);
 
368
                    objp = binary_val_rel(real_bin,src_base);
342
369
                    if (thing_subtag(*objp) == HEAP_BINARY_SUBTAG) {
343
370
                        ErlHeapBin* from = (ErlHeapBin *) objp;
344
371
                        ErlHeapBin* to;
368
395
                        off_heap->first = (struct erl_off_heap_header*) to;
369
396
                        OH_OVERHEAD(off_heap, to->size / sizeof(Eterm));
370
397
                    }
371
 
                    *argp = make_binary(hbot);
 
398
                    *argp = make_binary_rel(hbot, dst_base);
372
399
                    if (extra_bytes != 0) {
373
400
                        ErlSubBin* res;
374
401
                        hbot -= ERL_SUB_BIN_SIZE;
380
407
                        res->offs = 0;
381
408
                        res->is_writable = 0;
382
409
                        res->orig = *argp;
383
 
                        *argp = make_binary(hbot);
 
410
                        *argp = make_binary_rel(hbot, dst_base);
384
411
                    }
385
412
                    break;
386
413
                }
400
427
                    off_heap->first = (struct erl_off_heap_header*) funp;
401
428
                    erts_refc_inc(&funp->fe->refc, 2);
402
429
#endif
403
 
                    *argp = make_fun(tp);
 
430
                    *argp = make_fun_rel(tp, dst_base);
404
431
                }
405
432
                break;
406
433
            case EXTERNAL_PID_SUBTAG:
420
447
                  off_heap->first = (struct erl_off_heap_header*)etp;
421
448
                  erts_refc_inc(&etp->node->refc, 2);
422
449
 
423
 
                  *argp = make_external(tp);
 
450
                  *argp = make_external_rel(tp, dst_base);
424
451
                }
425
452
                break;
426
453
            case BIN_MATCHSTATE_SUBTAG:
430
457
                i = thing_arityval(hdr)+1;
431
458
                hbot -= i;
432
459
                tp = hbot;
433
 
                *argp = make_boxed(hbot);
 
460
                *argp = make_boxed_rel(hbot, dst_base);
434
461
                while (i--) {
435
462
                    *tp++ = *objp++;
436
463
                }
450
477
    if (htop != hbot)
451
478
        erl_exit(ERTS_ABORT_EXIT,
452
479
                 "Internal error in copy_struct() when copying %T:"
453
 
                 " htop=%p != hbot=%p (sz=%bpu)\n",
 
480
                 " htop=%p != hbot=%p (sz=%beu)\n",
454
481
                 org_obj, htop, hbot, org_sz); 
455
482
#else
456
483
    if (htop > hbot) {
885
912
 *
886
913
 * NOTE: Assumes that term is a tuple (ptr is an untagged tuple ptr).
887
914
 */
888
 
Eterm
889
 
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
890
921
{
891
922
    Eterm* tp = ptr;
892
923
    Eterm* hp = *hpp;
893
 
    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
894
930
 
895
931
    while (sz--) {
896
932
        Eterm val = *tp++;
901
937
            break;
902
938
        case TAG_PRIMARY_LIST:
903
939
        case TAG_PRIMARY_BOXED:
904
 
            *hp++ = offset_ptr(val, offs);
 
940
            *hp++ = byte_offset_ptr(val, offs);
905
941
            break;
906
942
        case TAG_PRIMARY_HEADER:
907
943
            *hp++ = val;
958
994
        }
959
995
    }
960
996
    *hpp = hp;
961
 
    return make_tuple(ptr + offs); 
 
997
 
 
998
    return res;
962
999
}
963
1000
 
964
1001
/* Move all terms in heap fragments into heap. The terms must be guaranteed to