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

« back to all changes in this revision

Viewing changes to erts/emulator/beam/erl_binary.h

  • 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 2000-2009. All Rights Reserved.
5
 
 * 
 
3
 *
 
4
 * Copyright Ericsson AB 2000-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
 
21
21
#define __ERL_BINARY_H
22
22
 
23
23
#include "erl_threads.h"
 
24
#include "bif.h"
24
25
 
25
26
/*
26
27
 * Maximum number of bytes to place in a heap binary.
70
71
 */
71
72
 
72
73
#define binary_size(Bin) (binary_val(Bin)[1])
 
74
#define binary_size_rel(Bin,BasePtr) (binary_val_rel(Bin,BasePtr)[1])
73
75
 
74
76
#define binary_bitsize(Bin)                     \
75
77
  ((*binary_val(Bin) == HEADER_SUB_BIN) ?       \
92
94
 * Bitsize: output variable (Uint)
93
95
 */
94
96
 
95
 
#define ERTS_GET_BINARY_BYTES(Bin,Bytep,Bitoffs,Bitsize)                \
 
97
#define ERTS_GET_BINARY_BYTES(Bin,Bytep,Bitoffs,Bitsize) \
 
98
     ERTS_GET_BINARY_BYTES_REL(Bin,Bytep,Bitoffs,Bitsize,NULL)
 
99
 
 
100
#define ERTS_GET_BINARY_BYTES_REL(Bin,Bytep,Bitoffs,Bitsize,BasePtr)    \
96
101
do {                                                                    \
97
 
    Eterm* _real_bin = binary_val(Bin);                                 \
 
102
    Eterm* _real_bin = binary_val_rel(Bin,BasePtr);                     \
98
103
    Uint _offs = 0;                                                     \
99
104
    Bitoffs = Bitsize = 0;                                              \
100
105
    if (*_real_bin == HEADER_SUB_BIN) {                                 \
102
107
        _offs = _sb->offs;                                              \
103
108
        Bitoffs = _sb->bitoffs;                                         \
104
109
        Bitsize = _sb->bitsize;                                         \
105
 
        _real_bin = binary_val(_sb->orig);                              \
 
110
        _real_bin = binary_val_rel(_sb->orig,BasePtr);                  \
106
111
    }                                                                   \
107
112
    if (*_real_bin == HEADER_PROC_BIN) {                                \
108
113
        Bytep = ((ProcBin *) _real_bin)->bytes + _offs;                 \
124
129
 * BitSize: Extra bit size (Uint)
125
130
 */
126
131
 
127
 
#define ERTS_GET_REAL_BIN(Bin, RealBin, ByteOffset, BitOffset, BitSize) \
 
132
#define ERTS_GET_REAL_BIN(Bin, RealBin, ByteOffset, BitOffset, BitSize) \
 
133
     ERTS_GET_REAL_BIN_REL(Bin, RealBin, ByteOffset, BitOffset, BitSize, NULL)
 
134
 
 
135
#define ERTS_GET_REAL_BIN_REL(Bin, RealBin, ByteOffset, BitOffset, BitSize, BasePtr) \
128
136
  do {                                                                  \
129
 
    ErlSubBin* _sb = (ErlSubBin *) binary_val(Bin);                     \
 
137
    ErlSubBin* _sb = (ErlSubBin *) binary_val_rel(Bin,BasePtr);         \
130
138
    if (_sb->thing_word == HEADER_SUB_BIN) {                            \
131
139
      RealBin = _sb->orig;                                              \
132
140
      ByteOffset = _sb->offs;                                           \
150
158
 
151
159
void erts_init_binary(void);
152
160
 
153
 
byte* erts_get_aligned_binary_bytes(Eterm, byte**);
 
161
byte* erts_get_aligned_binary_bytes_extra(Eterm, byte**, ErtsAlcType_t, unsigned extra);
 
162
/* Used by unicode module */
 
163
Eterm erts_bin_bytes_to_list(Eterm previous, Eterm* hp, byte* bytes, Uint size, Uint bitoffs);
 
164
 
 
165
/*
 
166
 * Common implementation for erlang:list_to_binary/1 and binary:list_to_bin/1
 
167
 */
 
168
 
 
169
BIF_RETTYPE erts_list_to_binary_bif(Process *p, Eterm arg);
 
170
BIF_RETTYPE erts_gc_binary_part(Process *p, Eterm *reg, Eterm live, int range_is_tuple);
 
171
BIF_RETTYPE erts_binary_part(Process *p, Eterm binary, Eterm epos, Eterm elen);
 
172
 
154
173
 
155
174
#if defined(__i386__) || !defined(__GNUC__)
156
175
/*
164
183
#endif
165
184
 
166
185
#define ERTS_CHK_BIN_ALIGNMENT(B) \
167
 
  do { ASSERT(!(B) || (((Uint) &((Binary *)(B))->orig_bytes[0]) & ERTS_BIN_ALIGNMENT_MASK) == ((Uint) 0)) } while(0)
 
186
  do { ASSERT(!(B) || (((UWord) &((Binary *)(B))->orig_bytes[0]) & ERTS_BIN_ALIGNMENT_MASK) == ((UWord) 0)) } while(0)
168
187
 
 
188
ERTS_GLB_INLINE byte* erts_get_aligned_binary_bytes(Eterm bin, byte** base_ptr);
169
189
ERTS_GLB_INLINE void erts_free_aligned_binary_bytes(byte* buf);
 
190
ERTS_GLB_INLINE void erts_free_aligned_binary_bytes_extra(byte* buf, ErtsAlcType_t);
170
191
ERTS_GLB_INLINE Binary *erts_bin_drv_alloc_fnf(Uint size);
171
192
ERTS_GLB_INLINE Binary *erts_bin_drv_alloc(Uint size);
172
193
ERTS_GLB_INLINE Binary *erts_bin_nrml_alloc(Uint size);
178
199
 
179
200
#if ERTS_GLB_INLINE_INCL_FUNC_DEF
180
201
 
 
202
#include <stddef.h> /* offsetof */
 
203
 
 
204
ERTS_GLB_INLINE byte*
 
205
erts_get_aligned_binary_bytes(Eterm bin, byte** base_ptr)
 
206
{
 
207
    return erts_get_aligned_binary_bytes_extra(bin, base_ptr, ERTS_ALC_T_TMP, 0);
 
208
}
 
209
 
181
210
ERTS_GLB_INLINE void
182
 
erts_free_aligned_binary_bytes(byte* buf)
 
211
erts_free_aligned_binary_bytes_extra(byte* buf, ErtsAlcType_t allocator)
183
212
{
184
213
    if (buf) {
185
 
        erts_free(ERTS_ALC_T_TMP, (void *) buf);
 
214
        erts_free(allocator, (void *) buf);
186
215
    }
187
216
}
188
217
 
 
218
ERTS_GLB_INLINE void
 
219
erts_free_aligned_binary_bytes(byte* buf)
 
220
{
 
221
    erts_free_aligned_binary_bytes_extra(buf,ERTS_ALC_T_TMP);
 
222
}
 
223
 
 
224
/* Explicit extra bytes allocated to counter buggy drivers.
 
225
** These extra bytes where earlier (< R13B04) added by an alignment-bug
 
226
** in this code. Do we dare remove this in some major release (R14?) maybe?
 
227
*/
 
228
#ifdef DEBUG
 
229
#  define CHICKEN_PAD 0
 
230
#else
 
231
#  define CHICKEN_PAD (sizeof(void*) - 1)
 
232
#endif
 
233
 
189
234
ERTS_GLB_INLINE Binary *
190
235
erts_bin_drv_alloc_fnf(Uint size)
191
236
{
192
 
    Uint bsize = sizeof(Binary) - 1 + size;
 
237
    Uint bsize = ERTS_SIZEOF_Binary(size) + CHICKEN_PAD;
193
238
    void *res;
194
239
    res = erts_alloc_fnf(ERTS_ALC_T_DRV_BINARY, bsize);
195
240
    ERTS_CHK_BIN_ALIGNMENT(res);
199
244
ERTS_GLB_INLINE Binary *
200
245
erts_bin_drv_alloc(Uint size)
201
246
{
202
 
    Uint bsize = sizeof(Binary) - 1 + size;
 
247
    Uint bsize = ERTS_SIZEOF_Binary(size) + CHICKEN_PAD;
203
248
    void *res;
204
249
    res = erts_alloc(ERTS_ALC_T_DRV_BINARY, bsize);
205
250
    ERTS_CHK_BIN_ALIGNMENT(res);
210
255
ERTS_GLB_INLINE Binary *
211
256
erts_bin_nrml_alloc(Uint size)
212
257
{
213
 
    Uint bsize = sizeof(Binary) - 1 + size;
 
258
    Uint bsize = ERTS_SIZEOF_Binary(size) + CHICKEN_PAD;
214
259
    void *res;
215
260
    res = erts_alloc(ERTS_ALC_T_BINARY, bsize);
216
261
    ERTS_CHK_BIN_ALIGNMENT(res);
221
266
erts_bin_realloc_fnf(Binary *bp, Uint size)
222
267
{
223
268
    Binary *nbp;
224
 
    Uint bsize = sizeof(Binary) - 1 + size;
 
269
    Uint bsize = ERTS_SIZEOF_Binary(size) + CHICKEN_PAD;
225
270
    ASSERT((bp->flags & BIN_FLAG_MAGIC) == 0);
226
271
    if (bp->flags & BIN_FLAG_DRV)
227
272
        nbp = erts_realloc_fnf(ERTS_ALC_T_DRV_BINARY, (void *) bp, bsize);
235
280
erts_bin_realloc(Binary *bp, Uint size)
236
281
{
237
282
    Binary *nbp;
238
 
    Uint bsize = sizeof(Binary) - 1 + size;
 
283
    Uint bsize = ERTS_SIZEOF_Binary(size) + CHICKEN_PAD;
239
284
    ASSERT((bp->flags & BIN_FLAG_MAGIC) == 0);
240
285
    if (bp->flags & BIN_FLAG_DRV)
241
286
        nbp = erts_realloc_fnf(ERTS_ALC_T_DRV_BINARY, (void *) bp, bsize);
265
310
ERTS_GLB_INLINE Binary *
266
311
erts_create_magic_binary(Uint size, void (*destructor)(Binary *))
267
312
{
268
 
    Uint bsize = sizeof(Binary) - 1 + sizeof(ErtsBinaryMagicPart) - 1 + size;
 
313
    Uint bsize = ERTS_MAGIC_BIN_SIZE(size);
269
314
    Binary* bptr = erts_alloc_fnf(ERTS_ALC_T_BINARY, bsize);
270
315
    if (!bptr)
271
316
        erts_alloc_n_enomem(ERTS_ALC_T2N(ERTS_ALC_T_BINARY), bsize);
272
317
    ERTS_CHK_BIN_ALIGNMENT(bptr);
273
318
    bptr->flags = BIN_FLAG_MAGIC;
274
 
    bptr->orig_size = sizeof(ErtsBinaryMagicPart) - 1 + size;
 
319
    bptr->orig_size = ERTS_MAGIC_BIN_ORIG_SIZE(size);
275
320
    erts_refc_init(&bptr->refc, 0);
276
321
    ERTS_MAGIC_BIN_DESTRUCTOR(bptr) = destructor;
277
322
    return bptr;