~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
28
28
#include "bif.h"
29
29
#include "big.h"
30
30
#include "erl_binary.h"
31
 
 
 
31
#include "erl_bits.h"
32
32
 
33
33
Uint erts_allocated_binaries;
 
34
erts_mtx_t erts_bin_alloc_mtx;
34
35
 
35
36
void
36
37
erts_init_binary(void)
37
38
{
38
39
    erts_allocated_binaries = 0;
 
40
    erts_mtx_init(&erts_bin_alloc_mtx, "binary_alloc");
 
41
 
 
42
    /* Verify Binary alignment... */
 
43
    if ((((Uint) &((Binary *) 0)->orig_bytes[0]) % ((Uint) 8)) != 0) {
 
44
        /* I assume that any compiler should be able to optimize this
 
45
           away. If not, this test is not very expensive... */
 
46
        erl_exit(ERTS_ABORT_EXIT,
 
47
                 "Internal error: Address of orig_bytes[0] of a Binary"
 
48
                 "is *not* 8-byte aligned\n");
 
49
    }
39
50
}
40
51
 
41
52
/*
64
75
    bptr = erts_bin_nrml_alloc(len);
65
76
    bptr->flags = 0;
66
77
    bptr->orig_size = len;
67
 
    bptr->refc = 1;
 
78
    erts_refc_init(&bptr->refc, 1);
68
79
    if (buf != NULL) {
69
80
        sys_memcpy(bptr->orig_bytes, buf, len);
70
81
    }
78
89
    pb->next = MSO(p).mso;
79
90
    MSO(p).mso = pb;
80
91
    pb->val = bptr;
81
 
    pb->bytes = bptr->orig_bytes;
 
92
    pb->bytes = (byte*) bptr->orig_bytes;
82
93
 
83
94
    /*
84
95
     * Miscellanous updates. Return the tagged binary.
105
116
    return make_binary(hb);
106
117
}
107
118
 
 
119
#if !defined(HEAP_FRAG_ELIM_TEST)
108
120
/* Like new_binary, but uses ArithAlloc. */
109
121
/* Silly name. Come up with something better. */
110
122
Eterm new_binary_arith(Process *p, byte *buf, int len)
128
140
    bptr = erts_bin_nrml_alloc(len);
129
141
    bptr->flags = 0;
130
142
    bptr->orig_size = len;
131
 
    bptr->refc = 1;
 
143
    erts_refc_init(&bptr->refc, 1);
132
144
    if (buf != NULL) {
133
145
        sys_memcpy(bptr->orig_bytes, buf, len);
134
146
    }
142
154
    pb->next = MSO(p).mso;
143
155
    MSO(p).mso = pb;
144
156
    pb->val = bptr;
145
 
    pb->bytes = bptr->orig_bytes;
 
157
    pb->bytes = (byte*) bptr->orig_bytes;
146
158
 
