1 /*
2  * %CopyrightBegin%
3  *
4  * Copyright Ericsson AB 2000-2020. All Rights Reserved.
5  *
6  * Licensed under the Apache License, Version 2.0 (the "License");
7  * you may not use this file except in compliance with the License.
8  * You may obtain a copy of the License at
9  *
10  *     http://www.apache.org/licenses/LICENSE-2.0
11  *
12  * Unless required by applicable law or agreed to in writing, software
13  * distributed under the License is distributed on an "AS IS" BASIS,
14  * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15  * See the License for the specific language governing permissions and
16  * limitations under the License.
17  *
18  * %CopyrightEnd%
19  */
20 
21 #ifndef ERL_BINARY_H__TYPES__
22 #define ERL_BINARY_H__TYPES__
23 
24 /*
25 ** Just like the driver binary but with initial flags
26 ** Note that the two structures Binary and ErlDrvBinary HAVE to
27 ** be equal except for extra fields in the beginning of the struct.
28 ** ErlDrvBinary is defined in erl_driver.h.
29 ** When driver_alloc_binary is called, a Binary is allocated, but
30 ** the pointer returned is to the address of the first element that
31 ** also occurs in the ErlDrvBinary struct (driver.*binary takes care if this).
32 ** The driver need never know about additions to the internal Binary of the
33 ** emulator. One should however NEVER be sloppy when mixing ErlDrvBinary
34 ** and Binary, the macros below can convert one type to the other, as they both
35 ** in reality are equal.
36 */
37 
38 #ifdef ARCH_32
39  /* *DO NOT USE* only for alignment. */
40 #define ERTS_BINARY_STRUCT_ALIGNMENT Uint32 align__;
41 #else
42 #define ERTS_BINARY_STRUCT_ALIGNMENT
43 #endif
44 
45 /* Add fields in binary_internals, otherwise the drivers crash */
46 struct binary_internals {
47     UWord flags;
48     erts_refc_t refc;
49     ERTS_BINARY_STRUCT_ALIGNMENT
50 };
51 
52 
53 typedef struct binary {
54     struct binary_internals intern;
55     SWord orig_size;
56     char orig_bytes[1]; /* to be continued */
57 } Binary;
58 
59 #define ERTS_SIZEOF_Binary(Sz) \
60     (offsetof(Binary,orig_bytes) + (Sz))
61 
62 #if ERTS_REF_NUMBERS != 3
63 #error "Update ErtsMagicBinary"
64 #endif
65 
66 typedef struct magic_binary ErtsMagicBinary;
67 struct magic_binary {
68     struct binary_internals intern;
69     SWord orig_size;
70     int (*destructor)(Binary *);
71     Uint32 refn[ERTS_REF_NUMBERS];
72     ErtsAlcType_t alloc_type;
73     union {
74         struct {
75             ERTS_BINARY_STRUCT_ALIGNMENT
76             char data[1];
77         } aligned;
78         struct {
79             char data[1];
80         } unaligned;
81     } u;
82 };
83 
84 #define ERTS_MAGIC_BIN_BYTES_TO_ALIGN \
85     (offsetof(ErtsMagicBinary,u.aligned.data) - \
86      offsetof(ErtsMagicBinary,u.unaligned.data))
87 
88 typedef union {
89     Binary binary;
90     ErtsMagicBinary magic_binary;
91     struct {
92 	struct binary_internals intern;
93 	ErlDrvBinary binary;
94     } driver;
95 } ErtsBinary;
96 
97 /*
98  * 'Binary' alignment:
99  *   Address of orig_bytes[0] of a Binary should always be 8-byte aligned.
100  * It is assumed that the flags, refc, and orig_size fields are 4 bytes on
101  * 32-bits architectures and 8 bytes on 64-bits architectures.
102  */
103 
104 #define ERTS_MAGIC_BIN_REFN(BP) \
105   ((ErtsBinary *) (BP))->magic_binary.refn
106 #define ERTS_MAGIC_BIN_ATYPE(BP) \
107   ((ErtsBinary *) (BP))->magic_binary.alloc_type
108 #define ERTS_MAGIC_DATA_OFFSET \
109   (offsetof(ErtsMagicBinary,u.aligned.data) - offsetof(Binary,orig_bytes))
110 #define ERTS_MAGIC_BIN_DESTRUCTOR(BP) \
111   ((ErtsBinary *) (BP))->magic_binary.destructor
112 #define ERTS_MAGIC_BIN_DATA(BP) \
113   ((void *) ((ErtsBinary *) (BP))->magic_binary.u.aligned.data)
114 #define ERTS_MAGIC_BIN_DATA_SIZE(BP) \
115   ((BP)->orig_size - ERTS_MAGIC_DATA_OFFSET)
116 #define ERTS_MAGIC_DATA_OFFSET \
117   (offsetof(ErtsMagicBinary,u.aligned.data) - offsetof(Binary,orig_bytes))
118 #define ERTS_MAGIC_BIN_ORIG_SIZE(Sz) \
119   (ERTS_MAGIC_DATA_OFFSET + (Sz))
120 #define ERTS_MAGIC_BIN_SIZE(Sz) \
121   (offsetof(ErtsMagicBinary,u.aligned.data) + (Sz))
122 #define ERTS_MAGIC_BIN_FROM_DATA(DATA) \
123   ((ErtsBinary*)((char*)(DATA) - offsetof(ErtsMagicBinary,u.aligned.data)))
124 
125 /* On 32-bit arch these macro variants will save memory
126    by not forcing 8-byte alignment for the magic payload.
127 */
128 #define ERTS_MAGIC_BIN_UNALIGNED_DATA(BP) \
129   ((void *) ((ErtsBinary *) (BP))->magic_binary.u.unaligned.data)
130 #define ERTS_MAGIC_UNALIGNED_DATA_OFFSET \
131   (offsetof(ErtsMagicBinary,u.unaligned.data) - offsetof(Binary,orig_bytes))
132 #define ERTS_MAGIC_BIN_UNALIGNED_DATA_SIZE(BP) \
133   ((BP)->orig_size - ERTS_MAGIC_UNALIGNED_DATA_OFFSET)
134 #define ERTS_MAGIC_BIN_UNALIGNED_ORIG_SIZE(Sz) \
135   (ERTS_MAGIC_UNALIGNED_DATA_OFFSET + (Sz))
136 #define ERTS_MAGIC_BIN_UNALIGNED_SIZE(Sz) \
137   (offsetof(ErtsMagicBinary,u.unaligned.data) + (Sz))
138 #define ERTS_MAGIC_BIN_FROM_UNALIGNED_DATA(DATA) \
139   ((ErtsBinary*)((char*)(DATA) - offsetof(ErtsMagicBinary,u.unaligned.data)))
140 
141 
142 #define Binary2ErlDrvBinary(B) (&((ErtsBinary *) (B))->driver.binary)
143 #define ErlDrvBinary2Binary(D) ((Binary *) \
144 				(((char *) (D)) \
145 				 - offsetof(ErtsBinary, driver.binary)))
146 
147 /* A "magic" binary flag */
148 #define BIN_FLAG_MAGIC      1
149 #define BIN_FLAG_DRV        2
150 
151 #endif /* ERL_BINARY_H__TYPES__ */
152 
153 #if !defined(ERL_BINARY_H__) && !defined(ERTS_BINARY_TYPES_ONLY__)
154 #define ERL_BINARY_H__
155 
156 #include "erl_threads.h"
157 #include "bif.h"
158 #include "erl_bif_unique.h"
159 #include "erl_bits.h"
160 
161 /*
162  * Maximum number of bytes to place in a heap binary.
163  */
164 
165 #define ERL_ONHEAP_BIN_LIMIT 64
166 
167 #define ERL_SUB_BIN_SIZE (sizeof(ErlSubBin)/sizeof(Eterm))
168 #define HEADER_SUB_BIN	_make_header(ERL_SUB_BIN_SIZE-2,_TAG_HEADER_SUB_BIN)
169 
170 /*
171  * This structure represents a HEAP_BINARY.
172  */
173 
174 typedef struct erl_heap_bin {
175     Eterm thing_word;		/* Subtag HEAP_BINARY_SUBTAG. */
176     Uint size;			/* Binary size in bytes. */
177     Eterm data[1];		/* The data in the binary. */
178 } ErlHeapBin;
179 
180 #define heap_bin_size(num_bytes)		\
181   (sizeof(ErlHeapBin)/sizeof(Eterm) - 1 +	\
182    ((num_bytes)+sizeof(Eterm)-1)/sizeof(Eterm))
183 
184 #define header_heap_bin(num_bytes) \
185   _make_header(heap_bin_size(num_bytes)-1,_TAG_HEADER_HEAP_BIN)
186 
187 /*
188  * Get the size in bytes of any type of binary.
189  */
190 
191 #define binary_size(Bin) (binary_val(Bin)[1])
192 
193 #define binary_bitsize(Bin)			\
194   ((*binary_val(Bin) == HEADER_SUB_BIN) ?	\
195    ((ErlSubBin *) binary_val(Bin))->bitsize:	\
196    0)
197 
198 #define binary_bitoffset(Bin)			\
199   ((*binary_val(Bin) == HEADER_SUB_BIN) ?	\
200    ((ErlSubBin *) binary_val(Bin))->bitoffs:	\
201    0)
202 
203 /*
204  * Get the pointer to the actual data bytes in a binary.
205  * Works for any type of binary. Always use binary_bytes() if
206  * you know that the binary cannot be a sub binary.
207  *
208  * Bin: input variable (Eterm)
209  * Bytep: output variable (byte *)
210  * Bitoffs: output variable (Uint)
211  * Bitsize: output variable (Uint)
212  */
213 
214 #define ERTS_GET_BINARY_BYTES(Bin,Bytep,Bitoffs,Bitsize)                \
215 do {									\
216     Eterm* _real_bin = binary_val(Bin);		                	\
217     Uint _offs = 0;							\
218     Bitoffs = Bitsize = 0;						\
219     if (*_real_bin == HEADER_SUB_BIN) {					\
220 	ErlSubBin* _sb = (ErlSubBin *) _real_bin;			\
221 	_offs = _sb->offs;						\
222         Bitoffs = _sb->bitoffs;						\
223         Bitsize = _sb->bitsize;						\
224 	_real_bin = binary_val(_sb->orig);	        		\
225     }									\
226     if (*_real_bin == HEADER_PROC_BIN) {				\
227 	Bytep = ((ProcBin *) _real_bin)->bytes + _offs;			\
228     } else {								\
229 	Bytep = (byte *)(&(((ErlHeapBin *) _real_bin)->data)) + _offs;	\
230     }									\
231 } while (0)
232 
233 /*
234  * Get the real binary from any binary type, where "real" means
235  * a REFC or HEAP binary. Also get the byte and bit offset into the
236  * real binary. Useful if you want to build a SUB binary from
237  * any binary.
238  *
239  * Bin: Input variable (Eterm)
240  * RealBin: Output variable (Eterm)
241  * ByteOffset: Output variable (Uint)
242  * BitOffset: Offset in bits (Uint)
243  * BitSize: Extra bit size (Uint)
244  */
245 
246 #define ERTS_GET_REAL_BIN(Bin, RealBin, ByteOffset, BitOffset, BitSize) \
247   do {									\
248     ErlSubBin* _sb = (ErlSubBin *) binary_val(Bin);	                \
249     if (_sb->thing_word == HEADER_SUB_BIN) {				\
250       RealBin = _sb->orig;						\
251       ByteOffset = _sb->offs;						\
252       BitOffset = _sb->bitoffs;						\
253       BitSize = _sb->bitsize;						\
254     } else {								\
255       RealBin = Bin;							\
256       ByteOffset = BitOffset = BitSize = 0;				\
257     }									\
258   } while (0)
259 
260 /*
261  * Get a pointer to the binary bytes, for a heap or refc binary
262  * (NOT sub binary).
263  */
264 #define binary_bytes(Bin)						\
265   (*binary_val(Bin) == HEADER_PROC_BIN ?				\
266    ((ProcBin *) binary_val(Bin))->bytes :				\
267    (ASSERT(thing_subtag(*binary_val(Bin)) == HEAP_BINARY_SUBTAG),	\
268    (byte *)(&(((ErlHeapBin *) binary_val(Bin))->data))))
269 
270 void erts_init_binary(void);
271 
272 byte* erts_get_aligned_binary_bytes_extra(Eterm, byte**, ErtsAlcType_t, unsigned extra);
273 /* Used by unicode module */
274 Eterm erts_bin_bytes_to_list(Eterm previous, Eterm* hp, byte* bytes, Uint size, Uint bitoffs);
275 
276 /*
277  * Common implementation for erlang:list_to_binary/1 and binary:list_to_bin/1
278  */
279 
280 BIF_RETTYPE erts_list_to_binary_bif(Process *p, Eterm arg, Export *bif);
281 BIF_RETTYPE erts_binary_part(Process *p, Eterm binary, Eterm epos, Eterm elen);
282 
283 
284 typedef union {
285     /*
286      * These two are almost always of
287      * the same size, but when fallback
288      * atomics are used they might
289      * differ in size.
290      */
291     erts_atomic_t smp_atomic_word;
292     erts_atomic_t atomic_word;
293 } ErtsMagicIndirectionWord;
294 
295 #if defined(__i386__) || !defined(__GNUC__)
296 /*
297  * Doubles aren't required to be 8-byte aligned on intel x86.
298  * (if not gnuc we don't know if __i386__ is defined on x86;
299  *  therefore, assume intel x86...)
300  */
301 #  define ERTS_BIN_ALIGNMENT_MASK ((Uint) 3)
302 #else
303 #  define ERTS_BIN_ALIGNMENT_MASK ((Uint) 7)
304 #endif
305 
306 #define ERTS_CHK_BIN_ALIGNMENT(B) \
307   do { ASSERT(!(B) || (((UWord) &((Binary *)(B))->orig_bytes[0]) & ERTS_BIN_ALIGNMENT_MASK) == ((UWord) 0)); } while(0)
308 
309 ERTS_GLB_INLINE byte* erts_get_aligned_binary_bytes(Eterm bin, byte** base_ptr);
310 ERTS_GLB_INLINE void erts_free_aligned_binary_bytes(byte* buf);
311 ERTS_GLB_INLINE void erts_free_aligned_binary_bytes_extra(byte* buf, ErtsAlcType_t);
312 ERTS_GLB_INLINE Binary *erts_bin_drv_alloc_fnf(Uint size);
313 ERTS_GLB_INLINE Binary *erts_bin_drv_alloc(Uint size);
314 ERTS_GLB_INLINE Binary *erts_bin_nrml_alloc_fnf(Uint size);
315 ERTS_GLB_INLINE Binary *erts_bin_nrml_alloc(Uint size);
316 ERTS_GLB_INLINE Binary *erts_bin_realloc_fnf(Binary *bp, Uint size);
317 ERTS_GLB_INLINE Binary *erts_bin_realloc(Binary *bp, Uint size);
318 ERTS_GLB_INLINE void erts_magic_binary_free(Binary *bp);
319 ERTS_GLB_INLINE void erts_bin_free(Binary *bp);
320 ERTS_GLB_INLINE void erts_bin_release(Binary *bp);
321 ERTS_GLB_INLINE Binary *erts_create_magic_binary_x(Uint size,
322                                                   int (*destructor)(Binary *),
323                                                    ErtsAlcType_t alloc_type,
324                                                   int unaligned);
325 ERTS_GLB_INLINE Binary *erts_create_magic_binary(Uint size,
326 						 int (*destructor)(Binary *));
327 ERTS_GLB_INLINE Binary *erts_create_magic_indirection(int (*destructor)(Binary *));
328 ERTS_GLB_INLINE erts_atomic_t *erts_binary_to_magic_indirection(Binary *bp);
329 ERTS_GLB_INLINE erts_atomic_t *erts_binary_to_magic_indirection(Binary *bp);
330 
331 #if ERTS_GLB_INLINE_INCL_FUNC_DEF
332 
333 #include <stddef.h> /* offsetof */
334 
335 ERTS_GLB_INLINE byte*
erts_get_aligned_binary_bytes(Eterm bin,byte ** base_ptr)336 erts_get_aligned_binary_bytes(Eterm bin, byte** base_ptr)
337 {
338     return erts_get_aligned_binary_bytes_extra(bin, base_ptr, ERTS_ALC_T_TMP, 0);
339 }
340 
341 ERTS_GLB_INLINE void
erts_free_aligned_binary_bytes_extra(byte * buf,ErtsAlcType_t allocator)342 erts_free_aligned_binary_bytes_extra(byte* buf, ErtsAlcType_t allocator)
343 {
344     if (buf) {
345 	erts_free(allocator, (void *) buf);
346     }
347 }
348 
349 ERTS_GLB_INLINE void
erts_free_aligned_binary_bytes(byte * buf)350 erts_free_aligned_binary_bytes(byte* buf)
351 {
352     erts_free_aligned_binary_bytes_extra(buf,ERTS_ALC_T_TMP);
353 }
354 
355 /* A binary's size in bits must fit into a word for matching to work. We used
356  * to allow creating larger binaries than this, but they acted really strangely
357  * in Erlang code and were pretty much only usable in drivers and NIFs.
358  *
359  * This check also ensures, indirectly, that there won't be an overflow when
360  * the size is bumped by CHICKEN_PAD and the binary struct itself. */
361 #define IS_BINARY_SIZE_OK(BYTE_SIZE) \
362     ERTS_LIKELY(BYTE_SIZE <= ERTS_UWORD_MAX / CHAR_BIT)
363 
364 /* Explicit extra bytes allocated to counter buggy drivers.
365 ** These extra bytes where earlier (< R13B04) added by an alignment-bug
366 ** in this code. Do we dare remove this in some major release (R14?) maybe?
367 */
368 #if defined(DEBUG) || defined(VALGRIND) || defined(ADDRESS_SANITIZER)
369 #  define CHICKEN_PAD 0
370 #else
371 #  define CHICKEN_PAD (sizeof(void*) - 1)
372 #endif
373 
374 ERTS_GLB_INLINE Binary *
erts_bin_drv_alloc_fnf(Uint size)375 erts_bin_drv_alloc_fnf(Uint size)
376 {
377     Binary *res;
378     Uint bsize;
379 
380     if (!IS_BINARY_SIZE_OK(size))
381         return NULL;
382     bsize = ERTS_SIZEOF_Binary(size) + CHICKEN_PAD;
383 
384     res = (Binary *)erts_alloc_fnf(ERTS_ALC_T_DRV_BINARY, bsize);
385     ERTS_CHK_BIN_ALIGNMENT(res);
386 
387     if (res) {
388         res->orig_size = size;
389         res->intern.flags = BIN_FLAG_DRV;
390         erts_refc_init(&res->intern.refc, 1);
391     }
392 
393     return res;
394 }
395 
396 ERTS_GLB_INLINE Binary *
erts_bin_drv_alloc(Uint size)397 erts_bin_drv_alloc(Uint size)
398 {
399     Binary *res = erts_bin_drv_alloc_fnf(size);
400 
401     if (res) {
402         return res;
403     }
404 
405     erts_alloc_enomem(ERTS_ALC_T_DRV_BINARY, size);
406 }
407 
408 ERTS_GLB_INLINE Binary *
erts_bin_nrml_alloc_fnf(Uint size)409 erts_bin_nrml_alloc_fnf(Uint size)
410 {
411     Binary *res;
412     Uint bsize;
413 
414     if (!IS_BINARY_SIZE_OK(size))
415         return NULL;
416     bsize = ERTS_SIZEOF_Binary(size);
417 
418     res = (Binary *)erts_alloc_fnf(ERTS_ALC_T_BINARY, bsize);
419     ERTS_CHK_BIN_ALIGNMENT(res);
420 
421     if (res) {
422         res->orig_size = size;
423         res->intern.flags = 0;
424         erts_refc_init(&res->intern.refc, 1);
425     }
426 
427     return res;
428 }
429 
430 ERTS_GLB_INLINE Binary *
erts_bin_nrml_alloc(Uint size)431 erts_bin_nrml_alloc(Uint size)
432 {
433     Binary *res = erts_bin_nrml_alloc_fnf(size);
434 
435     if (res) {
436         return res;
437     }
438 
439     erts_alloc_enomem(ERTS_ALC_T_BINARY, size);
440 }
441 
442 ERTS_GLB_INLINE Binary *
erts_bin_realloc_fnf(Binary * bp,Uint size)443 erts_bin_realloc_fnf(Binary *bp, Uint size)
444 {
445     ErtsAlcType_t type;
446     Binary *nbp;
447     Uint bsize;
448 
449     ASSERT((bp->intern.flags & BIN_FLAG_MAGIC) == 0);
450     if (!IS_BINARY_SIZE_OK(size))
451         return NULL;
452     bsize = ERTS_SIZEOF_Binary(size);
453 
454     if (bp->intern.flags & BIN_FLAG_DRV) {
455         type = ERTS_ALC_T_DRV_BINARY;
456         bsize += CHICKEN_PAD;
457     }
458     else {
459         type = ERTS_ALC_T_BINARY;
460     }
461 
462     nbp = (Binary *)erts_realloc_fnf(type, (void *) bp, bsize);
463     ERTS_CHK_BIN_ALIGNMENT(nbp);
464 
465     if (nbp) {
466         nbp->orig_size = size;
467     }
468 
469     return nbp;
470 }
471 
472 ERTS_GLB_INLINE Binary *
erts_bin_realloc(Binary * bp,Uint size)473 erts_bin_realloc(Binary *bp, Uint size)
474 {
475     Binary *nbp = erts_bin_realloc_fnf(bp, size);
476 
477     if (nbp) {
478         return nbp;
479     }
480 
481     if (bp->intern.flags & BIN_FLAG_DRV) {
482         erts_realloc_enomem(ERTS_ALC_T_DRV_BINARY, bp, size);
483     } else {
484         erts_realloc_enomem(ERTS_ALC_T_BINARY, bp, size);
485     }
486 }
487 
488 ERTS_GLB_INLINE void
erts_magic_binary_free(Binary * bp)489 erts_magic_binary_free(Binary *bp)
490 {
491     erts_magic_ref_remove_bin(ERTS_MAGIC_BIN_REFN(bp));
492     erts_free(ERTS_MAGIC_BIN_ATYPE(bp), (void *) bp);
493 }
494 
495 ERTS_GLB_INLINE void
erts_bin_free(Binary * bp)496 erts_bin_free(Binary *bp)
497 {
498     if (bp->intern.flags & BIN_FLAG_MAGIC) {
499         if (!ERTS_MAGIC_BIN_DESTRUCTOR(bp)(bp)) {
500             /* Destructor took control of the deallocation */
501             return;
502         }
503         erts_magic_binary_free(bp);
504     }
505     else if (bp->intern.flags & BIN_FLAG_DRV)
506 	erts_free(ERTS_ALC_T_DRV_BINARY, (void *) bp);
507     else
508 	erts_free(ERTS_ALC_T_BINARY, (void *) bp);
509 }
510 
511 ERTS_GLB_INLINE void
erts_bin_release(Binary * bp)512 erts_bin_release(Binary *bp)
513 {
514     if (erts_refc_dectest(&bp->intern.refc, 0) == 0) {
515         erts_bin_free(bp);
516     }
517 }
518 
519 ERTS_GLB_INLINE Binary *
erts_create_magic_binary_x(Uint size,int (* destructor)(Binary *),ErtsAlcType_t alloc_type,int unaligned)520 erts_create_magic_binary_x(Uint size, int (*destructor)(Binary *),
521                            ErtsAlcType_t alloc_type,
522                            int unaligned)
523 {
524     Uint bsize = unaligned ? ERTS_MAGIC_BIN_UNALIGNED_SIZE(size)
525                            : ERTS_MAGIC_BIN_SIZE(size);
526     Binary* bptr = (Binary *)erts_alloc_fnf(alloc_type, bsize);
527     ASSERT(bsize > size);
528     if (!bptr)
529 	erts_alloc_n_enomem(ERTS_ALC_T2N(alloc_type), bsize);
530     ERTS_CHK_BIN_ALIGNMENT(bptr);
531     bptr->intern.flags = BIN_FLAG_MAGIC;
532     bptr->orig_size = unaligned ? ERTS_MAGIC_BIN_UNALIGNED_ORIG_SIZE(size)
533                                 : ERTS_MAGIC_BIN_ORIG_SIZE(size);
534     erts_refc_init(&bptr->intern.refc, 0);
535     ERTS_MAGIC_BIN_DESTRUCTOR(bptr) = destructor;
536     ERTS_MAGIC_BIN_ATYPE(bptr) = alloc_type;
537     erts_make_magic_ref_in_array(ERTS_MAGIC_BIN_REFN(bptr));
538     return bptr;
539 }
540 
541 ERTS_GLB_INLINE Binary *
erts_create_magic_binary(Uint size,int (* destructor)(Binary *))542 erts_create_magic_binary(Uint size, int (*destructor)(Binary *))
543 {
544     return erts_create_magic_binary_x(size, destructor,
545                                       ERTS_ALC_T_BINARY, 0);
546 }
547 
548 ERTS_GLB_INLINE Binary *
erts_create_magic_indirection(int (* destructor)(Binary *))549 erts_create_magic_indirection(int (*destructor)(Binary *))
550 {
551     return erts_create_magic_binary_x(sizeof(ErtsMagicIndirectionWord),
552                                       destructor,
553                                       ERTS_ALC_T_MINDIRECTION,
554                                       1); /* Not 64-bit aligned,
555                                              but word aligned */
556 }
557 
558 ERTS_GLB_INLINE erts_atomic_t *
erts_binary_to_magic_indirection(Binary * bp)559 erts_binary_to_magic_indirection(Binary *bp)
560 {
561     ErtsMagicIndirectionWord *mip;
562     ASSERT(bp->intern.flags & BIN_FLAG_MAGIC);
563     ASSERT(ERTS_MAGIC_BIN_ATYPE(bp) == ERTS_ALC_T_MINDIRECTION);
564     mip = (ErtsMagicIndirectionWord*)ERTS_MAGIC_BIN_UNALIGNED_DATA(bp);
565     return &mip->smp_atomic_word;
566 }
567 
568 #endif /* #if ERTS_GLB_INLINE_INCL_FUNC_DEF */
569 
570 #endif /* !ERL_BINARY_H__ */
571