182949828SMatthew Dillon /*
282949828SMatthew Dillon * NMALLOC.C - New Malloc (ported from kernel slab allocator)
382949828SMatthew Dillon *
44989e1f1SMatthew Dillon * Copyright (c) 2003,2004,2009,2010-2019 The DragonFly Project,
54989e1f1SMatthew Dillon * All rights reserved.
682949828SMatthew Dillon *
782949828SMatthew Dillon * This code is derived from software contributed to The DragonFly Project
80bb7d8c8SVenkatesh Srinivas * by Matthew Dillon <dillon@backplane.com> and by
90bb7d8c8SVenkatesh Srinivas * Venkatesh Srinivas <me@endeavour.zapto.org>.
1082949828SMatthew Dillon *
1182949828SMatthew Dillon * Redistribution and use in source and binary forms, with or without
1282949828SMatthew Dillon * modification, are permitted provided that the following conditions
1382949828SMatthew Dillon * are met:
1482949828SMatthew Dillon *
1582949828SMatthew Dillon * 1. Redistributions of source code must retain the above copyright
1682949828SMatthew Dillon * notice, this list of conditions and the following disclaimer.
1782949828SMatthew Dillon * 2. Redistributions in binary form must reproduce the above copyright
1882949828SMatthew Dillon * notice, this list of conditions and the following disclaimer in
1982949828SMatthew Dillon * the documentation and/or other materials provided with the
2082949828SMatthew Dillon * distribution.
2182949828SMatthew Dillon * 3. Neither the name of The DragonFly Project nor the names of its
2282949828SMatthew Dillon * contributors may be used to endorse or promote products derived
2382949828SMatthew Dillon * from this software without specific, prior written permission.
2482949828SMatthew Dillon *
2582949828SMatthew Dillon * THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
2682949828SMatthew Dillon * ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
2782949828SMatthew Dillon * LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
2882949828SMatthew Dillon * FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
2982949828SMatthew Dillon * COPYRIGHT HOLDERS OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
3082949828SMatthew Dillon * INCIDENTAL, SPECIAL, EXEMPLARY OR CONSEQUENTIAL DAMAGES (INCLUDING,
3182949828SMatthew Dillon * BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
3282949828SMatthew Dillon * LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED
3382949828SMatthew Dillon * AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY,
3482949828SMatthew Dillon * OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT
3582949828SMatthew Dillon * OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
3682949828SMatthew Dillon * SUCH DAMAGE.
370bb7d8c8SVenkatesh Srinivas *
380bb7d8c8SVenkatesh Srinivas * $Id: nmalloc.c,v 1.37 2010/07/23 08:20:35 vsrinivas Exp $
3982949828SMatthew Dillon */
4082949828SMatthew Dillon /*
4182949828SMatthew Dillon * This module implements a slab allocator drop-in replacement for the
4282949828SMatthew Dillon * libc malloc().
4382949828SMatthew Dillon *
4482949828SMatthew Dillon * A slab allocator reserves a ZONE for each chunk size, then lays the
4582949828SMatthew Dillon * chunks out in an array within the zone. Allocation and deallocation
460bb7d8c8SVenkatesh Srinivas * is nearly instantaneous, and overhead losses are limited to a fixed
4782949828SMatthew Dillon * worst-case amount.
4882949828SMatthew Dillon *
4982949828SMatthew Dillon * The slab allocator does not have to pre-initialize the list of
5082949828SMatthew Dillon * free chunks for each zone, and the underlying VM will not be
5182949828SMatthew Dillon * touched at all beyond the zone header until an actual allocation
5282949828SMatthew Dillon * needs it.
5382949828SMatthew Dillon *
5482949828SMatthew Dillon * Slab management and locking is done on a per-zone basis.
5582949828SMatthew Dillon *
5682949828SMatthew Dillon * Alloc Size Chunking Number of zones
5782949828SMatthew Dillon * 0-127 8 16
5882949828SMatthew Dillon * 128-255 16 8
5982949828SMatthew Dillon * 256-511 32 8
6082949828SMatthew Dillon * 512-1023 64 8
6182949828SMatthew Dillon * 1024-2047 128 8
6282949828SMatthew Dillon * 2048-4095 256 8
6382949828SMatthew Dillon * 4096-8191 512 8
6482949828SMatthew Dillon * 8192-16383 1024 8
6582949828SMatthew Dillon * 16384-32767 2048 8
6682949828SMatthew Dillon *
67369c9b6cSMatthew Dillon * Allocations >= ZoneLimit go directly to mmap and a hash table
6882949828SMatthew Dillon * is used to locate for free. One and Two-page allocations use the
6982949828SMatthew Dillon * zone mechanic to avoid excessive mmap()/munmap() calls.
7082949828SMatthew Dillon *
7182949828SMatthew Dillon * API FEATURES AND SIDE EFFECTS
7282949828SMatthew Dillon *
7382949828SMatthew Dillon * + power-of-2 sized allocations up to a page will be power-of-2 aligned.
7482949828SMatthew Dillon * Above that power-of-2 sized allocations are page-aligned. Non
7582949828SMatthew Dillon * power-of-2 sized allocations are aligned the same as the chunk
7682949828SMatthew Dillon * size for their zone.
7782949828SMatthew Dillon * + malloc(0) returns a special non-NULL value
7882949828SMatthew Dillon * + ability to allocate arbitrarily large chunks of memory
7982949828SMatthew Dillon * + realloc will reuse the passed pointer if possible, within the
8082949828SMatthew Dillon * limitations of the zone chunking.
810bb7d8c8SVenkatesh Srinivas *
820bb7d8c8SVenkatesh Srinivas * Multithreaded enhancements for small allocations introduced August 2010.
830bb7d8c8SVenkatesh Srinivas * These are in the spirit of 'libumem'. See:
840bb7d8c8SVenkatesh Srinivas * Bonwick, J.; Adams, J. (2001). "Magazines and Vmem: Extending the
850bb7d8c8SVenkatesh Srinivas * slab allocator to many CPUs and arbitrary resources". In Proc. 2001
860bb7d8c8SVenkatesh Srinivas * USENIX Technical Conference. USENIX Association.
870bb7d8c8SVenkatesh Srinivas *
8807a8ffeaSMatthew Dillon * Oversized allocations employ the BIGCACHE mechanic whereby large
8907a8ffeaSMatthew Dillon * allocations may be handed significantly larger buffers, allowing them
9007a8ffeaSMatthew Dillon * to avoid mmap/munmap operations even through significant realloc()s.
9107a8ffeaSMatthew Dillon * The excess space is only trimmed if too many large allocations have been
9207a8ffeaSMatthew Dillon * given this treatment.
9307a8ffeaSMatthew Dillon *
940bb7d8c8SVenkatesh Srinivas * TUNING
950bb7d8c8SVenkatesh Srinivas *
960bb7d8c8SVenkatesh Srinivas * The value of the environment variable MALLOC_OPTIONS is a character string
970bb7d8c8SVenkatesh Srinivas * containing various flags to tune nmalloc.
980bb7d8c8SVenkatesh Srinivas *
990bb7d8c8SVenkatesh Srinivas * 'U' / ['u'] Generate / do not generate utrace entries for ktrace(1)
1000bb7d8c8SVenkatesh Srinivas * This will generate utrace events for all malloc,
1010bb7d8c8SVenkatesh Srinivas * realloc, and free calls. There are tools (mtrplay) to
1020bb7d8c8SVenkatesh Srinivas * replay and allocation pattern or to graph heap structure
1030bb7d8c8SVenkatesh Srinivas * (mtrgraph) which can interpret these logs.
1040bb7d8c8SVenkatesh Srinivas * 'Z' / ['z'] Zero out / do not zero all allocations.
1050bb7d8c8SVenkatesh Srinivas * Each new byte of memory allocated by malloc, realloc, or
1060bb7d8c8SVenkatesh Srinivas * reallocf will be initialized to 0. This is intended for
1070bb7d8c8SVenkatesh Srinivas * debugging and will affect performance negatively.
1080bb7d8c8SVenkatesh Srinivas * 'H' / ['h'] Pass a hint to the kernel about pages unused by the
1090bb7d8c8SVenkatesh Srinivas * allocation functions.
11082949828SMatthew Dillon */
11182949828SMatthew Dillon
1120bb7d8c8SVenkatesh Srinivas /* cc -shared -fPIC -g -O -I/usr/src/lib/libc/include -o nmalloc.so nmalloc.c */
1130bb7d8c8SVenkatesh Srinivas
114d19ab22dSSascha Wildner #include "namespace.h"
11582949828SMatthew Dillon #include <sys/param.h>
11682949828SMatthew Dillon #include <sys/types.h>
11782949828SMatthew Dillon #include <sys/mman.h>
1180bb7d8c8SVenkatesh Srinivas #include <sys/queue.h>
1190bb7d8c8SVenkatesh Srinivas #include <sys/ktrace.h>
12082949828SMatthew Dillon #include <stdio.h>
1210bb7d8c8SVenkatesh Srinivas #include <stdint.h>
12282949828SMatthew Dillon #include <stdlib.h>
12382949828SMatthew Dillon #include <stdarg.h>
12482949828SMatthew Dillon #include <stddef.h>
12582949828SMatthew Dillon #include <unistd.h>
12682949828SMatthew Dillon #include <string.h>
12782949828SMatthew Dillon #include <fcntl.h>
12882949828SMatthew Dillon #include <errno.h>
1290bb7d8c8SVenkatesh Srinivas #include <pthread.h>
13007a8ffeaSMatthew Dillon #include <machine/atomic.h>
13182949828SMatthew Dillon #include "un-namespace.h"
13282949828SMatthew Dillon
133d19ab22dSSascha Wildner #include "libc_private.h"
134d19ab22dSSascha Wildner #include "spinlock.h"
13507a8ffeaSMatthew Dillon
136a32e3ba6SSascha Wildner void __free(void *);
137a32e3ba6SSascha Wildner void *__malloc(size_t);
138a32e3ba6SSascha Wildner void *__calloc(size_t, size_t);
139a32e3ba6SSascha Wildner void *__realloc(void *, size_t);
140a32e3ba6SSascha Wildner void *__aligned_alloc(size_t, size_t);
141d780b39fSAntonio Huete Jimenez size_t __malloc_usable_size(const void *ptr);
142a32e3ba6SSascha Wildner int __posix_memalign(void **, size_t, size_t);
143a32e3ba6SSascha Wildner
14482949828SMatthew Dillon /*
14582949828SMatthew Dillon * Linked list of large allocations
14682949828SMatthew Dillon */
14782949828SMatthew Dillon typedef struct bigalloc {
14882949828SMatthew Dillon struct bigalloc *next; /* hash link */
14982949828SMatthew Dillon void *base; /* base pointer */
15007a8ffeaSMatthew Dillon u_long active; /* bytes active */
15182949828SMatthew Dillon u_long bytes; /* bytes allocated */
15282949828SMatthew Dillon } *bigalloc_t;
15382949828SMatthew Dillon
15482949828SMatthew Dillon /*
15582949828SMatthew Dillon * Note that any allocations which are exact multiples of PAGE_SIZE, or
15682949828SMatthew Dillon * which are >= ZALLOC_ZONE_LIMIT, will fall through to the kmem subsystem.
15782949828SMatthew Dillon */
158369c9b6cSMatthew Dillon #define MAX_SLAB_PAGEALIGN (2 * PAGE_SIZE) /* max slab for PAGE_SIZE*n */
15982949828SMatthew Dillon #define ZALLOC_ZONE_LIMIT (16 * 1024) /* max slab-managed alloc */
160369c9b6cSMatthew Dillon #define ZALLOC_ZONE_SIZE (64 * 1024) /* zone size */
16182949828SMatthew Dillon #define ZALLOC_SLAB_MAGIC 0x736c6162 /* magic sanity */
16282949828SMatthew Dillon
16382949828SMatthew Dillon #if ZALLOC_ZONE_LIMIT == 16384
16482949828SMatthew Dillon #define NZONES 72
16582949828SMatthew Dillon #elif ZALLOC_ZONE_LIMIT == 32768
16682949828SMatthew Dillon #define NZONES 80
16782949828SMatthew Dillon #else
16882949828SMatthew Dillon #error "I couldn't figure out NZONES"
16982949828SMatthew Dillon #endif
17082949828SMatthew Dillon
17182949828SMatthew Dillon /*
17282949828SMatthew Dillon * Chunk structure for free elements
17382949828SMatthew Dillon */
17482949828SMatthew Dillon typedef struct slchunk {
17582949828SMatthew Dillon struct slchunk *c_Next;
17682949828SMatthew Dillon } *slchunk_t;
17782949828SMatthew Dillon
17882949828SMatthew Dillon /*
17982949828SMatthew Dillon * The IN-BAND zone header is placed at the beginning of each zone.
18082949828SMatthew Dillon */
18182949828SMatthew Dillon struct slglobaldata;
18282949828SMatthew Dillon
18382949828SMatthew Dillon typedef struct slzone {
1840bb7d8c8SVenkatesh Srinivas int32_t z_Magic; /* magic number for sanity check */
18582949828SMatthew Dillon int z_NFree; /* total free chunks / ualloc space */
18682949828SMatthew Dillon struct slzone *z_Next; /* ZoneAry[] link if z_NFree non-zero */
18782949828SMatthew Dillon int z_NMax; /* maximum free chunks */
18882949828SMatthew Dillon char *z_BasePtr; /* pointer to start of chunk array */
18982949828SMatthew Dillon int z_UIndex; /* current initial allocation index */
19082949828SMatthew Dillon int z_UEndIndex; /* last (first) allocation index */
19182949828SMatthew Dillon int z_ChunkSize; /* chunk size for validation */
19282949828SMatthew Dillon int z_FirstFreePg; /* chunk list on a page-by-page basis */
19382949828SMatthew Dillon int z_ZoneIndex;
19482949828SMatthew Dillon int z_Flags;
19582949828SMatthew Dillon struct slchunk *z_PageAry[ZALLOC_ZONE_SIZE / PAGE_SIZE];
19682949828SMatthew Dillon } *slzone_t;
19782949828SMatthew Dillon
19882949828SMatthew Dillon typedef struct slglobaldata {
19982949828SMatthew Dillon spinlock_t Spinlock;
20082949828SMatthew Dillon slzone_t ZoneAry[NZONES];/* linked list of zones NFree > 0 */
20182949828SMatthew Dillon } *slglobaldata_t;
20282949828SMatthew Dillon
20382949828SMatthew Dillon #define SLZF_UNOTZEROD 0x0001
20482949828SMatthew Dillon
2050bb7d8c8SVenkatesh Srinivas #define FASTSLABREALLOC 0x02
2060bb7d8c8SVenkatesh Srinivas
20782949828SMatthew Dillon /*
20882949828SMatthew Dillon * Misc constants. Note that allocations that are exact multiples of
20982949828SMatthew Dillon * PAGE_SIZE, or exceed the zone limit, fall through to the kmem module.
21082949828SMatthew Dillon * IN_SAME_PAGE_MASK is used to sanity-check the per-page free lists.
21182949828SMatthew Dillon */
21282949828SMatthew Dillon #define MIN_CHUNK_SIZE 8 /* in bytes */
21382949828SMatthew Dillon #define MIN_CHUNK_MASK (MIN_CHUNK_SIZE - 1)
21482949828SMatthew Dillon #define IN_SAME_PAGE_MASK (~(intptr_t)PAGE_MASK | MIN_CHUNK_MASK)
21582949828SMatthew Dillon
21682949828SMatthew Dillon /*
2178ff099aeSMatthew Dillon * WARNING: A limited number of spinlocks are available, BIGXSIZE should
2188ff099aeSMatthew Dillon * not be larger then 64.
21982949828SMatthew Dillon */
22082949828SMatthew Dillon #define BIGHSHIFT 10 /* bigalloc hash table */
22182949828SMatthew Dillon #define BIGHSIZE (1 << BIGHSHIFT)
22282949828SMatthew Dillon #define BIGHMASK (BIGHSIZE - 1)
22382949828SMatthew Dillon #define BIGXSIZE (BIGHSIZE / 16) /* bigalloc lock table */
22482949828SMatthew Dillon #define BIGXMASK (BIGXSIZE - 1)
22582949828SMatthew Dillon
22607a8ffeaSMatthew Dillon /*
22707a8ffeaSMatthew Dillon * BIGCACHE caches oversized allocations. Note that a linear search is
22807a8ffeaSMatthew Dillon * performed, so do not make the cache too large.
22907a8ffeaSMatthew Dillon *
23007a8ffeaSMatthew Dillon * BIGCACHE will garbage-collect excess space when the excess exceeds the
23107a8ffeaSMatthew Dillon * specified value. A relatively large number should be used here because
23207a8ffeaSMatthew Dillon * garbage collection is expensive.
23307a8ffeaSMatthew Dillon */
23407a8ffeaSMatthew Dillon #define BIGCACHE 16
23507a8ffeaSMatthew Dillon #define BIGCACHE_MASK (BIGCACHE - 1)
23607a8ffeaSMatthew Dillon #define BIGCACHE_LIMIT (1024 * 1024) /* size limit */
23707a8ffeaSMatthew Dillon #define BIGCACHE_EXCESS (16 * 1024 * 1024) /* garbage collect */
23807a8ffeaSMatthew Dillon
2398b07b5e8SMatthew Dillon #define CACHE_CHUNKS 32
2408b07b5e8SMatthew Dillon
24182949828SMatthew Dillon #define SAFLAG_ZERO 0x0001
24282949828SMatthew Dillon #define SAFLAG_PASSIVE 0x0002
2438b07b5e8SMatthew Dillon #define SAFLAG_MAGS 0x0004
24482949828SMatthew Dillon
24582949828SMatthew Dillon /*
24682949828SMatthew Dillon * Thread control
24782949828SMatthew Dillon */
24882949828SMatthew Dillon
24982949828SMatthew Dillon #define arysize(ary) (sizeof(ary)/sizeof((ary)[0]))
25082949828SMatthew Dillon
251721505deSMatthew Dillon /*
252721505deSMatthew Dillon * The assertion macros try to pretty-print assertion failures
253721505deSMatthew Dillon * which can be caused by corruption. If a lock is held, we
254721505deSMatthew Dillon * provide a macro that attempts to release it before asserting
255721505deSMatthew Dillon * in order to prevent (e.g.) a reentrant SIGABRT calling malloc
256721505deSMatthew Dillon * and deadlocking, resulting in the program freezing up.
257721505deSMatthew Dillon */
258721505deSMatthew Dillon #define MASSERT(exp) \
259721505deSMatthew Dillon do { if (__predict_false(!(exp))) \
26082949828SMatthew Dillon _mpanic("assertion: %s in %s", \
26182949828SMatthew Dillon #exp, __func__); \
26282949828SMatthew Dillon } while (0)
26382949828SMatthew Dillon
264721505deSMatthew Dillon #define MASSERT_WTHUNLK(exp, unlk) \
265721505deSMatthew Dillon do { if (__predict_false(!(exp))) { \
266721505deSMatthew Dillon unlk; \
267721505deSMatthew Dillon _mpanic("assertion: %s in %s", \
268721505deSMatthew Dillon #exp, __func__); \
269721505deSMatthew Dillon } \
270721505deSMatthew Dillon } while (0)
271721505deSMatthew Dillon
27282949828SMatthew Dillon /*
273369c9b6cSMatthew Dillon * Magazines, arrange so the structure is roughly 4KB.
2740bb7d8c8SVenkatesh Srinivas */
275369c9b6cSMatthew Dillon #define M_MAX_ROUNDS (512 - 3)
276369c9b6cSMatthew Dillon #define M_MIN_ROUNDS 16
277369c9b6cSMatthew Dillon #define M_ZONE_INIT_ROUNDS 64
278369c9b6cSMatthew Dillon #define M_ZONE_HYSTERESIS 32
2790bb7d8c8SVenkatesh Srinivas
2800bb7d8c8SVenkatesh Srinivas struct magazine {
2810bb7d8c8SVenkatesh Srinivas SLIST_ENTRY(magazine) nextmagazine;
2820bb7d8c8SVenkatesh Srinivas
2830bb7d8c8SVenkatesh Srinivas int flags;
2840bb7d8c8SVenkatesh Srinivas int capacity; /* Max rounds in this magazine */
2850bb7d8c8SVenkatesh Srinivas int rounds; /* Current number of free rounds */
286369c9b6cSMatthew Dillon int unused01;
2870bb7d8c8SVenkatesh Srinivas void *objects[M_MAX_ROUNDS];
2880bb7d8c8SVenkatesh Srinivas };
2890bb7d8c8SVenkatesh Srinivas
2900bb7d8c8SVenkatesh Srinivas SLIST_HEAD(magazinelist, magazine);
2910bb7d8c8SVenkatesh Srinivas
2920bb7d8c8SVenkatesh Srinivas static spinlock_t zone_mag_lock;
293e2caf0e7SMatthew Dillon static spinlock_t depot_spinlock;
2940bb7d8c8SVenkatesh Srinivas static struct magazine zone_magazine = {
295369c9b6cSMatthew Dillon .flags = 0,
296369c9b6cSMatthew Dillon .capacity = M_ZONE_INIT_ROUNDS,
2970bb7d8c8SVenkatesh Srinivas .rounds = 0,
2980bb7d8c8SVenkatesh Srinivas };
2990bb7d8c8SVenkatesh Srinivas
3000bb7d8c8SVenkatesh Srinivas #define MAGAZINE_FULL(mp) (mp->rounds == mp->capacity)
3010bb7d8c8SVenkatesh Srinivas #define MAGAZINE_NOTFULL(mp) (mp->rounds < mp->capacity)
3020bb7d8c8SVenkatesh Srinivas #define MAGAZINE_EMPTY(mp) (mp->rounds == 0)
3030bb7d8c8SVenkatesh Srinivas #define MAGAZINE_NOTEMPTY(mp) (mp->rounds != 0)
3040bb7d8c8SVenkatesh Srinivas
30507a8ffeaSMatthew Dillon /*
30607a8ffeaSMatthew Dillon * Each thread will have a pair of magazines per size-class (NZONES)
3070bb7d8c8SVenkatesh Srinivas * The loaded magazine will support immediate allocations, the previous
30807a8ffeaSMatthew Dillon * magazine will either be full or empty and can be swapped at need
30907a8ffeaSMatthew Dillon */
3100bb7d8c8SVenkatesh Srinivas typedef struct magazine_pair {
3110bb7d8c8SVenkatesh Srinivas struct magazine *loaded;
3120bb7d8c8SVenkatesh Srinivas struct magazine *prev;
3130bb7d8c8SVenkatesh Srinivas } magazine_pair;
3140bb7d8c8SVenkatesh Srinivas
3150bb7d8c8SVenkatesh Srinivas /* A depot is a collection of magazines for a single zone. */
3160bb7d8c8SVenkatesh Srinivas typedef struct magazine_depot {
3170bb7d8c8SVenkatesh Srinivas struct magazinelist full;
3180bb7d8c8SVenkatesh Srinivas struct magazinelist empty;
319ebe0d361SMatthew Dillon spinlock_t lock;
3200bb7d8c8SVenkatesh Srinivas } magazine_depot;
3210bb7d8c8SVenkatesh Srinivas
3220bb7d8c8SVenkatesh Srinivas typedef struct thr_mags {
3230bb7d8c8SVenkatesh Srinivas magazine_pair mags[NZONES];
324e58e48b4SMatthew Dillon struct magazine *newmag;
3250bb7d8c8SVenkatesh Srinivas int init;
3260bb7d8c8SVenkatesh Srinivas } thr_mags;
3270bb7d8c8SVenkatesh Srinivas
3280bb7d8c8SVenkatesh Srinivas static __thread thr_mags thread_mags TLS_ATTRIBUTE;
3290bb7d8c8SVenkatesh Srinivas static pthread_key_t thread_mags_key;
3300bb7d8c8SVenkatesh Srinivas static pthread_once_t thread_mags_once = PTHREAD_ONCE_INIT;
3310bb7d8c8SVenkatesh Srinivas static magazine_depot depots[NZONES];
3320bb7d8c8SVenkatesh Srinivas
3330bb7d8c8SVenkatesh Srinivas /*
33482949828SMatthew Dillon * Fixed globals (not per-cpu)
33582949828SMatthew Dillon */
33682949828SMatthew Dillon static const int ZoneSize = ZALLOC_ZONE_SIZE;
33782949828SMatthew Dillon static const int ZoneLimit = ZALLOC_ZONE_LIMIT;
33882949828SMatthew Dillon static const int ZonePageCount = ZALLOC_ZONE_SIZE / PAGE_SIZE;
33982949828SMatthew Dillon static const int ZoneMask = ZALLOC_ZONE_SIZE - 1;
34082949828SMatthew Dillon
3410bb7d8c8SVenkatesh Srinivas static int opt_madvise = 0;
3420bb7d8c8SVenkatesh Srinivas static int opt_utrace = 0;
3430bb7d8c8SVenkatesh Srinivas static int g_malloc_flags = 0;
3440bb7d8c8SVenkatesh Srinivas static struct slglobaldata SLGlobalData;
34582949828SMatthew Dillon static bigalloc_t bigalloc_array[BIGHSIZE];
34682949828SMatthew Dillon static spinlock_t bigspin_array[BIGXSIZE];
34707a8ffeaSMatthew Dillon static volatile void *bigcache_array[BIGCACHE]; /* atomic swap */
34807a8ffeaSMatthew Dillon static volatile size_t bigcache_size_array[BIGCACHE]; /* SMP races ok */
34907a8ffeaSMatthew Dillon static volatile int bigcache_index; /* SMP races ok */
35082949828SMatthew Dillon static int malloc_panic;
35107a8ffeaSMatthew Dillon static size_t excess_alloc; /* excess big allocs */
35282949828SMatthew Dillon
35382949828SMatthew Dillon static void *_slaballoc(size_t size, int flags);
35482949828SMatthew Dillon static void *_slabrealloc(void *ptr, size_t size);
355d780b39fSAntonio Huete Jimenez static size_t _slabusablesize(const void *ptr);
3560bb7d8c8SVenkatesh Srinivas static void _slabfree(void *ptr, int, bigalloc_t *);
357d3a54aeeSzrj static int _slabmemalign(void **memptr, size_t alignment, size_t size);
35882949828SMatthew Dillon static void *_vmem_alloc(size_t bytes, size_t align, int flags);
35982949828SMatthew Dillon static void _vmem_free(void *ptr, size_t bytes);
360369c9b6cSMatthew Dillon static void *magazine_alloc(struct magazine *);
3610bb7d8c8SVenkatesh Srinivas static int magazine_free(struct magazine *, void *);
3628b07b5e8SMatthew Dillon static void *mtmagazine_alloc(int zi, int flags);
3630bb7d8c8SVenkatesh Srinivas static int mtmagazine_free(int zi, void *);
3640bb7d8c8SVenkatesh Srinivas static void mtmagazine_init(void);
3650bb7d8c8SVenkatesh Srinivas static void mtmagazine_destructor(void *);
3660bb7d8c8SVenkatesh Srinivas static slzone_t zone_alloc(int flags);
3670bb7d8c8SVenkatesh Srinivas static void zone_free(void *z);
368b58f1e66SSascha Wildner static void _mpanic(const char *ctl, ...) __printflike(1, 2);
369450f08dbSSascha Wildner static void malloc_init(void) __constructor(101);
37082949828SMatthew Dillon
3710bb7d8c8SVenkatesh Srinivas struct nmalloc_utrace {
3720bb7d8c8SVenkatesh Srinivas void *p;
3730bb7d8c8SVenkatesh Srinivas size_t s;
3740bb7d8c8SVenkatesh Srinivas void *r;
3750bb7d8c8SVenkatesh Srinivas };
3760bb7d8c8SVenkatesh Srinivas
3770bb7d8c8SVenkatesh Srinivas #define UTRACE(a, b, c) \
3780bb7d8c8SVenkatesh Srinivas if (opt_utrace) { \
3790bb7d8c8SVenkatesh Srinivas struct nmalloc_utrace ut = { \
3800bb7d8c8SVenkatesh Srinivas .p = (a), \
3810bb7d8c8SVenkatesh Srinivas .s = (b), \
3820bb7d8c8SVenkatesh Srinivas .r = (c) \
3830bb7d8c8SVenkatesh Srinivas }; \
3840bb7d8c8SVenkatesh Srinivas utrace(&ut, sizeof(ut)); \
3850bb7d8c8SVenkatesh Srinivas }
3860bb7d8c8SVenkatesh Srinivas
3870bb7d8c8SVenkatesh Srinivas static void
malloc_init(void)3880bb7d8c8SVenkatesh Srinivas malloc_init(void)
3890bb7d8c8SVenkatesh Srinivas {
3900bb7d8c8SVenkatesh Srinivas const char *p = NULL;
3910bb7d8c8SVenkatesh Srinivas
3920bb7d8c8SVenkatesh Srinivas if (issetugid() == 0)
3930bb7d8c8SVenkatesh Srinivas p = getenv("MALLOC_OPTIONS");
3940bb7d8c8SVenkatesh Srinivas
3950bb7d8c8SVenkatesh Srinivas for (; p != NULL && *p != '\0'; p++) {
3960bb7d8c8SVenkatesh Srinivas switch(*p) {
3970bb7d8c8SVenkatesh Srinivas case 'u': opt_utrace = 0; break;
3980bb7d8c8SVenkatesh Srinivas case 'U': opt_utrace = 1; break;
3990bb7d8c8SVenkatesh Srinivas case 'h': opt_madvise = 0; break;
4000bb7d8c8SVenkatesh Srinivas case 'H': opt_madvise = 1; break;
4010bb7d8c8SVenkatesh Srinivas case 'z': g_malloc_flags = 0; break;
4020bb7d8c8SVenkatesh Srinivas case 'Z': g_malloc_flags = SAFLAG_ZERO; break;
4030bb7d8c8SVenkatesh Srinivas default:
4040bb7d8c8SVenkatesh Srinivas break;
4050bb7d8c8SVenkatesh Srinivas }
4060bb7d8c8SVenkatesh Srinivas }
4070bb7d8c8SVenkatesh Srinivas
4080bb7d8c8SVenkatesh Srinivas UTRACE((void *) -1, 0, NULL);
4090bb7d8c8SVenkatesh Srinivas }
4100bb7d8c8SVenkatesh Srinivas
41182949828SMatthew Dillon /*
4126c4de62cSMatthew Dillon * We have to install a handler for nmalloc thread teardowns when
4136c4de62cSMatthew Dillon * the thread is created. We cannot delay this because destructors in
4146c4de62cSMatthew Dillon * sophisticated userland programs can call malloc() for the first time
4156c4de62cSMatthew Dillon * during their thread exit.
4166c4de62cSMatthew Dillon *
4176c4de62cSMatthew Dillon * This routine is called directly from pthreads.
4186c4de62cSMatthew Dillon */
4196c4de62cSMatthew Dillon void
_nmalloc_thr_init(void)4206c4de62cSMatthew Dillon _nmalloc_thr_init(void)
4216c4de62cSMatthew Dillon {
4226c4de62cSMatthew Dillon thr_mags *tp;
4236c4de62cSMatthew Dillon
4246c4de62cSMatthew Dillon /*
4256c4de62cSMatthew Dillon * Disallow mtmagazine operations until the mtmagazine is
4266c4de62cSMatthew Dillon * initialized.
4276c4de62cSMatthew Dillon */
4286c4de62cSMatthew Dillon tp = &thread_mags;
4296c4de62cSMatthew Dillon tp->init = -1;
4306c4de62cSMatthew Dillon
431d19ab22dSSascha Wildner _pthread_once(&thread_mags_once, mtmagazine_init);
432d19ab22dSSascha Wildner _pthread_setspecific(thread_mags_key, tp);
4336c4de62cSMatthew Dillon tp->init = 1;
4346c4de62cSMatthew Dillon }
4356c4de62cSMatthew Dillon
436e2caf0e7SMatthew Dillon void
_nmalloc_thr_prepfork(void)437e2caf0e7SMatthew Dillon _nmalloc_thr_prepfork(void)
438e2caf0e7SMatthew Dillon {
439e2caf0e7SMatthew Dillon if (__isthreaded) {
440e2caf0e7SMatthew Dillon _SPINLOCK(&zone_mag_lock);
441e2caf0e7SMatthew Dillon _SPINLOCK(&depot_spinlock);
442e2caf0e7SMatthew Dillon }
443e2caf0e7SMatthew Dillon }
444e2caf0e7SMatthew Dillon
445e2caf0e7SMatthew Dillon void
_nmalloc_thr_parentfork(void)446e2caf0e7SMatthew Dillon _nmalloc_thr_parentfork(void)
447e2caf0e7SMatthew Dillon {
448e2caf0e7SMatthew Dillon if (__isthreaded) {
449e2caf0e7SMatthew Dillon _SPINUNLOCK(&depot_spinlock);
450e2caf0e7SMatthew Dillon _SPINUNLOCK(&zone_mag_lock);
451e2caf0e7SMatthew Dillon }
452e2caf0e7SMatthew Dillon }
453e2caf0e7SMatthew Dillon
454e2caf0e7SMatthew Dillon void
_nmalloc_thr_childfork(void)455e2caf0e7SMatthew Dillon _nmalloc_thr_childfork(void)
456e2caf0e7SMatthew Dillon {
457e2caf0e7SMatthew Dillon if (__isthreaded) {
458e2caf0e7SMatthew Dillon _SPINUNLOCK(&depot_spinlock);
459e2caf0e7SMatthew Dillon _SPINUNLOCK(&zone_mag_lock);
460e2caf0e7SMatthew Dillon }
461e2caf0e7SMatthew Dillon }
462e2caf0e7SMatthew Dillon
4636c4de62cSMatthew Dillon /*
464721505deSMatthew Dillon * Handle signal reentrancy safely whether we are threaded or not.
465721505deSMatthew Dillon * This improves the stability for mono and will probably improve
466721505deSMatthew Dillon * stability for other high-level languages which are becoming increasingly
467721505deSMatthew Dillon * sophisticated.
468721505deSMatthew Dillon *
469721505deSMatthew Dillon * The sigblockall()/sigunblockall() implementation uses a counter on
470721505deSMatthew Dillon * a per-thread shared user/kernel page, avoids system calls, and is thus
471721505deSMatthew Dillon * very fast.
472721505deSMatthew Dillon */
473721505deSMatthew Dillon static __inline void
nmalloc_sigblockall(void)474721505deSMatthew Dillon nmalloc_sigblockall(void)
475721505deSMatthew Dillon {
476721505deSMatthew Dillon sigblockall();
477721505deSMatthew Dillon }
478721505deSMatthew Dillon
479721505deSMatthew Dillon static __inline void
nmalloc_sigunblockall(void)480721505deSMatthew Dillon nmalloc_sigunblockall(void)
481721505deSMatthew Dillon {
482721505deSMatthew Dillon sigunblockall();
483721505deSMatthew Dillon }
484721505deSMatthew Dillon
485721505deSMatthew Dillon /*
48682949828SMatthew Dillon * Thread locks.
48782949828SMatthew Dillon */
48882949828SMatthew Dillon static __inline void
slgd_lock(slglobaldata_t slgd)48982949828SMatthew Dillon slgd_lock(slglobaldata_t slgd)
49082949828SMatthew Dillon {
49182949828SMatthew Dillon if (__isthreaded)
49282949828SMatthew Dillon _SPINLOCK(&slgd->Spinlock);
49382949828SMatthew Dillon }
49482949828SMatthew Dillon
49582949828SMatthew Dillon static __inline void
slgd_unlock(slglobaldata_t slgd)49682949828SMatthew Dillon slgd_unlock(slglobaldata_t slgd)
49782949828SMatthew Dillon {
49882949828SMatthew Dillon if (__isthreaded)
49982949828SMatthew Dillon _SPINUNLOCK(&slgd->Spinlock);
50082949828SMatthew Dillon }
50182949828SMatthew Dillon
5020bb7d8c8SVenkatesh Srinivas static __inline void
depot_lock(magazine_depot * dp __unused)50384ebaf33SSascha Wildner depot_lock(magazine_depot *dp __unused)
5040bb7d8c8SVenkatesh Srinivas {
5050bb7d8c8SVenkatesh Srinivas if (__isthreaded)
506e2caf0e7SMatthew Dillon _SPINLOCK(&depot_spinlock);
5070bb7d8c8SVenkatesh Srinivas }
5080bb7d8c8SVenkatesh Srinivas
5090bb7d8c8SVenkatesh Srinivas static __inline void
depot_unlock(magazine_depot * dp __unused)51084ebaf33SSascha Wildner depot_unlock(magazine_depot *dp __unused)
5110bb7d8c8SVenkatesh Srinivas {
5120bb7d8c8SVenkatesh Srinivas if (__isthreaded)
513e2caf0e7SMatthew Dillon _SPINUNLOCK(&depot_spinlock);
5140bb7d8c8SVenkatesh Srinivas }
5150bb7d8c8SVenkatesh Srinivas
5160bb7d8c8SVenkatesh Srinivas static __inline void
zone_magazine_lock(void)5170bb7d8c8SVenkatesh Srinivas zone_magazine_lock(void)
5180bb7d8c8SVenkatesh Srinivas {
5190bb7d8c8SVenkatesh Srinivas if (__isthreaded)
5200bb7d8c8SVenkatesh Srinivas _SPINLOCK(&zone_mag_lock);
5210bb7d8c8SVenkatesh Srinivas }
5220bb7d8c8SVenkatesh Srinivas
5230bb7d8c8SVenkatesh Srinivas static __inline void
zone_magazine_unlock(void)5240bb7d8c8SVenkatesh Srinivas zone_magazine_unlock(void)
5250bb7d8c8SVenkatesh Srinivas {
5260bb7d8c8SVenkatesh Srinivas if (__isthreaded)
5270bb7d8c8SVenkatesh Srinivas _SPINUNLOCK(&zone_mag_lock);
5280bb7d8c8SVenkatesh Srinivas }
5290bb7d8c8SVenkatesh Srinivas
5300bb7d8c8SVenkatesh Srinivas static __inline void
swap_mags(magazine_pair * mp)5310bb7d8c8SVenkatesh Srinivas swap_mags(magazine_pair *mp)
5320bb7d8c8SVenkatesh Srinivas {
5330bb7d8c8SVenkatesh Srinivas struct magazine *tmp;
5340bb7d8c8SVenkatesh Srinivas tmp = mp->loaded;
5350bb7d8c8SVenkatesh Srinivas mp->loaded = mp->prev;
5360bb7d8c8SVenkatesh Srinivas mp->prev = tmp;
5370bb7d8c8SVenkatesh Srinivas }
5380bb7d8c8SVenkatesh Srinivas
53982949828SMatthew Dillon /*
54082949828SMatthew Dillon * bigalloc hashing and locking support.
54182949828SMatthew Dillon *
54282949828SMatthew Dillon * Return an unmasked hash code for the passed pointer.
54382949828SMatthew Dillon */
54482949828SMatthew Dillon static __inline int
_bigalloc_hash(const void * ptr)545d780b39fSAntonio Huete Jimenez _bigalloc_hash(const void *ptr)
54682949828SMatthew Dillon {
54782949828SMatthew Dillon int hv;
54882949828SMatthew Dillon
5499a768e12SMatthew Dillon hv = ((int)(intptr_t)ptr >> PAGE_SHIFT) ^
5509a768e12SMatthew Dillon ((int)(intptr_t)ptr >> (PAGE_SHIFT + BIGHSHIFT));
55182949828SMatthew Dillon
55282949828SMatthew Dillon return(hv);
55382949828SMatthew Dillon }
55482949828SMatthew Dillon
55582949828SMatthew Dillon /*
55682949828SMatthew Dillon * Lock the hash chain and return a pointer to its base for the specified
55782949828SMatthew Dillon * address.
55882949828SMatthew Dillon */
55982949828SMatthew Dillon static __inline bigalloc_t *
bigalloc_lock(void * ptr)56082949828SMatthew Dillon bigalloc_lock(void *ptr)
56182949828SMatthew Dillon {
56282949828SMatthew Dillon int hv = _bigalloc_hash(ptr);
56382949828SMatthew Dillon bigalloc_t *bigp;
56482949828SMatthew Dillon
56582949828SMatthew Dillon bigp = &bigalloc_array[hv & BIGHMASK];
56682949828SMatthew Dillon if (__isthreaded)
56782949828SMatthew Dillon _SPINLOCK(&bigspin_array[hv & BIGXMASK]);
56882949828SMatthew Dillon return(bigp);
56982949828SMatthew Dillon }
57082949828SMatthew Dillon
57182949828SMatthew Dillon /*
57282949828SMatthew Dillon * Lock the hash chain and return a pointer to its base for the specified
57382949828SMatthew Dillon * address.
57482949828SMatthew Dillon *
57582949828SMatthew Dillon * BUT, if the hash chain is empty, just return NULL and do not bother
57682949828SMatthew Dillon * to lock anything.
57782949828SMatthew Dillon */
57882949828SMatthew Dillon static __inline bigalloc_t *
bigalloc_check_and_lock(const void * ptr)579d780b39fSAntonio Huete Jimenez bigalloc_check_and_lock(const void *ptr)
58082949828SMatthew Dillon {
58182949828SMatthew Dillon int hv = _bigalloc_hash(ptr);
58282949828SMatthew Dillon bigalloc_t *bigp;
58382949828SMatthew Dillon
58482949828SMatthew Dillon bigp = &bigalloc_array[hv & BIGHMASK];
58582949828SMatthew Dillon if (*bigp == NULL)
58682949828SMatthew Dillon return(NULL);
58782949828SMatthew Dillon if (__isthreaded) {
58882949828SMatthew Dillon _SPINLOCK(&bigspin_array[hv & BIGXMASK]);
58982949828SMatthew Dillon }
59082949828SMatthew Dillon return(bigp);
59182949828SMatthew Dillon }
59282949828SMatthew Dillon
59382949828SMatthew Dillon static __inline void
bigalloc_unlock(const void * ptr)594d780b39fSAntonio Huete Jimenez bigalloc_unlock(const void *ptr)
59582949828SMatthew Dillon {
59682949828SMatthew Dillon int hv;
59782949828SMatthew Dillon
59882949828SMatthew Dillon if (__isthreaded) {
59982949828SMatthew Dillon hv = _bigalloc_hash(ptr);
60082949828SMatthew Dillon _SPINUNLOCK(&bigspin_array[hv & BIGXMASK]);
60182949828SMatthew Dillon }
60282949828SMatthew Dillon }
60382949828SMatthew Dillon
60482949828SMatthew Dillon /*
60507a8ffeaSMatthew Dillon * Find a bigcache entry that might work for the allocation. SMP races are
60607a8ffeaSMatthew Dillon * ok here except for the swap (that is, it is ok if bigcache_size_array[i]
60707a8ffeaSMatthew Dillon * is wrong or if a NULL or too-small big is returned).
60807a8ffeaSMatthew Dillon *
60907a8ffeaSMatthew Dillon * Generally speaking it is ok to find a large entry even if the bytes
61007a8ffeaSMatthew Dillon * requested are relatively small (but still oversized), because we really
61107a8ffeaSMatthew Dillon * don't know *what* the application is going to do with the buffer.
61207a8ffeaSMatthew Dillon */
61307a8ffeaSMatthew Dillon static __inline
61407a8ffeaSMatthew Dillon bigalloc_t
bigcache_find_alloc(size_t bytes)61507a8ffeaSMatthew Dillon bigcache_find_alloc(size_t bytes)
61607a8ffeaSMatthew Dillon {
61707a8ffeaSMatthew Dillon bigalloc_t big = NULL;
61807a8ffeaSMatthew Dillon size_t test;
61907a8ffeaSMatthew Dillon int i;
62007a8ffeaSMatthew Dillon
62107a8ffeaSMatthew Dillon for (i = 0; i < BIGCACHE; ++i) {
62207a8ffeaSMatthew Dillon test = bigcache_size_array[i];
62307a8ffeaSMatthew Dillon if (bytes <= test) {
62407a8ffeaSMatthew Dillon bigcache_size_array[i] = 0;
62507a8ffeaSMatthew Dillon big = atomic_swap_ptr(&bigcache_array[i], NULL);
62607a8ffeaSMatthew Dillon break;
62707a8ffeaSMatthew Dillon }
62807a8ffeaSMatthew Dillon }
62907a8ffeaSMatthew Dillon return big;
63007a8ffeaSMatthew Dillon }
63107a8ffeaSMatthew Dillon
63207a8ffeaSMatthew Dillon /*
63307a8ffeaSMatthew Dillon * Free a bigcache entry, possibly returning one that the caller really must
63407a8ffeaSMatthew Dillon * free. This is used to cache recent oversized memory blocks. Only
63507a8ffeaSMatthew Dillon * big blocks smaller than BIGCACHE_LIMIT will be cached this way, so try
63607a8ffeaSMatthew Dillon * to collect the biggest ones we can that are under the limit.
63707a8ffeaSMatthew Dillon */
63807a8ffeaSMatthew Dillon static __inline
63907a8ffeaSMatthew Dillon bigalloc_t
bigcache_find_free(bigalloc_t big)64007a8ffeaSMatthew Dillon bigcache_find_free(bigalloc_t big)
64107a8ffeaSMatthew Dillon {
64207a8ffeaSMatthew Dillon int i;
64307a8ffeaSMatthew Dillon int j;
64407a8ffeaSMatthew Dillon int b;
64507a8ffeaSMatthew Dillon
64607a8ffeaSMatthew Dillon b = ++bigcache_index;
64707a8ffeaSMatthew Dillon for (i = 0; i < BIGCACHE; ++i) {
64807a8ffeaSMatthew Dillon j = (b + i) & BIGCACHE_MASK;
64907a8ffeaSMatthew Dillon if (bigcache_size_array[j] < big->bytes) {
65007a8ffeaSMatthew Dillon bigcache_size_array[j] = big->bytes;
65107a8ffeaSMatthew Dillon big = atomic_swap_ptr(&bigcache_array[j], big);
65207a8ffeaSMatthew Dillon break;
65307a8ffeaSMatthew Dillon }
65407a8ffeaSMatthew Dillon }
65507a8ffeaSMatthew Dillon return big;
65607a8ffeaSMatthew Dillon }
65707a8ffeaSMatthew Dillon
65807a8ffeaSMatthew Dillon static __inline
65907a8ffeaSMatthew Dillon void
handle_excess_big(void)66007a8ffeaSMatthew Dillon handle_excess_big(void)
66107a8ffeaSMatthew Dillon {
66207a8ffeaSMatthew Dillon int i;
66307a8ffeaSMatthew Dillon bigalloc_t big;
66407a8ffeaSMatthew Dillon bigalloc_t *bigp;
66507a8ffeaSMatthew Dillon
66607a8ffeaSMatthew Dillon if (excess_alloc <= BIGCACHE_EXCESS)
66707a8ffeaSMatthew Dillon return;
66807a8ffeaSMatthew Dillon
66907a8ffeaSMatthew Dillon for (i = 0; i < BIGHSIZE; ++i) {
67007a8ffeaSMatthew Dillon bigp = &bigalloc_array[i];
67107a8ffeaSMatthew Dillon if (*bigp == NULL)
67207a8ffeaSMatthew Dillon continue;
67307a8ffeaSMatthew Dillon if (__isthreaded)
67407a8ffeaSMatthew Dillon _SPINLOCK(&bigspin_array[i & BIGXMASK]);
67507a8ffeaSMatthew Dillon for (big = *bigp; big; big = big->next) {
67607a8ffeaSMatthew Dillon if (big->active < big->bytes) {
677721505deSMatthew Dillon MASSERT_WTHUNLK((big->active & PAGE_MASK) == 0,
678721505deSMatthew Dillon _SPINUNLOCK(&bigspin_array[i & BIGXMASK]));
679721505deSMatthew Dillon MASSERT_WTHUNLK((big->bytes & PAGE_MASK) == 0,
680721505deSMatthew Dillon _SPINUNLOCK(&bigspin_array[i & BIGXMASK]));
68107a8ffeaSMatthew Dillon munmap((char *)big->base + big->active,
68207a8ffeaSMatthew Dillon big->bytes - big->active);
68307a8ffeaSMatthew Dillon atomic_add_long(&excess_alloc,
68407a8ffeaSMatthew Dillon big->active - big->bytes);
68507a8ffeaSMatthew Dillon big->bytes = big->active;
68607a8ffeaSMatthew Dillon }
68707a8ffeaSMatthew Dillon }
68807a8ffeaSMatthew Dillon if (__isthreaded)
68907a8ffeaSMatthew Dillon _SPINUNLOCK(&bigspin_array[i & BIGXMASK]);
69007a8ffeaSMatthew Dillon }
69107a8ffeaSMatthew Dillon }
69207a8ffeaSMatthew Dillon
69307a8ffeaSMatthew Dillon /*
69482949828SMatthew Dillon * Calculate the zone index for the allocation request size and set the
69582949828SMatthew Dillon * allocation request size to that particular zone's chunk size.
69682949828SMatthew Dillon */
69782949828SMatthew Dillon static __inline int
zoneindex(size_t * bytes,size_t * chunking)69882949828SMatthew Dillon zoneindex(size_t *bytes, size_t *chunking)
69982949828SMatthew Dillon {
70082949828SMatthew Dillon size_t n = (unsigned int)*bytes; /* unsigned for shift opt */
7013f81f453SMatthew Dillon
7023f81f453SMatthew Dillon /*
7033f81f453SMatthew Dillon * This used to be 8-byte chunks and 16 zones for n < 128.
7043f81f453SMatthew Dillon * However some instructions may require 16-byte alignment
7053f81f453SMatthew Dillon * (aka SIMD) and programs might not request an aligned size
7063f81f453SMatthew Dillon * (aka GCC-7), so change this as follows:
7073f81f453SMatthew Dillon *
7083f81f453SMatthew Dillon * 0-15 bytes 8-byte alignment in two zones (0-1)
7093f81f453SMatthew Dillon * 16-127 bytes 16-byte alignment in four zones (3-10)
7103f81f453SMatthew Dillon * zone index 2 and 11-15 are currently unused.
7113f81f453SMatthew Dillon */
7123f81f453SMatthew Dillon if (n < 16) {
71382949828SMatthew Dillon *bytes = n = (n + 7) & ~7;
71482949828SMatthew Dillon *chunking = 8;
7153f81f453SMatthew Dillon return(n / 8 - 1); /* 8 byte chunks, 2 zones */
7163f81f453SMatthew Dillon /* zones 0,1, zone 2 is unused */
7173f81f453SMatthew Dillon }
7183f81f453SMatthew Dillon if (n < 128) {
7193f81f453SMatthew Dillon *bytes = n = (n + 15) & ~15;
7203f81f453SMatthew Dillon *chunking = 16;
7213f81f453SMatthew Dillon return(n / 16 + 2); /* 16 byte chunks, 8 zones */
7223f81f453SMatthew Dillon /* zones 3-10, zones 11-15 unused */
72382949828SMatthew Dillon }
72482949828SMatthew Dillon if (n < 256) {
72582949828SMatthew Dillon *bytes = n = (n + 15) & ~15;
72682949828SMatthew Dillon *chunking = 16;
72782949828SMatthew Dillon return(n / 16 + 7);
72882949828SMatthew Dillon }
72982949828SMatthew Dillon if (n < 8192) {
73082949828SMatthew Dillon if (n < 512) {
73182949828SMatthew Dillon *bytes = n = (n + 31) & ~31;
73282949828SMatthew Dillon *chunking = 32;
73382949828SMatthew Dillon return(n / 32 + 15);
73482949828SMatthew Dillon }
73582949828SMatthew Dillon if (n < 1024) {
73682949828SMatthew Dillon *bytes = n = (n + 63) & ~63;
73782949828SMatthew Dillon *chunking = 64;
73882949828SMatthew Dillon return(n / 64 + 23);
73982949828SMatthew Dillon }
74082949828SMatthew Dillon if (n < 2048) {
74182949828SMatthew Dillon *bytes = n = (n + 127) & ~127;
74282949828SMatthew Dillon *chunking = 128;
74382949828SMatthew Dillon return(n / 128 + 31);
74482949828SMatthew Dillon }
74582949828SMatthew Dillon if (n < 4096) {
74682949828SMatthew Dillon *bytes = n = (n + 255) & ~255;
74782949828SMatthew Dillon *chunking = 256;
74882949828SMatthew Dillon return(n / 256 + 39);
74982949828SMatthew Dillon }
75082949828SMatthew Dillon *bytes = n = (n + 511) & ~511;
75182949828SMatthew Dillon *chunking = 512;
75282949828SMatthew Dillon return(n / 512 + 47);
75382949828SMatthew Dillon }
75482949828SMatthew Dillon #if ZALLOC_ZONE_LIMIT > 8192
75582949828SMatthew Dillon if (n < 16384) {
75682949828SMatthew Dillon *bytes = n = (n + 1023) & ~1023;
75782949828SMatthew Dillon *chunking = 1024;
75882949828SMatthew Dillon return(n / 1024 + 55);
75982949828SMatthew Dillon }
76082949828SMatthew Dillon #endif
76182949828SMatthew Dillon #if ZALLOC_ZONE_LIMIT > 16384
76282949828SMatthew Dillon if (n < 32768) {
76382949828SMatthew Dillon *bytes = n = (n + 2047) & ~2047;
76482949828SMatthew Dillon *chunking = 2048;
76582949828SMatthew Dillon return(n / 2048 + 63);
76682949828SMatthew Dillon }
76782949828SMatthew Dillon #endif
7680a227237SSascha Wildner _mpanic("Unexpected byte count %zu", n);
76982949828SMatthew Dillon return(0);
77082949828SMatthew Dillon }
77182949828SMatthew Dillon
77282949828SMatthew Dillon /*
773369c9b6cSMatthew Dillon * We want large magazines for small allocations
774369c9b6cSMatthew Dillon */
775369c9b6cSMatthew Dillon static __inline int
zonecapacity(int zi)776369c9b6cSMatthew Dillon zonecapacity(int zi)
777369c9b6cSMatthew Dillon {
778369c9b6cSMatthew Dillon int cap;
779369c9b6cSMatthew Dillon
780369c9b6cSMatthew Dillon cap = (NZONES - zi) * (M_MAX_ROUNDS - M_MIN_ROUNDS) / NZONES +
781369c9b6cSMatthew Dillon M_MIN_ROUNDS;
782369c9b6cSMatthew Dillon
783369c9b6cSMatthew Dillon return cap;
784369c9b6cSMatthew Dillon }
785369c9b6cSMatthew Dillon
786369c9b6cSMatthew Dillon /*
78782949828SMatthew Dillon * malloc() - call internal slab allocator
78882949828SMatthew Dillon */
78982949828SMatthew Dillon void *
__malloc(size_t size)79069baab3bSImre Vadász __malloc(size_t size)
79182949828SMatthew Dillon {
79211e45f67SMatthew Dillon void *ptr;
79311e45f67SMatthew Dillon
794721505deSMatthew Dillon nmalloc_sigblockall();
79511e45f67SMatthew Dillon ptr = _slaballoc(size, 0);
79611e45f67SMatthew Dillon if (ptr == NULL)
79711e45f67SMatthew Dillon errno = ENOMEM;
7980bb7d8c8SVenkatesh Srinivas else
7990bb7d8c8SVenkatesh Srinivas UTRACE(0, size, ptr);
800721505deSMatthew Dillon nmalloc_sigunblockall();
801721505deSMatthew Dillon
80211e45f67SMatthew Dillon return(ptr);
80382949828SMatthew Dillon }
80482949828SMatthew Dillon
8052d114219SJoris Giovannangeli #define MUL_NO_OVERFLOW (1UL << (sizeof(size_t) * 4))
8062d114219SJoris Giovannangeli
80782949828SMatthew Dillon /*
80882949828SMatthew Dillon * calloc() - call internal slab allocator
80982949828SMatthew Dillon */
81082949828SMatthew Dillon void *
__calloc(size_t number,size_t size)81169baab3bSImre Vadász __calloc(size_t number, size_t size)
81282949828SMatthew Dillon {
81311e45f67SMatthew Dillon void *ptr;
81411e45f67SMatthew Dillon
81532af0e61SJoris Giovannangeli if ((number >= MUL_NO_OVERFLOW || size >= MUL_NO_OVERFLOW) &&
81632af0e61SJoris Giovannangeli number > 0 && SIZE_MAX / number < size) {
8172d114219SJoris Giovannangeli errno = ENOMEM;
8182d114219SJoris Giovannangeli return(NULL);
8192d114219SJoris Giovannangeli }
8202d114219SJoris Giovannangeli
821721505deSMatthew Dillon nmalloc_sigblockall();
82211e45f67SMatthew Dillon ptr = _slaballoc(number * size, SAFLAG_ZERO);
82311e45f67SMatthew Dillon if (ptr == NULL)
82411e45f67SMatthew Dillon errno = ENOMEM;
8250bb7d8c8SVenkatesh Srinivas else
8260bb7d8c8SVenkatesh Srinivas UTRACE(0, number * size, ptr);
827721505deSMatthew Dillon nmalloc_sigunblockall();
828721505deSMatthew Dillon
82911e45f67SMatthew Dillon return(ptr);
83082949828SMatthew Dillon }
83182949828SMatthew Dillon
83282949828SMatthew Dillon /*
83382949828SMatthew Dillon * realloc() (SLAB ALLOCATOR)
83482949828SMatthew Dillon *
83582949828SMatthew Dillon * We do not attempt to optimize this routine beyond reusing the same
83682949828SMatthew Dillon * pointer if the new size fits within the chunking of the old pointer's
83782949828SMatthew Dillon * zone.
83882949828SMatthew Dillon */
83982949828SMatthew Dillon void *
__realloc(void * ptr,size_t size)84069baab3bSImre Vadász __realloc(void *ptr, size_t size)
84182949828SMatthew Dillon {
8420bb7d8c8SVenkatesh Srinivas void *ret;
843721505deSMatthew Dillon
844721505deSMatthew Dillon nmalloc_sigblockall();
8450bb7d8c8SVenkatesh Srinivas ret = _slabrealloc(ptr, size);
8460bb7d8c8SVenkatesh Srinivas if (ret == NULL)
84711e45f67SMatthew Dillon errno = ENOMEM;
8480bb7d8c8SVenkatesh Srinivas else
8490bb7d8c8SVenkatesh Srinivas UTRACE(ptr, size, ret);
850721505deSMatthew Dillon nmalloc_sigunblockall();
851721505deSMatthew Dillon
8520bb7d8c8SVenkatesh Srinivas return(ret);
85382949828SMatthew Dillon }
85482949828SMatthew Dillon
85511e45f67SMatthew Dillon /*
856d780b39fSAntonio Huete Jimenez * malloc_usable_size() (SLAB ALLOCATOR)
857d780b39fSAntonio Huete Jimenez */
858d780b39fSAntonio Huete Jimenez size_t
__malloc_usable_size(const void * ptr)859d780b39fSAntonio Huete Jimenez __malloc_usable_size(const void *ptr)
860d780b39fSAntonio Huete Jimenez {
861d780b39fSAntonio Huete Jimenez return _slabusablesize(ptr);
862d780b39fSAntonio Huete Jimenez }
863d780b39fSAntonio Huete Jimenez
864d780b39fSAntonio Huete Jimenez /*
865d3a54aeeSzrj * aligned_alloc()
866d3a54aeeSzrj *
867d3a54aeeSzrj * Allocate (size) bytes with a alignment of (alignment).
868d3a54aeeSzrj */
869d3a54aeeSzrj void *
__aligned_alloc(size_t alignment,size_t size)870d3a54aeeSzrj __aligned_alloc(size_t alignment, size_t size)
871d3a54aeeSzrj {
872d3a54aeeSzrj void *ptr;
873d3a54aeeSzrj int rc;
874d3a54aeeSzrj
875721505deSMatthew Dillon nmalloc_sigblockall();
876d3a54aeeSzrj ptr = NULL;
877d3a54aeeSzrj rc = _slabmemalign(&ptr, alignment, size);
878d3a54aeeSzrj if (rc)
879d3a54aeeSzrj errno = rc;
880721505deSMatthew Dillon nmalloc_sigunblockall();
881d3a54aeeSzrj
882d3a54aeeSzrj return (ptr);
883d3a54aeeSzrj }
884d3a54aeeSzrj
885d3a54aeeSzrj /*
88611e45f67SMatthew Dillon * posix_memalign()
88711e45f67SMatthew Dillon *
88811e45f67SMatthew Dillon * Allocate (size) bytes with a alignment of (alignment), where (alignment)
88911e45f67SMatthew Dillon * is a power of 2 >= sizeof(void *).
890d3a54aeeSzrj */
891d3a54aeeSzrj int
__posix_memalign(void ** memptr,size_t alignment,size_t size)892d3a54aeeSzrj __posix_memalign(void **memptr, size_t alignment, size_t size)
893d3a54aeeSzrj {
894d3a54aeeSzrj int rc;
895d3a54aeeSzrj
896d3a54aeeSzrj /*
897d3a54aeeSzrj * OpenGroup spec issue 6 check
898d3a54aeeSzrj */
899d3a54aeeSzrj if (alignment < sizeof(void *)) {
900d3a54aeeSzrj *memptr = NULL;
901d3a54aeeSzrj return(EINVAL);
902d3a54aeeSzrj }
903d3a54aeeSzrj
904721505deSMatthew Dillon nmalloc_sigblockall();
905d3a54aeeSzrj rc = _slabmemalign(memptr, alignment, size);
906721505deSMatthew Dillon nmalloc_sigunblockall();
907d3a54aeeSzrj
908d3a54aeeSzrj return (rc);
909d3a54aeeSzrj }
910d3a54aeeSzrj
911d3a54aeeSzrj /*
91211e45f67SMatthew Dillon * The slab allocator will allocate on power-of-2 boundaries up to
91311e45f67SMatthew Dillon * at least PAGE_SIZE. We use the zoneindex mechanic to find a
91411e45f67SMatthew Dillon * zone matching the requirements, and _vmem_alloc() otherwise.
91511e45f67SMatthew Dillon */
916d3a54aeeSzrj static int
_slabmemalign(void ** memptr,size_t alignment,size_t size)917d3a54aeeSzrj _slabmemalign(void **memptr, size_t alignment, size_t size)
91811e45f67SMatthew Dillon {
91911e45f67SMatthew Dillon bigalloc_t *bigp;
92011e45f67SMatthew Dillon bigalloc_t big;
9216c23d8e0SJordan Gordeev size_t chunking;
922cf515c3aSJohn Marino int zi __unused;
92311e45f67SMatthew Dillon
924d3a54aeeSzrj if (alignment < 1) {
925d3a54aeeSzrj *memptr = NULL;
926d3a54aeeSzrj return(EINVAL);
927d3a54aeeSzrj }
928d3a54aeeSzrj
92911e45f67SMatthew Dillon /*
93011e45f67SMatthew Dillon * OpenGroup spec issue 6 checks
93111e45f67SMatthew Dillon */
93211e45f67SMatthew Dillon if ((alignment | (alignment - 1)) + 1 != (alignment << 1)) {
93311e45f67SMatthew Dillon *memptr = NULL;
93411e45f67SMatthew Dillon return(EINVAL);
93511e45f67SMatthew Dillon }
93611e45f67SMatthew Dillon
93711e45f67SMatthew Dillon /*
9388ff099aeSMatthew Dillon * Our zone mechanism guarantees same-sized alignment for any
9398ff099aeSMatthew Dillon * power-of-2 allocation. If size is a power-of-2 and reasonable
9408ff099aeSMatthew Dillon * we can just call _slaballoc() and be done. We round size up
9418ff099aeSMatthew Dillon * to the nearest alignment boundary to improve our odds of
9428ff099aeSMatthew Dillon * it becoming a power-of-2 if it wasn't before.
94311e45f67SMatthew Dillon */
9448ff099aeSMatthew Dillon if (size <= alignment)
94511e45f67SMatthew Dillon size = alignment;
9468ff099aeSMatthew Dillon else
9478ff099aeSMatthew Dillon size = (size + alignment - 1) & ~(size_t)(alignment - 1);
948e9586122Szrj
949e9586122Szrj /*
95072732463SMatthew Dillon * If we have overflowed above when rounding to the nearest alignment
951e9586122Szrj * boundary, just return ENOMEM, size should be == N * sizeof(void *).
95272732463SMatthew Dillon *
95372732463SMatthew Dillon * Power-of-2 allocations up to 8KB will be aligned to the allocation
95472732463SMatthew Dillon * size and _slaballoc() can simply be used. Please see line 1082
95572732463SMatthew Dillon * for this special case: 'Align the storage in the zone based on
95672732463SMatthew Dillon * the chunking' has a special case for powers of 2.
957e9586122Szrj */
958e9586122Szrj if (size == 0)
959e9586122Szrj return(ENOMEM);
960e9586122Szrj
961369c9b6cSMatthew Dillon if (size <= MAX_SLAB_PAGEALIGN &&
962369c9b6cSMatthew Dillon (size | (size - 1)) + 1 == (size << 1)) {
9638ff099aeSMatthew Dillon *memptr = _slaballoc(size, 0);
9648ff099aeSMatthew Dillon return(*memptr ? 0 : ENOMEM);
9658ff099aeSMatthew Dillon }
9668ff099aeSMatthew Dillon
9678ff099aeSMatthew Dillon /*
9688ff099aeSMatthew Dillon * Otherwise locate a zone with a chunking that matches
9698ff099aeSMatthew Dillon * the requested alignment, within reason. Consider two cases:
9708ff099aeSMatthew Dillon *
9718ff099aeSMatthew Dillon * (1) A 1K allocation on a 32-byte alignment. The first zoneindex
9728ff099aeSMatthew Dillon * we find will be the best fit because the chunking will be
9738ff099aeSMatthew Dillon * greater or equal to the alignment.
9748ff099aeSMatthew Dillon *
9758ff099aeSMatthew Dillon * (2) A 513 allocation on a 256-byte alignment. In this case
9768ff099aeSMatthew Dillon * the first zoneindex we find will be for 576 byte allocations
9778ff099aeSMatthew Dillon * with a chunking of 64, which is not sufficient. To fix this
9788ff099aeSMatthew Dillon * we simply find the nearest power-of-2 >= size and use the
9798ff099aeSMatthew Dillon * same side-effect of _slaballoc() which guarantees
9808ff099aeSMatthew Dillon * same-alignment on a power-of-2 allocation.
9818ff099aeSMatthew Dillon */
9828ff099aeSMatthew Dillon if (size < PAGE_SIZE) {
98311e45f67SMatthew Dillon zi = zoneindex(&size, &chunking);
98411e45f67SMatthew Dillon if (chunking >= alignment) {
98511e45f67SMatthew Dillon *memptr = _slaballoc(size, 0);
98611e45f67SMatthew Dillon return(*memptr ? 0 : ENOMEM);
98711e45f67SMatthew Dillon }
9888ff099aeSMatthew Dillon if (size >= 1024)
9898ff099aeSMatthew Dillon alignment = 1024;
9908ff099aeSMatthew Dillon if (size >= 16384)
9918ff099aeSMatthew Dillon alignment = 16384;
9928ff099aeSMatthew Dillon while (alignment < size)
9938ff099aeSMatthew Dillon alignment <<= 1;
9948ff099aeSMatthew Dillon *memptr = _slaballoc(alignment, 0);
9958ff099aeSMatthew Dillon return(*memptr ? 0 : ENOMEM);
99611e45f67SMatthew Dillon }
99711e45f67SMatthew Dillon
99811e45f67SMatthew Dillon /*
99911e45f67SMatthew Dillon * If the slab allocator cannot handle it use vmem_alloc().
100011e45f67SMatthew Dillon *
100111e45f67SMatthew Dillon * Alignment must be adjusted up to at least PAGE_SIZE in this case.
100211e45f67SMatthew Dillon */
100311e45f67SMatthew Dillon if (alignment < PAGE_SIZE)
100411e45f67SMatthew Dillon alignment = PAGE_SIZE;
100511e45f67SMatthew Dillon if (size < alignment)
100611e45f67SMatthew Dillon size = alignment;
100711e45f67SMatthew Dillon size = (size + PAGE_MASK) & ~(size_t)PAGE_MASK;
1008c8a21d03SImre Vadász if (alignment == PAGE_SIZE && size <= BIGCACHE_LIMIT) {
1009c8a21d03SImre Vadász big = bigcache_find_alloc(size);
1010c8a21d03SImre Vadász if (big && big->bytes < size) {
1011c8a21d03SImre Vadász _slabfree(big->base, FASTSLABREALLOC, &big);
1012c8a21d03SImre Vadász big = NULL;
1013c8a21d03SImre Vadász }
1014c8a21d03SImre Vadász if (big) {
1015c8a21d03SImre Vadász *memptr = big->base;
1016c8a21d03SImre Vadász big->active = size;
1017c8a21d03SImre Vadász if (big->active < big->bytes) {
1018c8a21d03SImre Vadász atomic_add_long(&excess_alloc,
1019c8a21d03SImre Vadász big->bytes - big->active);
1020c8a21d03SImre Vadász }
1021c8a21d03SImre Vadász bigp = bigalloc_lock(*memptr);
1022c8a21d03SImre Vadász big->next = *bigp;
1023c8a21d03SImre Vadász *bigp = big;
1024c8a21d03SImre Vadász bigalloc_unlock(*memptr);
1025c8a21d03SImre Vadász handle_excess_big();
1026c8a21d03SImre Vadász return(0);
1027c8a21d03SImre Vadász }
1028c8a21d03SImre Vadász }
102911e45f67SMatthew Dillon *memptr = _vmem_alloc(size, alignment, 0);
103011e45f67SMatthew Dillon if (*memptr == NULL)
103111e45f67SMatthew Dillon return(ENOMEM);
103211e45f67SMatthew Dillon
103311e45f67SMatthew Dillon big = _slaballoc(sizeof(struct bigalloc), 0);
103411e45f67SMatthew Dillon if (big == NULL) {
103511e45f67SMatthew Dillon _vmem_free(*memptr, size);
103611e45f67SMatthew Dillon *memptr = NULL;
103711e45f67SMatthew Dillon return(ENOMEM);
103811e45f67SMatthew Dillon }
103911e45f67SMatthew Dillon bigp = bigalloc_lock(*memptr);
104011e45f67SMatthew Dillon big->base = *memptr;
104107a8ffeaSMatthew Dillon big->active = size;
104207a8ffeaSMatthew Dillon big->bytes = size; /* no excess */
104311e45f67SMatthew Dillon big->next = *bigp;
104411e45f67SMatthew Dillon *bigp = big;
104511e45f67SMatthew Dillon bigalloc_unlock(*memptr);
104611e45f67SMatthew Dillon
104711e45f67SMatthew Dillon return(0);
104811e45f67SMatthew Dillon }
104911e45f67SMatthew Dillon
105011e45f67SMatthew Dillon /*
105111e45f67SMatthew Dillon * free() (SLAB ALLOCATOR) - do the obvious
105211e45f67SMatthew Dillon */
105382949828SMatthew Dillon void
__free(void * ptr)105469baab3bSImre Vadász __free(void *ptr)
105582949828SMatthew Dillon {
10560bb7d8c8SVenkatesh Srinivas UTRACE(ptr, 0, 0);
10574989e1f1SMatthew Dillon
1058721505deSMatthew Dillon nmalloc_sigblockall();
10590bb7d8c8SVenkatesh Srinivas _slabfree(ptr, 0, NULL);
1060721505deSMatthew Dillon nmalloc_sigunblockall();
106182949828SMatthew Dillon }
106282949828SMatthew Dillon
106382949828SMatthew Dillon /*
106482949828SMatthew Dillon * _slaballoc() (SLAB ALLOCATOR)
106582949828SMatthew Dillon *
106682949828SMatthew Dillon * Allocate memory via the slab allocator. If the request is too large,
106782949828SMatthew Dillon * or if it page-aligned beyond a certain size, we fall back to the
106882949828SMatthew Dillon * KMEM subsystem
106982949828SMatthew Dillon */
107082949828SMatthew Dillon static void *
_slaballoc(size_t size,int flags)107182949828SMatthew Dillon _slaballoc(size_t size, int flags)
107282949828SMatthew Dillon {
107382949828SMatthew Dillon slzone_t z;
107482949828SMatthew Dillon slchunk_t chunk;
107582949828SMatthew Dillon slglobaldata_t slgd;
10766c23d8e0SJordan Gordeev size_t chunking;
10778b07b5e8SMatthew Dillon thr_mags *tp;
10788b07b5e8SMatthew Dillon struct magazine *mp;
10798b07b5e8SMatthew Dillon int count;
108082949828SMatthew Dillon int zi;
108182949828SMatthew Dillon int off;
10820bb7d8c8SVenkatesh Srinivas void *obj;
10830bb7d8c8SVenkatesh Srinivas
108482949828SMatthew Dillon /*
108582949828SMatthew Dillon * Handle the degenerate size == 0 case. Yes, this does happen.
108682949828SMatthew Dillon * Return a special pointer. This is to maintain compatibility with
108782949828SMatthew Dillon * the original malloc implementation. Certain devices, such as the
108882949828SMatthew Dillon * adaptec driver, not only allocate 0 bytes, they check for NULL and
108982949828SMatthew Dillon * also realloc() later on. Joy.
109082949828SMatthew Dillon */
109182949828SMatthew Dillon if (size == 0)
1092e2caf0e7SMatthew Dillon size = 1;
109382949828SMatthew Dillon
10940bb7d8c8SVenkatesh Srinivas /* Capture global flags */
10950bb7d8c8SVenkatesh Srinivas flags |= g_malloc_flags;
10960bb7d8c8SVenkatesh Srinivas
109782949828SMatthew Dillon /*
1098369c9b6cSMatthew Dillon * Handle large allocations directly, with a separate bigmem cache.
109982949828SMatthew Dillon *
110082949828SMatthew Dillon * The backend allocator is pretty nasty on a SMP system. Use the
110182949828SMatthew Dillon * slab allocator for one and two page-sized chunks even though we
110282949828SMatthew Dillon * lose some efficiency.
110372732463SMatthew Dillon *
1104369c9b6cSMatthew Dillon * NOTE: Please see _slabmemalign(), which assumes that power-of-2
1105369c9b6cSMatthew Dillon * allocations up to an including MAX_SLAB_PAGEALIGN
110672732463SMatthew Dillon * can use _slaballoc() and be aligned to the same. The
110772732463SMatthew Dillon * zone cache can be used for this case, bigalloc does not
110872732463SMatthew Dillon * have to be used.
110982949828SMatthew Dillon */
111082949828SMatthew Dillon if (size >= ZoneLimit ||
1111369c9b6cSMatthew Dillon ((size & PAGE_MASK) == 0 && size > MAX_SLAB_PAGEALIGN)) {
111282949828SMatthew Dillon bigalloc_t big;
111382949828SMatthew Dillon bigalloc_t *bigp;
111482949828SMatthew Dillon
11158120f5e2SMatthew Dillon /*
11168120f5e2SMatthew Dillon * Page-align and cache-color in case of virtually indexed
11178120f5e2SMatthew Dillon * physically tagged L1 caches (aka SandyBridge). No sweat
11188120f5e2SMatthew Dillon * otherwise, so just do it.
111907a8ffeaSMatthew Dillon *
112007a8ffeaSMatthew Dillon * (don't count as excess).
11218120f5e2SMatthew Dillon */
112282949828SMatthew Dillon size = (size + PAGE_MASK) & ~(size_t)PAGE_MASK;
1123d0bc7769Szrj
1124d0bc7769Szrj /*
112572732463SMatthew Dillon * If we have overflowed above when rounding to the page
1126d0bc7769Szrj * boundary, something has passed us (size_t)[-PAGE_MASK..-1]
1127d0bc7769Szrj * so just return NULL, size at this point should be >= 0.
1128d0bc7769Szrj */
1129d0bc7769Szrj if (size == 0)
1130d0bc7769Szrj return (NULL);
1131d0bc7769Szrj
1132369c9b6cSMatthew Dillon /*
1133369c9b6cSMatthew Dillon * Force an additional page offset for 8KB-aligned requests
1134369c9b6cSMatthew Dillon * (i.e. 8KB, 16KB, etc) that helps spread data across the
1135369c9b6cSMatthew Dillon * CPU caches at the cost of some dead space in the memory
1136369c9b6cSMatthew Dillon * map.
1137369c9b6cSMatthew Dillon */
113807a8ffeaSMatthew Dillon if ((size & (PAGE_SIZE * 2 - 1)) == 0)
113907a8ffeaSMatthew Dillon size += PAGE_SIZE;
11408120f5e2SMatthew Dillon
114107a8ffeaSMatthew Dillon /*
114207a8ffeaSMatthew Dillon * Try to reuse a cached big block to avoid mmap'ing. If it
114307a8ffeaSMatthew Dillon * turns out not to fit our requirements we throw it away
114407a8ffeaSMatthew Dillon * and allocate normally.
114507a8ffeaSMatthew Dillon */
114607a8ffeaSMatthew Dillon big = NULL;
114707a8ffeaSMatthew Dillon if (size <= BIGCACHE_LIMIT) {
114807a8ffeaSMatthew Dillon big = bigcache_find_alloc(size);
114907a8ffeaSMatthew Dillon if (big && big->bytes < size) {
115007a8ffeaSMatthew Dillon _slabfree(big->base, FASTSLABREALLOC, &big);
115107a8ffeaSMatthew Dillon big = NULL;
115207a8ffeaSMatthew Dillon }
115307a8ffeaSMatthew Dillon }
115407a8ffeaSMatthew Dillon if (big) {
115507a8ffeaSMatthew Dillon chunk = big->base;
115607a8ffeaSMatthew Dillon if (flags & SAFLAG_ZERO)
115707a8ffeaSMatthew Dillon bzero(chunk, size);
115807a8ffeaSMatthew Dillon } else {
115982949828SMatthew Dillon chunk = _vmem_alloc(size, PAGE_SIZE, flags);
116082949828SMatthew Dillon if (chunk == NULL)
116182949828SMatthew Dillon return(NULL);
116282949828SMatthew Dillon
116382949828SMatthew Dillon big = _slaballoc(sizeof(struct bigalloc), 0);
116411e45f67SMatthew Dillon if (big == NULL) {
116511e45f67SMatthew Dillon _vmem_free(chunk, size);
116611e45f67SMatthew Dillon return(NULL);
116711e45f67SMatthew Dillon }
116882949828SMatthew Dillon big->base = chunk;
116982949828SMatthew Dillon big->bytes = size;
117007a8ffeaSMatthew Dillon }
117107a8ffeaSMatthew Dillon big->active = size;
117207a8ffeaSMatthew Dillon
117307a8ffeaSMatthew Dillon bigp = bigalloc_lock(chunk);
117407a8ffeaSMatthew Dillon if (big->active < big->bytes) {
117507a8ffeaSMatthew Dillon atomic_add_long(&excess_alloc,
117607a8ffeaSMatthew Dillon big->bytes - big->active);
117707a8ffeaSMatthew Dillon }
117882949828SMatthew Dillon big->next = *bigp;
117982949828SMatthew Dillon *bigp = big;
118082949828SMatthew Dillon bigalloc_unlock(chunk);
118107a8ffeaSMatthew Dillon handle_excess_big();
118282949828SMatthew Dillon
118382949828SMatthew Dillon return(chunk);
118482949828SMatthew Dillon }
118582949828SMatthew Dillon
11860bb7d8c8SVenkatesh Srinivas /* Compute allocation zone; zoneindex will panic on excessive sizes */
11870bb7d8c8SVenkatesh Srinivas zi = zoneindex(&size, &chunking);
11880bb7d8c8SVenkatesh Srinivas MASSERT(zi < NZONES);
11890bb7d8c8SVenkatesh Srinivas
11908b07b5e8SMatthew Dillon obj = mtmagazine_alloc(zi, flags);
11910bb7d8c8SVenkatesh Srinivas if (obj != NULL) {
11920bb7d8c8SVenkatesh Srinivas if (flags & SAFLAG_ZERO)
11930bb7d8c8SVenkatesh Srinivas bzero(obj, size);
11940bb7d8c8SVenkatesh Srinivas return (obj);
119582949828SMatthew Dillon }
119682949828SMatthew Dillon
119782949828SMatthew Dillon /*
11988b07b5e8SMatthew Dillon * Attempt to allocate out of an existing global zone. If all zones
11998b07b5e8SMatthew Dillon * are exhausted pull one off the free list or allocate a new one.
120082949828SMatthew Dillon */
12018b07b5e8SMatthew Dillon slgd = &SLGlobalData;
12028b07b5e8SMatthew Dillon
12038b07b5e8SMatthew Dillon again:
12048b07b5e8SMatthew Dillon if (slgd->ZoneAry[zi] == NULL) {
12050bb7d8c8SVenkatesh Srinivas z = zone_alloc(flags);
120682949828SMatthew Dillon if (z == NULL)
120782949828SMatthew Dillon goto fail;
120882949828SMatthew Dillon
120982949828SMatthew Dillon /*
121082949828SMatthew Dillon * How big is the base structure?
121182949828SMatthew Dillon */
121282949828SMatthew Dillon off = sizeof(struct slzone);
121382949828SMatthew Dillon
121482949828SMatthew Dillon /*
121582949828SMatthew Dillon * Align the storage in the zone based on the chunking.
121682949828SMatthew Dillon *
12170bb7d8c8SVenkatesh Srinivas * Guarantee power-of-2 alignment for power-of-2-sized
121882949828SMatthew Dillon * chunks. Otherwise align based on the chunking size
121982949828SMatthew Dillon * (typically 8 or 16 bytes for small allocations).
122082949828SMatthew Dillon *
122182949828SMatthew Dillon * NOTE: Allocations >= ZoneLimit are governed by the
122282949828SMatthew Dillon * bigalloc code and typically only guarantee page-alignment.
122382949828SMatthew Dillon *
122482949828SMatthew Dillon * Set initial conditions for UIndex near the zone header
122582949828SMatthew Dillon * to reduce unecessary page faults, vs semi-randomization
122682949828SMatthew Dillon * to improve L1 cache saturation.
122772732463SMatthew Dillon *
1228369c9b6cSMatthew Dillon * NOTE: Please see _slabmemalign(), which assumes that
1229369c9b6cSMatthew Dillon * power-of-2 allocations up to an including
1230369c9b6cSMatthew Dillon * MAX_SLAB_PAGEALIGN can use _slaballoc()
1231369c9b6cSMatthew Dillon * and be aligned to the same. The zone cache can be
1232369c9b6cSMatthew Dillon * used for this case, bigalloc does not have to be
1233369c9b6cSMatthew Dillon * used.
123472732463SMatthew Dillon *
123572732463SMatthew Dillon * ALL power-of-2 requests that fall through to this
123672732463SMatthew Dillon * code use this rule (conditionals above limit this
1237369c9b6cSMatthew Dillon * to <= MAX_SLAB_PAGEALIGN).
123882949828SMatthew Dillon */
123982949828SMatthew Dillon if ((size | (size - 1)) + 1 == (size << 1))
1240965b839fSSascha Wildner off = roundup2(off, size);
124182949828SMatthew Dillon else
1242965b839fSSascha Wildner off = roundup2(off, chunking);
124382949828SMatthew Dillon z->z_Magic = ZALLOC_SLAB_MAGIC;
124482949828SMatthew Dillon z->z_ZoneIndex = zi;
124582949828SMatthew Dillon z->z_NMax = (ZoneSize - off) / size;
124682949828SMatthew Dillon z->z_NFree = z->z_NMax;
124782949828SMatthew Dillon z->z_BasePtr = (char *)z + off;
124882949828SMatthew Dillon z->z_UIndex = z->z_UEndIndex = 0;
124982949828SMatthew Dillon z->z_ChunkSize = size;
125082949828SMatthew Dillon z->z_FirstFreePg = ZonePageCount;
125182949828SMatthew Dillon if ((z->z_Flags & SLZF_UNOTZEROD) == 0) {
125282949828SMatthew Dillon flags &= ~SAFLAG_ZERO; /* already zero'd */
125382949828SMatthew Dillon flags |= SAFLAG_PASSIVE;
125482949828SMatthew Dillon }
125582949828SMatthew Dillon
125682949828SMatthew Dillon /*
125782949828SMatthew Dillon * Slide the base index for initial allocations out of the
125882949828SMatthew Dillon * next zone we create so we do not over-weight the lower
125982949828SMatthew Dillon * part of the cpu memory caches.
126082949828SMatthew Dillon */
12618b07b5e8SMatthew Dillon slgd_lock(slgd);
12628b07b5e8SMatthew Dillon z->z_Next = slgd->ZoneAry[zi];
12638b07b5e8SMatthew Dillon slgd->ZoneAry[zi] = z;
12648b07b5e8SMatthew Dillon } else {
12658b07b5e8SMatthew Dillon slgd_lock(slgd);
12668b07b5e8SMatthew Dillon z = slgd->ZoneAry[zi];
12678b07b5e8SMatthew Dillon if (z == NULL) {
12688b07b5e8SMatthew Dillon slgd_unlock(slgd);
12698b07b5e8SMatthew Dillon goto again;
12708b07b5e8SMatthew Dillon }
127182949828SMatthew Dillon }
127282949828SMatthew Dillon
127382949828SMatthew Dillon /*
127482949828SMatthew Dillon * Ok, we have a zone from which at least one chunk is available.
127582949828SMatthew Dillon */
1276721505deSMatthew Dillon MASSERT_WTHUNLK(z->z_NFree > 0, slgd_unlock(slgd));
127782949828SMatthew Dillon
12788b07b5e8SMatthew Dillon /*
12798b07b5e8SMatthew Dillon * Try to cache <count> chunks, up to CACHE_CHUNKS (32 typ)
12808b07b5e8SMatthew Dillon * to avoid unnecessary global lock contention.
12818b07b5e8SMatthew Dillon */
12828b07b5e8SMatthew Dillon tp = &thread_mags;
12838b07b5e8SMatthew Dillon mp = tp->mags[zi].loaded;
12848b07b5e8SMatthew Dillon count = 0;
12858b07b5e8SMatthew Dillon if (mp && tp->init >= 0) {
12868b07b5e8SMatthew Dillon count = mp->capacity - mp->rounds;
12878b07b5e8SMatthew Dillon if (count >= z->z_NFree)
12888b07b5e8SMatthew Dillon count = z->z_NFree - 1;
12898b07b5e8SMatthew Dillon if (count > CACHE_CHUNKS)
12908b07b5e8SMatthew Dillon count = CACHE_CHUNKS;
129182949828SMatthew Dillon }
129282949828SMatthew Dillon
129382949828SMatthew Dillon /*
129482949828SMatthew Dillon * Locate a chunk in a free page. This attempts to localize
129582949828SMatthew Dillon * reallocations into earlier pages without us having to sort
129682949828SMatthew Dillon * the chunk list. A chunk may still overlap a page boundary.
129782949828SMatthew Dillon */
129882949828SMatthew Dillon while (z->z_FirstFreePg < ZonePageCount) {
129982949828SMatthew Dillon if ((chunk = z->z_PageAry[z->z_FirstFreePg]) != NULL) {
1300721505deSMatthew Dillon if (((uintptr_t)chunk & ZoneMask) == 0) {
1301721505deSMatthew Dillon slgd_unlock(slgd);
1302721505deSMatthew Dillon _mpanic("assertion: corrupt malloc zone");
1303721505deSMatthew Dillon }
130482949828SMatthew Dillon z->z_PageAry[z->z_FirstFreePg] = chunk->c_Next;
13058b07b5e8SMatthew Dillon --z->z_NFree;
13068b07b5e8SMatthew Dillon
13078b07b5e8SMatthew Dillon if (count == 0)
130882949828SMatthew Dillon goto done;
13098b07b5e8SMatthew Dillon mp->objects[mp->rounds++] = chunk;
13108b07b5e8SMatthew Dillon --count;
13118b07b5e8SMatthew Dillon continue;
131282949828SMatthew Dillon }
131382949828SMatthew Dillon ++z->z_FirstFreePg;
131482949828SMatthew Dillon }
131582949828SMatthew Dillon
131682949828SMatthew Dillon /*
131782949828SMatthew Dillon * No chunks are available but NFree said we had some memory,
131882949828SMatthew Dillon * so it must be available in the never-before-used-memory
131982949828SMatthew Dillon * area governed by UIndex. The consequences are very
132082949828SMatthew Dillon * serious if our zone got corrupted so we use an explicit
132182949828SMatthew Dillon * panic rather then a KASSERT.
132282949828SMatthew Dillon */
13238b07b5e8SMatthew Dillon for (;;) {
132482949828SMatthew Dillon chunk = (slchunk_t)(z->z_BasePtr + z->z_UIndex * size);
13258b07b5e8SMatthew Dillon --z->z_NFree;
132682949828SMatthew Dillon if (++z->z_UIndex == z->z_NMax)
132782949828SMatthew Dillon z->z_UIndex = 0;
132882949828SMatthew Dillon if (z->z_UIndex == z->z_UEndIndex) {
13298b07b5e8SMatthew Dillon if (z->z_NFree != 0) {
13308b07b5e8SMatthew Dillon slgd_unlock(slgd);
133182949828SMatthew Dillon _mpanic("slaballoc: corrupted zone");
133282949828SMatthew Dillon }
13338b07b5e8SMatthew Dillon }
13348b07b5e8SMatthew Dillon if (count == 0)
13358b07b5e8SMatthew Dillon break;
13368b07b5e8SMatthew Dillon mp->objects[mp->rounds++] = chunk;
13378b07b5e8SMatthew Dillon --count;
13388b07b5e8SMatthew Dillon }
133982949828SMatthew Dillon
134082949828SMatthew Dillon if ((z->z_Flags & SLZF_UNOTZEROD) == 0) {
134182949828SMatthew Dillon flags &= ~SAFLAG_ZERO;
134282949828SMatthew Dillon flags |= SAFLAG_PASSIVE;
134382949828SMatthew Dillon }
134482949828SMatthew Dillon
134582949828SMatthew Dillon done:
13468b07b5e8SMatthew Dillon /*
13478b07b5e8SMatthew Dillon * Remove us from the ZoneAry[] when we become empty
13488b07b5e8SMatthew Dillon */
13498b07b5e8SMatthew Dillon if (z->z_NFree == 0) {
13508b07b5e8SMatthew Dillon slgd->ZoneAry[zi] = z->z_Next;
13518b07b5e8SMatthew Dillon z->z_Next = NULL;
13528b07b5e8SMatthew Dillon }
135382949828SMatthew Dillon slgd_unlock(slgd);
13546aa0e649SSascha Wildner if (flags & SAFLAG_ZERO)
135582949828SMatthew Dillon bzero(chunk, size);
13568b07b5e8SMatthew Dillon
135782949828SMatthew Dillon return(chunk);
135882949828SMatthew Dillon fail:
135982949828SMatthew Dillon return(NULL);
136082949828SMatthew Dillon }
136182949828SMatthew Dillon
136282949828SMatthew Dillon /*
136382949828SMatthew Dillon * Reallocate memory within the chunk
136482949828SMatthew Dillon */
136582949828SMatthew Dillon static void *
_slabrealloc(void * ptr,size_t size)136682949828SMatthew Dillon _slabrealloc(void *ptr, size_t size)
136782949828SMatthew Dillon {
136882949828SMatthew Dillon bigalloc_t *bigp;
136982949828SMatthew Dillon void *nptr;
137082949828SMatthew Dillon slzone_t z;
137182949828SMatthew Dillon size_t chunking;
137282949828SMatthew Dillon
1373e2caf0e7SMatthew Dillon if (ptr == NULL) {
137482949828SMatthew Dillon return(_slaballoc(size, 0));
1375ebe0d361SMatthew Dillon }
137682949828SMatthew Dillon
1377e2caf0e7SMatthew Dillon if (size == 0)
1378e2caf0e7SMatthew Dillon size = 1;
137982949828SMatthew Dillon
138082949828SMatthew Dillon /*
13810bb7d8c8SVenkatesh Srinivas * Handle oversized allocations.
138282949828SMatthew Dillon */
138382949828SMatthew Dillon if ((bigp = bigalloc_check_and_lock(ptr)) != NULL) {
138482949828SMatthew Dillon bigalloc_t big;
138582949828SMatthew Dillon size_t bigbytes;
138682949828SMatthew Dillon
138782949828SMatthew Dillon while ((big = *bigp) != NULL) {
138882949828SMatthew Dillon if (big->base == ptr) {
138982949828SMatthew Dillon size = (size + PAGE_MASK) & ~(size_t)PAGE_MASK;
139082949828SMatthew Dillon bigbytes = big->bytes;
139197f56c04SMatthew Dillon
139297f56c04SMatthew Dillon /*
139397f56c04SMatthew Dillon * If it already fits determine if it makes
139497f56c04SMatthew Dillon * sense to shrink/reallocate. Try to optimize
139597f56c04SMatthew Dillon * programs which stupidly make incremental
139697f56c04SMatthew Dillon * reallocations larger or smaller by scaling
139797f56c04SMatthew Dillon * the allocation. Also deal with potential
139897f56c04SMatthew Dillon * coloring.
139997f56c04SMatthew Dillon */
140007a8ffeaSMatthew Dillon if (size >= (bigbytes >> 1) &&
140107a8ffeaSMatthew Dillon size <= bigbytes) {
140207a8ffeaSMatthew Dillon if (big->active != size) {
140307a8ffeaSMatthew Dillon atomic_add_long(&excess_alloc,
140407a8ffeaSMatthew Dillon big->active -
140507a8ffeaSMatthew Dillon size);
140607a8ffeaSMatthew Dillon }
140707a8ffeaSMatthew Dillon big->active = size;
140882949828SMatthew Dillon bigalloc_unlock(ptr);
140982949828SMatthew Dillon return(ptr);
14100bb7d8c8SVenkatesh Srinivas }
141197f56c04SMatthew Dillon
141297f56c04SMatthew Dillon /*
141307a8ffeaSMatthew Dillon * For large reallocations, allocate more space
141497f56c04SMatthew Dillon * than we need to try to avoid excessive
141597f56c04SMatthew Dillon * reallocations later on.
141697f56c04SMatthew Dillon */
141707a8ffeaSMatthew Dillon chunking = size + (size >> 3);
141807a8ffeaSMatthew Dillon chunking = (chunking + PAGE_MASK) &
141997f56c04SMatthew Dillon ~(size_t)PAGE_MASK;
142007a8ffeaSMatthew Dillon
142107a8ffeaSMatthew Dillon /*
142207a8ffeaSMatthew Dillon * Try to allocate adjacently in case the
142307a8ffeaSMatthew Dillon * program is idiotically realloc()ing a
142407a8ffeaSMatthew Dillon * huge memory block just slightly bigger.
142507a8ffeaSMatthew Dillon * (llvm's llc tends to do this a lot).
142607a8ffeaSMatthew Dillon *
142707a8ffeaSMatthew Dillon * (MAP_TRYFIXED forces mmap to fail if there
142807a8ffeaSMatthew Dillon * is already something at the address).
142907a8ffeaSMatthew Dillon */
143007a8ffeaSMatthew Dillon if (chunking > bigbytes) {
143107a8ffeaSMatthew Dillon char *addr;
1432e00a0047Szrj int errno_save = errno;
143307a8ffeaSMatthew Dillon
143407a8ffeaSMatthew Dillon addr = mmap((char *)ptr + bigbytes,
143507a8ffeaSMatthew Dillon chunking - bigbytes,
143607a8ffeaSMatthew Dillon PROT_READ|PROT_WRITE,
143707a8ffeaSMatthew Dillon MAP_PRIVATE|MAP_ANON|
143807a8ffeaSMatthew Dillon MAP_TRYFIXED,
143907a8ffeaSMatthew Dillon -1, 0);
1440e00a0047Szrj errno = errno_save;
144107a8ffeaSMatthew Dillon if (addr == (char *)ptr + bigbytes) {
144207a8ffeaSMatthew Dillon atomic_add_long(&excess_alloc,
144307a8ffeaSMatthew Dillon big->active -
144407a8ffeaSMatthew Dillon big->bytes +
144507a8ffeaSMatthew Dillon chunking -
144607a8ffeaSMatthew Dillon size);
144707a8ffeaSMatthew Dillon big->bytes = chunking;
144807a8ffeaSMatthew Dillon big->active = size;
144907a8ffeaSMatthew Dillon bigalloc_unlock(ptr);
145007a8ffeaSMatthew Dillon
145107a8ffeaSMatthew Dillon return(ptr);
145207a8ffeaSMatthew Dillon }
1453721505deSMatthew Dillon MASSERT_WTHUNLK(
1454721505deSMatthew Dillon (void *)addr == MAP_FAILED,
1455721505deSMatthew Dillon bigalloc_unlock(ptr));
145697f56c04SMatthew Dillon }
145797f56c04SMatthew Dillon
145807a8ffeaSMatthew Dillon /*
145907a8ffeaSMatthew Dillon * Failed, unlink big and allocate fresh.
146007a8ffeaSMatthew Dillon * (note that we have to leave (big) intact
146107a8ffeaSMatthew Dillon * in case the slaballoc fails).
146207a8ffeaSMatthew Dillon */
14630bb7d8c8SVenkatesh Srinivas *bigp = big->next;
14640bb7d8c8SVenkatesh Srinivas bigalloc_unlock(ptr);
14650bb7d8c8SVenkatesh Srinivas if ((nptr = _slaballoc(size, 0)) == NULL) {
14660bb7d8c8SVenkatesh Srinivas /* Relink block */
14670bb7d8c8SVenkatesh Srinivas bigp = bigalloc_lock(ptr);
14680bb7d8c8SVenkatesh Srinivas big->next = *bigp;
14690bb7d8c8SVenkatesh Srinivas *bigp = big;
14700bb7d8c8SVenkatesh Srinivas bigalloc_unlock(ptr);
147182949828SMatthew Dillon return(NULL);
14720bb7d8c8SVenkatesh Srinivas }
147382949828SMatthew Dillon if (size > bigbytes)
147482949828SMatthew Dillon size = bigbytes;
147582949828SMatthew Dillon bcopy(ptr, nptr, size);
147607a8ffeaSMatthew Dillon atomic_add_long(&excess_alloc, big->active -
147707a8ffeaSMatthew Dillon big->bytes);
14780bb7d8c8SVenkatesh Srinivas _slabfree(ptr, FASTSLABREALLOC, &big);
147907a8ffeaSMatthew Dillon
148082949828SMatthew Dillon return(nptr);
148182949828SMatthew Dillon }
148282949828SMatthew Dillon bigp = &big->next;
148382949828SMatthew Dillon }
148482949828SMatthew Dillon bigalloc_unlock(ptr);
148507a8ffeaSMatthew Dillon handle_excess_big();
148682949828SMatthew Dillon }
148782949828SMatthew Dillon
148882949828SMatthew Dillon /*
148982949828SMatthew Dillon * Get the original allocation's zone. If the new request winds
149082949828SMatthew Dillon * up using the same chunk size we do not have to do anything.
149182949828SMatthew Dillon *
149282949828SMatthew Dillon * NOTE: We don't have to lock the globaldata here, the fields we
149382949828SMatthew Dillon * access here will not change at least as long as we have control
149482949828SMatthew Dillon * over the allocation.
149582949828SMatthew Dillon */
149682949828SMatthew Dillon z = (slzone_t)((uintptr_t)ptr & ~(uintptr_t)ZoneMask);
149782949828SMatthew Dillon MASSERT(z->z_Magic == ZALLOC_SLAB_MAGIC);
149882949828SMatthew Dillon
149982949828SMatthew Dillon /*
150082949828SMatthew Dillon * Use zoneindex() to chunk-align the new size, as long as the
150182949828SMatthew Dillon * new size is not too large.
150282949828SMatthew Dillon */
150382949828SMatthew Dillon if (size < ZoneLimit) {
150482949828SMatthew Dillon zoneindex(&size, &chunking);
1505ebe0d361SMatthew Dillon if (z->z_ChunkSize == size) {
150682949828SMatthew Dillon return(ptr);
150782949828SMatthew Dillon }
1508ebe0d361SMatthew Dillon }
150982949828SMatthew Dillon
151082949828SMatthew Dillon /*
151182949828SMatthew Dillon * Allocate memory for the new request size and copy as appropriate.
151282949828SMatthew Dillon */
151382949828SMatthew Dillon if ((nptr = _slaballoc(size, 0)) != NULL) {
151482949828SMatthew Dillon if (size > z->z_ChunkSize)
151582949828SMatthew Dillon size = z->z_ChunkSize;
151682949828SMatthew Dillon bcopy(ptr, nptr, size);
15170bb7d8c8SVenkatesh Srinivas _slabfree(ptr, 0, NULL);
151882949828SMatthew Dillon }
151982949828SMatthew Dillon
152082949828SMatthew Dillon return(nptr);
152182949828SMatthew Dillon }
152282949828SMatthew Dillon
152382949828SMatthew Dillon /*
1524d780b39fSAntonio Huete Jimenez * Returns the usable area of an allocated pointer
1525d780b39fSAntonio Huete Jimenez */
1526d780b39fSAntonio Huete Jimenez static size_t
_slabusablesize(const void * ptr)1527d780b39fSAntonio Huete Jimenez _slabusablesize(const void *ptr)
1528d780b39fSAntonio Huete Jimenez {
1529d780b39fSAntonio Huete Jimenez size_t size;
1530d780b39fSAntonio Huete Jimenez bigalloc_t *bigp;
1531d780b39fSAntonio Huete Jimenez slzone_t z;
1532d780b39fSAntonio Huete Jimenez
1533d780b39fSAntonio Huete Jimenez if (ptr == NULL)
1534d780b39fSAntonio Huete Jimenez return 0;
1535d780b39fSAntonio Huete Jimenez
1536d780b39fSAntonio Huete Jimenez /*
1537d780b39fSAntonio Huete Jimenez * Handle oversized allocations.
1538d780b39fSAntonio Huete Jimenez */
1539d780b39fSAntonio Huete Jimenez if ((bigp = bigalloc_check_and_lock(ptr)) != NULL) {
1540d780b39fSAntonio Huete Jimenez bigalloc_t big;
1541d780b39fSAntonio Huete Jimenez
1542d780b39fSAntonio Huete Jimenez while ((big = *bigp) != NULL) {
1543d780b39fSAntonio Huete Jimenez const char *base = big->base;
1544d780b39fSAntonio Huete Jimenez
1545d780b39fSAntonio Huete Jimenez if ((const char *)ptr >= base &&
1546d780b39fSAntonio Huete Jimenez (const char *)ptr < base + big->bytes)
1547d780b39fSAntonio Huete Jimenez {
1548d780b39fSAntonio Huete Jimenez size = base + big->bytes - (const char *)ptr;
1549d780b39fSAntonio Huete Jimenez
1550d753779fSMatthew Dillon bigalloc_unlock(ptr);
1551d753779fSMatthew Dillon
1552d780b39fSAntonio Huete Jimenez return size;
1553d780b39fSAntonio Huete Jimenez }
1554d780b39fSAntonio Huete Jimenez bigp = &big->next;
1555d780b39fSAntonio Huete Jimenez }
1556d780b39fSAntonio Huete Jimenez bigalloc_unlock(ptr);
1557d780b39fSAntonio Huete Jimenez handle_excess_big();
1558d780b39fSAntonio Huete Jimenez }
1559d780b39fSAntonio Huete Jimenez
1560d780b39fSAntonio Huete Jimenez /*
1561d780b39fSAntonio Huete Jimenez * Get the original allocation's zone. If the new request winds
1562d780b39fSAntonio Huete Jimenez * up using the same chunk size we do not have to do anything.
1563d780b39fSAntonio Huete Jimenez *
1564d780b39fSAntonio Huete Jimenez * NOTE: We don't have to lock the globaldata here, the fields we
1565d780b39fSAntonio Huete Jimenez * access here will not change at least as long as we have control
1566d780b39fSAntonio Huete Jimenez * over the allocation.
1567d780b39fSAntonio Huete Jimenez */
1568d780b39fSAntonio Huete Jimenez z = (slzone_t)((uintptr_t)ptr & ~(uintptr_t)ZoneMask);
1569d780b39fSAntonio Huete Jimenez MASSERT(z->z_Magic == ZALLOC_SLAB_MAGIC);
1570d780b39fSAntonio Huete Jimenez
1571d780b39fSAntonio Huete Jimenez size = z->z_ChunkSize -
1572d780b39fSAntonio Huete Jimenez ((const char *)ptr - (const char *)z->z_BasePtr) %
1573d780b39fSAntonio Huete Jimenez z->z_ChunkSize;
1574d780b39fSAntonio Huete Jimenez return size;
1575d780b39fSAntonio Huete Jimenez }
1576d780b39fSAntonio Huete Jimenez
1577d780b39fSAntonio Huete Jimenez /*
157882949828SMatthew Dillon * free (SLAB ALLOCATOR)
157982949828SMatthew Dillon *
158082949828SMatthew Dillon * Free a memory block previously allocated by malloc. Note that we do not
158182949828SMatthew Dillon * attempt to uplodate ks_loosememuse as MP races could prevent us from
158282949828SMatthew Dillon * checking memory limits in malloc.
158382949828SMatthew Dillon *
15840bb7d8c8SVenkatesh Srinivas * flags:
15854cd64cfeSMatthew Dillon * FASTSLABREALLOC Fast call from realloc, *rbigp already
15864cd64cfeSMatthew Dillon * unlinked.
15874cd64cfeSMatthew Dillon *
158882949828SMatthew Dillon * MPSAFE
158982949828SMatthew Dillon */
159082949828SMatthew Dillon static void
_slabfree(void * ptr,int flags,bigalloc_t * rbigp)15910bb7d8c8SVenkatesh Srinivas _slabfree(void *ptr, int flags, bigalloc_t *rbigp)
159282949828SMatthew Dillon {
159382949828SMatthew Dillon slzone_t z;
159482949828SMatthew Dillon slchunk_t chunk;
159582949828SMatthew Dillon bigalloc_t big;
159682949828SMatthew Dillon bigalloc_t *bigp;
159782949828SMatthew Dillon slglobaldata_t slgd;
159882949828SMatthew Dillon size_t size;
15990bb7d8c8SVenkatesh Srinivas int zi;
160082949828SMatthew Dillon int pgno;
160182949828SMatthew Dillon
16020bb7d8c8SVenkatesh Srinivas /* Fast realloc path for big allocations */
16030bb7d8c8SVenkatesh Srinivas if (flags & FASTSLABREALLOC) {
16040bb7d8c8SVenkatesh Srinivas big = *rbigp;
16050bb7d8c8SVenkatesh Srinivas goto fastslabrealloc;
16060bb7d8c8SVenkatesh Srinivas }
16070bb7d8c8SVenkatesh Srinivas
160882949828SMatthew Dillon /*
160982949828SMatthew Dillon * Handle NULL frees and special 0-byte allocations
161082949828SMatthew Dillon */
161182949828SMatthew Dillon if (ptr == NULL)
161282949828SMatthew Dillon return;
161382949828SMatthew Dillon
161482949828SMatthew Dillon /*
161582949828SMatthew Dillon * Handle oversized allocations.
161682949828SMatthew Dillon */
161782949828SMatthew Dillon if ((bigp = bigalloc_check_and_lock(ptr)) != NULL) {
161882949828SMatthew Dillon while ((big = *bigp) != NULL) {
161982949828SMatthew Dillon if (big->base == ptr) {
162082949828SMatthew Dillon *bigp = big->next;
162107a8ffeaSMatthew Dillon atomic_add_long(&excess_alloc, big->active -
162207a8ffeaSMatthew Dillon big->bytes);
162382949828SMatthew Dillon bigalloc_unlock(ptr);
162407a8ffeaSMatthew Dillon
162507a8ffeaSMatthew Dillon /*
162607a8ffeaSMatthew Dillon * Try to stash the block we are freeing,
162707a8ffeaSMatthew Dillon * potentially receiving another block in
162807a8ffeaSMatthew Dillon * return which must be freed.
162907a8ffeaSMatthew Dillon */
16300bb7d8c8SVenkatesh Srinivas fastslabrealloc:
163107a8ffeaSMatthew Dillon if (big->bytes <= BIGCACHE_LIMIT) {
163207a8ffeaSMatthew Dillon big = bigcache_find_free(big);
163307a8ffeaSMatthew Dillon if (big == NULL)
163407a8ffeaSMatthew Dillon return;
163507a8ffeaSMatthew Dillon }
163607a8ffeaSMatthew Dillon ptr = big->base; /* reload */
163782949828SMatthew Dillon size = big->bytes;
16380bb7d8c8SVenkatesh Srinivas _slabfree(big, 0, NULL);
163982949828SMatthew Dillon _vmem_free(ptr, size);
164082949828SMatthew Dillon return;
164182949828SMatthew Dillon }
164282949828SMatthew Dillon bigp = &big->next;
164382949828SMatthew Dillon }
164482949828SMatthew Dillon bigalloc_unlock(ptr);
164507a8ffeaSMatthew Dillon handle_excess_big();
164682949828SMatthew Dillon }
164782949828SMatthew Dillon
164882949828SMatthew Dillon /*
164982949828SMatthew Dillon * Zone case. Figure out the zone based on the fact that it is
165082949828SMatthew Dillon * ZoneSize aligned.
165182949828SMatthew Dillon */
165282949828SMatthew Dillon z = (slzone_t)((uintptr_t)ptr & ~(uintptr_t)ZoneMask);
165382949828SMatthew Dillon MASSERT(z->z_Magic == ZALLOC_SLAB_MAGIC);
165482949828SMatthew Dillon
16550bb7d8c8SVenkatesh Srinivas size = z->z_ChunkSize;
16560bb7d8c8SVenkatesh Srinivas zi = z->z_ZoneIndex;
16570bb7d8c8SVenkatesh Srinivas
16580bb7d8c8SVenkatesh Srinivas if (g_malloc_flags & SAFLAG_ZERO)
16590bb7d8c8SVenkatesh Srinivas bzero(ptr, size);
16600bb7d8c8SVenkatesh Srinivas
16616c4de62cSMatthew Dillon if (mtmagazine_free(zi, ptr) == 0)
16620bb7d8c8SVenkatesh Srinivas return;
16630bb7d8c8SVenkatesh Srinivas
166482949828SMatthew Dillon pgno = ((char *)ptr - (char *)z) >> PAGE_SHIFT;
166582949828SMatthew Dillon chunk = ptr;
166682949828SMatthew Dillon
166782949828SMatthew Dillon /*
166882949828SMatthew Dillon * Add this free non-zero'd chunk to a linked list for reuse, adjust
166982949828SMatthew Dillon * z_FirstFreePg.
167082949828SMatthew Dillon */
16718b07b5e8SMatthew Dillon slgd = &SLGlobalData;
16728b07b5e8SMatthew Dillon slgd_lock(slgd);
16738b07b5e8SMatthew Dillon
167482949828SMatthew Dillon chunk->c_Next = z->z_PageAry[pgno];
167582949828SMatthew Dillon z->z_PageAry[pgno] = chunk;
167682949828SMatthew Dillon if (z->z_FirstFreePg > pgno)
167782949828SMatthew Dillon z->z_FirstFreePg = pgno;
167882949828SMatthew Dillon
167982949828SMatthew Dillon /*
168082949828SMatthew Dillon * Bump the number of free chunks. If it becomes non-zero the zone
168182949828SMatthew Dillon * must be added back onto the appropriate list.
168282949828SMatthew Dillon */
168382949828SMatthew Dillon if (z->z_NFree++ == 0) {
168482949828SMatthew Dillon z->z_Next = slgd->ZoneAry[z->z_ZoneIndex];
168582949828SMatthew Dillon slgd->ZoneAry[z->z_ZoneIndex] = z;
168682949828SMatthew Dillon }
168782949828SMatthew Dillon
168882949828SMatthew Dillon /*
16898b07b5e8SMatthew Dillon * If the zone becomes totally free we get rid of it.
169082949828SMatthew Dillon */
169182949828SMatthew Dillon if (z->z_NFree == z->z_NMax) {
169282949828SMatthew Dillon slzone_t *pz;
169382949828SMatthew Dillon
169482949828SMatthew Dillon pz = &slgd->ZoneAry[z->z_ZoneIndex];
169582949828SMatthew Dillon while (z != *pz)
169682949828SMatthew Dillon pz = &(*pz)->z_Next;
169782949828SMatthew Dillon *pz = z->z_Next;
169882949828SMatthew Dillon z->z_Magic = -1;
16990bb7d8c8SVenkatesh Srinivas z->z_Next = NULL;
170082949828SMatthew Dillon slgd_unlock(slgd);
17018b07b5e8SMatthew Dillon zone_free(z);
17028b07b5e8SMatthew Dillon } else {
17038b07b5e8SMatthew Dillon slgd_unlock(slgd);
17048b07b5e8SMatthew Dillon }
170582949828SMatthew Dillon }
170682949828SMatthew Dillon
17074cd64cfeSMatthew Dillon /*
1708369c9b6cSMatthew Dillon * Allocate and return a magazine. Return NULL if no magazines are
1709369c9b6cSMatthew Dillon * available.
17104cd64cfeSMatthew Dillon */
17110bb7d8c8SVenkatesh Srinivas static __inline void *
magazine_alloc(struct magazine * mp)1712369c9b6cSMatthew Dillon magazine_alloc(struct magazine *mp)
17130bb7d8c8SVenkatesh Srinivas {
17144cd64cfeSMatthew Dillon void *obj;
17150bb7d8c8SVenkatesh Srinivas
1716369c9b6cSMatthew Dillon if (mp && MAGAZINE_NOTEMPTY(mp)) {
17170bb7d8c8SVenkatesh Srinivas obj = mp->objects[--mp->rounds];
1718369c9b6cSMatthew Dillon } else {
1719369c9b6cSMatthew Dillon obj = NULL;
1720369c9b6cSMatthew Dillon }
17214cd64cfeSMatthew Dillon return (obj);
17220bb7d8c8SVenkatesh Srinivas }
17230bb7d8c8SVenkatesh Srinivas
17240bb7d8c8SVenkatesh Srinivas static __inline int
magazine_free(struct magazine * mp,void * p)17250bb7d8c8SVenkatesh Srinivas magazine_free(struct magazine *mp, void *p)
17260bb7d8c8SVenkatesh Srinivas {
17270bb7d8c8SVenkatesh Srinivas if (mp != NULL && MAGAZINE_NOTFULL(mp)) {
17280bb7d8c8SVenkatesh Srinivas mp->objects[mp->rounds++] = p;
17290bb7d8c8SVenkatesh Srinivas return 0;
17300bb7d8c8SVenkatesh Srinivas }
17310bb7d8c8SVenkatesh Srinivas
17320bb7d8c8SVenkatesh Srinivas return -1;
17330bb7d8c8SVenkatesh Srinivas }
17340bb7d8c8SVenkatesh Srinivas
17350bb7d8c8SVenkatesh Srinivas static void *
mtmagazine_alloc(int zi,int flags)17368b07b5e8SMatthew Dillon mtmagazine_alloc(int zi, int flags)
17370bb7d8c8SVenkatesh Srinivas {
17380bb7d8c8SVenkatesh Srinivas thr_mags *tp;
17390bb7d8c8SVenkatesh Srinivas struct magazine *mp, *emptymag;
17400bb7d8c8SVenkatesh Srinivas magazine_depot *d;
1741e58e48b4SMatthew Dillon void *obj;
17420bb7d8c8SVenkatesh Srinivas
17436c4de62cSMatthew Dillon /*
17446c4de62cSMatthew Dillon * Do not try to access per-thread magazines while the mtmagazine
17456c4de62cSMatthew Dillon * is being initialized or destroyed.
17466c4de62cSMatthew Dillon */
17470bb7d8c8SVenkatesh Srinivas tp = &thread_mags;
17486c4de62cSMatthew Dillon if (tp->init < 0)
17496c4de62cSMatthew Dillon return(NULL);
17500bb7d8c8SVenkatesh Srinivas
17516c4de62cSMatthew Dillon /*
17526c4de62cSMatthew Dillon * Primary per-thread allocation loop
17536c4de62cSMatthew Dillon */
17547b033ca7SVenkatesh Srinivas for (;;) {
1755e58e48b4SMatthew Dillon /*
17568b07b5e8SMatthew Dillon * Make sure we have a magazine available for use.
17578b07b5e8SMatthew Dillon */
17588b07b5e8SMatthew Dillon if (tp->newmag == NULL && (flags & SAFLAG_MAGS) == 0) {
17598b07b5e8SMatthew Dillon mp = _slaballoc(sizeof(struct magazine),
17608b07b5e8SMatthew Dillon SAFLAG_ZERO | SAFLAG_MAGS);
17618b07b5e8SMatthew Dillon if (mp == NULL) {
17628b07b5e8SMatthew Dillon obj = NULL;
17638b07b5e8SMatthew Dillon break;
17648b07b5e8SMatthew Dillon }
17658b07b5e8SMatthew Dillon if (tp->newmag) {
17668b07b5e8SMatthew Dillon _slabfree(mp, 0, NULL);
17678b07b5e8SMatthew Dillon } else {
17688b07b5e8SMatthew Dillon tp->newmag = mp;
17698b07b5e8SMatthew Dillon }
17708b07b5e8SMatthew Dillon }
17718b07b5e8SMatthew Dillon
17728b07b5e8SMatthew Dillon /*
1773e58e48b4SMatthew Dillon * If the loaded magazine has rounds, allocate and return
1774e58e48b4SMatthew Dillon */
1775e58e48b4SMatthew Dillon mp = tp->mags[zi].loaded;
1776369c9b6cSMatthew Dillon obj = magazine_alloc(mp);
1777e58e48b4SMatthew Dillon if (obj)
17780bb7d8c8SVenkatesh Srinivas break;
17790bb7d8c8SVenkatesh Srinivas
1780e58e48b4SMatthew Dillon /*
17818b07b5e8SMatthew Dillon * The prev magazine can only be completely empty or completely
17828b07b5e8SMatthew Dillon * full. If it is full, swap it with the loaded magazine
17838b07b5e8SMatthew Dillon * and retry.
1784e58e48b4SMatthew Dillon */
1785e58e48b4SMatthew Dillon mp = tp->mags[zi].prev;
1786e58e48b4SMatthew Dillon if (mp && MAGAZINE_FULL(mp)) {
1787e58e48b4SMatthew Dillon MASSERT(mp->rounds != 0);
1788443d9a50SMatthew Dillon swap_mags(&tp->mags[zi]); /* prev now empty */
17890bb7d8c8SVenkatesh Srinivas continue;
17900bb7d8c8SVenkatesh Srinivas }
17910bb7d8c8SVenkatesh Srinivas
17924cd64cfeSMatthew Dillon /*
17938b07b5e8SMatthew Dillon * If the depot has no loaded magazines ensure that tp->loaded
17948b07b5e8SMatthew Dillon * is not NULL and return NULL. This will allow _slaballoc()
17958b07b5e8SMatthew Dillon * to cache referals to SLGlobalData in a magazine.
17964cd64cfeSMatthew Dillon */
17970bb7d8c8SVenkatesh Srinivas d = &depots[zi];
17988b07b5e8SMatthew Dillon if (SLIST_EMPTY(&d->full)) { /* UNLOCKED TEST IS SAFE */
17998b07b5e8SMatthew Dillon mp = tp->mags[zi].loaded;
18008b07b5e8SMatthew Dillon if (mp == NULL && tp->newmag) {
18018b07b5e8SMatthew Dillon mp = tp->newmag;
18028b07b5e8SMatthew Dillon tp->newmag = NULL;
1803369c9b6cSMatthew Dillon mp->capacity = zonecapacity(zi);
18048b07b5e8SMatthew Dillon mp->rounds = 0;
18058b07b5e8SMatthew Dillon mp->flags = 0;
1806e58e48b4SMatthew Dillon tp->mags[zi].loaded = mp;
18078b07b5e8SMatthew Dillon }
18088b07b5e8SMatthew Dillon break;
18098b07b5e8SMatthew Dillon }
18108b07b5e8SMatthew Dillon
18118b07b5e8SMatthew Dillon /*
18128b07b5e8SMatthew Dillon * Cycle: depot(loaded) -> loaded -> prev -> depot(empty)
18138b07b5e8SMatthew Dillon *
18148b07b5e8SMatthew Dillon * If we race and the depot has no full magazines, retry.
18158b07b5e8SMatthew Dillon */
18168b07b5e8SMatthew Dillon depot_lock(d);
18178b07b5e8SMatthew Dillon mp = SLIST_FIRST(&d->full);
1818e58e48b4SMatthew Dillon if (mp) {
18190bb7d8c8SVenkatesh Srinivas SLIST_REMOVE_HEAD(&d->full, nextmagazine);
18208b07b5e8SMatthew Dillon emptymag = tp->mags[zi].prev;
18218b07b5e8SMatthew Dillon if (emptymag) {
18228b07b5e8SMatthew Dillon SLIST_INSERT_HEAD(&d->empty, emptymag,
18238b07b5e8SMatthew Dillon nextmagazine);
18248b07b5e8SMatthew Dillon }
18258b07b5e8SMatthew Dillon tp->mags[zi].prev = tp->mags[zi].loaded;
18268b07b5e8SMatthew Dillon tp->mags[zi].loaded = mp;
1827721505deSMatthew Dillon MASSERT(MAGAZINE_NOTEMPTY(mp));
18280bb7d8c8SVenkatesh Srinivas }
18294cd64cfeSMatthew Dillon depot_unlock(d);
18308b07b5e8SMatthew Dillon continue;
18317b033ca7SVenkatesh Srinivas }
18320bb7d8c8SVenkatesh Srinivas
18330bb7d8c8SVenkatesh Srinivas return (obj);
18340bb7d8c8SVenkatesh Srinivas }
18350bb7d8c8SVenkatesh Srinivas
18360bb7d8c8SVenkatesh Srinivas static int
mtmagazine_free(int zi,void * ptr)18370bb7d8c8SVenkatesh Srinivas mtmagazine_free(int zi, void *ptr)
18380bb7d8c8SVenkatesh Srinivas {
18390bb7d8c8SVenkatesh Srinivas thr_mags *tp;
1840e58e48b4SMatthew Dillon struct magazine *mp, *loadedmag;
18410bb7d8c8SVenkatesh Srinivas magazine_depot *d;
18420bb7d8c8SVenkatesh Srinivas int rc = -1;
18430bb7d8c8SVenkatesh Srinivas
18446c4de62cSMatthew Dillon /*
18456c4de62cSMatthew Dillon * Do not try to access per-thread magazines while the mtmagazine
18466c4de62cSMatthew Dillon * is being initialized or destroyed.
18476c4de62cSMatthew Dillon */
18480bb7d8c8SVenkatesh Srinivas tp = &thread_mags;
18496c4de62cSMatthew Dillon if (tp->init < 0)
18506c4de62cSMatthew Dillon return(-1);
18510bb7d8c8SVenkatesh Srinivas
18526c4de62cSMatthew Dillon /*
18536c4de62cSMatthew Dillon * Primary per-thread freeing loop
18546c4de62cSMatthew Dillon */
18557b033ca7SVenkatesh Srinivas for (;;) {
1856e58e48b4SMatthew Dillon /*
1857443d9a50SMatthew Dillon * Make sure a new magazine is available in case we have
1858443d9a50SMatthew Dillon * to use it. Staging the newmag allows us to avoid
1859443d9a50SMatthew Dillon * some locking/reentrancy complexity.
1860443d9a50SMatthew Dillon *
1861443d9a50SMatthew Dillon * Temporarily disable the per-thread caches for this
1862443d9a50SMatthew Dillon * allocation to avoid reentrancy and/or to avoid a
1863443d9a50SMatthew Dillon * stack overflow if the [zi] happens to be the same that
1864443d9a50SMatthew Dillon * would be used to allocate the new magazine.
1865064bf225SMatthew Dillon *
1866064bf225SMatthew Dillon * WARNING! Calling _slaballoc() can indirectly modify
1867064bf225SMatthew Dillon * tp->newmag.
1868443d9a50SMatthew Dillon */
1869443d9a50SMatthew Dillon if (tp->newmag == NULL) {
1870064bf225SMatthew Dillon mp = _slaballoc(sizeof(struct magazine),
1871064bf225SMatthew Dillon SAFLAG_ZERO | SAFLAG_MAGS);
1872064bf225SMatthew Dillon if (tp->newmag && mp)
1873064bf225SMatthew Dillon _slabfree(mp, 0, NULL);
1874064bf225SMatthew Dillon else
1875064bf225SMatthew Dillon tp->newmag = mp;
1876443d9a50SMatthew Dillon if (tp->newmag == NULL) {
1877443d9a50SMatthew Dillon rc = -1;
1878443d9a50SMatthew Dillon break;
1879443d9a50SMatthew Dillon }
1880443d9a50SMatthew Dillon }
1881443d9a50SMatthew Dillon
1882443d9a50SMatthew Dillon /*
1883e58e48b4SMatthew Dillon * If the loaded magazine has space, free directly to it
1884e58e48b4SMatthew Dillon */
1885e58e48b4SMatthew Dillon rc = magazine_free(tp->mags[zi].loaded, ptr);
1886e58e48b4SMatthew Dillon if (rc == 0)
18870bb7d8c8SVenkatesh Srinivas break;
18880bb7d8c8SVenkatesh Srinivas
1889e58e48b4SMatthew Dillon /*
18908b07b5e8SMatthew Dillon * The prev magazine can only be completely empty or completely
18918b07b5e8SMatthew Dillon * full. If it is empty, swap it with the loaded magazine
18928b07b5e8SMatthew Dillon * and retry.
1893e58e48b4SMatthew Dillon */
1894e58e48b4SMatthew Dillon mp = tp->mags[zi].prev;
1895e58e48b4SMatthew Dillon if (mp && MAGAZINE_EMPTY(mp)) {
1896e58e48b4SMatthew Dillon MASSERT(mp->rounds == 0);
1897443d9a50SMatthew Dillon swap_mags(&tp->mags[zi]); /* prev now full */
18980bb7d8c8SVenkatesh Srinivas continue;
18990bb7d8c8SVenkatesh Srinivas }
19000bb7d8c8SVenkatesh Srinivas
1901e58e48b4SMatthew Dillon /*
1902e58e48b4SMatthew Dillon * Try to get an empty magazine from the depot. Cycle
1903e58e48b4SMatthew Dillon * through depot(empty)->loaded->prev->depot(full).
1904e58e48b4SMatthew Dillon * Retry if an empty magazine was available from the depot.
19054cd64cfeSMatthew Dillon */
1906e58e48b4SMatthew Dillon d = &depots[zi];
19074cd64cfeSMatthew Dillon depot_lock(d);
1908e58e48b4SMatthew Dillon
1909e58e48b4SMatthew Dillon if ((loadedmag = tp->mags[zi].prev) != NULL)
1910e58e48b4SMatthew Dillon SLIST_INSERT_HEAD(&d->full, loadedmag, nextmagazine);
1911e58e48b4SMatthew Dillon tp->mags[zi].prev = tp->mags[zi].loaded;
1912e58e48b4SMatthew Dillon mp = SLIST_FIRST(&d->empty);
1913e58e48b4SMatthew Dillon if (mp) {
1914e58e48b4SMatthew Dillon tp->mags[zi].loaded = mp;
1915e58e48b4SMatthew Dillon SLIST_REMOVE_HEAD(&d->empty, nextmagazine);
1916721505deSMatthew Dillon depot_unlock(d);
1917e58e48b4SMatthew Dillon MASSERT(MAGAZINE_NOTFULL(mp));
1918e58e48b4SMatthew Dillon } else {
1919e58e48b4SMatthew Dillon mp = tp->newmag;
1920e58e48b4SMatthew Dillon tp->newmag = NULL;
1921369c9b6cSMatthew Dillon mp->capacity = zonecapacity(zi);
1922e58e48b4SMatthew Dillon mp->rounds = 0;
1923e58e48b4SMatthew Dillon mp->flags = 0;
1924e58e48b4SMatthew Dillon tp->mags[zi].loaded = mp;
1925e58e48b4SMatthew Dillon depot_unlock(d);
19267b033ca7SVenkatesh Srinivas }
1927721505deSMatthew Dillon }
19280bb7d8c8SVenkatesh Srinivas
19290bb7d8c8SVenkatesh Srinivas return rc;
19300bb7d8c8SVenkatesh Srinivas }
19310bb7d8c8SVenkatesh Srinivas
19320bb7d8c8SVenkatesh Srinivas static void
mtmagazine_init(void)19336c4de62cSMatthew Dillon mtmagazine_init(void)
19346c4de62cSMatthew Dillon {
1935*17183580SMatthew Dillon /* ignore error from stub if not threaded */
1936*17183580SMatthew Dillon _pthread_key_create(&thread_mags_key, mtmagazine_destructor);
19370bb7d8c8SVenkatesh Srinivas }
19380bb7d8c8SVenkatesh Srinivas
19396c4de62cSMatthew Dillon /*
19406c4de62cSMatthew Dillon * This function is only used by the thread exit destructor
19416c4de62cSMatthew Dillon */
19420bb7d8c8SVenkatesh Srinivas static void
mtmagazine_drain(struct magazine * mp)19430bb7d8c8SVenkatesh Srinivas mtmagazine_drain(struct magazine *mp)
19440bb7d8c8SVenkatesh Srinivas {
19450bb7d8c8SVenkatesh Srinivas void *obj;
19460bb7d8c8SVenkatesh Srinivas
19474989e1f1SMatthew Dillon nmalloc_sigblockall();
19480bb7d8c8SVenkatesh Srinivas while (MAGAZINE_NOTEMPTY(mp)) {
1949369c9b6cSMatthew Dillon obj = magazine_alloc(mp);
19506c4de62cSMatthew Dillon _slabfree(obj, 0, NULL);
19510bb7d8c8SVenkatesh Srinivas }
19524989e1f1SMatthew Dillon nmalloc_sigunblockall();
19530bb7d8c8SVenkatesh Srinivas }
19540bb7d8c8SVenkatesh Srinivas
19550bb7d8c8SVenkatesh Srinivas /*
19560bb7d8c8SVenkatesh Srinivas * mtmagazine_destructor()
19570bb7d8c8SVenkatesh Srinivas *
19580bb7d8c8SVenkatesh Srinivas * When a thread exits, we reclaim all its resources; all its magazines are
19590bb7d8c8SVenkatesh Srinivas * drained and the structures are freed.
19606c4de62cSMatthew Dillon *
19616c4de62cSMatthew Dillon * WARNING! The destructor can be called multiple times if the larger user
19626c4de62cSMatthew Dillon * program has its own destructors which run after ours which
19636c4de62cSMatthew Dillon * allocate or free memory.
19640bb7d8c8SVenkatesh Srinivas */
19650bb7d8c8SVenkatesh Srinivas static void
mtmagazine_destructor(void * thrp)19660bb7d8c8SVenkatesh Srinivas mtmagazine_destructor(void *thrp)
19670bb7d8c8SVenkatesh Srinivas {
19680bb7d8c8SVenkatesh Srinivas thr_mags *tp = thrp;
19690bb7d8c8SVenkatesh Srinivas struct magazine *mp;
19700bb7d8c8SVenkatesh Srinivas int i;
19710bb7d8c8SVenkatesh Srinivas
19728b07b5e8SMatthew Dillon if (__isexiting)
19738b07b5e8SMatthew Dillon return;
19748b07b5e8SMatthew Dillon
19756c4de62cSMatthew Dillon /*
19766c4de62cSMatthew Dillon * Prevent further use of mtmagazines while we are destructing
19776c4de62cSMatthew Dillon * them, as well as for any destructors which are run after us
19786c4de62cSMatthew Dillon * prior to the thread actually being destroyed.
19796c4de62cSMatthew Dillon */
19806c4de62cSMatthew Dillon tp->init = -1;
19816c4de62cSMatthew Dillon
19824989e1f1SMatthew Dillon nmalloc_sigblockall();
19830bb7d8c8SVenkatesh Srinivas for (i = 0; i < NZONES; i++) {
19840bb7d8c8SVenkatesh Srinivas mp = tp->mags[i].loaded;
19856c4de62cSMatthew Dillon tp->mags[i].loaded = NULL;
1986e58e48b4SMatthew Dillon if (mp) {
1987e58e48b4SMatthew Dillon if (MAGAZINE_NOTEMPTY(mp))
19880bb7d8c8SVenkatesh Srinivas mtmagazine_drain(mp);
19896c4de62cSMatthew Dillon _slabfree(mp, 0, NULL);
1990e58e48b4SMatthew Dillon }
19910bb7d8c8SVenkatesh Srinivas
19920bb7d8c8SVenkatesh Srinivas mp = tp->mags[i].prev;
19936c4de62cSMatthew Dillon tp->mags[i].prev = NULL;
1994e58e48b4SMatthew Dillon if (mp) {
1995e58e48b4SMatthew Dillon if (MAGAZINE_NOTEMPTY(mp))
19960bb7d8c8SVenkatesh Srinivas mtmagazine_drain(mp);
19976c4de62cSMatthew Dillon _slabfree(mp, 0, NULL);
19980bb7d8c8SVenkatesh Srinivas }
19990bb7d8c8SVenkatesh Srinivas }
2000e58e48b4SMatthew Dillon if (tp->newmag) {
2001e58e48b4SMatthew Dillon mp = tp->newmag;
2002e58e48b4SMatthew Dillon tp->newmag = NULL;
2003e58e48b4SMatthew Dillon _slabfree(mp, 0, NULL);
2004e58e48b4SMatthew Dillon }
20054989e1f1SMatthew Dillon nmalloc_sigunblockall();
2006e58e48b4SMatthew Dillon }
2007e58e48b4SMatthew Dillon
20080bb7d8c8SVenkatesh Srinivas /*
20090bb7d8c8SVenkatesh Srinivas * zone_alloc()
20100bb7d8c8SVenkatesh Srinivas *
2011369c9b6cSMatthew Dillon * Attempt to allocate a zone from the zone magazine.
20120bb7d8c8SVenkatesh Srinivas */
20130bb7d8c8SVenkatesh Srinivas static slzone_t
zone_alloc(int flags)20140bb7d8c8SVenkatesh Srinivas zone_alloc(int flags)
20150bb7d8c8SVenkatesh Srinivas {
20160bb7d8c8SVenkatesh Srinivas slzone_t z;
20170bb7d8c8SVenkatesh Srinivas
20180bb7d8c8SVenkatesh Srinivas zone_magazine_lock();
20190bb7d8c8SVenkatesh Srinivas
2020369c9b6cSMatthew Dillon z = magazine_alloc(&zone_magazine);
2021369c9b6cSMatthew Dillon if (z == NULL) {
20220bb7d8c8SVenkatesh Srinivas zone_magazine_unlock();
2023369c9b6cSMatthew Dillon z = _vmem_alloc(ZoneSize, ZoneSize, flags);
20240bb7d8c8SVenkatesh Srinivas } else {
20250bb7d8c8SVenkatesh Srinivas z->z_Flags |= SLZF_UNOTZEROD;
20260bb7d8c8SVenkatesh Srinivas zone_magazine_unlock();
20270bb7d8c8SVenkatesh Srinivas }
20280bb7d8c8SVenkatesh Srinivas return z;
20290bb7d8c8SVenkatesh Srinivas }
20300bb7d8c8SVenkatesh Srinivas
20310bb7d8c8SVenkatesh Srinivas /*
20328b07b5e8SMatthew Dillon * Free a zone.
20330bb7d8c8SVenkatesh Srinivas */
20340bb7d8c8SVenkatesh Srinivas static void
zone_free(void * z)20350bb7d8c8SVenkatesh Srinivas zone_free(void *z)
20360bb7d8c8SVenkatesh Srinivas {
2037369c9b6cSMatthew Dillon void *excess[M_ZONE_HYSTERESIS];
2038369c9b6cSMatthew Dillon int i;
20390bb7d8c8SVenkatesh Srinivas
20400bb7d8c8SVenkatesh Srinivas zone_magazine_lock();
20410bb7d8c8SVenkatesh Srinivas
20420bb7d8c8SVenkatesh Srinivas bzero(z, sizeof(struct slzone));
20430bb7d8c8SVenkatesh Srinivas
20440bb7d8c8SVenkatesh Srinivas if (opt_madvise)
20450bb7d8c8SVenkatesh Srinivas madvise(z, ZoneSize, MADV_FREE);
20460bb7d8c8SVenkatesh Srinivas
20470bb7d8c8SVenkatesh Srinivas i = magazine_free(&zone_magazine, z);
20480bb7d8c8SVenkatesh Srinivas
20494cd64cfeSMatthew Dillon /*
20504cd64cfeSMatthew Dillon * If we failed to free, collect excess magazines; release the zone
20510bb7d8c8SVenkatesh Srinivas * magazine lock, and then free to the system via _vmem_free. Re-enable
20524cd64cfeSMatthew Dillon * BURST mode for the magazine.
20534cd64cfeSMatthew Dillon */
20540bb7d8c8SVenkatesh Srinivas if (i == -1) {
2055369c9b6cSMatthew Dillon for (i = 0; i < M_ZONE_HYSTERESIS; ++i) {
2056369c9b6cSMatthew Dillon excess[i] = magazine_alloc(&zone_magazine);
2057721505deSMatthew Dillon MASSERT_WTHUNLK(excess[i] != NULL,
2058721505deSMatthew Dillon zone_magazine_unlock());
20590bb7d8c8SVenkatesh Srinivas }
20600bb7d8c8SVenkatesh Srinivas zone_magazine_unlock();
20610bb7d8c8SVenkatesh Srinivas
2062369c9b6cSMatthew Dillon for (i = 0; i < M_ZONE_HYSTERESIS; ++i)
20630bb7d8c8SVenkatesh Srinivas _vmem_free(excess[i], ZoneSize);
20640bb7d8c8SVenkatesh Srinivas _vmem_free(z, ZoneSize);
20650bb7d8c8SVenkatesh Srinivas } else {
20660bb7d8c8SVenkatesh Srinivas zone_magazine_unlock();
20670bb7d8c8SVenkatesh Srinivas }
20680bb7d8c8SVenkatesh Srinivas }
20690bb7d8c8SVenkatesh Srinivas
207082949828SMatthew Dillon /*
207182949828SMatthew Dillon * _vmem_alloc()
207282949828SMatthew Dillon *
207382949828SMatthew Dillon * Directly map memory in PAGE_SIZE'd chunks with the specified
207482949828SMatthew Dillon * alignment.
207582949828SMatthew Dillon *
207682949828SMatthew Dillon * Alignment must be a multiple of PAGE_SIZE.
207711e45f67SMatthew Dillon *
207811e45f67SMatthew Dillon * Size must be >= alignment.
207982949828SMatthew Dillon */
208082949828SMatthew Dillon static void *
_vmem_alloc(size_t size,size_t align,int flags)208182949828SMatthew Dillon _vmem_alloc(size_t size, size_t align, int flags)
208282949828SMatthew Dillon {
2083721505deSMatthew Dillon static char *addr_hint;
2084721505deSMatthew Dillon static int reset_hint = 16;
208582949828SMatthew Dillon char *addr;
208682949828SMatthew Dillon char *save;
2087721505deSMatthew Dillon
2088721505deSMatthew Dillon if (--reset_hint <= 0) {
2089721505deSMatthew Dillon addr_hint = NULL;
2090721505deSMatthew Dillon reset_hint = 16;
2091721505deSMatthew Dillon }
209282949828SMatthew Dillon
209382949828SMatthew Dillon /*
209482949828SMatthew Dillon * Map anonymous private memory.
209582949828SMatthew Dillon */
2096721505deSMatthew Dillon save = mmap(addr_hint, size, PROT_READ|PROT_WRITE,
209782949828SMatthew Dillon MAP_PRIVATE|MAP_ANON, -1, 0);
2098721505deSMatthew Dillon if (save == MAP_FAILED)
2099721505deSMatthew Dillon goto worst_case;
2100721505deSMatthew Dillon if (((uintptr_t)save & (align - 1)) == 0)
2101721505deSMatthew Dillon return((void *)save);
210282949828SMatthew Dillon
2103721505deSMatthew Dillon addr_hint = (char *)(((size_t)save + (align - 1)) & ~(align - 1));
2104721505deSMatthew Dillon munmap(save, size);
210511e45f67SMatthew Dillon
2106721505deSMatthew Dillon save = mmap(addr_hint, size, PROT_READ|PROT_WRITE,
2107721505deSMatthew Dillon MAP_PRIVATE|MAP_ANON, -1, 0);
2108721505deSMatthew Dillon if (save == MAP_FAILED)
2109721505deSMatthew Dillon goto worst_case;
2110721505deSMatthew Dillon if (((size_t)save & (align - 1)) == 0)
2111721505deSMatthew Dillon return((void *)save);
2112721505deSMatthew Dillon munmap(save, size);
211311e45f67SMatthew Dillon
2114721505deSMatthew Dillon worst_case:
2115721505deSMatthew Dillon save = mmap(NULL, size + align, PROT_READ|PROT_WRITE,
2116721505deSMatthew Dillon MAP_PRIVATE|MAP_ANON, -1, 0);
2117721505deSMatthew Dillon if (save == MAP_FAILED)
2118721505deSMatthew Dillon return NULL;
2119721505deSMatthew Dillon
2120721505deSMatthew Dillon addr = (char *)(((size_t)save + (align - 1)) & ~(align - 1));
2121721505deSMatthew Dillon if (save != addr)
2122721505deSMatthew Dillon munmap(save, addr - save);
2123721505deSMatthew Dillon if (addr + size != save + size + align)
2124721505deSMatthew Dillon munmap(addr + size, save + align - addr);
2125721505deSMatthew Dillon
2126721505deSMatthew Dillon addr_hint = addr + size;
2127721505deSMatthew Dillon
212882949828SMatthew Dillon return ((void *)addr);
212982949828SMatthew Dillon }
213082949828SMatthew Dillon
213182949828SMatthew Dillon /*
213282949828SMatthew Dillon * _vmem_free()
213382949828SMatthew Dillon *
213482949828SMatthew Dillon * Free a chunk of memory allocated with _vmem_alloc()
213582949828SMatthew Dillon */
213682949828SMatthew Dillon static void
_vmem_free(void * ptr,size_t size)2137b435182dSSimon Schubert _vmem_free(void *ptr, size_t size)
213882949828SMatthew Dillon {
213982949828SMatthew Dillon munmap(ptr, size);
214082949828SMatthew Dillon }
214182949828SMatthew Dillon
214282949828SMatthew Dillon /*
214382949828SMatthew Dillon * Panic on fatal conditions
214482949828SMatthew Dillon */
214582949828SMatthew Dillon static void
_mpanic(const char * ctl,...)214682949828SMatthew Dillon _mpanic(const char *ctl, ...)
214782949828SMatthew Dillon {
214882949828SMatthew Dillon va_list va;
214982949828SMatthew Dillon
215082949828SMatthew Dillon if (malloc_panic == 0) {
215182949828SMatthew Dillon malloc_panic = 1;
215282949828SMatthew Dillon va_start(va, ctl);
215382949828SMatthew Dillon vfprintf(stderr, ctl, va);
215482949828SMatthew Dillon fprintf(stderr, "\n");
215582949828SMatthew Dillon fflush(stderr);
215682949828SMatthew Dillon va_end(va);
215782949828SMatthew Dillon }
215882949828SMatthew Dillon abort();
215982949828SMatthew Dillon }
216069baab3bSImre Vadász
2161d3a54aeeSzrj __weak_reference(__aligned_alloc, aligned_alloc);
216269baab3bSImre Vadász __weak_reference(__malloc, malloc);
216369baab3bSImre Vadász __weak_reference(__calloc, calloc);
216469baab3bSImre Vadász __weak_reference(__posix_memalign, posix_memalign);
216569baab3bSImre Vadász __weak_reference(__realloc, realloc);
216669baab3bSImre Vadász __weak_reference(__free, free);
2167d780b39fSAntonio Huete Jimenez __weak_reference(__malloc_usable_size, malloc_usable_size);
2168