147
159
    /*
148
160
     * Miscellanous updates. Return the tagged binary.
150
162
    MSO(p).overhead += pb->size / BINARY_OVERHEAD_FACTOR / sizeof(Eterm);
151
163
    return make_binary(pb);
152
164
}
 
165
#endif
153
166
 
154
167
Eterm
155
168
erts_realloc_binary(Eterm bin, size_t size)
164
177
        newbin->orig_size = size;
165
178
        pb->val = newbin;
166
179
        pb->size = size;
167
 
        pb->bytes = newbin->orig_bytes;
 
180
        pb->bytes = (byte*) newbin->orig_bytes;
168
181
        bin = make_binary(pb);
169
182
    }
170
183
    return bin;
171
184
}
172
185
 
 
186
byte*
 
187
erts_get_aligned_binary_bytes(Eterm bin, byte** base_ptr)
 
188
{
 
189
    byte* bytes;
 
190
    Eterm* real_bin;
 
191
    Uint byte_size;
 
192
    Uint offs = 0;
 
193
    Uint bit_offs = 0;
 
194
    
 
195
    if (is_not_binary(bin)) {
 
196
        return NULL;
 
197
    }
 
198
    byte_size = binary_size(bin);
 
199
    real_bin = binary_val(bin);
 
200
    if (*real_bin == HEADER_SUB_BIN) {
 
201
        ErlSubBin* sb = (ErlSubBin *) real_bin;
 
202
        if (sb->bitsize) {
 
203
            return NULL;
 
204
        }
 
205
        offs = sb->offs;
 
206
        bit_offs = sb->bitoffs;
 
207
        real_bin = binary_val(sb->orig);
 
208
    }
 
209
    if (*real_bin == HEADER_PROC_BIN) {
 
210
        bytes = ((ProcBin *) real_bin)->bytes + offs;
 
211
    } else {
 
212
        bytes = (byte *)(&(((ErlHeapBin *) real_bin)->data)) + offs;
 
213
    }
 
214
    if (bit_offs) {
 
215
        byte* buf = (byte *) erts_alloc(ERTS_ALC_T_TMP, byte_size);
 
216
 
 
217
        erts_copy_bits(bytes, bit_offs, 1, buf, 0, 1, byte_size*8);
 
218
        *base_ptr = buf;
 
219
        bytes = buf;
 
220
    }
 
221
    return bytes;
 
222
}
 
223
 
 
224
static Eterm
 
225
bin_bytes_to_list(Eterm previous, Eterm* hp, byte* bytes, Uint size, Uint bitoffs)
 
226
{
 
227
    if (bitoffs == 0) {
 
228
        while (size) {
 
229
            previous = CONS(hp, make_small(bytes[--size]), previous);
 
230
            hp += 2;
 
231
        }
 
232
    } else {
 
233
        byte present;
 
234
        byte next;
 
235
        next = bytes[size];
 
236
        while (size) {
 
237
            present = next;
 
238
            next = bytes[--size];
 
239
            previous = CONS(hp, make_small(((present >> (8-bitoffs)) |
 
240
                                            (next << bitoffs)) & 255), previous);
 
241
            hp += 2;
 
242
        }
 
243
    }
 
244
    return previous;
 
245
}
 
246
 
 
247
 
173
248
BIF_RETTYPE binary_to_list_1(BIF_ALIST_1)
174
249
{
 
250
    Eterm real_bin;
 
251
    Uint offset;
175
252
    Uint size;
176
 
    Eterm previous;
 
253
    Uint bitsize;
 
254
    Uint bitoffs;
 
255
    byte* bytes;
 
256
    Eterm previous = NIL;
177
257
    Eterm* hp;
178
 
    byte* bufp;
179
258
 
180
259
    if (is_not_binary(BIF_ARG_1)) {
181
260
        BIF_ERROR(BIF_P, BADARG);
182
261
    }
183
 
 
184
262
    size = binary_size(BIF_ARG_1);
185
 
    hp = HAlloc(BIF_P, 2 * size);
186
 
    GET_BINARY_BYTES(BIF_ARG_1, bufp);
 
263
    ERTS_GET_REAL_BIN(BIF_ARG_1, real_bin, offset, bitoffs, bitsize);
 
264
    bytes = binary_bytes(real_bin)+offset;
 
265
    if (bitsize == 0) {
 
266
        hp = HAlloc(BIF_P, 2 * size);
 
267
    } else {
 
268
        ErlSubBin* last;
187
269
 
188
 
    previous = NIL;
189
 
    while (size) {
190
 
        previous = CONS(hp, make_small(bufp[--size]), previous);
 
270
        hp = HAlloc(BIF_P, ERL_SUB_BIN_SIZE+2+2*size);
 
271
        last = (ErlSubBin *) hp;
 
272
        last->thing_word = HEADER_SUB_BIN;
 
273
        last->size = 0;
 
274
        last->bitsize = bitsize;
 
275
        last->offs = offset+size;
 
276
        last->bitoffs = bitoffs;
 
277
        last->orig = real_bin;
 
278
        hp += ERL_SUB_BIN_SIZE;
 
279
        previous = CONS(hp, make_binary(last), previous);
191
280
        hp += 2;
192
281
    }
193
 
    BIF_RET(previous);
 
282
    BIF_RET(bin_bytes_to_list(previous, hp, bytes, size, bitoffs));
194
283
}
195
284
 
196
285
BIF_RETTYPE binary_to_list_3(BIF_ALIST_3)
197
286
{
198
 
    Eterm previous;
199
287
    byte* bytes;
200
 
    int size;
 
288
    Uint size;
 
289
    Uint bitoffs;
 
290
    Uint bitsize;
201
291
    Uint i;
202
292
    Uint start;
203
293
    Uint stop;
204
294
    Eterm* hp;
205
295
 
206
296
    if (is_not_binary(BIF_ARG_1)) {
207
 
        goto error;
 
297
    error:
 
298
        BIF_ERROR(BIF_P, BADARG);
208
299
    }
209
300
    if (!term_to_Uint(BIF_ARG_2, &start) || !term_to_Uint(BIF_ARG_3, &stop)) {
210
301
        goto error;
211
302
    }
212
303
    size = binary_size(BIF_ARG_1);
213
 
    GET_BINARY_BYTES(BIF_ARG_1, bytes);
214
 
    if (start < 1 || start > size || stop < 1 || stop > size || stop < start) {
 
304
    ERTS_GET_BINARY_BYTES(BIF_ARG_1, bytes, bitoffs, bitsize);
 
305
    if (start < 1 || start > size || stop < 1 ||
 
306
        stop > size || stop < start || bitsize != 0) {
215
307
        goto error;
216
308
    }
217
 
 
218
309
    i = stop-start+1;
219
310
    hp = HAlloc(BIF_P, 2*i);
220
 
    previous = NIL;
221
 
    bytes += stop;
222
 
    while (i-- > 0) {
223
 
        previous = CONS(hp, make_small(*--bytes), previous);
224
 
        hp += 2;
225
 
    }
226
 
    BIF_RET(previous);
227
 
 
228
 
 error:
229
 
    BIF_ERROR(BIF_P, BADARG);
 
311
    BIF_RET(bin_bytes_to_list(NIL, hp, bytes+start-1, i, bitoffs));
230
312
}
231
313
 
232
314
 
236
318
BIF_RETTYPE list_to_binary_1(BIF_ALIST_1)
237
319
{
238
320
    Eterm bin;
239
 
    int i;
240
 
    byte* bytes;
241
 
 
242
 
    if (is_nil(BIF_ARG_1)) {
243
 
        BIF_RET(new_binary(BIF_P,(byte*)"",0));
244
 
    }
245
 
    if (is_not_list(BIF_ARG_1)) {
246
 
    error:
247
 
        BIF_ERROR(BIF_P, BADARG);
248
 
    }
249
 
    if ((i = io_list_len(BIF_ARG_1)) < 0) {
250
 
        goto error;
251
 
    }
252
 
    bin = new_binary(BIF_P, (byte *)NULL, i);
253
 
    GET_BINARY_BYTES(bin, bytes);
254
 
    if (io_list_to_buf(BIF_ARG_1, (char*) bytes, i) < 0) {
255
 
        goto error;
 
321
    int i,offset;
 
322
    byte* bytes;
 
323
    ErlSubBin* sb1; 
 
324
    Eterm* hp;
 
325
    
 
326
    if (is_nil(BIF_ARG_1)) {
 
327
        BIF_RET(new_binary(BIF_P,(byte*)"",0));
 
328
    }
 
329
    if (is_not_list(BIF_ARG_1)) {
 
330
    error:
 
331
        BIF_ERROR(BIF_P, BADARG);
 
332
    }
 
333
    if ((i = io_list_len(BIF_ARG_1)) < 0) {
 
334
        goto error;
 
335
    }
 
336
    bin = new_binary(BIF_P, (byte *)NULL, i);
 
337
    bytes = binary_bytes(bin);
 
338
    offset = io_list_to_buf2(BIF_ARG_1, (char*) bytes, i);
 
339
    if (offset < 0) {
 
340
        goto error;
 
341
    } else if (offset > 0) {
 
342
        hp = HAlloc(BIF_P, ERL_SUB_BIN_SIZE);
 
343
        sb1 = (ErlSubBin *) hp;
 
344
        sb1->thing_word = HEADER_SUB_BIN;
 
345
        sb1->size = i-1;
 
346
        sb1->offs = 0;
 
347
        sb1->orig = bin;
 
348
        sb1->bitoffs = 0;
 
349
        sb1->bitsize = offset;
 
350
        hp += ERL_SUB_BIN_SIZE;
 
351
        bin = make_binary(sb1);
 
352
    }
 
353
    
 
354
    BIF_RET(bin);
 
355
}
 
356
 
 
357
/* Turn a possibly deep list of ints (and binaries) into */
 
