Home | History | Annotate | Line # | Download | only in stdlib
jemalloc.c revision 1.31
      1 /*	$NetBSD: jemalloc.c,v 1.31 2014/02/17 08:50:50 martin Exp $	*/
      2 
      3 /*-
      4  * Copyright (C) 2006,2007 Jason Evans <jasone (at) FreeBSD.org>.
      5  * All rights reserved.
      6  *
      7  * Redistribution and use in source and binary forms, with or without
      8  * modification, are permitted provided that the following conditions
      9  * are met:
     10  * 1. Redistributions of source code must retain the above copyright
     11  *    notice(s), this list of conditions and the following disclaimer as
     12  *    the first lines of this file unmodified other than the possible
     13  *    addition of one or more copyright notices.
     14  * 2. Redistributions in binary form must reproduce the above copyright
     15  *    notice(s), this list of conditions and the following disclaimer in
     16  *    the documentation and/or other materials provided with the
     17  *    distribution.
     18  *
     19  * THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDER(S) ``AS IS'' AND ANY
     20  * EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
     21  * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
     22  * PURPOSE ARE DISCLAIMED.  IN NO EVENT SHALL THE COPYRIGHT HOLDER(S) BE
     23  * LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
     24  * CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
     25  * SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR
     26  * BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY,
     27  * WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE
     28  * OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE,
     29  * EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
     30  *
     31  *******************************************************************************
     32  *
     33  * This allocator implementation is designed to provide scalable performance
     34  * for multi-threaded programs on multi-processor systems.  The following
     35  * features are included for this purpose:
     36  *
     37  *   + Multiple arenas are used if there are multiple CPUs, which reduces lock
     38  *     contention and cache sloshing.
     39  *
     40  *   + Cache line sharing between arenas is avoided for internal data
     41  *     structures.
     42  *
     43  *   + Memory is managed in chunks and runs (chunks can be split into runs),
     44  *     rather than as individual pages.  This provides a constant-time
     45  *     mechanism for associating allocations with particular arenas.
     46  *
     47  * Allocation requests are rounded up to the nearest size class, and no record
     48  * of the original request size is maintained.  Allocations are broken into
     49  * categories according to size class.  Assuming runtime defaults, 4 kB pages
     50  * and a 16 byte quantum, the size classes in each category are as follows:
     51  *
     52  *   |=====================================|
     53  *   | Category | Subcategory    |    Size |
     54  *   |=====================================|
     55  *   | Small    | Tiny           |       2 |
     56  *   |          |                |       4 |
     57  *   |          |                |       8 |
     58  *   |          |----------------+---------|
     59  *   |          | Quantum-spaced |      16 |
     60  *   |          |                |      32 |
     61  *   |          |                |      48 |
     62  *   |          |                |     ... |
     63  *   |          |                |     480 |
     64  *   |          |                |     496 |
     65  *   |          |                |     512 |
     66  *   |          |----------------+---------|
     67  *   |          | Sub-page       |    1 kB |
     68  *   |          |                |    2 kB |
     69  *   |=====================================|
     70  *   | Large                     |    4 kB |
     71  *   |                           |    8 kB |
     72  *   |                           |   12 kB |
     73  *   |                           |     ... |
     74  *   |                           | 1012 kB |
     75  *   |                           | 1016 kB |
     76  *   |                           | 1020 kB |
     77  *   |=====================================|
     78  *   | Huge                      |    1 MB |
     79  *   |                           |    2 MB |
     80  *   |                           |    3 MB |
     81  *   |                           |     ... |
     82  *   |=====================================|
     83  *
     84  * A different mechanism is used for each category:
     85  *
     86  *   Small : Each size class is segregated into its own set of runs.  Each run
     87  *           maintains a bitmap of which regions are free/allocated.
     88  *
     89  *   Large : Each allocation is backed by a dedicated run.  Metadata are stored
     90  *           in the associated arena chunk header maps.
     91  *
     92  *   Huge : Each allocation is backed by a dedicated contiguous set of chunks.
     93  *          Metadata are stored in a separate red-black tree.
     94  *
     95  *******************************************************************************
     96  */
     97 
     98 /* LINTLIBRARY */
     99 
    100 #ifdef __NetBSD__
    101 #  define xutrace(a, b)		utrace("malloc", (a), (b))
    102 #  define __DECONST(x, y)	((x)__UNCONST(y))
    103 #  define NO_TLS
    104 #else
    105 #  define xutrace(a, b)		utrace((a), (b))
    106 #endif	/* __NetBSD__ */
    107 
    108 /*
    109  * MALLOC_PRODUCTION disables assertions and statistics gathering.  It also
    110  * defaults the A and J runtime options to off.  These settings are appropriate
    111  * for production systems.
    112  */
    113 #define MALLOC_PRODUCTION
    114 
    115 #ifndef MALLOC_PRODUCTION
    116 #  define MALLOC_DEBUG
    117 #endif
    118 
    119 #include <sys/cdefs.h>
    120 /* __FBSDID("$FreeBSD: src/lib/libc/stdlib/malloc.c,v 1.147 2007/06/15 22:00:16 jasone Exp $"); */
    121 __RCSID("$NetBSD: jemalloc.c,v 1.31 2014/02/17 08:50:50 martin Exp $");
    122 
    123 #ifdef __FreeBSD__
    124 #include "libc_private.h"
    125 #ifdef MALLOC_DEBUG
    126 #  define _LOCK_DEBUG
    127 #endif
    128 #include "spinlock.h"
    129 #endif
    130 #include "namespace.h"
    131 #include <sys/mman.h>
    132 #include <sys/param.h>
    133 #ifdef __FreeBSD__
    134 #include <sys/stddef.h>
    135 #endif
    136 #include <sys/time.h>
    137 #include <sys/types.h>
    138 #include <sys/sysctl.h>
    139 #include <sys/tree.h>
    140 #include <sys/uio.h>
    141 #include <sys/ktrace.h> /* Must come after several other sys/ includes. */
    142 
    143 #ifdef __FreeBSD__
    144 #include <machine/atomic.h>
    145 #include <machine/cpufunc.h>
    146 #endif
    147 #include <machine/vmparam.h>
    148 
    149 #include <errno.h>
    150 #include <limits.h>
    151 #include <pthread.h>
    152 #include <sched.h>
    153 #include <stdarg.h>
    154 #include <stdbool.h>
    155 #include <stdio.h>
    156 #include <stdint.h>
    157 #include <stdlib.h>
    158 #include <string.h>
    159 #include <strings.h>
    160 #include <unistd.h>
    161 
    162 #ifdef __NetBSD__
    163 #  include <reentrant.h>
    164 #  include "extern.h"
    165 
    166 #define STRERROR_R(a, b, c)	__strerror_r(a, b, c);
    167 /*
    168  * A non localized version of strerror, that avoids bringing in
    169  * stdio and the locale code. All the malloc messages are in English
    170  * so why bother?
    171  */
    172 static int
    173 __strerror_r(int e, char *s, size_t l)
    174 {
    175 	int rval;
    176 	size_t slen;
    177 
    178 	if (e >= 0 && e < sys_nerr) {
    179 		slen = strlcpy(s, sys_errlist[e], l);
    180 		rval = 0;
    181 	} else {
    182 		slen = snprintf_ss(s, l, "Unknown error %u", e);
    183 		rval = EINVAL;
    184 	}
    185 	return slen >= l ? ERANGE : rval;
    186 }
    187 #endif
    188 
    189 #ifdef __FreeBSD__
    190 #define STRERROR_R(a, b, c)	strerror_r(a, b, c);
    191 #include "un-namespace.h"
    192 #endif
    193 
    194 /* MALLOC_STATS enables statistics calculation. */
    195 #ifndef MALLOC_PRODUCTION
    196 #  define MALLOC_STATS
    197 #endif
    198 
    199 #ifdef MALLOC_DEBUG
    200 #  ifdef NDEBUG
    201 #    undef NDEBUG
    202 #  endif
    203 #else
    204 #  ifndef NDEBUG
    205 #    define NDEBUG
    206 #  endif
    207 #endif
    208 #include <assert.h>
    209 
    210 #ifdef MALLOC_DEBUG
    211    /* Disable inlining to make debugging easier. */
    212 #  define inline
    213 #endif
    214 
    215 /* Size of stack-allocated buffer passed to strerror_r(). */
    216 #define	STRERROR_BUF		64
    217 
    218 /* Minimum alignment of allocations is 2^QUANTUM_2POW_MIN bytes. */
    219 
    220 /*
    221  * If you touch the TINY_MIN_2POW definition for any architecture, please
    222  * make sure to adjust the corresponding definition for JEMALLOC_TINY_MIN_2POW
    223  * in the gcc 4.8 tree in dist/gcc/tree-ssa-ccp.c and verify that a native
    224  * gcc is still buildable!
    225  */
    226 
    227 #ifdef __i386__
    228 #  define QUANTUM_2POW_MIN	4
    229 #  define SIZEOF_PTR_2POW	2
    230 #  define USE_BRK
    231 #endif
    232 #ifdef __ia64__
    233 #  define QUANTUM_2POW_MIN	4
    234 #  define SIZEOF_PTR_2POW	3
    235 #endif
    236 #ifdef __alpha__
    237 #  define QUANTUM_2POW_MIN	4
    238 #  define SIZEOF_PTR_2POW	3
    239 #  define TINY_MIN_2POW		3
    240 #  define NO_TLS
    241 #endif
    242 #ifdef __sparc64__
    243 #  define QUANTUM_2POW_MIN	4
    244 #  define SIZEOF_PTR_2POW	3
    245 #  define TINY_MIN_2POW		3
    246 #  define NO_TLS
    247 #endif
    248 #ifdef __amd64__
    249 #  define QUANTUM_2POW_MIN	4
    250 #  define SIZEOF_PTR_2POW	3
    251 #  define TINY_MIN_2POW		3
    252 #endif
    253 #ifdef __arm__
    254 #  define QUANTUM_2POW_MIN	3
    255 #  define SIZEOF_PTR_2POW	2
    256 #  define USE_BRK
    257 #  ifdef __ARM_EABI__
    258 #    define TINY_MIN_2POW	3
    259 #  endif
    260 #  define NO_TLS
    261 #endif
    262 #ifdef __powerpc__
    263 #  define QUANTUM_2POW_MIN	4
    264 #  define SIZEOF_PTR_2POW	2
    265 #  define USE_BRK
    266 #endif
    267 #if defined(__sparc__) && !defined(__sparc64__)
    268 #  define QUANTUM_2POW_MIN	4
    269 #  define SIZEOF_PTR_2POW	2
    270 #  define USE_BRK
    271 #endif
    272 #ifdef __vax__
    273 #  define QUANTUM_2POW_MIN	4
    274 #  define SIZEOF_PTR_2POW	2
    275 #  define USE_BRK
    276 #endif
    277 #ifdef __sh__
    278 #  define QUANTUM_2POW_MIN	4
    279 #  define SIZEOF_PTR_2POW	2
    280 #  define USE_BRK
    281 #endif
    282 #ifdef __m68k__
    283 #  define QUANTUM_2POW_MIN	4
    284 #  define SIZEOF_PTR_2POW	2
    285 #  define USE_BRK
    286 #endif
    287 #ifdef __mips__
    288 #  define QUANTUM_2POW_MIN	4
    289 #  define SIZEOF_PTR_2POW	2
    290 #  define USE_BRK
    291 #endif
    292 #ifdef __hppa__
    293 #  define QUANTUM_2POW_MIN     4
    294 #  define SIZEOF_PTR_2POW      2
    295 #  define USE_BRK
    296 #endif
    297 
    298 #define	SIZEOF_PTR		(1 << SIZEOF_PTR_2POW)
    299 
    300 /* sizeof(int) == (1 << SIZEOF_INT_2POW). */
    301 #ifndef SIZEOF_INT_2POW
    302 #  define SIZEOF_INT_2POW	2
    303 #endif
    304 
    305 /*
    306  * Size and alignment of memory chunks that are allocated by the OS's virtual
    307  * memory system.
    308  */
    309 #define	CHUNK_2POW_DEFAULT	20
    310 
    311 /*
    312  * Maximum size of L1 cache line.  This is used to avoid cache line aliasing,
    313  * so over-estimates are okay (up to a point), but under-estimates will
    314  * negatively affect performance.
    315  */
    316 #define	CACHELINE_2POW		6
    317 #define	CACHELINE		((size_t)(1 << CACHELINE_2POW))
    318 
    319 /* Smallest size class to support. */
    320 #ifndef TINY_MIN_2POW
    321 #define	TINY_MIN_2POW		2
    322 #endif
    323 
    324 /*
    325  * Maximum size class that is a multiple of the quantum, but not (necessarily)
    326  * a power of 2.  Above this size, allocations are rounded up to the nearest
    327  * power of 2.
    328  */
    329 #define	SMALL_MAX_2POW_DEFAULT	9
    330 #define	SMALL_MAX_DEFAULT	(1 << SMALL_MAX_2POW_DEFAULT)
    331 
    332 /*
    333  * RUN_MAX_OVRHD indicates maximum desired run header overhead.  Runs are sized
    334  * as small as possible such that this setting is still honored, without
    335  * violating other constraints.  The goal is to make runs as small as possible
    336  * without exceeding a per run external fragmentation threshold.
    337  *
    338  * We use binary fixed point math for overhead computations, where the binary
    339  * point is implicitly RUN_BFP bits to the left.
    340  *
    341  * Note that it is possible to set RUN_MAX_OVRHD low enough that it cannot be
    342  * honored for some/all object sizes, since there is one bit of header overhead
    343  * per object (plus a constant).  This constraint is relaxed (ignored) for runs
    344  * that are so small that the per-region overhead is greater than:
    345  *
    346  *   (RUN_MAX_OVRHD / (reg_size << (3+RUN_BFP))
    347  */
    348 #define RUN_BFP			12
    349 /*                              \/   Implicit binary fixed point. */
    350 #define RUN_MAX_OVRHD		0x0000003dU
    351 #define RUN_MAX_OVRHD_RELAX	0x00001800U
    352 
    353 /* Put a cap on small object run size.  This overrides RUN_MAX_OVRHD. */
    354 #define RUN_MAX_SMALL_2POW	15
    355 #define RUN_MAX_SMALL		(1 << RUN_MAX_SMALL_2POW)
    356 
    357 /******************************************************************************/
    358 
    359 #ifdef __FreeBSD__
    360 /*
    361  * Mutexes based on spinlocks.  We can't use normal pthread mutexes, because
    362  * they require malloc()ed memory.
    363  */
    364 typedef struct {
    365 	spinlock_t	lock;
    366 } malloc_mutex_t;
    367 
    368 /* Set to true once the allocator has been initialized. */
    369 static bool malloc_initialized = false;
    370 
    371 /* Used to avoid initialization races. */
    372 static malloc_mutex_t init_lock = {_SPINLOCK_INITIALIZER};
    373 #else
    374 #define	malloc_mutex_t	mutex_t
    375 
    376 /* Set to true once the allocator has been initialized. */
    377 static bool malloc_initialized = false;
    378 
    379 /* Used to avoid initialization races. */
    380 static mutex_t init_lock = MUTEX_INITIALIZER;
    381 #endif
    382 
    383 /******************************************************************************/
    384 /*
    385  * Statistics data structures.
    386  */
    387 
    388 #ifdef MALLOC_STATS
    389 
    390 typedef struct malloc_bin_stats_s malloc_bin_stats_t;
    391 struct malloc_bin_stats_s {
    392 	/*
    393 	 * Number of allocation requests that corresponded to the size of this
    394 	 * bin.
    395 	 */
    396 	uint64_t	nrequests;
    397 
    398 	/* Total number of runs created for this bin's size class. */
    399 	uint64_t	nruns;
    400 
    401 	/*
    402 	 * Total number of runs reused by extracting them from the runs tree for
    403 	 * this bin's size class.
    404 	 */
    405 	uint64_t	reruns;
    406 
    407 	/* High-water mark for this bin. */
    408 	unsigned long	highruns;
    409 
    410 	/* Current number of runs in this bin. */
    411 	unsigned long	curruns;
    412 };
    413 
    414 typedef struct arena_stats_s arena_stats_t;
    415 struct arena_stats_s {
    416 	/* Number of bytes currently mapped. */
    417 	size_t		mapped;
    418 
    419 	/* Per-size-category statistics. */
    420 	size_t		allocated_small;
    421 	uint64_t	nmalloc_small;
    422 	uint64_t	ndalloc_small;
    423 
    424 	size_t		allocated_large;
    425 	uint64_t	nmalloc_large;
    426 	uint64_t	ndalloc_large;
    427 };
    428 
    429 typedef struct chunk_stats_s chunk_stats_t;
    430 struct chunk_stats_s {
    431 	/* Number of chunks that were allocated. */
    432 	uint64_t	nchunks;
    433 
    434 	/* High-water mark for number of chunks allocated. */
    435 	unsigned long	highchunks;
    436 
    437 	/*
    438 	 * Current number of chunks allocated.  This value isn't maintained for
    439 	 * any other purpose, so keep track of it in order to be able to set
    440 	 * highchunks.
    441 	 */
    442 	unsigned long	curchunks;
    443 };
    444 
    445 #endif /* #ifdef MALLOC_STATS */
    446 
    447 /******************************************************************************/
    448 /*
    449  * Chunk data structures.
    450  */
    451 
    452 /* Tree of chunks. */
    453 typedef struct chunk_node_s chunk_node_t;
    454 struct chunk_node_s {
    455 	/* Linkage for the chunk tree. */
    456 	RB_ENTRY(chunk_node_s) link;
    457 
    458 	/*
    459 	 * Pointer to the chunk that this tree node is responsible for.  In some
    460 	 * (but certainly not all) cases, this data structure is placed at the
    461 	 * beginning of the corresponding chunk, so this field may point to this
    462 	 * node.
    463 	 */
    464 	void	*chunk;
    465 
    466 	/* Total chunk size. */
    467 	size_t	size;
    468 };
    469 typedef struct chunk_tree_s chunk_tree_t;
    470 RB_HEAD(chunk_tree_s, chunk_node_s);
    471 
    472 /******************************************************************************/
    473 /*
    474  * Arena data structures.
    475  */
    476 
    477 typedef struct arena_s arena_t;
    478 typedef struct arena_bin_s arena_bin_t;
    479 
    480 typedef struct arena_chunk_map_s arena_chunk_map_t;
    481 struct arena_chunk_map_s {
    482 	/* Number of pages in run. */
    483 	uint32_t	npages;
    484 	/*
    485 	 * Position within run.  For a free run, this is POS_FREE for the first
    486 	 * and last pages.  The POS_FREE special value makes it possible to
    487 	 * quickly coalesce free runs.
    488 	 *
    489 	 * This is the limiting factor for chunksize; there can be at most 2^31
    490 	 * pages in a run.
    491 	 */
    492 #define POS_FREE ((uint32_t)0xffffffffU)
    493 	uint32_t	pos;
    494 };
    495 
    496 /* Arena chunk header. */
    497 typedef struct arena_chunk_s arena_chunk_t;
    498 struct arena_chunk_s {
    499 	/* Arena that owns the chunk. */
    500 	arena_t *arena;
    501 
    502 	/* Linkage for the arena's chunk tree. */
    503 	RB_ENTRY(arena_chunk_s) link;
    504 
    505 	/*
    506 	 * Number of pages in use.  This is maintained in order to make
    507 	 * detection of empty chunks fast.
    508 	 */
    509 	uint32_t pages_used;
    510 
    511 	/*
    512 	 * Every time a free run larger than this value is created/coalesced,
    513 	 * this value is increased.  The only way that the value decreases is if
    514 	 * arena_run_alloc() fails to find a free run as large as advertised by
    515 	 * this value.
    516 	 */
    517 	uint32_t max_frun_npages;
    518 
    519 	/*
    520 	 * Every time a free run that starts at an earlier page than this value
    521 	 * is created/coalesced, this value is decreased.  It is reset in a
    522 	 * similar fashion to max_frun_npages.
    523 	 */
    524 	uint32_t min_frun_ind;
    525 
    526 	/*
    527 	 * Map of pages within chunk that keeps track of free/large/small.  For
    528 	 * free runs, only the map entries for the first and last pages are
    529 	 * kept up to date, so that free runs can be quickly coalesced.
    530 	 */
    531 	arena_chunk_map_t map[1]; /* Dynamically sized. */
    532 };
    533 typedef struct arena_chunk_tree_s arena_chunk_tree_t;
    534 RB_HEAD(arena_chunk_tree_s, arena_chunk_s);
    535 
    536 typedef struct arena_run_s arena_run_t;
    537 struct arena_run_s {
    538 	/* Linkage for run trees. */
    539 	RB_ENTRY(arena_run_s) link;
    540 
    541 #ifdef MALLOC_DEBUG
    542 	uint32_t	magic;
    543 #  define ARENA_RUN_MAGIC 0x384adf93
    544 #endif
    545 
    546 	/* Bin this run is associated with. */
    547 	arena_bin_t	*bin;
    548 
    549 	/* Index of first element that might have a free region. */
    550 	unsigned	regs_minelm;
    551 
    552 	/* Number of free regions in run. */
    553 	unsigned	nfree;
    554 
    555 	/* Bitmask of in-use regions (0: in use, 1: free). */
    556 	unsigned	regs_mask[1]; /* Dynamically sized. */
    557 };
    558 typedef struct arena_run_tree_s arena_run_tree_t;
    559 RB_HEAD(arena_run_tree_s, arena_run_s);
    560 
    561 struct arena_bin_s {
    562 	/*
    563 	 * Current run being used to service allocations of this bin's size
    564 	 * class.
    565 	 */
    566 	arena_run_t	*runcur;
    567 
    568 	/*
    569 	 * Tree of non-full runs.  This tree is used when looking for an
    570 	 * existing run when runcur is no longer usable.  We choose the
    571 	 * non-full run that is lowest in memory; this policy tends to keep
    572 	 * objects packed well, and it can also help reduce the number of
    573 	 * almost-empty chunks.
    574 	 */
    575 	arena_run_tree_t runs;
    576 
    577 	/* Size of regions in a run for this bin's size class. */
    578 	size_t		reg_size;
    579 
    580 	/* Total size of a run for this bin's size class. */
    581 	size_t		run_size;
    582 
    583 	/* Total number of regions in a run for this bin's size class. */
    584 	uint32_t	nregs;
    585 
    586 	/* Number of elements in a run's regs_mask for this bin's size class. */
    587 	uint32_t	regs_mask_nelms;
    588 
    589 	/* Offset of first region in a run for this bin's size class. */
    590 	uint32_t	reg0_offset;
    591 
    592 #ifdef MALLOC_STATS
    593 	/* Bin statistics. */
    594 	malloc_bin_stats_t stats;
    595 #endif
    596 };
    597 
    598 struct arena_s {
    599 #ifdef MALLOC_DEBUG
    600 	uint32_t		magic;
    601 #  define ARENA_MAGIC 0x947d3d24
    602 #endif
    603 
    604 	/* All operations on this arena require that mtx be locked. */
    605 	malloc_mutex_t		mtx;
    606 
    607 #ifdef MALLOC_STATS
    608 	arena_stats_t		stats;
    609 #endif
    610 
    611 	/*
    612 	 * Tree of chunks this arena manages.
    613 	 */
    614 	arena_chunk_tree_t	chunks;
    615 
    616 	/*
    617 	 * In order to avoid rapid chunk allocation/deallocation when an arena
    618 	 * oscillates right on the cusp of needing a new chunk, cache the most
    619 	 * recently freed chunk.  This caching is disabled by opt_hint.
    620 	 *
    621 	 * There is one spare chunk per arena, rather than one spare total, in
    622 	 * order to avoid interactions between multiple threads that could make
    623 	 * a single spare inadequate.
    624 	 */
    625 	arena_chunk_t *spare;
    626 
    627 	/*
    628 	 * bins is used to store rings of free regions of the following sizes,
    629 	 * assuming a 16-byte quantum, 4kB pagesize, and default MALLOC_OPTIONS.
    630 	 *
    631 	 *   bins[i] | size |
    632 	 *   --------+------+
    633 	 *        0  |    2 |
    634 	 *        1  |    4 |
    635 	 *        2  |    8 |
    636 	 *   --------+------+
    637 	 *        3  |   16 |
    638 	 *        4  |   32 |
    639 	 *        5  |   48 |
    640 	 *        6  |   64 |
    641 	 *           :      :
    642 	 *           :      :
    643 	 *       33  |  496 |
    644 	 *       34  |  512 |
    645 	 *   --------+------+
    646 	 *       35  | 1024 |
    647 	 *       36  | 2048 |
    648 	 *   --------+------+
    649 	 */
    650 	arena_bin_t		bins[1]; /* Dynamically sized. */
    651 };
    652 
    653 /******************************************************************************/
    654 /*
    655  * Data.
    656  */
    657 
    658 /* Number of CPUs. */
    659 static unsigned		ncpus;
    660 
    661 /* VM page size. */
    662 static size_t		pagesize;
    663 static size_t		pagesize_mask;
    664 static int		pagesize_2pow;
    665 
    666 /* Various bin-related settings. */
    667 static size_t		bin_maxclass; /* Max size class for bins. */
    668 static unsigned		ntbins; /* Number of (2^n)-spaced tiny bins. */
    669 static unsigned		nqbins; /* Number of quantum-spaced bins. */
    670 static unsigned		nsbins; /* Number of (2^n)-spaced sub-page bins. */
    671 static size_t		small_min;
    672 static size_t		small_max;
    673 
    674 /* Various quantum-related settings. */
    675 static size_t		quantum;
    676 static size_t		quantum_mask; /* (quantum - 1). */
    677 
    678 /* Various chunk-related settings. */
    679 static size_t		chunksize;
    680 static size_t		chunksize_mask; /* (chunksize - 1). */
    681 static int		chunksize_2pow;
    682 static unsigned		chunk_npages;
    683 static unsigned		arena_chunk_header_npages;
    684 static size_t		arena_maxclass; /* Max size class for arenas. */
    685 
    686 /********/
    687 /*
    688  * Chunks.
    689  */
    690 
    691 /* Protects chunk-related data structures. */
    692 static malloc_mutex_t	chunks_mtx;
    693 
    694 /* Tree of chunks that are stand-alone huge allocations. */
    695 static chunk_tree_t	huge;
    696 
    697 #ifdef USE_BRK
    698 /*
    699  * Try to use brk for chunk-size allocations, due to address space constraints.
    700  */
    701 /*
    702  * Protects sbrk() calls.  This must be separate from chunks_mtx, since
    703  * base_pages_alloc() also uses sbrk(), but cannot lock chunks_mtx (doing so
    704  * could cause recursive lock acquisition).
    705  */
    706 static malloc_mutex_t	brk_mtx;
    707 /* Result of first sbrk(0) call. */
    708 static void		*brk_base;
    709 /* Current end of brk, or ((void *)-1) if brk is exhausted. */
    710 static void		*brk_prev;
    711 /* Current upper limit on brk addresses. */
    712 static void		*brk_max;
    713 #endif
    714 
    715 #ifdef MALLOC_STATS
    716 /* Huge allocation statistics. */
    717 static uint64_t		huge_nmalloc;
    718 static uint64_t		huge_ndalloc;
    719 static uint64_t		huge_nralloc;
    720 static size_t		huge_allocated;
    721 #endif
    722 
    723 /*
    724  * Tree of chunks that were previously allocated.  This is used when allocating
    725  * chunks, in an attempt to re-use address space.
    726  */
    727 static chunk_tree_t	old_chunks;
    728 
    729 /****************************/
    730 /*
    731  * base (internal allocation).
    732  */
    733 
    734 /*
    735  * Current pages that are being used for internal memory allocations.  These
    736  * pages are carved up in cacheline-size quanta, so that there is no chance of
    737  * false cache line sharing.
    738  */
    739 static void		*base_pages;
    740 static void		*base_next_addr;
    741 static void		*base_past_addr; /* Addr immediately past base_pages. */
    742 static chunk_node_t	*base_chunk_nodes; /* LIFO cache of chunk nodes. */
    743 static malloc_mutex_t	base_mtx;
    744 #ifdef MALLOC_STATS
    745 static size_t		base_mapped;
    746 #endif
    747 
    748 /********/
    749 /*
    750  * Arenas.
    751  */
    752 
    753 /*
    754  * Arenas that are used to service external requests.  Not all elements of the
    755  * arenas array are necessarily used; arenas are created lazily as needed.
    756  */
    757 static arena_t		**arenas;
    758 static unsigned		narenas;
    759 static unsigned		next_arena;
    760 static malloc_mutex_t	arenas_mtx; /* Protects arenas initialization. */
    761 
    762 #ifndef NO_TLS
    763 /*
    764  * Map of pthread_self() --> arenas[???], used for selecting an arena to use
    765  * for allocations.
    766  */
    767 static __thread arena_t	*arenas_map;
    768 #define	get_arenas_map()	(arenas_map)
    769 #define	set_arenas_map(x)	(arenas_map = x)
    770 #else
    771 static thread_key_t arenas_map_key;
    772 #define	get_arenas_map()	thr_getspecific(arenas_map_key)
    773 #define	set_arenas_map(x)	thr_setspecific(arenas_map_key, x)
    774 #endif
    775 
    776 #ifdef MALLOC_STATS
    777 /* Chunk statistics. */
    778 static chunk_stats_t	stats_chunks;
    779 #endif
    780 
    781 /*******************************/
    782 /*
    783  * Runtime configuration options.
    784  */
    785 const char	*_malloc_options;
    786 
    787 #ifndef MALLOC_PRODUCTION
    788 static bool	opt_abort = true;
    789 static bool	opt_junk = true;
    790 #else
    791 static bool	opt_abort = false;
    792 static bool	opt_junk = false;
    793 #endif
    794 static bool	opt_hint = false;
    795 static bool	opt_print_stats = false;
    796 static int	opt_quantum_2pow = QUANTUM_2POW_MIN;
    797 static int	opt_small_max_2pow = SMALL_MAX_2POW_DEFAULT;
    798 static int	opt_chunk_2pow = CHUNK_2POW_DEFAULT;
    799 static bool	opt_utrace = false;
    800 static bool	opt_sysv = false;
    801 static bool	opt_xmalloc = false;
    802 static bool	opt_zero = false;
    803 static int32_t	opt_narenas_lshift = 0;
    804 
    805 typedef struct {
    806 	void	*p;
    807 	size_t	s;
    808 	void	*r;
    809 } malloc_utrace_t;
    810 
    811 #define	UTRACE(a, b, c)							\
    812 	if (opt_utrace) {						\
    813 		malloc_utrace_t ut;					\
    814 		ut.p = a;						\
    815 		ut.s = b;						\
    816 		ut.r = c;						\
    817 		xutrace(&ut, sizeof(ut));				\
    818 	}
    819 
    820 /******************************************************************************/
    821 /*
    822  * Begin function prototypes for non-inline static functions.
    823  */
    824 
    825 static void	wrtmessage(const char *p1, const char *p2, const char *p3,
    826 		const char *p4);
    827 #ifdef MALLOC_STATS
    828 static void	malloc_printf(const char *format, ...);
    829 #endif
    830 static char	*size_t2s(size_t x, char *s);
    831 static bool	base_pages_alloc(size_t minsize);
    832 static void	*base_alloc(size_t size);
    833 static chunk_node_t *base_chunk_node_alloc(void);
    834 static void	base_chunk_node_dealloc(chunk_node_t *node);
    835 #ifdef MALLOC_STATS
    836 static void	stats_print(arena_t *arena);
    837 #endif
    838 static void	*pages_map(void *addr, size_t size);
    839 static void	*pages_map_align(void *addr, size_t size, int align);
    840 static void	pages_unmap(void *addr, size_t size);
    841 static void	*chunk_alloc(size_t size);
    842 static void	chunk_dealloc(void *chunk, size_t size);
    843 static void	arena_run_split(arena_t *arena, arena_run_t *run, size_t size);
    844 static arena_chunk_t *arena_chunk_alloc(arena_t *arena);
    845 static void	arena_chunk_dealloc(arena_t *arena, arena_chunk_t *chunk);
    846 static arena_run_t *arena_run_alloc(arena_t *arena, size_t size);
    847 static void	arena_run_dalloc(arena_t *arena, arena_run_t *run, size_t size);
    848 static arena_run_t *arena_bin_nonfull_run_get(arena_t *arena, arena_bin_t *bin);
    849 static void *arena_bin_malloc_hard(arena_t *arena, arena_bin_t *bin);
    850 static size_t arena_bin_run_size_calc(arena_bin_t *bin, size_t min_run_size);
    851 static void	*arena_malloc(arena_t *arena, size_t size);
    852 static void	*arena_palloc(arena_t *arena, size_t alignment, size_t size,
    853     size_t alloc_size);
    854 static size_t	arena_salloc(const void *ptr);
    855 static void	*arena_ralloc(void *ptr, size_t size, size_t oldsize);
    856 static void	arena_dalloc(arena_t *arena, arena_chunk_t *chunk, void *ptr);
    857 static bool	arena_new(arena_t *arena);
    858 static arena_t	*arenas_extend(unsigned ind);
    859 static void	*huge_malloc(size_t size);
    860 static void	*huge_palloc(size_t alignment, size_t size);
    861 static void	*huge_ralloc(void *ptr, size_t size, size_t oldsize);
    862 static void	huge_dalloc(void *ptr);
    863 static void	*imalloc(size_t size);
    864 static void	*ipalloc(size_t alignment, size_t size);
    865 static void	*icalloc(size_t size);
    866 static size_t	isalloc(const void *ptr);
    867 static void	*iralloc(void *ptr, size_t size);
    868 static void	idalloc(void *ptr);
    869 static void	malloc_print_stats(void);
    870 static bool	malloc_init_hard(void);
    871 
    872 /*
    873  * End function prototypes.
    874  */
    875 /******************************************************************************/
    876 /*
    877  * Begin mutex.
    878  */
    879 
    880 #ifdef __NetBSD__
    881 #define	malloc_mutex_init(m)	mutex_init(m, NULL)
    882 #define	malloc_mutex_lock(m)	mutex_lock(m)
    883 #define	malloc_mutex_unlock(m)	mutex_unlock(m)
    884 #else	/* __NetBSD__ */
    885 static inline void
    886 malloc_mutex_init(malloc_mutex_t *a_mutex)
    887 {
    888 	static const spinlock_t lock = _SPINLOCK_INITIALIZER;
    889 
    890 	a_mutex->lock = lock;
    891 }
    892 
    893 static inline void
    894 malloc_mutex_lock(malloc_mutex_t *a_mutex)
    895 {
    896 
    897 	if (__isthreaded)
    898 		_SPINLOCK(&a_mutex->lock);
    899 }
    900 
    901 static inline void
    902 malloc_mutex_unlock(malloc_mutex_t *a_mutex)
    903 {
    904 
    905 	if (__isthreaded)
    906 		_SPINUNLOCK(&a_mutex->lock);
    907 }
    908 #endif	/* __NetBSD__ */
    909 
    910 /*
    911  * End mutex.
    912  */
    913 /******************************************************************************/
    914 /*
    915  * Begin Utility functions/macros.
    916  */
    917 
    918 /* Return the chunk address for allocation address a. */
    919 #define	CHUNK_ADDR2BASE(a)						\
    920 	((void *)((uintptr_t)(a) & ~chunksize_mask))
    921 
    922 /* Return the chunk offset of address a. */
    923 #define	CHUNK_ADDR2OFFSET(a)						\
    924 	((size_t)((uintptr_t)(a) & chunksize_mask))
    925 
    926 /* Return the smallest chunk multiple that is >= s. */
    927 #define	CHUNK_CEILING(s)						\
    928 	(((s) + chunksize_mask) & ~chunksize_mask)
    929 
    930 /* Return the smallest cacheline multiple that is >= s. */
    931 #define	CACHELINE_CEILING(s)						\
    932 	(((s) + (CACHELINE - 1)) & ~(CACHELINE - 1))
    933 
    934 /* Return the smallest quantum multiple that is >= a. */
    935 #define	QUANTUM_CEILING(a)						\
    936 	(((a) + quantum_mask) & ~quantum_mask)
    937 
    938 /* Return the smallest pagesize multiple that is >= s. */
    939 #define	PAGE_CEILING(s)							\
    940 	(((s) + pagesize_mask) & ~pagesize_mask)
    941 
    942 /* Compute the smallest power of 2 that is >= x. */
    943 static inline size_t
    944 pow2_ceil(size_t x)
    945 {
    946 
    947 	x--;
    948 	x |= x >> 1;
    949 	x |= x >> 2;
    950 	x |= x >> 4;
    951 	x |= x >> 8;
    952 	x |= x >> 16;
    953 #if (SIZEOF_PTR == 8)
    954 	x |= x >> 32;
    955 #endif
    956 	x++;
    957 	return (x);
    958 }
    959 
    960 static void
    961 wrtmessage(const char *p1, const char *p2, const char *p3, const char *p4)
    962 {
    963 
    964 	write(STDERR_FILENO, p1, strlen(p1));
    965 	write(STDERR_FILENO, p2, strlen(p2));
    966 	write(STDERR_FILENO, p3, strlen(p3));
    967 	write(STDERR_FILENO, p4, strlen(p4));
    968 }
    969 
    970 void	(*_malloc_message)(const char *p1, const char *p2, const char *p3,
    971 	    const char *p4) = wrtmessage;
    972 
    973 #ifdef MALLOC_STATS
    974 /*
    975  * Print to stderr in such a way as to (hopefully) avoid memory allocation.
    976  */
    977 static void
    978 malloc_printf(const char *format, ...)
    979 {
    980 	char buf[4096];
    981 	va_list ap;
    982 
    983 	va_start(ap, format);
    984 	vsnprintf(buf, sizeof(buf), format, ap);
    985 	va_end(ap);
    986 	_malloc_message(buf, "", "", "");
    987 }
    988 #endif
    989 
    990 /*
    991  * We don't want to depend on vsnprintf() for production builds, since that can
    992  * cause unnecessary bloat for static binaries.  size_t2s() provides minimal
    993  * integer printing functionality, so that malloc_printf() use can be limited to
    994  * MALLOC_STATS code.
    995  */
    996 #define UMAX2S_BUFSIZE	21
    997 static char *
    998 size_t2s(size_t x, char *s)
    999 {
   1000 	unsigned i;
   1001 
   1002 	/* Make sure UMAX2S_BUFSIZE is large enough. */
   1003 	/* LINTED */
   1004 	assert(sizeof(size_t) <= 8);
   1005 
   1006 	i = UMAX2S_BUFSIZE - 1;
   1007 	s[i] = '\0';
   1008 	do {
   1009 		i--;
   1010 		s[i] = "0123456789"[(int)x % 10];
   1011 		x /= (uintmax_t)10LL;
   1012 	} while (x > 0);
   1013 
   1014 	return (&s[i]);
   1015 }
   1016 
   1017 /******************************************************************************/
   1018 
   1019 static bool
   1020 base_pages_alloc(size_t minsize)
   1021 {
   1022 	size_t csize = 0;
   1023 
   1024 #ifdef USE_BRK
   1025 	/*
   1026 	 * Do special brk allocation here, since base allocations don't need to
   1027 	 * be chunk-aligned.
   1028 	 */
   1029 	if (brk_prev != (void *)-1) {
   1030 		void *brk_cur;
   1031 		intptr_t incr;
   1032 
   1033 		if (minsize != 0)
   1034 			csize = CHUNK_CEILING(minsize);
   1035 
   1036 		malloc_mutex_lock(&brk_mtx);
   1037 		do {
   1038 			/* Get the current end of brk. */
   1039 			brk_cur = sbrk(0);
   1040 
   1041 			/*
   1042 			 * Calculate how much padding is necessary to
   1043 			 * chunk-align the end of brk.  Don't worry about
   1044 			 * brk_cur not being chunk-aligned though.
   1045 			 */
   1046 			incr = (intptr_t)chunksize
   1047 			    - (intptr_t)CHUNK_ADDR2OFFSET(brk_cur);
   1048 			assert(incr >= 0);
   1049 			if ((size_t)incr < minsize)
   1050 				incr += csize;
   1051 
   1052 			brk_prev = sbrk(incr);
   1053 			if (brk_prev == brk_cur) {
   1054 				/* Success. */
   1055 				malloc_mutex_unlock(&brk_mtx);
   1056 				base_pages = brk_cur;
   1057 				base_next_addr = base_pages;
   1058 				base_past_addr = (void *)((uintptr_t)base_pages
   1059 				    + incr);
   1060 #ifdef MALLOC_STATS
   1061 				base_mapped += incr;
   1062 #endif
   1063 				return (false);
   1064 			}
   1065 		} while (brk_prev != (void *)-1);
   1066 		malloc_mutex_unlock(&brk_mtx);
   1067 	}
   1068 	if (minsize == 0) {
   1069 		/*
   1070 		 * Failure during initialization doesn't matter, so avoid
   1071 		 * falling through to the mmap-based page mapping code.
   1072 		 */
   1073 		return (true);
   1074 	}
   1075 #endif
   1076 	assert(minsize != 0);
   1077 	csize = PAGE_CEILING(minsize);
   1078 	base_pages = pages_map(NULL, csize);
   1079 	if (base_pages == NULL)
   1080 		return (true);
   1081 	base_next_addr = base_pages;
   1082 	base_past_addr = (void *)((uintptr_t)base_pages + csize);
   1083 #ifdef MALLOC_STATS
   1084 	base_mapped += csize;
   1085 #endif
   1086 	return (false);
   1087 }
   1088 
   1089 static void *
   1090 base_alloc(size_t size)
   1091 {
   1092 	void *ret;
   1093 	size_t csize;
   1094 
   1095 	/* Round size up to nearest multiple of the cacheline size. */
   1096 	csize = CACHELINE_CEILING(size);
   1097 
   1098 	malloc_mutex_lock(&base_mtx);
   1099 
   1100 	/* Make sure there's enough space for the allocation. */
   1101 	if ((uintptr_t)base_next_addr + csize > (uintptr_t)base_past_addr) {
   1102 		if (base_pages_alloc(csize)) {
   1103 			ret = NULL;
   1104 			goto RETURN;
   1105 		}
   1106 	}
   1107 
   1108 	/* Allocate. */
   1109 	ret = base_next_addr;
   1110 	base_next_addr = (void *)((uintptr_t)base_next_addr + csize);
   1111 
   1112 RETURN:
   1113 	malloc_mutex_unlock(&base_mtx);
   1114 	return (ret);
   1115 }
   1116 
   1117 static chunk_node_t *
   1118 base_chunk_node_alloc(void)
   1119 {
   1120 	chunk_node_t *ret;
   1121 
   1122 	malloc_mutex_lock(&base_mtx);
   1123 	if (base_chunk_nodes != NULL) {
   1124 		ret = base_chunk_nodes;
   1125 		/* LINTED */
   1126 		base_chunk_nodes = *(chunk_node_t **)ret;
   1127 		malloc_mutex_unlock(&base_mtx);
   1128 	} else {
   1129 		malloc_mutex_unlock(&base_mtx);
   1130 		ret = (chunk_node_t *)base_alloc(sizeof(chunk_node_t));
   1131 	}
   1132 
   1133 	return (ret);
   1134 }
   1135 
   1136 static void
   1137 base_chunk_node_dealloc(chunk_node_t *node)
   1138 {
   1139 
   1140 	malloc_mutex_lock(&base_mtx);
   1141 	/* LINTED */
   1142 	*(chunk_node_t **)node = base_chunk_nodes;
   1143 	base_chunk_nodes = node;
   1144 	malloc_mutex_unlock(&base_mtx);
   1145 }
   1146 
   1147 /******************************************************************************/
   1148 
   1149 #ifdef MALLOC_STATS
   1150 static void
   1151 stats_print(arena_t *arena)
   1152 {
   1153 	unsigned i;
   1154 	int gap_start;
   1155 
   1156 	malloc_printf(
   1157 	    "          allocated/mapped            nmalloc      ndalloc\n");
   1158 
   1159 	malloc_printf("small: %12zu %-12s %12llu %12llu\n",
   1160 	    arena->stats.allocated_small, "", arena->stats.nmalloc_small,
   1161 	    arena->stats.ndalloc_small);
   1162 	malloc_printf("large: %12zu %-12s %12llu %12llu\n",
   1163 	    arena->stats.allocated_large, "", arena->stats.nmalloc_large,
   1164 	    arena->stats.ndalloc_large);
   1165 	malloc_printf("total: %12zu/%-12zu %12llu %12llu\n",
   1166 	    arena->stats.allocated_small + arena->stats.allocated_large,
   1167 	    arena->stats.mapped,
   1168 	    arena->stats.nmalloc_small + arena->stats.nmalloc_large,
   1169 	    arena->stats.ndalloc_small + arena->stats.ndalloc_large);
   1170 
   1171 	malloc_printf("bins:     bin   size regs pgs  requests   newruns"
   1172 	    "    reruns maxruns curruns\n");
   1173 	for (i = 0, gap_start = -1; i < ntbins + nqbins + nsbins; i++) {
   1174 		if (arena->bins[i].stats.nrequests == 0) {
   1175 			if (gap_start == -1)
   1176 				gap_start = i;
   1177 		} else {
   1178 			if (gap_start != -1) {
   1179 				if (i > gap_start + 1) {
   1180 					/* Gap of more than one size class. */
   1181 					malloc_printf("[%u..%u]\n",
   1182 					    gap_start, i - 1);
   1183 				} else {
   1184 					/* Gap of one size class. */
   1185 					malloc_printf("[%u]\n", gap_start);
   1186 				}
   1187 				gap_start = -1;
   1188 			}
   1189 			malloc_printf(
   1190 			    "%13u %1s %4u %4u %3u %9llu %9llu"
   1191 			    " %9llu %7lu %7lu\n",
   1192 			    i,
   1193 			    i < ntbins ? "T" : i < ntbins + nqbins ? "Q" : "S",
   1194 			    arena->bins[i].reg_size,
   1195 			    arena->bins[i].nregs,
   1196 			    arena->bins[i].run_size >> pagesize_2pow,
   1197 			    arena->bins[i].stats.nrequests,
   1198 			    arena->bins[i].stats.nruns,
   1199 			    arena->bins[i].stats.reruns,
   1200 			    arena->bins[i].stats.highruns,
   1201 			    arena->bins[i].stats.curruns);
   1202 		}
   1203 	}
   1204 	if (gap_start != -1) {
   1205 		if (i > gap_start + 1) {
   1206 			/* Gap of more than one size class. */
   1207 			malloc_printf("[%u..%u]\n", gap_start, i - 1);
   1208 		} else {
   1209 			/* Gap of one size class. */
   1210 			malloc_printf("[%u]\n", gap_start);
   1211 		}
   1212 	}
   1213 }
   1214 #endif
   1215 
   1216 /*
   1217  * End Utility functions/macros.
   1218  */
   1219 /******************************************************************************/
   1220 /*
   1221  * Begin chunk management functions.
   1222  */
   1223 
   1224 #ifndef lint
   1225 static inline int
   1226 chunk_comp(chunk_node_t *a, chunk_node_t *b)
   1227 {
   1228 
   1229 	assert(a != NULL);
   1230 	assert(b != NULL);
   1231 
   1232 	if ((uintptr_t)a->chunk < (uintptr_t)b->chunk)
   1233 		return (-1);
   1234 	else if (a->chunk == b->chunk)
   1235 		return (0);
   1236 	else
   1237 		return (1);
   1238 }
   1239 
   1240 /* Generate red-black tree code for chunks. */
   1241 RB_GENERATE_STATIC(chunk_tree_s, chunk_node_s, link, chunk_comp);
   1242 #endif
   1243 
   1244 static void *
   1245 pages_map_align(void *addr, size_t size, int align)
   1246 {
   1247 	void *ret;
   1248 
   1249 	/*
   1250 	 * We don't use MAP_FIXED here, because it can cause the *replacement*
   1251 	 * of existing mappings, and we only want to create new mappings.
   1252 	 */
   1253 	ret = mmap(addr, size, PROT_READ | PROT_WRITE,
   1254 	    MAP_PRIVATE | MAP_ANON | MAP_ALIGNED(align), -1, 0);
   1255 	assert(ret != NULL);
   1256 
   1257 	if (ret == MAP_FAILED)
   1258 		ret = NULL;
   1259 	else if (addr != NULL && ret != addr) {
   1260 		/*
   1261 		 * We succeeded in mapping memory, but not in the right place.
   1262 		 */
   1263 		if (munmap(ret, size) == -1) {
   1264 			char buf[STRERROR_BUF];
   1265 
   1266 			STRERROR_R(errno, buf, sizeof(buf));
   1267 			_malloc_message(getprogname(),
   1268 			    ": (malloc) Error in munmap(): ", buf, "\n");
   1269 			if (opt_abort)
   1270 				abort();
   1271 		}
   1272 		ret = NULL;
   1273 	}
   1274 
   1275 	assert(ret == NULL || (addr == NULL && ret != addr)
   1276 	    || (addr != NULL && ret == addr));
   1277 	return (ret);
   1278 }
   1279 
   1280 static void *
   1281 pages_map(void *addr, size_t size)
   1282 {
   1283 
   1284 	return pages_map_align(addr, size, 0);
   1285 }
   1286 
   1287 static void
   1288 pages_unmap(void *addr, size_t size)
   1289 {
   1290 
   1291 	if (munmap(addr, size) == -1) {
   1292 		char buf[STRERROR_BUF];
   1293 
   1294 		STRERROR_R(errno, buf, sizeof(buf));
   1295 		_malloc_message(getprogname(),
   1296 		    ": (malloc) Error in munmap(): ", buf, "\n");
   1297 		if (opt_abort)
   1298 			abort();
   1299 	}
   1300 }
   1301 
   1302 static void *
   1303 chunk_alloc(size_t size)
   1304 {
   1305 	void *ret, *chunk;
   1306 	chunk_node_t *tchunk, *delchunk;
   1307 
   1308 	assert(size != 0);
   1309 	assert((size & chunksize_mask) == 0);
   1310 
   1311 	malloc_mutex_lock(&chunks_mtx);
   1312 
   1313 	if (size == chunksize) {
   1314 		/*
   1315 		 * Check for address ranges that were previously chunks and try
   1316 		 * to use them.
   1317 		 */
   1318 
   1319 		/* LINTED */
   1320 		tchunk = RB_MIN(chunk_tree_s, &old_chunks);
   1321 		while (tchunk != NULL) {
   1322 			/* Found an address range.  Try to recycle it. */
   1323 
   1324 			chunk = tchunk->chunk;
   1325 			delchunk = tchunk;
   1326 			/* LINTED */
   1327 			tchunk = RB_NEXT(chunk_tree_s, &old_chunks, delchunk);
   1328 
   1329 			/* Remove delchunk from the tree. */
   1330 			/* LINTED */
   1331 			RB_REMOVE(chunk_tree_s, &old_chunks, delchunk);
   1332 			base_chunk_node_dealloc(delchunk);
   1333 
   1334 #ifdef USE_BRK
   1335 			if ((uintptr_t)chunk >= (uintptr_t)brk_base
   1336 			    && (uintptr_t)chunk < (uintptr_t)brk_max) {
   1337 				/* Re-use a previously freed brk chunk. */
   1338 				ret = chunk;
   1339 				goto RETURN;
   1340 			}
   1341 #endif
   1342 			if ((ret = pages_map(chunk, size)) != NULL) {
   1343 				/* Success. */
   1344 				goto RETURN;
   1345 			}
   1346 		}
   1347 	}
   1348 
   1349 	/*
   1350 	 * Try to over-allocate, but allow the OS to place the allocation
   1351 	 * anywhere.  Beware of size_t wrap-around.
   1352 	 */
   1353 	if (size + chunksize > size) {
   1354 		if ((ret = pages_map_align(NULL, size, chunksize_2pow))
   1355 		    != NULL) {
   1356 			goto RETURN;
   1357 		}
   1358 	}
   1359 
   1360 #ifdef USE_BRK
   1361 	/*
   1362 	 * Try to create allocations in brk, in order to make full use of
   1363 	 * limited address space.
   1364 	 */
   1365 	if (brk_prev != (void *)-1) {
   1366 		void *brk_cur;
   1367 		intptr_t incr;
   1368 
   1369 		/*
   1370 		 * The loop is necessary to recover from races with other
   1371 		 * threads that are using brk for something other than malloc.
   1372 		 */
   1373 		malloc_mutex_lock(&brk_mtx);
   1374 		do {
   1375 			/* Get the current end of brk. */
   1376 			brk_cur = sbrk(0);
   1377 
   1378 			/*
   1379 			 * Calculate how much padding is necessary to
   1380 			 * chunk-align the end of brk.
   1381 			 */
   1382 			incr = (intptr_t)size
   1383 			    - (intptr_t)CHUNK_ADDR2OFFSET(brk_cur);
   1384 			if (incr == (intptr_t)size) {
   1385 				ret = brk_cur;
   1386 			} else {
   1387 				ret = (void *)((intptr_t)brk_cur + incr);
   1388 				incr += size;
   1389 			}
   1390 
   1391 			brk_prev = sbrk(incr);
   1392 			if (brk_prev == brk_cur) {
   1393 				/* Success. */
   1394 				malloc_mutex_unlock(&brk_mtx);
   1395 				brk_max = (void *)((intptr_t)ret + size);
   1396 				goto RETURN;
   1397 			}
   1398 		} while (brk_prev != (void *)-1);
   1399 		malloc_mutex_unlock(&brk_mtx);
   1400 	}
   1401 #endif
   1402 
   1403 	/* All strategies for allocation failed. */
   1404 	ret = NULL;
   1405 RETURN:
   1406 	if (ret != NULL) {
   1407 		chunk_node_t key;
   1408 		/*
   1409 		 * Clean out any entries in old_chunks that overlap with the
   1410 		 * memory we just allocated.
   1411 		 */
   1412 		key.chunk = ret;
   1413 		/* LINTED */
   1414 		tchunk = RB_NFIND(chunk_tree_s, &old_chunks, &key);
   1415 		while (tchunk != NULL
   1416 		    && (uintptr_t)tchunk->chunk >= (uintptr_t)ret
   1417 		    && (uintptr_t)tchunk->chunk < (uintptr_t)ret + size) {
   1418 			delchunk = tchunk;
   1419 			/* LINTED */
   1420 			tchunk = RB_NEXT(chunk_tree_s, &old_chunks, delchunk);
   1421 			/* LINTED */
   1422 			RB_REMOVE(chunk_tree_s, &old_chunks, delchunk);
   1423 			base_chunk_node_dealloc(delchunk);
   1424 		}
   1425 
   1426 	}
   1427 #ifdef MALLOC_STATS
   1428 	if (ret != NULL) {
   1429 		stats_chunks.nchunks += (size / chunksize);
   1430 		stats_chunks.curchunks += (size / chunksize);
   1431 	}
   1432 	if (stats_chunks.curchunks > stats_chunks.highchunks)
   1433 		stats_chunks.highchunks = stats_chunks.curchunks;
   1434 #endif
   1435 	malloc_mutex_unlock(&chunks_mtx);
   1436 
   1437 	assert(CHUNK_ADDR2BASE(ret) == ret);
   1438 	return (ret);
   1439 }
   1440 
   1441 static void
   1442 chunk_dealloc(void *chunk, size_t size)
   1443 {
   1444 	chunk_node_t *node;
   1445 
   1446 	assert(chunk != NULL);
   1447 	assert(CHUNK_ADDR2BASE(chunk) == chunk);
   1448 	assert(size != 0);
   1449 	assert((size & chunksize_mask) == 0);
   1450 
   1451 	malloc_mutex_lock(&chunks_mtx);
   1452 
   1453 #ifdef USE_BRK
   1454 	if ((uintptr_t)chunk >= (uintptr_t)brk_base
   1455 	    && (uintptr_t)chunk < (uintptr_t)brk_max) {
   1456 		void *brk_cur;
   1457 
   1458 		malloc_mutex_lock(&brk_mtx);
   1459 		/* Get the current end of brk. */
   1460 		brk_cur = sbrk(0);
   1461 
   1462 		/*
   1463 		 * Try to shrink the data segment if this chunk is at the end
   1464 		 * of the data segment.  The sbrk() call here is subject to a
   1465 		 * race condition with threads that use brk(2) or sbrk(2)
   1466 		 * directly, but the alternative would be to leak memory for
   1467 		 * the sake of poorly designed multi-threaded programs.
   1468 		 */
   1469 		if (brk_cur == brk_max
   1470 		    && (void *)((uintptr_t)chunk + size) == brk_max
   1471 		    && sbrk(-(intptr_t)size) == brk_max) {
   1472 			malloc_mutex_unlock(&brk_mtx);
   1473 			if (brk_prev == brk_max) {
   1474 				/* Success. */
   1475 				brk_prev = (void *)((intptr_t)brk_max
   1476 				    - (intptr_t)size);
   1477 				brk_max = brk_prev;
   1478 			}
   1479 		} else {
   1480 			size_t offset;
   1481 
   1482 			malloc_mutex_unlock(&brk_mtx);
   1483 			madvise(chunk, size, MADV_FREE);
   1484 
   1485 			/*
   1486 			 * Iteratively create records of each chunk-sized
   1487 			 * memory region that 'chunk' is comprised of, so that
   1488 			 * the address range can be recycled if memory usage
   1489 			 * increases later on.
   1490 			 */
   1491 			for (offset = 0; offset < size; offset += chunksize) {
   1492 				node = base_chunk_node_alloc();
   1493 				if (node == NULL)
   1494 					break;
   1495 
   1496 				node->chunk = (void *)((uintptr_t)chunk
   1497 				    + (uintptr_t)offset);
   1498 				node->size = chunksize;
   1499 				/* LINTED */
   1500 				RB_INSERT(chunk_tree_s, &old_chunks, node);
   1501 			}
   1502 		}
   1503 	} else {
   1504 #endif
   1505 		pages_unmap(chunk, size);
   1506 
   1507 		/*
   1508 		 * Make a record of the chunk's address, so that the address
   1509 		 * range can be recycled if memory usage increases later on.
   1510 		 * Don't bother to create entries if (size > chunksize), since
   1511 		 * doing so could cause scalability issues for truly gargantuan
   1512 		 * objects (many gigabytes or larger).
   1513 		 */
   1514 		if (size == chunksize) {
   1515 			node = base_chunk_node_alloc();
   1516 			if (node != NULL) {
   1517 				node->chunk = (void *)(uintptr_t)chunk;
   1518 				node->size = chunksize;
   1519 				/* LINTED */
   1520 				RB_INSERT(chunk_tree_s, &old_chunks, node);
   1521 			}
   1522 		}
   1523 #ifdef USE_BRK
   1524 	}
   1525 #endif
   1526 
   1527 #ifdef MALLOC_STATS
   1528 	stats_chunks.curchunks -= (size / chunksize);
   1529 #endif
   1530 	malloc_mutex_unlock(&chunks_mtx);
   1531 }
   1532 
   1533 /*
   1534  * End chunk management functions.
   1535  */
   1536 /******************************************************************************/
   1537 /*
   1538  * Begin arena.
   1539  */
   1540 
   1541 /*
   1542  * Choose an arena based on a per-thread and (optimistically) per-CPU value.
   1543  *
   1544  * We maintain at least one block of arenas.  Usually there are more.
   1545  * The blocks are $ncpu arenas in size.  Whole blocks are 'hashed'
   1546  * amongst threads.  To accomplish this, next_arena advances only in
   1547  * ncpu steps.
   1548  */
   1549 static __noinline arena_t *
   1550 choose_arena_hard(void)
   1551 {
   1552 	unsigned i, curcpu;
   1553 	arena_t **map;
   1554 
   1555 	/* Initialize the current block of arenas and advance to next. */
   1556 	malloc_mutex_lock(&arenas_mtx);
   1557 	assert(next_arena % ncpus == 0);
   1558 	assert(narenas % ncpus == 0);
   1559 	map = &arenas[next_arena];
   1560 	set_arenas_map(map);
   1561 	for (i = 0; i < ncpus; i++) {
   1562 		if (arenas[next_arena] == NULL)
   1563 			arenas_extend(next_arena);
   1564 		next_arena = (next_arena + 1) % narenas;
   1565 	}
   1566 	malloc_mutex_unlock(&arenas_mtx);
   1567 
   1568 	/*
   1569 	 * If we were unable to allocate an arena above, then default to
   1570 	 * the first arena, which is always present.
   1571 	 */
   1572 	curcpu = thr_curcpu();
   1573 	if (map[curcpu] != NULL)
   1574 		return map[curcpu];
   1575 	return arenas[0];
   1576 }
   1577 
   1578 static inline arena_t *
   1579 choose_arena(void)
   1580 {
   1581 	unsigned curcpu;
   1582 	arena_t **map;
   1583 
   1584 	map = get_arenas_map();
   1585 	curcpu = thr_curcpu();
   1586 	if (__predict_true(map != NULL && map[curcpu] != NULL))
   1587 		return map[curcpu];
   1588 
   1589         return choose_arena_hard();
   1590 }
   1591 
   1592 #ifndef lint
   1593 static inline int
   1594 arena_chunk_comp(arena_chunk_t *a, arena_chunk_t *b)
   1595 {
   1596 
   1597 	assert(a != NULL);
   1598 	assert(b != NULL);
   1599 
   1600 	if ((uintptr_t)a < (uintptr_t)b)
   1601 		return (-1);
   1602 	else if (a == b)
   1603 		return (0);
   1604 	else
   1605 		return (1);
   1606 }
   1607 
   1608 /* Generate red-black tree code for arena chunks. */
   1609 RB_GENERATE_STATIC(arena_chunk_tree_s, arena_chunk_s, link, arena_chunk_comp);
   1610 #endif
   1611 
   1612 #ifndef lint
   1613 static inline int
   1614 arena_run_comp(arena_run_t *a, arena_run_t *b)
   1615 {
   1616 
   1617 	assert(a != NULL);
   1618 	assert(b != NULL);
   1619 
   1620 	if ((uintptr_t)a < (uintptr_t)b)
   1621 		return (-1);
   1622 	else if (a == b)
   1623 		return (0);
   1624 	else
   1625 		return (1);
   1626 }
   1627 
   1628 /* Generate red-black tree code for arena runs. */
   1629 RB_GENERATE_STATIC(arena_run_tree_s, arena_run_s, link, arena_run_comp);
   1630 #endif
   1631 
   1632 static inline void *
   1633 arena_run_reg_alloc(arena_run_t *run, arena_bin_t *bin)
   1634 {
   1635 	void *ret;
   1636 	unsigned i, mask, bit, regind;
   1637 
   1638 	assert(run->magic == ARENA_RUN_MAGIC);
   1639 	assert(run->regs_minelm < bin->regs_mask_nelms);
   1640 
   1641 	/*
   1642 	 * Move the first check outside the loop, so that run->regs_minelm can
   1643 	 * be updated unconditionally, without the possibility of updating it
   1644 	 * multiple times.
   1645 	 */
   1646 	i = run->regs_minelm;
   1647 	mask = run->regs_mask[i];
   1648 	if (mask != 0) {
   1649 		/* Usable allocation found. */
   1650 		bit = ffs((int)mask) - 1;
   1651 
   1652 		regind = ((i << (SIZEOF_INT_2POW + 3)) + bit);
   1653 		ret = (void *)(((uintptr_t)run) + bin->reg0_offset
   1654 		    + (bin->reg_size * regind));
   1655 
   1656 		/* Clear bit. */
   1657 		mask ^= (1 << bit);
   1658 		run->regs_mask[i] = mask;
   1659 
   1660 		return (ret);
   1661 	}
   1662 
   1663 	for (i++; i < bin->regs_mask_nelms; i++) {
   1664 		mask = run->regs_mask[i];
   1665 		if (mask != 0) {
   1666 			/* Usable allocation found. */
   1667 			bit = ffs((int)mask) - 1;
   1668 
   1669 			regind = ((i << (SIZEOF_INT_2POW + 3)) + bit);
   1670 			ret = (void *)(((uintptr_t)run) + bin->reg0_offset
   1671 			    + (bin->reg_size * regind));
   1672 
   1673 			/* Clear bit. */
   1674 			mask ^= (1 << bit);
   1675 			run->regs_mask[i] = mask;
   1676 
   1677 			/*
   1678 			 * Make a note that nothing before this element
   1679 			 * contains a free region.
   1680 			 */
   1681 			run->regs_minelm = i; /* Low payoff: + (mask == 0); */
   1682 
   1683 			return (ret);
   1684 		}
   1685 	}
   1686 	/* Not reached. */
   1687 	/* LINTED */
   1688 	assert(0);
   1689 	return (NULL);
   1690 }
   1691 
   1692 static inline void
   1693 arena_run_reg_dalloc(arena_run_t *run, arena_bin_t *bin, void *ptr, size_t size)
   1694 {
   1695 	/*
   1696 	 * To divide by a number D that is not a power of two we multiply
   1697 	 * by (2^21 / D) and then right shift by 21 positions.
   1698 	 *
   1699 	 *   X / D
   1700 	 *
   1701 	 * becomes
   1702 	 *
   1703 	 *   (X * size_invs[(D >> QUANTUM_2POW_MIN) - 3]) >> SIZE_INV_SHIFT
   1704 	 */
   1705 #define SIZE_INV_SHIFT 21
   1706 #define SIZE_INV(s) (((1 << SIZE_INV_SHIFT) / (s << QUANTUM_2POW_MIN)) + 1)
   1707 	static const unsigned size_invs[] = {
   1708 	    SIZE_INV(3),
   1709 	    SIZE_INV(4), SIZE_INV(5), SIZE_INV(6), SIZE_INV(7),
   1710 	    SIZE_INV(8), SIZE_INV(9), SIZE_INV(10), SIZE_INV(11),
   1711 	    SIZE_INV(12),SIZE_INV(13), SIZE_INV(14), SIZE_INV(15),
   1712 	    SIZE_INV(16),SIZE_INV(17), SIZE_INV(18), SIZE_INV(19),
   1713 	    SIZE_INV(20),SIZE_INV(21), SIZE_INV(22), SIZE_INV(23),
   1714 	    SIZE_INV(24),SIZE_INV(25), SIZE_INV(26), SIZE_INV(27),
   1715 	    SIZE_INV(28),SIZE_INV(29), SIZE_INV(30), SIZE_INV(31)
   1716 #if (QUANTUM_2POW_MIN < 4)
   1717 	    ,
   1718 	    SIZE_INV(32), SIZE_INV(33), SIZE_INV(34), SIZE_INV(35),
   1719 	    SIZE_INV(36), SIZE_INV(37), SIZE_INV(38), SIZE_INV(39),
   1720 	    SIZE_INV(40), SIZE_INV(41), SIZE_INV(42), SIZE_INV(43),
   1721 	    SIZE_INV(44), SIZE_INV(45), SIZE_INV(46), SIZE_INV(47),
   1722 	    SIZE_INV(48), SIZE_INV(49), SIZE_INV(50), SIZE_INV(51),
   1723 	    SIZE_INV(52), SIZE_INV(53), SIZE_INV(54), SIZE_INV(55),
   1724 	    SIZE_INV(56), SIZE_INV(57), SIZE_INV(58), SIZE_INV(59),
   1725 	    SIZE_INV(60), SIZE_INV(61), SIZE_INV(62), SIZE_INV(63)
   1726 #endif
   1727 	};
   1728 	unsigned diff, regind, elm, bit;
   1729 
   1730 	/* LINTED */
   1731 	assert(run->magic == ARENA_RUN_MAGIC);
   1732 	assert(((sizeof(size_invs)) / sizeof(unsigned)) + 3
   1733 	    >= (SMALL_MAX_DEFAULT >> QUANTUM_2POW_MIN));
   1734 
   1735 	/*
   1736 	 * Avoid doing division with a variable divisor if possible.  Using
   1737 	 * actual division here can reduce allocator throughput by over 20%!
   1738 	 */
   1739 	diff = (unsigned)((uintptr_t)ptr - (uintptr_t)run - bin->reg0_offset);
   1740 	if ((size & (size - 1)) == 0) {
   1741 		/*
   1742 		 * log2_table allows fast division of a power of two in the
   1743 		 * [1..128] range.
   1744 		 *
   1745 		 * (x / divisor) becomes (x >> log2_table[divisor - 1]).
   1746 		 */
   1747 		static const unsigned char log2_table[] = {
   1748 		    0, 1, 0, 2, 0, 0, 0, 3, 0, 0, 0, 0, 0, 0, 0, 4,
   1749 		    0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5,
   1750 		    0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0,
   1751 		    0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6,
   1752 		    0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0,
   1753 		    0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0,
   1754 		    0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0,
   1755 		    0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 7
   1756 		};
   1757 
   1758 		if (size <= 128)
   1759 			regind = (diff >> log2_table[size - 1]);
   1760 		else if (size <= 32768)
   1761 			regind = diff >> (8 + log2_table[(size >> 8) - 1]);
   1762 		else {
   1763 			/*
   1764 			 * The page size is too large for us to use the lookup
   1765 			 * table.  Use real division.
   1766 			 */
   1767 			regind = (unsigned)(diff / size);
   1768 		}
   1769 	} else if (size <= ((sizeof(size_invs) / sizeof(unsigned))
   1770 	    << QUANTUM_2POW_MIN) + 2) {
   1771 		regind = size_invs[(size >> QUANTUM_2POW_MIN) - 3] * diff;
   1772 		regind >>= SIZE_INV_SHIFT;
   1773 	} else {
   1774 		/*
   1775 		 * size_invs isn't large enough to handle this size class, so
   1776 		 * calculate regind using actual division.  This only happens
   1777 		 * if the user increases small_max via the 'S' runtime
   1778 		 * configuration option.
   1779 		 */
   1780 		regind = (unsigned)(diff / size);
   1781 	};
   1782 	assert(diff == regind * size);
   1783 	assert(regind < bin->nregs);
   1784 
   1785 	elm = regind >> (SIZEOF_INT_2POW + 3);
   1786 	if (elm < run->regs_minelm)
   1787 		run->regs_minelm = elm;
   1788 	bit = regind - (elm << (SIZEOF_INT_2POW + 3));
   1789 	assert((run->regs_mask[elm] & (1 << bit)) == 0);
   1790 	run->regs_mask[elm] |= (1 << bit);
   1791 #undef SIZE_INV
   1792 #undef SIZE_INV_SHIFT
   1793 }
   1794 
   1795 static void
   1796 arena_run_split(arena_t *arena, arena_run_t *run, size_t size)
   1797 {
   1798 	arena_chunk_t *chunk;
   1799 	unsigned run_ind, map_offset, total_pages, need_pages, rem_pages;
   1800 	unsigned i;
   1801 
   1802 	chunk = (arena_chunk_t *)CHUNK_ADDR2BASE(run);
   1803 	run_ind = (unsigned)(((uintptr_t)run - (uintptr_t)chunk)
   1804 	    >> pagesize_2pow);
   1805 	total_pages = chunk->map[run_ind].npages;
   1806 	need_pages = (unsigned)(size >> pagesize_2pow);
   1807 	assert(need_pages <= total_pages);
   1808 	rem_pages = total_pages - need_pages;
   1809 
   1810 	/* Split enough pages from the front of run to fit allocation size. */
   1811 	map_offset = run_ind;
   1812 	for (i = 0; i < need_pages; i++) {
   1813 		chunk->map[map_offset + i].npages = need_pages;
   1814 		chunk->map[map_offset + i].pos = i;
   1815 	}
   1816 
   1817 	/* Keep track of trailing unused pages for later use. */
   1818 	if (rem_pages > 0) {
   1819 		/* Update map for trailing pages. */
   1820 		map_offset += need_pages;
   1821 		chunk->map[map_offset].npages = rem_pages;
   1822 		chunk->map[map_offset].pos = POS_FREE;
   1823 		chunk->map[map_offset + rem_pages - 1].npages = rem_pages;
   1824 		chunk->map[map_offset + rem_pages - 1].pos = POS_FREE;
   1825 	}
   1826 
   1827 	chunk->pages_used += need_pages;
   1828 }
   1829 
   1830 static arena_chunk_t *
   1831 arena_chunk_alloc(arena_t *arena)
   1832 {
   1833 	arena_chunk_t *chunk;
   1834 
   1835 	if (arena->spare != NULL) {
   1836 		chunk = arena->spare;
   1837 		arena->spare = NULL;
   1838 
   1839 		/* LINTED */
   1840 		RB_INSERT(arena_chunk_tree_s, &arena->chunks, chunk);
   1841 	} else {
   1842 		chunk = (arena_chunk_t *)chunk_alloc(chunksize);
   1843 		if (chunk == NULL)
   1844 			return (NULL);
   1845 #ifdef MALLOC_STATS
   1846 		arena->stats.mapped += chunksize;
   1847 #endif
   1848 
   1849 		chunk->arena = arena;
   1850 
   1851 		/* LINTED */
   1852 		RB_INSERT(arena_chunk_tree_s, &arena->chunks, chunk);
   1853 
   1854 		/*
   1855 		 * Claim that no pages are in use, since the header is merely
   1856 		 * overhead.
   1857 		 */
   1858 		chunk->pages_used = 0;
   1859 
   1860 		chunk->max_frun_npages = chunk_npages -
   1861 		    arena_chunk_header_npages;
   1862 		chunk->min_frun_ind = arena_chunk_header_npages;
   1863 
   1864 		/*
   1865 		 * Initialize enough of the map to support one maximal free run.
   1866 		 */
   1867 		chunk->map[arena_chunk_header_npages].npages = chunk_npages -
   1868 		    arena_chunk_header_npages;
   1869 		chunk->map[arena_chunk_header_npages].pos = POS_FREE;
   1870 		chunk->map[chunk_npages - 1].npages = chunk_npages -
   1871 		    arena_chunk_header_npages;
   1872 		chunk->map[chunk_npages - 1].pos = POS_FREE;
   1873 	}
   1874 
   1875 	return (chunk);
   1876 }
   1877 
   1878 static void
   1879 arena_chunk_dealloc(arena_t *arena, arena_chunk_t *chunk)
   1880 {
   1881 
   1882 	/*
   1883 	 * Remove chunk from the chunk tree, regardless of whether this chunk
   1884 	 * will be cached, so that the arena does not use it.
   1885 	 */
   1886 	/* LINTED */
   1887 	RB_REMOVE(arena_chunk_tree_s, &chunk->arena->chunks, chunk);
   1888 
   1889 	if (opt_hint == false) {
   1890 		if (arena->spare != NULL) {
   1891 			chunk_dealloc((void *)arena->spare, chunksize);
   1892 #ifdef MALLOC_STATS
   1893 			arena->stats.mapped -= chunksize;
   1894 #endif
   1895 		}
   1896 		arena->spare = chunk;
   1897 	} else {
   1898 		assert(arena->spare == NULL);
   1899 		chunk_dealloc((void *)chunk, chunksize);
   1900 #ifdef MALLOC_STATS
   1901 		arena->stats.mapped -= chunksize;
   1902 #endif
   1903 	}
   1904 }
   1905 
   1906 static arena_run_t *
   1907 arena_run_alloc(arena_t *arena, size_t size)
   1908 {
   1909 	arena_chunk_t *chunk;
   1910 	arena_run_t *run;
   1911 	unsigned need_npages, limit_pages, compl_need_npages;
   1912 
   1913 	assert(size <= (chunksize - (arena_chunk_header_npages <<
   1914 	    pagesize_2pow)));
   1915 	assert((size & pagesize_mask) == 0);
   1916 
   1917 	/*
   1918 	 * Search through arena's chunks in address order for a free run that is
   1919 	 * large enough.  Look for the first fit.
   1920 	 */
   1921 	need_npages = (unsigned)(size >> pagesize_2pow);
   1922 	limit_pages = chunk_npages - arena_chunk_header_npages;
   1923 	compl_need_npages = limit_pages - need_npages;
   1924 	/* LINTED */
   1925 	RB_FOREACH(chunk, arena_chunk_tree_s, &arena->chunks) {
   1926 		/*
   1927 		 * Avoid searching this chunk if there are not enough
   1928 		 * contiguous free pages for there to possibly be a large
   1929 		 * enough free run.
   1930 		 */
   1931 		if (chunk->pages_used <= compl_need_npages &&
   1932 		    need_npages <= chunk->max_frun_npages) {
   1933 			arena_chunk_map_t *mapelm;
   1934 			unsigned i;
   1935 			unsigned max_frun_npages = 0;
   1936 			unsigned min_frun_ind = chunk_npages;
   1937 
   1938 			assert(chunk->min_frun_ind >=
   1939 			    arena_chunk_header_npages);
   1940 			for (i = chunk->min_frun_ind; i < chunk_npages;) {
   1941 				mapelm = &chunk->map[i];
   1942 				if (mapelm->pos == POS_FREE) {
   1943 					if (mapelm->npages >= need_npages) {
   1944 						run = (arena_run_t *)
   1945 						    ((uintptr_t)chunk + (i <<
   1946 						    pagesize_2pow));
   1947 						/* Update page map. */
   1948 						arena_run_split(arena, run,
   1949 						    size);
   1950 						return (run);
   1951 					}
   1952 					if (mapelm->npages >
   1953 					    max_frun_npages) {
   1954 						max_frun_npages =
   1955 						    mapelm->npages;
   1956 					}
   1957 					if (i < min_frun_ind) {
   1958 						min_frun_ind = i;
   1959 						if (i < chunk->min_frun_ind)
   1960 							chunk->min_frun_ind = i;
   1961 					}
   1962 				}
   1963 				i += mapelm->npages;
   1964 			}
   1965 			/*
   1966 			 * Search failure.  Reset cached chunk->max_frun_npages.
   1967 			 * chunk->min_frun_ind was already reset above (if
   1968 			 * necessary).
   1969 			 */
   1970 			chunk->max_frun_npages = max_frun_npages;
   1971 		}
   1972 	}
   1973 
   1974 	/*
   1975 	 * No usable runs.  Create a new chunk from which to allocate the run.
   1976 	 */
   1977 	chunk = arena_chunk_alloc(arena);
   1978 	if (chunk == NULL)
   1979 		return (NULL);
   1980 	run = (arena_run_t *)((uintptr_t)chunk + (arena_chunk_header_npages <<
   1981 	    pagesize_2pow));
   1982 	/* Update page map. */
   1983 	arena_run_split(arena, run, size);
   1984 	return (run);
   1985 }
   1986 
   1987 static void
   1988 arena_run_dalloc(arena_t *arena, arena_run_t *run, size_t size)
   1989 {
   1990 	arena_chunk_t *chunk;
   1991 	unsigned run_ind, run_pages;
   1992 
   1993 	chunk = (arena_chunk_t *)CHUNK_ADDR2BASE(run);
   1994 
   1995 	run_ind = (unsigned)(((uintptr_t)run - (uintptr_t)chunk)
   1996 	    >> pagesize_2pow);
   1997 	assert(run_ind >= arena_chunk_header_npages);
   1998 	assert(run_ind < (chunksize >> pagesize_2pow));
   1999 	run_pages = (unsigned)(size >> pagesize_2pow);
   2000 	assert(run_pages == chunk->map[run_ind].npages);
   2001 
   2002 	/* Subtract pages from count of pages used in chunk. */
   2003 	chunk->pages_used -= run_pages;
   2004 
   2005 	/* Mark run as deallocated. */
   2006 	assert(chunk->map[run_ind].npages == run_pages);
   2007 	chunk->map[run_ind].pos = POS_FREE;
   2008 	assert(chunk->map[run_ind + run_pages - 1].npages == run_pages);
   2009 	chunk->map[run_ind + run_pages - 1].pos = POS_FREE;
   2010 
   2011 	/*
   2012 	 * Tell the kernel that we don't need the data in this run, but only if
   2013 	 * requested via runtime configuration.
   2014 	 */
   2015 	if (opt_hint)
   2016 		madvise(run, size, MADV_FREE);
   2017 
   2018 	/* Try to coalesce with neighboring runs. */
   2019 	if (run_ind > arena_chunk_header_npages &&
   2020 	    chunk->map[run_ind - 1].pos == POS_FREE) {
   2021 		unsigned prev_npages;
   2022 
   2023 		/* Coalesce with previous run. */
   2024 		prev_npages = chunk->map[run_ind - 1].npages;
   2025 		run_ind -= prev_npages;
   2026 		assert(chunk->map[run_ind].npages == prev_npages);
   2027 		assert(chunk->map[run_ind].pos == POS_FREE);
   2028 		run_pages += prev_npages;
   2029 
   2030 		chunk->map[run_ind].npages = run_pages;
   2031 		assert(chunk->map[run_ind].pos == POS_FREE);
   2032 		chunk->map[run_ind + run_pages - 1].npages = run_pages;
   2033 		assert(chunk->map[run_ind + run_pages - 1].pos == POS_FREE);
   2034 	}
   2035 
   2036 	if (run_ind + run_pages < chunk_npages &&
   2037 	    chunk->map[run_ind + run_pages].pos == POS_FREE) {
   2038 		unsigned next_npages;
   2039 
   2040 		/* Coalesce with next run. */
   2041 		next_npages = chunk->map[run_ind + run_pages].npages;
   2042 		run_pages += next_npages;
   2043 		assert(chunk->map[run_ind + run_pages - 1].npages ==
   2044 		    next_npages);
   2045 		assert(chunk->map[run_ind + run_pages - 1].pos == POS_FREE);
   2046 
   2047 		chunk->map[run_ind].npages = run_pages;
   2048 		chunk->map[run_ind].pos = POS_FREE;
   2049 		chunk->map[run_ind + run_pages - 1].npages = run_pages;
   2050 		assert(chunk->map[run_ind + run_pages - 1].pos == POS_FREE);
   2051 	}
   2052 
   2053 	if (chunk->map[run_ind].npages > chunk->max_frun_npages)
   2054 		chunk->max_frun_npages = chunk->map[run_ind].npages;
   2055 	if (run_ind < chunk->min_frun_ind)
   2056 		chunk->min_frun_ind = run_ind;
   2057 
   2058 	/* Deallocate chunk if it is now completely unused. */
   2059 	if (chunk->pages_used == 0)
   2060 		arena_chunk_dealloc(arena, chunk);
   2061 }
   2062 
   2063 static arena_run_t *
   2064 arena_bin_nonfull_run_get(arena_t *arena, arena_bin_t *bin)
   2065 {
   2066 	arena_run_t *run;
   2067 	unsigned i, remainder;
   2068 
   2069 	/* Look for a usable run. */
   2070 	/* LINTED */
   2071 	if ((run = RB_MIN(arena_run_tree_s, &bin->runs)) != NULL) {
   2072 		/* run is guaranteed to have available space. */
   2073 		/* LINTED */
   2074 		RB_REMOVE(arena_run_tree_s, &bin->runs, run);
   2075 #ifdef MALLOC_STATS
   2076 		bin->stats.reruns++;
   2077 #endif
   2078 		return (run);
   2079 	}
   2080 	/* No existing runs have any space available. */
   2081 
   2082 	/* Allocate a new run. */
   2083 	run = arena_run_alloc(arena, bin->run_size);
   2084 	if (run == NULL)
   2085 		return (NULL);
   2086 
   2087 	/* Initialize run internals. */
   2088 	run->bin = bin;
   2089 
   2090 	for (i = 0; i < bin->regs_mask_nelms; i++)
   2091 		run->regs_mask[i] = UINT_MAX;
   2092 	remainder = bin->nregs & ((1 << (SIZEOF_INT_2POW + 3)) - 1);
   2093 	if (remainder != 0) {
   2094 		/* The last element has spare bits that need to be unset. */
   2095 		run->regs_mask[i] = (UINT_MAX >> ((1 << (SIZEOF_INT_2POW + 3))
   2096 		    - remainder));
   2097 	}
   2098 
   2099 	run->regs_minelm = 0;
   2100 
   2101 	run->nfree = bin->nregs;
   2102 #ifdef MALLOC_DEBUG
   2103 	run->magic = ARENA_RUN_MAGIC;
   2104 #endif
   2105 
   2106 #ifdef MALLOC_STATS
   2107 	bin->stats.nruns++;
   2108 	bin->stats.curruns++;
   2109 	if (bin->stats.curruns > bin->stats.highruns)
   2110 		bin->stats.highruns = bin->stats.curruns;
   2111 #endif
   2112 	return (run);
   2113 }
   2114 
   2115 /* bin->runcur must have space available before this function is called. */
   2116 static inline void *
   2117 arena_bin_malloc_easy(arena_t *arena, arena_bin_t *bin, arena_run_t *run)
   2118 {
   2119 	void *ret;
   2120 
   2121 	assert(run->magic == ARENA_RUN_MAGIC);
   2122 	assert(run->nfree > 0);
   2123 
   2124 	ret = arena_run_reg_alloc(run, bin);
   2125 	assert(ret != NULL);
   2126 	run->nfree--;
   2127 
   2128 	return (ret);
   2129 }
   2130 
   2131 /* Re-fill bin->runcur, then call arena_bin_malloc_easy(). */
   2132 static void *
   2133 arena_bin_malloc_hard(arena_t *arena, arena_bin_t *bin)
   2134 {
   2135 
   2136 	bin->runcur = arena_bin_nonfull_run_get(arena, bin);
   2137 	if (bin->runcur == NULL)
   2138 		return (NULL);
   2139 	assert(bin->runcur->magic == ARENA_RUN_MAGIC);
   2140 	assert(bin->runcur->nfree > 0);
   2141 
   2142 	return (arena_bin_malloc_easy(arena, bin, bin->runcur));
   2143 }
   2144 
   2145 /*
   2146  * Calculate bin->run_size such that it meets the following constraints:
   2147  *
   2148  *   *) bin->run_size >= min_run_size
   2149  *   *) bin->run_size <= arena_maxclass
   2150  *   *) bin->run_size <= RUN_MAX_SMALL
   2151  *   *) run header overhead <= RUN_MAX_OVRHD (or header overhead relaxed).
   2152  *
   2153  * bin->nregs, bin->regs_mask_nelms, and bin->reg0_offset are
   2154  * also calculated here, since these settings are all interdependent.
   2155  */
   2156 static size_t
   2157 arena_bin_run_size_calc(arena_bin_t *bin, size_t min_run_size)
   2158 {
   2159 	size_t try_run_size, good_run_size;
   2160 	unsigned good_nregs, good_mask_nelms, good_reg0_offset;
   2161 	unsigned try_nregs, try_mask_nelms, try_reg0_offset;
   2162 
   2163 	assert(min_run_size >= pagesize);
   2164 	assert(min_run_size <= arena_maxclass);
   2165 	assert(min_run_size <= RUN_MAX_SMALL);
   2166 
   2167 	/*
   2168 	 * Calculate known-valid settings before entering the run_size
   2169 	 * expansion loop, so that the first part of the loop always copies
   2170 	 * valid settings.
   2171 	 *
   2172 	 * The do..while loop iteratively reduces the number of regions until
   2173 	 * the run header and the regions no longer overlap.  A closed formula
   2174 	 * would be quite messy, since there is an interdependency between the
   2175 	 * header's mask length and the number of regions.
   2176 	 */
   2177 	try_run_size = min_run_size;
   2178 	try_nregs = (unsigned)(((try_run_size - sizeof(arena_run_t)) /
   2179 	    bin->reg_size) + 1); /* Counter-act try_nregs-- in loop. */
   2180 	do {
   2181 		try_nregs--;
   2182 		try_mask_nelms = (try_nregs >> (SIZEOF_INT_2POW + 3)) +
   2183 		    ((try_nregs & ((1 << (SIZEOF_INT_2POW + 3)) - 1)) ? 1 : 0);
   2184 		try_reg0_offset = (unsigned)(try_run_size -
   2185 		    (try_nregs * bin->reg_size));
   2186 	} while (sizeof(arena_run_t) + (sizeof(unsigned) * (try_mask_nelms - 1))
   2187 	    > try_reg0_offset);
   2188 
   2189 	/* run_size expansion loop. */
   2190 	do {
   2191 		/*
   2192 		 * Copy valid settings before trying more aggressive settings.
   2193 		 */
   2194 		good_run_size = try_run_size;
   2195 		good_nregs = try_nregs;
   2196 		good_mask_nelms = try_mask_nelms;
   2197 		good_reg0_offset = try_reg0_offset;
   2198 
   2199 		/* Try more aggressive settings. */
   2200 		try_run_size += pagesize;
   2201 		try_nregs = (unsigned)(((try_run_size - sizeof(arena_run_t)) /
   2202 		    bin->reg_size) + 1); /* Counter-act try_nregs-- in loop. */
   2203 		do {
   2204 			try_nregs--;
   2205 			try_mask_nelms = (try_nregs >> (SIZEOF_INT_2POW + 3)) +
   2206 			    ((try_nregs & ((1 << (SIZEOF_INT_2POW + 3)) - 1)) ?
   2207 			    1 : 0);
   2208 			try_reg0_offset = (unsigned)(try_run_size - (try_nregs *
   2209 			    bin->reg_size));
   2210 		} while (sizeof(arena_run_t) + (sizeof(unsigned) *
   2211 		    (try_mask_nelms - 1)) > try_reg0_offset);
   2212 	} while (try_run_size <= arena_maxclass && try_run_size <= RUN_MAX_SMALL
   2213 	    && RUN_MAX_OVRHD * (bin->reg_size << 3) > RUN_MAX_OVRHD_RELAX
   2214 	    && (try_reg0_offset << RUN_BFP) > RUN_MAX_OVRHD * try_run_size);
   2215 
   2216 	assert(sizeof(arena_run_t) + (sizeof(unsigned) * (good_mask_nelms - 1))
   2217 	    <= good_reg0_offset);
   2218 	assert((good_mask_nelms << (SIZEOF_INT_2POW + 3)) >= good_nregs);
   2219 
   2220 	/* Copy final settings. */
   2221 	bin->run_size = good_run_size;
   2222 	bin->nregs = good_nregs;
   2223 	bin->regs_mask_nelms = good_mask_nelms;
   2224 	bin->reg0_offset = good_reg0_offset;
   2225 
   2226 	return (good_run_size);
   2227 }
   2228 
   2229 static void *
   2230 arena_malloc(arena_t *arena, size_t size)
   2231 {
   2232 	void *ret;
   2233 
   2234 	assert(arena != NULL);
   2235 	assert(arena->magic == ARENA_MAGIC);
   2236 	assert(size != 0);
   2237 	assert(QUANTUM_CEILING(size) <= arena_maxclass);
   2238 
   2239 	if (size <= bin_maxclass) {
   2240 		arena_bin_t *bin;
   2241 		arena_run_t *run;
   2242 
   2243 		/* Small allocation. */
   2244 
   2245 		if (size < small_min) {
   2246 			/* Tiny. */
   2247 			size = pow2_ceil(size);
   2248 			bin = &arena->bins[ffs((int)(size >> (TINY_MIN_2POW +
   2249 			    1)))];
   2250 #if (!defined(NDEBUG) || defined(MALLOC_STATS))
   2251 			/*
   2252 			 * Bin calculation is always correct, but we may need
   2253 			 * to fix size for the purposes of assertions and/or
   2254 			 * stats accuracy.
   2255 			 */
   2256 			if (size < (1 << TINY_MIN_2POW))
   2257 				size = (1 << TINY_MIN_2POW);
   2258 #endif
   2259 		} else if (size <= small_max) {
   2260 			/* Quantum-spaced. */
   2261 			size = QUANTUM_CEILING(size);
   2262 			bin = &arena->bins[ntbins + (size >> opt_quantum_2pow)
   2263 			    - 1];
   2264 		} else {
   2265 			/* Sub-page. */
   2266 			size = pow2_ceil(size);
   2267 			bin = &arena->bins[ntbins + nqbins
   2268 			    + (ffs((int)(size >> opt_small_max_2pow)) - 2)];
   2269 		}
   2270 		assert(size == bin->reg_size);
   2271 
   2272 		malloc_mutex_lock(&arena->mtx);
   2273 		if ((run = bin->runcur) != NULL && run->nfree > 0)
   2274 			ret = arena_bin_malloc_easy(arena, bin, run);
   2275 		else
   2276 			ret = arena_bin_malloc_hard(arena, bin);
   2277 
   2278 		if (ret == NULL) {
   2279 			malloc_mutex_unlock(&arena->mtx);
   2280 			return (NULL);
   2281 		}
   2282 
   2283 #ifdef MALLOC_STATS
   2284 		bin->stats.nrequests++;
   2285 		arena->stats.nmalloc_small++;
   2286 		arena->stats.allocated_small += size;
   2287 #endif
   2288 	} else {
   2289 		/* Large allocation. */
   2290 		size = PAGE_CEILING(size);
   2291 		malloc_mutex_lock(&arena->mtx);
   2292 		ret = (void *)arena_run_alloc(arena, size);
   2293 		if (ret == NULL) {
   2294 			malloc_mutex_unlock(&arena->mtx);
   2295 			return (NULL);
   2296 		}
   2297 #ifdef MALLOC_STATS
   2298 		arena->stats.nmalloc_large++;
   2299 		arena->stats.allocated_large += size;
   2300 #endif
   2301 	}
   2302 
   2303 	malloc_mutex_unlock(&arena->mtx);
   2304 
   2305 	if (opt_junk)
   2306 		memset(ret, 0xa5, size);
   2307 	else if (opt_zero)
   2308 		memset(ret, 0, size);
   2309 	return (ret);
   2310 }
   2311 
   2312 static inline void
   2313 arena_palloc_trim(arena_t *arena, arena_chunk_t *chunk, unsigned pageind,
   2314     unsigned npages)
   2315 {
   2316 	unsigned i;
   2317 
   2318 	assert(npages > 0);
   2319 
   2320 	/*
   2321 	 * Modifiy the map such that arena_run_dalloc() sees the run as
   2322 	 * separately allocated.
   2323 	 */
   2324 	for (i = 0; i < npages; i++) {
   2325 		chunk->map[pageind + i].npages = npages;
   2326 		chunk->map[pageind + i].pos = i;
   2327 	}
   2328 	arena_run_dalloc(arena, (arena_run_t *)((uintptr_t)chunk + (pageind <<
   2329 	    pagesize_2pow)), npages << pagesize_2pow);
   2330 }
   2331 
   2332 /* Only handles large allocations that require more than page alignment. */
   2333 static void *
   2334 arena_palloc(arena_t *arena, size_t alignment, size_t size, size_t alloc_size)
   2335 {
   2336 	void *ret;
   2337 	size_t offset;
   2338 	arena_chunk_t *chunk;
   2339 	unsigned pageind, i, npages;
   2340 
   2341 	assert((size & pagesize_mask) == 0);
   2342 	assert((alignment & pagesize_mask) == 0);
   2343 
   2344 	npages = (unsigned)(size >> pagesize_2pow);
   2345 
   2346 	malloc_mutex_lock(&arena->mtx);
   2347 	ret = (void *)arena_run_alloc(arena, alloc_size);
   2348 	if (ret == NULL) {
   2349 		malloc_mutex_unlock(&arena->mtx);
   2350 		return (NULL);
   2351 	}
   2352 
   2353 	chunk = (arena_chunk_t *)CHUNK_ADDR2BASE(ret);
   2354 
   2355 	offset = (uintptr_t)ret & (alignment - 1);
   2356 	assert((offset & pagesize_mask) == 0);
   2357 	assert(offset < alloc_size);
   2358 	if (offset == 0) {
   2359 		pageind = (unsigned)(((uintptr_t)ret - (uintptr_t)chunk) >>
   2360 		    pagesize_2pow);
   2361 
   2362 		/* Update the map for the run to be kept. */
   2363 		for (i = 0; i < npages; i++) {
   2364 			chunk->map[pageind + i].npages = npages;
   2365 			assert(chunk->map[pageind + i].pos == i);
   2366 		}
   2367 
   2368 		/* Trim trailing space. */
   2369 		arena_palloc_trim(arena, chunk, pageind + npages,
   2370 		    (unsigned)((alloc_size - size) >> pagesize_2pow));
   2371 	} else {
   2372 		size_t leadsize, trailsize;
   2373 
   2374 		leadsize = alignment - offset;
   2375 		ret = (void *)((uintptr_t)ret + leadsize);
   2376 		pageind = (unsigned)(((uintptr_t)ret - (uintptr_t)chunk) >>
   2377 		    pagesize_2pow);
   2378 
   2379 		/* Update the map for the run to be kept. */
   2380 		for (i = 0; i < npages; i++) {
   2381 			chunk->map[pageind + i].npages = npages;
   2382 			chunk->map[pageind + i].pos = i;
   2383 		}
   2384 
   2385 		/* Trim leading space. */
   2386 		arena_palloc_trim(arena, chunk,
   2387 		    (unsigned)(pageind - (leadsize >> pagesize_2pow)),
   2388 		    (unsigned)(leadsize >> pagesize_2pow));
   2389 
   2390 		trailsize = alloc_size - leadsize - size;
   2391 		if (trailsize != 0) {
   2392 			/* Trim trailing space. */
   2393 			assert(trailsize < alloc_size);
   2394 			arena_palloc_trim(arena, chunk, pageind + npages,
   2395 			    (unsigned)(trailsize >> pagesize_2pow));
   2396 		}
   2397 	}
   2398 
   2399 #ifdef MALLOC_STATS
   2400 	arena->stats.nmalloc_large++;
   2401 	arena->stats.allocated_large += size;
   2402 #endif
   2403 	malloc_mutex_unlock(&arena->mtx);
   2404 
   2405 	if (opt_junk)
   2406 		memset(ret, 0xa5, size);
   2407 	else if (opt_zero)
   2408 		memset(ret, 0, size);
   2409 	return (ret);
   2410 }
   2411 
   2412 /* Return the size of the allocation pointed to by ptr. */
   2413 static size_t
   2414 arena_salloc(const void *ptr)
   2415 {
   2416 	size_t ret;
   2417 	arena_chunk_t *chunk;
   2418 	arena_chunk_map_t *mapelm;
   2419 	unsigned pageind;
   2420 
   2421 	assert(ptr != NULL);
   2422 	assert(CHUNK_ADDR2BASE(ptr) != ptr);
   2423 
   2424 	/*
   2425 	 * No arena data structures that we query here can change in a way that
   2426 	 * affects this function, so we don't need to lock.
   2427 	 */
   2428 	chunk = (arena_chunk_t *)CHUNK_ADDR2BASE(ptr);
   2429 	pageind = (unsigned)(((uintptr_t)ptr - (uintptr_t)chunk) >>
   2430 	    pagesize_2pow);
   2431 	mapelm = &chunk->map[pageind];
   2432 	if (mapelm->pos != 0 || ptr != (char *)((uintptr_t)chunk) + (pageind <<
   2433 	    pagesize_2pow)) {
   2434 		arena_run_t *run;
   2435 
   2436 		pageind -= mapelm->pos;
   2437 
   2438 		run = (arena_run_t *)((uintptr_t)chunk + (pageind <<
   2439 		    pagesize_2pow));
   2440 		assert(run->magic == ARENA_RUN_MAGIC);
   2441 		ret = run->bin->reg_size;
   2442 	} else
   2443 		ret = mapelm->npages << pagesize_2pow;
   2444 
   2445 	return (ret);
   2446 }
   2447 
   2448 static void *
   2449 arena_ralloc(void *ptr, size_t size, size_t oldsize)
   2450 {
   2451 	void *ret;
   2452 
   2453 	/* Avoid moving the allocation if the size class would not change. */
   2454 	if (size < small_min) {
   2455 		if (oldsize < small_min &&
   2456 		    ffs((int)(pow2_ceil(size) >> (TINY_MIN_2POW + 1)))
   2457 		    == ffs((int)(pow2_ceil(oldsize) >> (TINY_MIN_2POW + 1))))
   2458 			goto IN_PLACE;
   2459 	} else if (size <= small_max) {
   2460 		if (oldsize >= small_min && oldsize <= small_max &&
   2461 		    (QUANTUM_CEILING(size) >> opt_quantum_2pow)
   2462 		    == (QUANTUM_CEILING(oldsize) >> opt_quantum_2pow))
   2463 			goto IN_PLACE;
   2464 	} else {
   2465 		/*
   2466 		 * We make no attempt to resize runs here, though it would be
   2467 		 * possible to do so.
   2468 		 */
   2469 		if (oldsize > small_max && PAGE_CEILING(size) == oldsize)
   2470 			goto IN_PLACE;
   2471 	}
   2472 
   2473 	/*
   2474 	 * If we get here, then size and oldsize are different enough that we
   2475 	 * need to use a different size class.  In that case, fall back to
   2476 	 * allocating new space and copying.
   2477 	 */
   2478 	ret = arena_malloc(choose_arena(), size);
   2479 	if (ret == NULL)
   2480 		return (NULL);
   2481 
   2482 	/* Junk/zero-filling were already done by arena_malloc(). */
   2483 	if (size < oldsize)
   2484 		memcpy(ret, ptr, size);
   2485 	else
   2486 		memcpy(ret, ptr, oldsize);
   2487 	idalloc(ptr);
   2488 	return (ret);
   2489 IN_PLACE:
   2490 	if (opt_junk && size < oldsize)
   2491 		memset((void *)((uintptr_t)ptr + size), 0x5a, oldsize - size);
   2492 	else if (opt_zero && size > oldsize)
   2493 		memset((void *)((uintptr_t)ptr + oldsize), 0, size - oldsize);
   2494 	return (ptr);
   2495 }
   2496 
   2497 static void
   2498 arena_dalloc(arena_t *arena, arena_chunk_t *chunk, void *ptr)
   2499 {
   2500 	unsigned pageind;
   2501 	arena_chunk_map_t *mapelm;
   2502 	size_t size;
   2503 
   2504 	assert(arena != NULL);
   2505 	assert(arena->magic == ARENA_MAGIC);
   2506 	assert(chunk->arena == arena);
   2507 	assert(ptr != NULL);
   2508 	assert(CHUNK_ADDR2BASE(ptr) != ptr);
   2509 
   2510 	pageind = (unsigned)(((uintptr_t)ptr - (uintptr_t)chunk) >>
   2511 	    pagesize_2pow);
   2512 	mapelm = &chunk->map[pageind];
   2513 	if (mapelm->pos != 0 || ptr != (char *)((uintptr_t)chunk) + (pageind <<
   2514 	    pagesize_2pow)) {
   2515 		arena_run_t *run;
   2516 		arena_bin_t *bin;
   2517 
   2518 		/* Small allocation. */
   2519 
   2520 		pageind -= mapelm->pos;
   2521 
   2522 		run = (arena_run_t *)((uintptr_t)chunk + (pageind <<
   2523 		    pagesize_2pow));
   2524 		assert(run->magic == ARENA_RUN_MAGIC);
   2525 		bin = run->bin;
   2526 		size = bin->reg_size;
   2527 
   2528 		if (opt_junk)
   2529 			memset(ptr, 0x5a, size);
   2530 
   2531 		malloc_mutex_lock(&arena->mtx);
   2532 		arena_run_reg_dalloc(run, bin, ptr, size);
   2533 		run->nfree++;
   2534 
   2535 		if (run->nfree == bin->nregs) {
   2536 			/* Deallocate run. */
   2537 			if (run == bin->runcur)
   2538 				bin->runcur = NULL;
   2539 			else if (bin->nregs != 1) {
   2540 				/*
   2541 				 * This block's conditional is necessary because
   2542 				 * if the run only contains one region, then it
   2543 				 * never gets inserted into the non-full runs
   2544 				 * tree.
   2545 				 */
   2546 				/* LINTED */
   2547 				RB_REMOVE(arena_run_tree_s, &bin->runs, run);
   2548 			}
   2549 #ifdef MALLOC_DEBUG
   2550 			run->magic = 0;
   2551 #endif
   2552 			arena_run_dalloc(arena, run, bin->run_size);
   2553 #ifdef MALLOC_STATS
   2554 			bin->stats.curruns--;
   2555 #endif
   2556 		} else if (run->nfree == 1 && run != bin->runcur) {
   2557 			/*
   2558 			 * Make sure that bin->runcur always refers to the
   2559 			 * lowest non-full run, if one exists.
   2560 			 */
   2561 			if (bin->runcur == NULL)
   2562 				bin->runcur = run;
   2563 			else if ((uintptr_t)run < (uintptr_t)bin->runcur) {
   2564 				/* Switch runcur. */
   2565 				if (bin->runcur->nfree > 0) {
   2566 					/* Insert runcur. */
   2567 					/* LINTED */
   2568 					RB_INSERT(arena_run_tree_s, &bin->runs,
   2569 					    bin->runcur);
   2570 				}
   2571 				bin->runcur = run;
   2572 			} else {
   2573 				/* LINTED */
   2574 				RB_INSERT(arena_run_tree_s, &bin->runs, run);
   2575 			}
   2576 		}
   2577 #ifdef MALLOC_STATS
   2578 		arena->stats.allocated_small -= size;
   2579 		arena->stats.ndalloc_small++;
   2580 #endif
   2581 	} else {
   2582 		/* Large allocation. */
   2583 
   2584 		size = mapelm->npages << pagesize_2pow;
   2585 		assert((((uintptr_t)ptr) & pagesize_mask) == 0);
   2586 
   2587 		if (opt_junk)
   2588 			memset(ptr, 0x5a, size);
   2589 
   2590 		malloc_mutex_lock(&arena->mtx);
   2591 		arena_run_dalloc(arena, (arena_run_t *)ptr, size);
   2592 #ifdef MALLOC_STATS
   2593 		arena->stats.allocated_large -= size;
   2594 		arena->stats.ndalloc_large++;
   2595 #endif
   2596 	}
   2597 
   2598 	malloc_mutex_unlock(&arena->mtx);
   2599 }
   2600 
   2601 static bool
   2602 arena_new(arena_t *arena)
   2603 {
   2604 	unsigned i;
   2605 	arena_bin_t *bin;
   2606 	size_t prev_run_size;
   2607 
   2608 	malloc_mutex_init(&arena->mtx);
   2609 
   2610 #ifdef MALLOC_STATS
   2611 	memset(&arena->stats, 0, sizeof(arena_stats_t));
   2612 #endif
   2613 
   2614 	/* Initialize chunks. */
   2615 	RB_INIT(&arena->chunks);
   2616 	arena->spare = NULL;
   2617 
   2618 	/* Initialize bins. */
   2619 	prev_run_size = pagesize;
   2620 
   2621 	/* (2^n)-spaced tiny bins. */
   2622 	for (i = 0; i < ntbins; i++) {
   2623 		bin = &arena->bins[i];
   2624 		bin->runcur = NULL;
   2625 		RB_INIT(&bin->runs);
   2626 
   2627 		bin->reg_size = (1 << (TINY_MIN_2POW + i));
   2628 		prev_run_size = arena_bin_run_size_calc(bin, prev_run_size);
   2629 
   2630 #ifdef MALLOC_STATS
   2631 		memset(&bin->stats, 0, sizeof(malloc_bin_stats_t));
   2632 #endif
   2633 	}
   2634 
   2635 	/* Quantum-spaced bins. */
   2636 	for (; i < ntbins + nqbins; i++) {
   2637 		bin = &arena->bins[i];
   2638 		bin->runcur = NULL;
   2639 		RB_INIT(&bin->runs);
   2640 
   2641 		bin->reg_size = quantum * (i - ntbins + 1);
   2642 /*
   2643 		pow2_size = pow2_ceil(quantum * (i - ntbins + 1));
   2644 */
   2645 		prev_run_size = arena_bin_run_size_calc(bin, prev_run_size);
   2646 
   2647 #ifdef MALLOC_STATS
   2648 		memset(&bin->stats, 0, sizeof(malloc_bin_stats_t));
   2649 #endif
   2650 	}
   2651 
   2652 	/* (2^n)-spaced sub-page bins. */
   2653 	for (; i < ntbins + nqbins + nsbins; i++) {
   2654 		bin = &arena->bins[i];
   2655 		bin->runcur = NULL;
   2656 		RB_INIT(&bin->runs);
   2657 
   2658 		bin->reg_size = (small_max << (i - (ntbins + nqbins) + 1));
   2659 
   2660 		prev_run_size = arena_bin_run_size_calc(bin, prev_run_size);
   2661 
   2662 #ifdef MALLOC_STATS
   2663 		memset(&bin->stats, 0, sizeof(malloc_bin_stats_t));
   2664 #endif
   2665 	}
   2666 
   2667 #ifdef MALLOC_DEBUG
   2668 	arena->magic = ARENA_MAGIC;
   2669 #endif
   2670 
   2671 	return (false);
   2672 }
   2673 
   2674 /* Create a new arena and insert it into the arenas array at index ind. */
   2675 static arena_t *
   2676 arenas_extend(unsigned ind)
   2677 {
   2678 	arena_t *ret;
   2679 
   2680 	/* Allocate enough space for trailing bins. */
   2681 	ret = (arena_t *)base_alloc(sizeof(arena_t)
   2682 	    + (sizeof(arena_bin_t) * (ntbins + nqbins + nsbins - 1)));
   2683 	if (ret != NULL && arena_new(ret) == false) {
   2684 		arenas[ind] = ret;
   2685 		return (ret);
   2686 	}
   2687 	/* Only reached if there is an OOM error. */
   2688 
   2689 	/*
   2690 	 * OOM here is quite inconvenient to propagate, since dealing with it
   2691 	 * would require a check for failure in the fast path.  Instead, punt
   2692 	 * by using arenas[0].  In practice, this is an extremely unlikely
   2693 	 * failure.
   2694 	 */
   2695 	_malloc_message(getprogname(),
   2696 	    ": (malloc) Error initializing arena\n", "", "");
   2697 	if (opt_abort)
   2698 		abort();
   2699 
   2700 	return (arenas[0]);
   2701 }
   2702 
   2703 /*
   2704  * End arena.
   2705  */
   2706 /******************************************************************************/
   2707 /*
   2708  * Begin general internal functions.
   2709  */
   2710 
   2711 static void *
   2712 huge_malloc(size_t size)
   2713 {
   2714 	void *ret;
   2715 	size_t csize;
   2716 	chunk_node_t *node;
   2717 
   2718 	/* Allocate one or more contiguous chunks for this request. */
   2719 
   2720 	csize = CHUNK_CEILING(size);
   2721 	if (csize == 0) {
   2722 		/* size is large enough to cause size_t wrap-around. */
   2723 		return (NULL);
   2724 	}
   2725 
   2726 	/* Allocate a chunk node with which to track the chunk. */
   2727 	node = base_chunk_node_alloc();
   2728 	if (node == NULL)
   2729 		return (NULL);
   2730 
   2731 	ret = chunk_alloc(csize);
   2732 	if (ret == NULL) {
   2733 		base_chunk_node_dealloc(node);
   2734 		return (NULL);
   2735 	}
   2736 
   2737 	/* Insert node into huge. */
   2738 	node->chunk = ret;
   2739 	node->size = csize;
   2740 
   2741 	malloc_mutex_lock(&chunks_mtx);
   2742 	RB_INSERT(chunk_tree_s, &huge, node);
   2743 #ifdef MALLOC_STATS
   2744 	huge_nmalloc++;
   2745 	huge_allocated += csize;
   2746 #endif
   2747 	malloc_mutex_unlock(&chunks_mtx);
   2748 
   2749 	if (opt_junk)
   2750 		memset(ret, 0xa5, csize);
   2751 	else if (opt_zero)
   2752 		memset(ret, 0, csize);
   2753 
   2754 	return (ret);
   2755 }
   2756 
   2757 /* Only handles large allocations that require more than chunk alignment. */
   2758 static void *
   2759 huge_palloc(size_t alignment, size_t size)
   2760 {
   2761 	void *ret;
   2762 	size_t alloc_size, chunk_size, offset;
   2763 	chunk_node_t *node;
   2764 
   2765 	/*
   2766 	 * This allocation requires alignment that is even larger than chunk
   2767 	 * alignment.  This means that huge_malloc() isn't good enough.
   2768 	 *
   2769 	 * Allocate almost twice as many chunks as are demanded by the size or
   2770 	 * alignment, in order to assure the alignment can be achieved, then
   2771 	 * unmap leading and trailing chunks.
   2772 	 */
   2773 	assert(alignment >= chunksize);
   2774 
   2775 	chunk_size = CHUNK_CEILING(size);
   2776 
   2777 	if (size >= alignment)
   2778 		alloc_size = chunk_size + alignment - chunksize;
   2779 	else
   2780 		alloc_size = (alignment << 1) - chunksize;
   2781 
   2782 	/* Allocate a chunk node with which to track the chunk. */
   2783 	node = base_chunk_node_alloc();
   2784 	if (node == NULL)
   2785 		return (NULL);
   2786 
   2787 	ret = chunk_alloc(alloc_size);
   2788 	if (ret == NULL) {
   2789 		base_chunk_node_dealloc(node);
   2790 		return (NULL);
   2791 	}
   2792 
   2793 	offset = (uintptr_t)ret & (alignment - 1);
   2794 	assert((offset & chunksize_mask) == 0);
   2795 	assert(offset < alloc_size);
   2796 	if (offset == 0) {
   2797 		/* Trim trailing space. */
   2798 		chunk_dealloc((void *)((uintptr_t)ret + chunk_size), alloc_size
   2799 		    - chunk_size);
   2800 	} else {
   2801 		size_t trailsize;
   2802 
   2803 		/* Trim leading space. */
   2804 		chunk_dealloc(ret, alignment - offset);
   2805 
   2806 		ret = (void *)((uintptr_t)ret + (alignment - offset));
   2807 
   2808 		trailsize = alloc_size - (alignment - offset) - chunk_size;
   2809 		if (trailsize != 0) {
   2810 		    /* Trim trailing space. */
   2811 		    assert(trailsize < alloc_size);
   2812 		    chunk_dealloc((void *)((uintptr_t)ret + chunk_size),
   2813 			trailsize);
   2814 		}
   2815 	}
   2816 
   2817 	/* Insert node into huge. */
   2818 	node->chunk = ret;
   2819 	node->size = chunk_size;
   2820 
   2821 	malloc_mutex_lock(&chunks_mtx);
   2822 	RB_INSERT(chunk_tree_s, &huge, node);
   2823 #ifdef MALLOC_STATS
   2824 	huge_nmalloc++;
   2825 	huge_allocated += chunk_size;
   2826 #endif
   2827 	malloc_mutex_unlock(&chunks_mtx);
   2828 
   2829 	if (opt_junk)
   2830 		memset(ret, 0xa5, chunk_size);
   2831 	else if (opt_zero)
   2832 		memset(ret, 0, chunk_size);
   2833 
   2834 	return (ret);
   2835 }
   2836 
   2837 static void *
   2838 huge_ralloc(void *ptr, size_t size, size_t oldsize)
   2839 {
   2840 	void *ret;
   2841 
   2842 	/* Avoid moving the allocation if the size class would not change. */
   2843 	if (oldsize > arena_maxclass &&
   2844 	    CHUNK_CEILING(size) == CHUNK_CEILING(oldsize)) {
   2845 		if (opt_junk && size < oldsize) {
   2846 			memset((void *)((uintptr_t)ptr + size), 0x5a, oldsize
   2847 			    - size);
   2848 		} else if (opt_zero && size > oldsize) {
   2849 			memset((void *)((uintptr_t)ptr + oldsize), 0, size
   2850 			    - oldsize);
   2851 		}
   2852 		return (ptr);
   2853 	}
   2854 
   2855 	if (CHUNK_ADDR2BASE(ptr) == ptr
   2856 #ifdef USE_BRK
   2857 	    && ((uintptr_t)ptr < (uintptr_t)brk_base
   2858 	    || (uintptr_t)ptr >= (uintptr_t)brk_max)
   2859 #endif
   2860 	    ) {
   2861 		chunk_node_t *node, key;
   2862 		void *newptr;
   2863 		size_t oldcsize;
   2864 		size_t newcsize;
   2865 
   2866 		newcsize = CHUNK_CEILING(size);
   2867 		oldcsize = CHUNK_CEILING(oldsize);
   2868 		assert(oldcsize != newcsize);
   2869 		if (newcsize == 0) {
   2870 			/* size_t wrap-around */
   2871 			return (NULL);
   2872 		}
   2873 
   2874 		/*
   2875 		 * Remove the old region from the tree now.  If mremap()
   2876 		 * returns the region to the system, other thread may
   2877 		 * map it for same huge allocation and insert it to the
   2878 		 * tree before we acquire the mutex lock again.
   2879 		 */
   2880 		malloc_mutex_lock(&chunks_mtx);
   2881 		key.chunk = __DECONST(void *, ptr);
   2882 		/* LINTED */
   2883 		node = RB_FIND(chunk_tree_s, &huge, &key);
   2884 		assert(node != NULL);
   2885 		assert(node->chunk == ptr);
   2886 		assert(node->size == oldcsize);
   2887 		RB_REMOVE(chunk_tree_s, &huge, node);
   2888 		malloc_mutex_unlock(&chunks_mtx);
   2889 
   2890 		newptr = mremap(ptr, oldcsize, NULL, newcsize,
   2891 		    MAP_ALIGNED(chunksize_2pow));
   2892 		if (newptr == MAP_FAILED) {
   2893 			/* We still own the old region. */
   2894 			malloc_mutex_lock(&chunks_mtx);
   2895 			RB_INSERT(chunk_tree_s, &huge, node);
   2896 			malloc_mutex_unlock(&chunks_mtx);
   2897 		} else {
   2898 			assert(CHUNK_ADDR2BASE(newptr) == newptr);
   2899 
   2900 			/* Insert new or resized old region. */
   2901 			malloc_mutex_lock(&chunks_mtx);
   2902 			node->size = newcsize;
   2903 			node->chunk = newptr;
   2904 			RB_INSERT(chunk_tree_s, &huge, node);
   2905 #ifdef MALLOC_STATS
   2906 			huge_nralloc++;
   2907 			huge_allocated += newcsize - oldcsize;
   2908 			if (newcsize > oldcsize) {
   2909 				stats_chunks.curchunks +=
   2910 				    (newcsize - oldcsize) / chunksize;
   2911 				if (stats_chunks.curchunks >
   2912 				    stats_chunks.highchunks)
   2913 					stats_chunks.highchunks =
   2914 					    stats_chunks.curchunks;
   2915 			} else {
   2916 				stats_chunks.curchunks -=
   2917 				    (oldcsize - newcsize) / chunksize;
   2918 			}
   2919 #endif
   2920 			malloc_mutex_unlock(&chunks_mtx);
   2921 
   2922 			if (opt_junk && size < oldsize) {
   2923 				memset((void *)((uintptr_t)newptr + size), 0x5a,
   2924 				    newcsize - size);
   2925 			} else if (opt_zero && size > oldsize) {
   2926 				memset((void *)((uintptr_t)newptr + oldsize), 0,
   2927 				    size - oldsize);
   2928 			}
   2929 			return (newptr);
   2930 		}
   2931 	}
   2932 
   2933 	/*
   2934 	 * If we get here, then size and oldsize are different enough that we
   2935 	 * need to use a different size class.  In that case, fall back to
   2936 	 * allocating new space and copying.
   2937 	 */
   2938 	ret = huge_malloc(size);
   2939 	if (ret == NULL)
   2940 		return (NULL);
   2941 
   2942 	if (CHUNK_ADDR2BASE(ptr) == ptr) {
   2943 		/* The old allocation is a chunk. */
   2944 		if (size < oldsize)
   2945 			memcpy(ret, ptr, size);
   2946 		else
   2947 			memcpy(ret, ptr, oldsize);
   2948 	} else {
   2949 		/* The old allocation is a region. */
   2950 		assert(oldsize < size);
   2951 		memcpy(ret, ptr, oldsize);
   2952 	}
   2953 	idalloc(ptr);
   2954 	return (ret);
   2955 }
   2956 
   2957 static void
   2958 huge_dalloc(void *ptr)
   2959 {
   2960 	chunk_node_t key;
   2961 	chunk_node_t *node;
   2962 
   2963 	malloc_mutex_lock(&chunks_mtx);
   2964 
   2965 	/* Extract from tree of huge allocations. */
   2966 	key.chunk = ptr;
   2967 	/* LINTED */
   2968 	node = RB_FIND(chunk_tree_s, &huge, &key);
   2969 	assert(node != NULL);
   2970 	assert(node->chunk == ptr);
   2971 	/* LINTED */
   2972 	RB_REMOVE(chunk_tree_s, &huge, node);
   2973 
   2974 #ifdef MALLOC_STATS
   2975 	huge_ndalloc++;
   2976 	huge_allocated -= node->size;
   2977 #endif
   2978 
   2979 	malloc_mutex_unlock(&chunks_mtx);
   2980 
   2981 	/* Unmap chunk. */
   2982 #ifdef USE_BRK
   2983 	if (opt_junk)
   2984 		memset(node->chunk, 0x5a, node->size);
   2985 #endif
   2986 	chunk_dealloc(node->chunk, node->size);
   2987 
   2988 	base_chunk_node_dealloc(node);
   2989 }
   2990 
   2991 static void *
   2992 imalloc(size_t size)
   2993 {
   2994 	void *ret;
   2995 
   2996 	assert(size != 0);
   2997 
   2998 	if (size <= arena_maxclass)
   2999 		ret = arena_malloc(choose_arena(), size);
   3000 	else
   3001 		ret = huge_malloc(size);
   3002 
   3003 	return (ret);
   3004 }
   3005 
   3006 static void *
   3007 ipalloc(size_t alignment, size_t size)
   3008 {
   3009 	void *ret;
   3010 	size_t ceil_size;
   3011 
   3012 	/*
   3013 	 * Round size up to the nearest multiple of alignment.
   3014 	 *
   3015 	 * This done, we can take advantage of the fact that for each small
   3016 	 * size class, every object is aligned at the smallest power of two
   3017 	 * that is non-zero in the base two representation of the size.  For
   3018 	 * example:
   3019 	 *
   3020 	 *   Size |   Base 2 | Minimum alignment
   3021 	 *   -----+----------+------------------
   3022 	 *     96 |  1100000 |  32
   3023 	 *    144 | 10100000 |  32
   3024 	 *    192 | 11000000 |  64
   3025 	 *
   3026 	 * Depending on runtime settings, it is possible that arena_malloc()
   3027 	 * will further round up to a power of two, but that never causes
   3028 	 * correctness issues.
   3029 	 */
   3030 	ceil_size = (size + (alignment - 1)) & (-alignment);
   3031 	/*
   3032 	 * (ceil_size < size) protects against the combination of maximal
   3033 	 * alignment and size greater than maximal alignment.
   3034 	 */
   3035 	if (ceil_size < size) {
   3036 		/* size_t overflow. */
   3037 		return (NULL);
   3038 	}
   3039 
   3040 	if (ceil_size <= pagesize || (alignment <= pagesize
   3041 	    && ceil_size <= arena_maxclass))
   3042 		ret = arena_malloc(choose_arena(), ceil_size);
   3043 	else {
   3044 		size_t run_size;
   3045 
   3046 		/*
   3047 		 * We can't achieve sub-page alignment, so round up alignment
   3048 		 * permanently; it makes later calculations simpler.
   3049 		 */
   3050 		alignment = PAGE_CEILING(alignment);
   3051 		ceil_size = PAGE_CEILING(size);
   3052 		/*
   3053 		 * (ceil_size < size) protects against very large sizes within
   3054 		 * pagesize of SIZE_T_MAX.
   3055 		 *
   3056 		 * (ceil_size + alignment < ceil_size) protects against the
   3057 		 * combination of maximal alignment and ceil_size large enough
   3058 		 * to cause overflow.  This is similar to the first overflow
   3059 		 * check above, but it needs to be repeated due to the new
   3060 		 * ceil_size value, which may now be *equal* to maximal
   3061 		 * alignment, whereas before we only detected overflow if the
   3062 		 * original size was *greater* than maximal alignment.
   3063 		 */
   3064 		if (ceil_size < size || ceil_size + alignment < ceil_size) {
   3065 			/* size_t overflow. */
   3066 			return (NULL);
   3067 		}
   3068 
   3069 		/*
   3070 		 * Calculate the size of the over-size run that arena_palloc()
   3071 		 * would need to allocate in order to guarantee the alignment.
   3072 		 */
   3073 		if (ceil_size >= alignment)
   3074 			run_size = ceil_size + alignment - pagesize;
   3075 		else {
   3076 			/*
   3077 			 * It is possible that (alignment << 1) will cause
   3078 			 * overflow, but it doesn't matter because we also
   3079 			 * subtract pagesize, which in the case of overflow
   3080 			 * leaves us with a very large run_size.  That causes
   3081 			 * the first conditional below to fail, which means
   3082 			 * that the bogus run_size value never gets used for
   3083 			 * anything important.
   3084 			 */
   3085 			run_size = (alignment << 1) - pagesize;
   3086 		}
   3087 
   3088 		if (run_size <= arena_maxclass) {
   3089 			ret = arena_palloc(choose_arena(), alignment, ceil_size,
   3090 			    run_size);
   3091 		} else if (alignment <= chunksize)
   3092 			ret = huge_malloc(ceil_size);
   3093 		else
   3094 			ret = huge_palloc(alignment, ceil_size);
   3095 	}
   3096 
   3097 	assert(((uintptr_t)ret & (alignment - 1)) == 0);
   3098 	return (ret);
   3099 }
   3100 
   3101 static void *
   3102 icalloc(size_t size)
   3103 {
   3104 	void *ret;
   3105 
   3106 	if (size <= arena_maxclass) {
   3107 		ret = arena_malloc(choose_arena(), size);
   3108 		if (ret == NULL)
   3109 			return (NULL);
   3110 		memset(ret, 0, size);
   3111 	} else {
   3112 		/*
   3113 		 * The virtual memory system provides zero-filled pages, so
   3114 		 * there is no need to do so manually, unless opt_junk is
   3115 		 * enabled, in which case huge_malloc() fills huge allocations
   3116 		 * with junk.
   3117 		 */
   3118 		ret = huge_malloc(size);
   3119 		if (ret == NULL)
   3120 			return (NULL);
   3121 
   3122 		if (opt_junk)
   3123 			memset(ret, 0, size);
   3124 #ifdef USE_BRK
   3125 		else if ((uintptr_t)ret >= (uintptr_t)brk_base
   3126 		    && (uintptr_t)ret < (uintptr_t)brk_max) {
   3127 			/*
   3128 			 * This may be a re-used brk chunk.  Therefore, zero
   3129 			 * the memory.
   3130 			 */
   3131 			memset(ret, 0, size);
   3132 		}
   3133 #endif
   3134 	}
   3135 
   3136 	return (ret);
   3137 }
   3138 
   3139 static size_t
   3140 isalloc(const void *ptr)
   3141 {
   3142 	size_t ret;
   3143 	arena_chunk_t *chunk;
   3144 
   3145 	assert(ptr != NULL);
   3146 
   3147 	chunk = (arena_chunk_t *)CHUNK_ADDR2BASE(ptr);
   3148 	if (chunk != ptr) {
   3149 		/* Region. */
   3150 		assert(chunk->arena->magic == ARENA_MAGIC);
   3151 
   3152 		ret = arena_salloc(ptr);
   3153 	} else {
   3154 		chunk_node_t *node, key;
   3155 
   3156 		/* Chunk (huge allocation). */
   3157 
   3158 		malloc_mutex_lock(&chunks_mtx);
   3159 
   3160 		/* Extract from tree of huge allocations. */
   3161 		key.chunk = __DECONST(void *, ptr);
   3162 		/* LINTED */
   3163 		node = RB_FIND(chunk_tree_s, &huge, &key);
   3164 		assert(node != NULL);
   3165 
   3166 		ret = node->size;
   3167 
   3168 		malloc_mutex_unlock(&chunks_mtx);
   3169 	}
   3170 
   3171 	return (ret);
   3172 }
   3173 
   3174 static void *
   3175 iralloc(void *ptr, size_t size)
   3176 {
   3177 	void *ret;
   3178 	size_t oldsize;
   3179 
   3180 	assert(ptr != NULL);
   3181 	assert(size != 0);
   3182 
   3183 	oldsize = isalloc(ptr);
   3184 
   3185 	if (size <= arena_maxclass)
   3186 		ret = arena_ralloc(ptr, size, oldsize);
   3187 	else
   3188 		ret = huge_ralloc(ptr, size, oldsize);
   3189 
   3190 	return (ret);
   3191 }
   3192 
   3193 static void
   3194 idalloc(void *ptr)
   3195 {
   3196 	arena_chunk_t *chunk;
   3197 
   3198 	assert(ptr != NULL);
   3199 
   3200 	chunk = (arena_chunk_t *)CHUNK_ADDR2BASE(ptr);
   3201 	if (chunk != ptr) {
   3202 		/* Region. */
   3203 		arena_dalloc(chunk->arena, chunk, ptr);
   3204 	} else
   3205 		huge_dalloc(ptr);
   3206 }
   3207 
   3208 static void
   3209 malloc_print_stats(void)
   3210 {
   3211 
   3212 	if (opt_print_stats) {
   3213 		char s[UMAX2S_BUFSIZE];
   3214 		_malloc_message("___ Begin malloc statistics ___\n", "", "",
   3215 		    "");
   3216 		_malloc_message("Assertions ",
   3217 #ifdef NDEBUG
   3218 		    "disabled",
   3219 #else
   3220 		    "enabled",
   3221 #endif
   3222 		    "\n", "");
   3223 		_malloc_message("Boolean MALLOC_OPTIONS: ",
   3224 		    opt_abort ? "A" : "a",
   3225 		    opt_junk ? "J" : "j",
   3226 		    opt_hint ? "H" : "h");
   3227 		_malloc_message(opt_utrace ? "PU" : "Pu",
   3228 		    opt_sysv ? "V" : "v",
   3229 		    opt_xmalloc ? "X" : "x",
   3230 		    opt_zero ? "Z\n" : "z\n");
   3231 
   3232 		_malloc_message("CPUs: ", size_t2s(ncpus, s), "\n", "");
   3233 		_malloc_message("Max arenas: ", size_t2s(narenas, s), "\n", "");
   3234 		_malloc_message("Pointer size: ", size_t2s(sizeof(void *), s),
   3235 		    "\n", "");
   3236 		_malloc_message("Quantum size: ", size_t2s(quantum, s), "\n", "");
   3237 		_malloc_message("Max small size: ", size_t2s(small_max, s), "\n",
   3238 		    "");
   3239 
   3240 		_malloc_message("Chunk size: ", size_t2s(chunksize, s), "", "");
   3241 		_malloc_message(" (2^", size_t2s((size_t)opt_chunk_2pow, s),
   3242 		    ")\n", "");
   3243 
   3244 #ifdef MALLOC_STATS
   3245 		{
   3246 			size_t allocated, mapped;
   3247 			unsigned i;
   3248 			arena_t *arena;
   3249 
   3250 			/* Calculate and print allocated/mapped stats. */
   3251 
   3252 			/* arenas. */
   3253 			for (i = 0, allocated = 0; i < narenas; i++) {
   3254 				if (arenas[i] != NULL) {
   3255 					malloc_mutex_lock(&arenas[i]->mtx);
   3256 					allocated +=
   3257 					    arenas[i]->stats.allocated_small;
   3258 					allocated +=
   3259 					    arenas[i]->stats.allocated_large;
   3260 					malloc_mutex_unlock(&arenas[i]->mtx);
   3261 				}
   3262 			}
   3263 
   3264 			/* huge/base. */
   3265 			malloc_mutex_lock(&chunks_mtx);
   3266 			allocated += huge_allocated;
   3267 			mapped = stats_chunks.curchunks * chunksize;
   3268 			malloc_mutex_unlock(&chunks_mtx);
   3269 
   3270 			malloc_mutex_lock(&base_mtx);
   3271 			mapped += base_mapped;
   3272 			malloc_mutex_unlock(&base_mtx);
   3273 
   3274 			malloc_printf("Allocated: %zu, mapped: %zu\n",
   3275 			    allocated, mapped);
   3276 
   3277 			/* Print chunk stats. */
   3278 			{
   3279 				chunk_stats_t chunks_stats;
   3280 
   3281 				malloc_mutex_lock(&chunks_mtx);
   3282 				chunks_stats = stats_chunks;
   3283 				malloc_mutex_unlock(&chunks_mtx);
   3284 
   3285 				malloc_printf("chunks: nchunks   "
   3286 				    "highchunks    curchunks\n");
   3287 				malloc_printf("  %13llu%13lu%13lu\n",
   3288 				    chunks_stats.nchunks,
   3289 				    chunks_stats.highchunks,
   3290 				    chunks_stats.curchunks);
   3291 			}
   3292 
   3293 			/* Print chunk stats. */
   3294 			malloc_printf(
   3295 			    "huge: nmalloc      ndalloc      "
   3296 			    "nralloc    allocated\n");
   3297 			malloc_printf(" %12llu %12llu %12llu %12zu\n",
   3298 			    huge_nmalloc, huge_ndalloc, huge_nralloc,
   3299 			    huge_allocated);
   3300 
   3301 			/* Print stats for each arena. */
   3302 			for (i = 0; i < narenas; i++) {
   3303 				arena = arenas[i];
   3304 				if (arena != NULL) {
   3305 					malloc_printf(
   3306 					    "\narenas[%u] @ %p\n", i, arena);
   3307 					malloc_mutex_lock(&arena->mtx);
   3308 					stats_print(arena);
   3309 					malloc_mutex_unlock(&arena->mtx);
   3310 				}
   3311 			}
   3312 		}
   3313 #endif /* #ifdef MALLOC_STATS */
   3314 		_malloc_message("--- End malloc statistics ---\n", "", "", "");
   3315 	}
   3316 }
   3317 
   3318 /*
   3319  * FreeBSD's pthreads implementation calls malloc(3), so the malloc
   3320  * implementation has to take pains to avoid infinite recursion during
   3321  * initialization.
   3322  */
   3323 static inline bool
   3324 malloc_init(void)
   3325 {
   3326 
   3327 	if (malloc_initialized == false)
   3328 		return (malloc_init_hard());
   3329 
   3330 	return (false);
   3331 }
   3332 
   3333 static bool
   3334 malloc_init_hard(void)
   3335 {
   3336 	unsigned i, j;
   3337 	ssize_t linklen;
   3338 	char buf[PATH_MAX + 1];
   3339 	const char *opts = "";
   3340 	int serrno;
   3341 
   3342 	malloc_mutex_lock(&init_lock);
   3343 	if (malloc_initialized) {
   3344 		/*
   3345 		 * Another thread initialized the allocator before this one
   3346 		 * acquired init_lock.
   3347 		 */
   3348 		malloc_mutex_unlock(&init_lock);
   3349 		return (false);
   3350 	}
   3351 
   3352 	serrno = errno;
   3353 	/* Get number of CPUs. */
   3354 	{
   3355 		int mib[2];
   3356 		size_t len;
   3357 
   3358 		mib[0] = CTL_HW;
   3359 		mib[1] = HW_NCPU;
   3360 		len = sizeof(ncpus);
   3361 		if (sysctl(mib, 2, &ncpus, &len, (void *) 0, 0) == -1) {
   3362 			/* Error. */
   3363 			ncpus = 1;
   3364 		}
   3365 	}
   3366 
   3367 	/* Get page size. */
   3368 	{
   3369 		long result;
   3370 
   3371 		result = sysconf(_SC_PAGESIZE);
   3372 		assert(result != -1);
   3373 		pagesize = (unsigned) result;
   3374 
   3375 		/*
   3376 		 * We assume that pagesize is a power of 2 when calculating
   3377 		 * pagesize_mask and pagesize_2pow.
   3378 		 */
   3379 		assert(((result - 1) & result) == 0);
   3380 		pagesize_mask = result - 1;
   3381 		pagesize_2pow = ffs((int)result) - 1;
   3382 	}
   3383 
   3384 	for (i = 0; i < 3; i++) {
   3385 		/* Get runtime configuration. */
   3386 		switch (i) {
   3387 		case 0:
   3388 			if ((linklen = readlink("/etc/malloc.conf", buf,
   3389 						sizeof(buf) - 1)) != -1) {
   3390 				/*
   3391 				 * Use the contents of the "/etc/malloc.conf"
   3392 				 * symbolic link's name.
   3393 				 */
   3394 				buf[linklen] = '\0';
   3395 				opts = buf;
   3396 			} else {
   3397 				/* No configuration specified. */
   3398 				buf[0] = '\0';
   3399 				opts = buf;
   3400 			}
   3401 			break;
   3402 		case 1:
   3403 			if ((opts = getenv("MALLOC_OPTIONS")) != NULL &&
   3404 			    issetugid() == 0) {
   3405 				/*
   3406 				 * Do nothing; opts is already initialized to
   3407 				 * the value of the MALLOC_OPTIONS environment
   3408 				 * variable.
   3409 				 */
   3410 			} else {
   3411 				/* No configuration specified. */
   3412 				buf[0] = '\0';
   3413 				opts = buf;
   3414 			}
   3415 			break;
   3416 		case 2:
   3417 			if (_malloc_options != NULL) {
   3418 			    /*
   3419 			     * Use options that were compiled into the program.
   3420 			     */
   3421 			    opts = _malloc_options;
   3422 			} else {
   3423 				/* No configuration specified. */
   3424 				buf[0] = '\0';
   3425 				opts = buf;
   3426 			}
   3427 			break;
   3428 		default:
   3429 			/* NOTREACHED */
   3430 			/* LINTED */
   3431 			assert(false);
   3432 		}
   3433 
   3434 		for (j = 0; opts[j] != '\0'; j++) {
   3435 			switch (opts[j]) {
   3436 			case 'a':
   3437 				opt_abort = false;
   3438 				break;
   3439 			case 'A':
   3440 				opt_abort = true;
   3441 				break;
   3442 			case 'h':
   3443 				opt_hint = false;
   3444 				break;
   3445 			case 'H':
   3446 				opt_hint = true;
   3447 				break;
   3448 			case 'j':
   3449 				opt_junk = false;
   3450 				break;
   3451 			case 'J':
   3452 				opt_junk = true;
   3453 				break;
   3454 			case 'k':
   3455 				/*
   3456 				 * Chunks always require at least one header
   3457 				 * page, so chunks can never be smaller than
   3458 				 * two pages.
   3459 				 */
   3460 				if (opt_chunk_2pow > pagesize_2pow + 1)
   3461 					opt_chunk_2pow--;
   3462 				break;
   3463 			case 'K':
   3464 				if (opt_chunk_2pow + 1 <
   3465 				    (int)(sizeof(size_t) << 3))
   3466 					opt_chunk_2pow++;
   3467 				break;
   3468 			case 'n':
   3469 				opt_narenas_lshift--;
   3470 				break;
   3471 			case 'N':
   3472 				opt_narenas_lshift++;
   3473 				break;
   3474 			case 'p':
   3475 				opt_print_stats = false;
   3476 				break;
   3477 			case 'P':
   3478 				opt_print_stats = true;
   3479 				break;
   3480 			case 'q':
   3481 				if (opt_quantum_2pow > QUANTUM_2POW_MIN)
   3482 					opt_quantum_2pow--;
   3483 				break;
   3484 			case 'Q':
   3485 				if (opt_quantum_2pow < pagesize_2pow - 1)
   3486 					opt_quantum_2pow++;
   3487 				break;
   3488 			case 's':
   3489 				if (opt_small_max_2pow > QUANTUM_2POW_MIN)
   3490 					opt_small_max_2pow--;
   3491 				break;
   3492 			case 'S':
   3493 				if (opt_small_max_2pow < pagesize_2pow - 1)
   3494 					opt_small_max_2pow++;
   3495 				break;
   3496 			case 'u':
   3497 				opt_utrace = false;
   3498 				break;
   3499 			case 'U':
   3500 				opt_utrace = true;
   3501 				break;
   3502 			case 'v':
   3503 				opt_sysv = false;
   3504 				break;
   3505 			case 'V':
   3506 				opt_sysv = true;
   3507 				break;
   3508 			case 'x':
   3509 				opt_xmalloc = false;
   3510 				break;
   3511 			case 'X':
   3512 				opt_xmalloc = true;
   3513 				break;
   3514 			case 'z':
   3515 				opt_zero = false;
   3516 				break;
   3517 			case 'Z':
   3518 				opt_zero = true;
   3519 				break;
   3520 			default: {
   3521 				char cbuf[2];
   3522 
   3523 				cbuf[0] = opts[j];
   3524 				cbuf[1] = '\0';
   3525 				_malloc_message(getprogname(),
   3526 				    ": (malloc) Unsupported character in "
   3527 				    "malloc options: '", cbuf, "'\n");
   3528 			}
   3529 			}
   3530 		}
   3531 	}
   3532 	errno = serrno;
   3533 
   3534 	/* Take care to call atexit() only once. */
   3535 	if (opt_print_stats) {
   3536 		/* Print statistics at exit. */
   3537 		atexit(malloc_print_stats);
   3538 	}
   3539 
   3540 	/* Set variables according to the value of opt_small_max_2pow. */
   3541 	if (opt_small_max_2pow < opt_quantum_2pow)
   3542 		opt_small_max_2pow = opt_quantum_2pow;
   3543 	small_max = (1 << opt_small_max_2pow);
   3544 
   3545 	/* Set bin-related variables. */
   3546 	bin_maxclass = (pagesize >> 1);
   3547 	assert(opt_quantum_2pow >= TINY_MIN_2POW);
   3548 	ntbins = (unsigned)(opt_quantum_2pow - TINY_MIN_2POW);
   3549 	assert(ntbins <= opt_quantum_2pow);
   3550 	nqbins = (unsigned)(small_max >> opt_quantum_2pow);
   3551 	nsbins = (unsigned)(pagesize_2pow - opt_small_max_2pow - 1);
   3552 
   3553 	/* Set variables according to the value of opt_quantum_2pow. */
   3554 	quantum = (1 << opt_quantum_2pow);
   3555 	quantum_mask = quantum - 1;
   3556 	if (ntbins > 0)
   3557 		small_min = (quantum >> 1) + 1;
   3558 	else
   3559 		small_min = 1;
   3560 	assert(small_min <= quantum);
   3561 
   3562 	/* Set variables according to the value of opt_chunk_2pow. */
   3563 	chunksize = (1LU << opt_chunk_2pow);
   3564 	chunksize_mask = chunksize - 1;
   3565 	chunksize_2pow = (unsigned)opt_chunk_2pow;
   3566 	chunk_npages = (unsigned)(chunksize >> pagesize_2pow);
   3567 	{
   3568 		unsigned header_size;
   3569 
   3570 		header_size = (unsigned)(sizeof(arena_chunk_t) +
   3571 		    (sizeof(arena_chunk_map_t) * (chunk_npages - 1)));
   3572 		arena_chunk_header_npages = (header_size >> pagesize_2pow);
   3573 		if ((header_size & pagesize_mask) != 0)
   3574 			arena_chunk_header_npages++;
   3575 	}
   3576 	arena_maxclass = chunksize - (arena_chunk_header_npages <<
   3577 	    pagesize_2pow);
   3578 
   3579 	UTRACE(0, 0, 0);
   3580 
   3581 #ifdef MALLOC_STATS
   3582 	memset(&stats_chunks, 0, sizeof(chunk_stats_t));
   3583 #endif
   3584 
   3585 	/* Various sanity checks that regard configuration. */
   3586 	assert(quantum >= sizeof(void *));
   3587 	assert(quantum <= pagesize);
   3588 	assert(chunksize >= pagesize);
   3589 	assert(quantum * 4 <= chunksize);
   3590 
   3591 	/* Initialize chunks data. */
   3592 	malloc_mutex_init(&chunks_mtx);
   3593 	RB_INIT(&huge);
   3594 #ifdef USE_BRK
   3595 	malloc_mutex_init(&brk_mtx);
   3596 	brk_base = sbrk(0);
   3597 	brk_prev = brk_base;
   3598 	brk_max = brk_base;
   3599 #endif
   3600 #ifdef MALLOC_STATS
   3601 	huge_nmalloc = 0;
   3602 	huge_ndalloc = 0;
   3603 	huge_nralloc = 0;
   3604 	huge_allocated = 0;
   3605 #endif
   3606 	RB_INIT(&old_chunks);
   3607 
   3608 	/* Initialize base allocation data structures. */
   3609 #ifdef MALLOC_STATS
   3610 	base_mapped = 0;
   3611 #endif
   3612 #ifdef USE_BRK
   3613 	/*
   3614 	 * Allocate a base chunk here, since it doesn't actually have to be
   3615 	 * chunk-aligned.  Doing this before allocating any other chunks allows
   3616 	 * the use of space that would otherwise be wasted.
   3617 	 */
   3618 	base_pages_alloc(0);
   3619 #endif
   3620 	base_chunk_nodes = NULL;
   3621 	malloc_mutex_init(&base_mtx);
   3622 
   3623 	if (ncpus > 1) {
   3624 		/*
   3625 		 * For SMP systems, create four times as many arenas as there
   3626 		 * are CPUs by default.
   3627 		 */
   3628 		opt_narenas_lshift += 2;
   3629 	}
   3630 
   3631 #ifdef NO_TLS
   3632 	/* Initialize arena key. */
   3633 	(void)thr_keycreate(&arenas_map_key, NULL);
   3634 #endif
   3635 
   3636 	/* Determine how many arenas to use. */
   3637 	narenas = ncpus;
   3638 	if (opt_narenas_lshift > 0) {
   3639 		if ((narenas << opt_narenas_lshift) > narenas)
   3640 			narenas <<= opt_narenas_lshift;
   3641 		/*
   3642 		 * Make sure not to exceed the limits of what base_malloc()
   3643 		 * can handle.
   3644 		 */
   3645 		if (narenas * sizeof(arena_t *) > chunksize)
   3646 			narenas = (unsigned)(chunksize / sizeof(arena_t *));
   3647 	} else if (opt_narenas_lshift < 0) {
   3648 		if ((narenas << opt_narenas_lshift) < narenas)
   3649 			narenas <<= opt_narenas_lshift;
   3650 		/* Make sure there is at least one arena. */
   3651 		if (narenas == 0)
   3652 			narenas = 1;
   3653 	}
   3654 
   3655 	next_arena = 0;
   3656 
   3657 	/* Allocate and initialize arenas. */
   3658 	arenas = (arena_t **)base_alloc(sizeof(arena_t *) * narenas);
   3659 	if (arenas == NULL) {
   3660 		malloc_mutex_unlock(&init_lock);
   3661 		return (true);
   3662 	}
   3663 	/*
   3664 	 * Zero the array.  In practice, this should always be pre-zeroed,
   3665 	 * since it was just mmap()ed, but let's be sure.
   3666 	 */
   3667 	memset(arenas, 0, sizeof(arena_t *) * narenas);
   3668 
   3669 	/*
   3670 	 * Initialize one arena here.  The rest are lazily created in
   3671 	 * arena_choose_hard().
   3672 	 */
   3673 	arenas_extend(0);
   3674 	if (arenas[0] == NULL) {
   3675 		malloc_mutex_unlock(&init_lock);
   3676 		return (true);
   3677 	}
   3678 
   3679 	malloc_mutex_init(&arenas_mtx);
   3680 
   3681 	malloc_initialized = true;
   3682 	malloc_mutex_unlock(&init_lock);
   3683 	return (false);
   3684 }
   3685 
   3686 /*
   3687  * End general internal functions.
   3688  */
   3689 /******************************************************************************/
   3690 /*
   3691  * Begin malloc(3)-compatible functions.
   3692  */
   3693 
   3694 void *
   3695 malloc(size_t size)
   3696 {
   3697 	void *ret;
   3698 
   3699 	if (malloc_init()) {
   3700 		ret = NULL;
   3701 		goto RETURN;
   3702 	}
   3703 
   3704 	if (size == 0) {
   3705 		if (opt_sysv == false)
   3706 			size = 1;
   3707 		else {
   3708 			ret = NULL;
   3709 			goto RETURN;
   3710 		}
   3711 	}
   3712 
   3713 	ret = imalloc(size);
   3714 
   3715 RETURN:
   3716 	if (ret == NULL) {
   3717 		if (opt_xmalloc) {
   3718 			_malloc_message(getprogname(),
   3719 			    ": (malloc) Error in malloc(): out of memory\n", "",
   3720 			    "");
   3721 			abort();
   3722 		}
   3723 		errno = ENOMEM;
   3724 	}
   3725 
   3726 	UTRACE(0, size, ret);
   3727 	return (ret);
   3728 }
   3729 
   3730 int
   3731 posix_memalign(void **memptr, size_t alignment, size_t size)
   3732 {
   3733 	int ret;
   3734 	void *result;
   3735 
   3736 	if (malloc_init())
   3737 		result = NULL;
   3738 	else {
   3739 		/* Make sure that alignment is a large enough power of 2. */
   3740 		if (((alignment - 1) & alignment) != 0
   3741 		    || alignment < sizeof(void *)) {
   3742 			if (opt_xmalloc) {
   3743 				_malloc_message(getprogname(),
   3744 				    ": (malloc) Error in posix_memalign(): "
   3745 				    "invalid alignment\n", "", "");
   3746 				abort();
   3747 			}
   3748 			result = NULL;
   3749 			ret = EINVAL;
   3750 			goto RETURN;
   3751 		}
   3752 
   3753 		result = ipalloc(alignment, size);
   3754 	}
   3755 
   3756 	if (result == NULL) {
   3757 		if (opt_xmalloc) {
   3758 			_malloc_message(getprogname(),
   3759 			": (malloc) Error in posix_memalign(): out of memory\n",
   3760 			"", "");
   3761 			abort();
   3762 		}
   3763 		ret = ENOMEM;
   3764 		goto RETURN;
   3765 	}
   3766 
   3767 	*memptr = result;
   3768 	ret = 0;
   3769 
   3770 RETURN:
   3771 	UTRACE(0, size, result);
   3772 	return (ret);
   3773 }
   3774 
   3775 void *
   3776 calloc(size_t num, size_t size)
   3777 {
   3778 	void *ret;
   3779 	size_t num_size;
   3780 
   3781 	if (malloc_init()) {
   3782 		num_size = 0;
   3783 		ret = NULL;
   3784 		goto RETURN;
   3785 	}
   3786 
   3787 	num_size = num * size;
   3788 	if (num_size == 0) {
   3789 		if ((opt_sysv == false) && ((num == 0) || (size == 0)))
   3790 			num_size = 1;
   3791 		else {
   3792 			ret = NULL;
   3793 			goto RETURN;
   3794 		}
   3795 	/*
   3796 	 * Try to avoid division here.  We know that it isn't possible to
   3797 	 * overflow during multiplication if neither operand uses any of the
   3798 	 * most significant half of the bits in a size_t.
   3799 	 */
   3800 	} else if ((unsigned long long)((num | size) &
   3801 	   ((unsigned long long)SIZE_T_MAX << (sizeof(size_t) << 2))) &&
   3802 	   (num_size / size != num)) {
   3803 		/* size_t overflow. */
   3804 		ret = NULL;
   3805 		goto RETURN;
   3806 	}
   3807 
   3808 	ret = icalloc(num_size);
   3809 
   3810 RETURN:
   3811 	if (ret == NULL) {
   3812 		if (opt_xmalloc) {
   3813 			_malloc_message(getprogname(),
   3814 			    ": (malloc) Error in calloc(): out of memory\n", "",
   3815 			    "");
   3816 			abort();
   3817 		}
   3818 		errno = ENOMEM;
   3819 	}
   3820 
   3821 	UTRACE(0, num_size, ret);
   3822 	return (ret);
   3823 }
   3824 
   3825 void *
   3826 realloc(void *ptr, size_t size)
   3827 {
   3828 	void *ret;
   3829 
   3830 	if (size == 0) {
   3831 		if (opt_sysv == false)
   3832 			size = 1;
   3833 		else {
   3834 			if (ptr != NULL)
   3835 				idalloc(ptr);
   3836 			ret = NULL;
   3837 			goto RETURN;
   3838 		}
   3839 	}
   3840 
   3841 	if (ptr != NULL) {
   3842 		assert(malloc_initialized);
   3843 
   3844 		ret = iralloc(ptr, size);
   3845 
   3846 		if (ret == NULL) {
   3847 			if (opt_xmalloc) {
   3848 				_malloc_message(getprogname(),
   3849 				    ": (malloc) Error in realloc(): out of "
   3850 				    "memory\n", "", "");
   3851 				abort();
   3852 			}
   3853 			errno = ENOMEM;
   3854 		}
   3855 	} else {
   3856 		if (malloc_init())
   3857 			ret = NULL;
   3858 		else
   3859 			ret = imalloc(size);
   3860 
   3861 		if (ret == NULL) {
   3862 			if (opt_xmalloc) {
   3863 				_malloc_message(getprogname(),
   3864 				    ": (malloc) Error in realloc(): out of "
   3865 				    "memory\n", "", "");
   3866 				abort();
   3867 			}
   3868 			errno = ENOMEM;
   3869 		}
   3870 	}
   3871 
   3872 RETURN:
   3873 	UTRACE(ptr, size, ret);
   3874 	return (ret);
   3875 }
   3876 
   3877 void
   3878 free(void *ptr)
   3879 {
   3880 
   3881 	UTRACE(ptr, 0, 0);
   3882 	if (ptr != NULL) {
   3883 		assert(malloc_initialized);
   3884 
   3885 		idalloc(ptr);
   3886 	}
   3887 }
   3888 
   3889 /*
   3890  * End malloc(3)-compatible functions.
   3891  */
   3892 /******************************************************************************/
   3893 /*
   3894  * Begin non-standard functions.
   3895  */
   3896 #ifndef __NetBSD__
   3897 size_t
   3898 malloc_usable_size(const void *ptr)
   3899 {
   3900 
   3901 	assert(ptr != NULL);
   3902 
   3903 	return (isalloc(ptr));
   3904 }
   3905 #endif
   3906 
   3907 /*
   3908  * End non-standard functions.
   3909  */
   3910 /******************************************************************************/
   3911 /*
   3912  * Begin library-private functions, used by threading libraries for protection
   3913  * of malloc during fork().  These functions are only called if the program is
   3914  * running in threaded mode, so there is no need to check whether the program
   3915  * is threaded here.
   3916  */
   3917 
   3918 void
   3919 _malloc_prefork(void)
   3920 {
   3921 	unsigned i;
   3922 
   3923 	/* Acquire all mutexes in a safe order. */
   3924 
   3925 	malloc_mutex_lock(&arenas_mtx);
   3926 	for (i = 0; i < narenas; i++) {
   3927 		if (arenas[i] != NULL)
   3928 			malloc_mutex_lock(&arenas[i]->mtx);
   3929 	}
   3930 	malloc_mutex_unlock(&arenas_mtx);
   3931 
   3932 	malloc_mutex_lock(&base_mtx);
   3933 
   3934 	malloc_mutex_lock(&chunks_mtx);
   3935 }
   3936 
   3937 void
   3938 _malloc_postfork(void)
   3939 {
   3940 	unsigned i;
   3941 
   3942 	/* Release all mutexes, now that fork() has completed. */
   3943 
   3944 	malloc_mutex_unlock(&chunks_mtx);
   3945 
   3946 	malloc_mutex_unlock(&base_mtx);
   3947 
   3948 	malloc_mutex_lock(&arenas_mtx);
   3949 	for (i = 0; i < narenas; i++) {
   3950 		if (arenas[i] != NULL)
   3951 			malloc_mutex_unlock(&arenas[i]->mtx);
   3952 	}
   3953 	malloc_mutex_unlock(&arenas_mtx);
   3954 }
   3955 
   3956 /*
   3957  * End library-private functions.
   3958  */
   3959 /******************************************************************************/
   3960