358
/* One large binary object                               */
 
359
 
 
360
BIF_RETTYPE iolist_to_binary_1(BIF_ALIST_1)
 
361
{
 
362
    Eterm bin;
 
363
    int i, offset;
 
364
    byte* bytes;
 
365
    ErlSubBin* sb1; 
 
366
    Eterm* hp;
 
367
 
 
368
    if (is_binary(BIF_ARG_1)) {
 
369
        BIF_RET(BIF_ARG_1);
 
370
    }
 
371
    if (is_nil(BIF_ARG_1)) {
 
372
        BIF_RET(new_binary(BIF_P,(byte*)"",0));
 
373
    }
 
374
    if (is_not_list(BIF_ARG_1)) {
 
375
    error:
 
376
        BIF_ERROR(BIF_P, BADARG);
 
377
    }
 
378
    if ((i = io_list_len(BIF_ARG_1)) < 0) {
 
379
        goto error;
 
380
    }
 
381
    bin = new_binary(BIF_P, (byte *)NULL, i);
 
382
    bytes = binary_bytes(bin);
 
383
    if ((offset = io_list_to_buf(BIF_ARG_1, (char*) bytes, i)) < 0) {
 
384
        goto error;
 
385
    } else if (offset > 0) {
 
386
        hp = HAlloc(BIF_P, ERL_SUB_BIN_SIZE);
 
387
        sb1 = (ErlSubBin *) hp;
 
388
        sb1->thing_word = HEADER_SUB_BIN;
 
389
        sb1->size = i-1;
 
390
        sb1->offs = 0;
 
391
        sb1->orig = bin;
 
392
        sb1->bitoffs = 0;
 
393
        sb1->bitsize = offset;
 
394
        hp += ERL_SUB_BIN_SIZE;
 
395
        bin = make_binary(sb1);
256
396
    }
257
397
    BIF_RET(bin);
258
398
}
265
405
    size_t orig_size;
266
406
    Eterm orig;
267
407
    Uint offset;
 
408
    Uint bit_offset;
 
409
    Uint bit_size;
268
410
    Eterm* hp;
269
411
 
270
412
    if (is_not_binary(BIF_ARG_1)) {
278
420
        goto error;
279
421
    }
280
422
    hp = HAlloc(BIF_P, 2*ERL_SUB_BIN_SIZE+3);
281
 
    GET_REAL_BIN(BIF_ARG_1, orig, offset);
 
423
    ERTS_GET_REAL_BIN(BIF_ARG_1, orig, offset, bit_offset, bit_size);
282
424
    sb1 = (ErlSubBin *) hp;
283
425
    sb1->thing_word = HEADER_SUB_BIN;
284
426
    sb1->size = pos;
285
427
    sb1->offs = offset;
286
428
    sb1->orig = orig;
 
429
    sb1->bitoffs = bit_offset;
 
430
    sb1->bitsize = 0;
287
431
    hp += ERL_SUB_BIN_SIZE;
288
432
 
289
433
    sb2 = (ErlSubBin *) hp;
291
435
    sb2->size = orig_size - pos;
292
436
    sb2->offs = offset + pos;
293
437
    sb2->orig = orig;
 
438
    sb2->bitoffs = bit_offset;
 
439
    sb2->bitsize = bit_size;    /* The extra bits go into the second binary. */
294
440
    hp += ERL_SUB_BIN_SIZE;
295
441
 
296
442
    return TUPLE2(hp, make_binary(sb1), make_binary(sb2));
301
447
{
302
448
    while (pb != NULL) {
303
449
        ProcBin* next = pb->next;
304
 
        ASSERT(pb->val->refc > 0);
305
 
        pb->val->refc--;
306
 
        if (pb->val->refc == 0) {
 
450
        if (erts_refc_dectest(&pb->val->refc, 0) == 0) {
307
451
            if (pb->val->flags & BIN_FLAG_MATCH_PROG) {
308
452
                erts_match_set_free(pb->val);
309
453
            } else {