xref: /openbsd-src/lib/libc/stdlib/malloc.c (revision ff0e7be1ebbcc809ea8ad2b6dafe215824da9e46)
1 /*	$OpenBSD: malloc.c,v 1.286 2023/06/07 12:56:22 aoyama Exp $	*/
2 /*
3  * Copyright (c) 2008, 2010, 2011, 2016, 2023 Otto Moerbeek <otto@drijf.net>
4  * Copyright (c) 2012 Matthew Dempsky <matthew@openbsd.org>
5  * Copyright (c) 2008 Damien Miller <djm@openbsd.org>
6  * Copyright (c) 2000 Poul-Henning Kamp <phk@FreeBSD.org>
7  *
8  * Permission to use, copy, modify, and distribute this software for any
9  * purpose with or without fee is hereby granted, provided that the above
10  * copyright notice and this permission notice appear in all copies.
11  *
12  * THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES
13  * WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF
14  * MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR
15  * ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES
16  * WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN
17  * ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF
18  * OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.
19  */
20 
21 /*
22  * If we meet some day, and you think this stuff is worth it, you
23  * can buy me a beer in return. Poul-Henning Kamp
24  */
25 
26 #ifndef MALLOC_SMALL
27 #define MALLOC_STATS
28 #endif
29 
30 #include <sys/types.h>
31 #include <sys/queue.h>
32 #include <sys/mman.h>
33 #include <sys/sysctl.h>
34 #include <uvm/uvmexp.h>
35 #include <errno.h>
36 #include <stdarg.h>
37 #include <stdint.h>
38 #include <stdio.h>
39 #include <stdlib.h>
40 #include <string.h>
41 #include <unistd.h>
42 
43 #ifdef MALLOC_STATS
44 #include <sys/tree.h>
45 #include <sys/ktrace.h>
46 #include <dlfcn.h>
47 #endif
48 
49 #include "thread_private.h"
50 #include <tib.h>
51 
52 #define MALLOC_PAGESHIFT	_MAX_PAGE_SHIFT
53 
54 #define MALLOC_MINSHIFT		4
55 #define MALLOC_MAXSHIFT		(MALLOC_PAGESHIFT - 1)
56 #define MALLOC_PAGESIZE		(1UL << MALLOC_PAGESHIFT)
57 #define MALLOC_MINSIZE		(1UL << MALLOC_MINSHIFT)
58 #define MALLOC_PAGEMASK		(MALLOC_PAGESIZE - 1)
59 #define MASK_POINTER(p)		((void *)(((uintptr_t)(p)) & ~MALLOC_PAGEMASK))
60 
61 #define MALLOC_MAXCHUNK		(1 << MALLOC_MAXSHIFT)
62 #define MALLOC_MAXCACHE		256
63 #define MALLOC_DELAYED_CHUNK_MASK	15
64 #ifdef MALLOC_STATS
65 #define MALLOC_INITIAL_REGIONS	512
66 #else
67 #define MALLOC_INITIAL_REGIONS	(MALLOC_PAGESIZE / sizeof(struct region_info))
68 #endif
69 #define MALLOC_DEFAULT_CACHE	64
70 #define MALLOC_CHUNK_LISTS	4
71 #define CHUNK_CHECK_LENGTH	32
72 
73 #define B2SIZE(b)		((b) * MALLOC_MINSIZE)
74 #define B2ALLOC(b)		((b) == 0 ? MALLOC_MINSIZE : \
75 				    (b) * MALLOC_MINSIZE)
76 #define BUCKETS 		(MALLOC_MAXCHUNK / MALLOC_MINSIZE)
77 
78 /*
79  * We move allocations between half a page and a whole page towards the end,
80  * subject to alignment constraints. This is the extra headroom we allow.
81  * Set to zero to be the most strict.
82  */
83 #define MALLOC_LEEWAY		0
84 #define MALLOC_MOVE_COND(sz)	((sz) - mopts.malloc_guard < 		\
85 				    MALLOC_PAGESIZE - MALLOC_LEEWAY)
86 #define MALLOC_MOVE(p, sz)  	(((char *)(p)) +			\
87 				    ((MALLOC_PAGESIZE - MALLOC_LEEWAY -	\
88 			    	    ((sz) - mopts.malloc_guard)) & 	\
89 				    ~(MALLOC_MINSIZE - 1)))
90 
91 #define PAGEROUND(x)  (((x) + (MALLOC_PAGEMASK)) & ~MALLOC_PAGEMASK)
92 
93 /*
94  * What to use for Junk.  This is the byte value we use to fill with
95  * when the 'J' option is enabled. Use SOME_JUNK right after alloc,
96  * and SOME_FREEJUNK right before free.
97  */
98 #define SOME_JUNK		0xdb	/* deadbeef */
99 #define SOME_FREEJUNK		0xdf	/* dead, free */
100 #define SOME_FREEJUNK_ULL	0xdfdfdfdfdfdfdfdfULL
101 
102 #define MMAP(sz,f)	mmap(NULL, (sz), PROT_READ | PROT_WRITE, \
103     MAP_ANON | MAP_PRIVATE | (f), -1, 0)
104 
105 #define MMAPNONE(sz,f)	mmap(NULL, (sz), PROT_NONE, \
106     MAP_ANON | MAP_PRIVATE | (f), -1, 0)
107 
108 #define MMAPA(a,sz,f)	mmap((a), (sz), PROT_READ | PROT_WRITE, \
109     MAP_ANON | MAP_PRIVATE | (f), -1, 0)
110 
111 struct region_info {
112 	void *p;		/* page; low bits used to mark chunks */
113 	uintptr_t size;		/* size for pages, or chunk_info pointer */
114 #ifdef MALLOC_STATS
115 	void *f;		/* where allocated from */
116 #endif
117 };
118 
119 LIST_HEAD(chunk_head, chunk_info);
120 
121 /*
122  * Two caches, one for "small" regions, one for "big".
123  * Small cache is an array per size, big cache is one array with different
124  * sized regions
125  */
126 #define MAX_SMALLCACHEABLE_SIZE	32
127 #define MAX_BIGCACHEABLE_SIZE	512
128 /* If the total # of pages is larger than this, evict before inserting */
129 #define BIGCACHE_FILL(sz)	(MAX_BIGCACHEABLE_SIZE * (sz) / 4)
130 
131 struct smallcache {
132 	void **pages;
133 	ushort length;
134 	ushort max;
135 };
136 
137 struct bigcache {
138 	void *page;
139 	size_t psize;
140 };
141 
142 struct dir_info {
143 	u_int32_t canary1;
144 	int active;			/* status of malloc */
145 	struct region_info *r;		/* region slots */
146 	size_t regions_total;		/* number of region slots */
147 	size_t regions_free;		/* number of free slots */
148 	size_t rbytesused;		/* random bytes used */
149 	char *func;			/* current function */
150 	int malloc_junk;		/* junk fill? */
151 	int mmap_flag;			/* extra flag for mmap */
152 	int mutex;
153 	int malloc_mt;			/* multi-threaded mode? */
154 					/* lists of free chunk info structs */
155 	struct chunk_head chunk_info_list[BUCKETS + 1];
156 					/* lists of chunks with free slots */
157 	struct chunk_head chunk_dir[BUCKETS + 1][MALLOC_CHUNK_LISTS];
158 					/* delayed free chunk slots */
159 	void *delayed_chunks[MALLOC_DELAYED_CHUNK_MASK + 1];
160 	u_char rbytes[32];		/* random bytes */
161 					/* free pages cache */
162 	struct smallcache smallcache[MAX_SMALLCACHEABLE_SIZE];
163 	size_t bigcache_used;
164 	size_t bigcache_size;
165 	struct bigcache *bigcache;
166 	void *chunk_pages;
167 	size_t chunk_pages_used;
168 #ifdef MALLOC_STATS
169 	size_t inserts;
170 	size_t insert_collisions;
171 	size_t finds;
172 	size_t find_collisions;
173 	size_t deletes;
174 	size_t delete_moves;
175 	size_t cheap_realloc_tries;
176 	size_t cheap_reallocs;
177 	size_t malloc_used;		/* bytes allocated */
178 	size_t malloc_guarded;		/* bytes used for guards */
179 	size_t pool_searches;		/* searches for pool */
180 	size_t other_pool;		/* searches in other pool */
181 #define STATS_ADD(x,y)	((x) += (y))
182 #define STATS_SUB(x,y)	((x) -= (y))
183 #define STATS_INC(x)	((x)++)
184 #define STATS_ZERO(x)	((x) = 0)
185 #define STATS_SETF(x,y)	((x)->f = (y))
186 #else
187 #define STATS_ADD(x,y)	/* nothing */
188 #define STATS_SUB(x,y)	/* nothing */
189 #define STATS_INC(x)	/* nothing */
190 #define STATS_ZERO(x)	/* nothing */
191 #define STATS_SETF(x,y)	/* nothing */
192 #endif /* MALLOC_STATS */
193 	u_int32_t canary2;
194 };
195 
196 static void unmap(struct dir_info *d, void *p, size_t sz, size_t clear);
197 
198 /*
199  * This structure describes a page worth of chunks.
200  *
201  * How many bits per u_short in the bitmap
202  */
203 #define MALLOC_BITS		(NBBY * sizeof(u_short))
204 struct chunk_info {
205 	LIST_ENTRY(chunk_info) entries;
206 	void *page;			/* pointer to the page */
207 	u_short canary;
208 	u_short bucket;
209 	u_short free;			/* how many free chunks */
210 	u_short total;			/* how many chunks */
211 	u_short offset;			/* requested size table offset */
212 	u_short bits[1];		/* which chunks are free */
213 };
214 
215 struct malloc_readonly {
216 					/* Main bookkeeping information */
217 	struct dir_info *malloc_pool[_MALLOC_MUTEXES];
218 	u_int	malloc_mutexes;		/* how much in actual use? */
219 	int	malloc_freecheck;	/* Extensive double free check */
220 	int	malloc_freeunmap;	/* mprotect free pages PROT_NONE? */
221 	int	def_malloc_junk;	/* junk fill? */
222 	int	malloc_realloc;		/* always realloc? */
223 	int	malloc_xmalloc;		/* xmalloc behaviour? */
224 	u_int	chunk_canaries;		/* use canaries after chunks? */
225 	int	internal_funcs;		/* use better recallocarray/freezero? */
226 	u_int	def_maxcache;		/* free pages we cache */
227 	u_int	junk_loc;		/* variation in location of junk */
228 	size_t	malloc_guard;		/* use guard pages after allocations? */
229 #ifdef MALLOC_STATS
230 	int	malloc_stats;		/* dump leak report at end */
231 	int	malloc_verbose;		/* dump verbose statistics at end */
232 #define	DO_STATS	mopts.malloc_stats
233 #else
234 #define	DO_STATS	0
235 #endif
236 	u_int32_t malloc_canary;	/* Matched against ones in pool */
237 };
238 
239 
240 /* This object is mapped PROT_READ after initialisation to prevent tampering */
241 static union {
242 	struct malloc_readonly mopts;
243 	u_char _pad[MALLOC_PAGESIZE];
244 } malloc_readonly __attribute__((aligned(MALLOC_PAGESIZE)))
245 		__attribute__((section(".openbsd.mutable")));
246 #define mopts	malloc_readonly.mopts
247 
248 char		*malloc_options;	/* compile-time options */
249 
250 static __dead void wrterror(struct dir_info *d, char *msg, ...)
251     __attribute__((__format__ (printf, 2, 3)));
252 
253 #ifdef MALLOC_STATS
254 void malloc_dump(void);
255 PROTO_NORMAL(malloc_dump);
256 static void malloc_exit(void);
257 #endif
258 #define CALLER	(DO_STATS ? __builtin_return_address(0) : NULL)
259 
260 /* low bits of r->p determine size: 0 means >= page size and r->size holding
261  * real size, otherwise low bits is the bucket + 1
262  */
263 #define REALSIZE(sz, r)						\
264 	(sz) = (uintptr_t)(r)->p & MALLOC_PAGEMASK,		\
265 	(sz) = ((sz) == 0 ? (r)->size : B2SIZE((sz) - 1))
266 
267 static inline size_t
268 hash(void *p)
269 {
270 	size_t sum;
271 	uintptr_t u;
272 
273 	u = (uintptr_t)p >> MALLOC_PAGESHIFT;
274 	sum = u;
275 	sum = (sum << 7) - sum + (u >> 16);
276 #ifdef __LP64__
277 	sum = (sum << 7) - sum + (u >> 32);
278 	sum = (sum << 7) - sum + (u >> 48);
279 #endif
280 	return sum;
281 }
282 
283 static inline struct dir_info *
284 getpool(void)
285 {
286 	if (mopts.malloc_pool[1] == NULL || !mopts.malloc_pool[1]->malloc_mt)
287 		return mopts.malloc_pool[1];
288 	else	/* first one reserved for special pool */
289 		return mopts.malloc_pool[1 + TIB_GET()->tib_tid %
290 		    (mopts.malloc_mutexes - 1)];
291 }
292 
293 static __dead void
294 wrterror(struct dir_info *d, char *msg, ...)
295 {
296 	int		saved_errno = errno;
297 	va_list		ap;
298 
299 	dprintf(STDERR_FILENO, "%s(%d) in %s(): ", __progname,
300 	    getpid(), (d != NULL && d->func) ? d->func : "unknown");
301 	va_start(ap, msg);
302 	vdprintf(STDERR_FILENO, msg, ap);
303 	va_end(ap);
304 	dprintf(STDERR_FILENO, "\n");
305 
306 #ifdef MALLOC_STATS
307 	if (DO_STATS && mopts.malloc_verbose)
308 		malloc_dump();
309 #endif
310 
311 	errno = saved_errno;
312 
313 	abort();
314 }
315 
316 static void
317 rbytes_init(struct dir_info *d)
318 {
319 	arc4random_buf(d->rbytes, sizeof(d->rbytes));
320 	/* add 1 to account for using d->rbytes[0] */
321 	d->rbytesused = 1 + d->rbytes[0] % (sizeof(d->rbytes) / 2);
322 }
323 
324 static inline u_char
325 getrbyte(struct dir_info *d)
326 {
327 	u_char x;
328 
329 	if (d->rbytesused >= sizeof(d->rbytes))
330 		rbytes_init(d);
331 	x = d->rbytes[d->rbytesused++];
332 	return x;
333 }
334 
335 static void
336 omalloc_parseopt(char opt)
337 {
338 	switch (opt) {
339 	case '+':
340 		mopts.malloc_mutexes <<= 1;
341 		if (mopts.malloc_mutexes > _MALLOC_MUTEXES)
342 			mopts.malloc_mutexes = _MALLOC_MUTEXES;
343 		break;
344 	case '-':
345 		mopts.malloc_mutexes >>= 1;
346 		if (mopts.malloc_mutexes < 2)
347 			mopts.malloc_mutexes = 2;
348 		break;
349 	case '>':
350 		mopts.def_maxcache <<= 1;
351 		if (mopts.def_maxcache > MALLOC_MAXCACHE)
352 			mopts.def_maxcache = MALLOC_MAXCACHE;
353 		break;
354 	case '<':
355 		mopts.def_maxcache >>= 1;
356 		break;
357 	case 'c':
358 		mopts.chunk_canaries = 0;
359 		break;
360 	case 'C':
361 		mopts.chunk_canaries = 1;
362 		break;
363 #ifdef MALLOC_STATS
364 	case 'd':
365 		mopts.malloc_stats = 0;
366 		break;
367 	case 'D':
368 		mopts.malloc_stats = 1;
369 		break;
370 #endif /* MALLOC_STATS */
371 	case 'f':
372 		mopts.malloc_freecheck = 0;
373 		mopts.malloc_freeunmap = 0;
374 		break;
375 	case 'F':
376 		mopts.malloc_freecheck = 1;
377 		mopts.malloc_freeunmap = 1;
378 		break;
379 	case 'g':
380 		mopts.malloc_guard = 0;
381 		break;
382 	case 'G':
383 		mopts.malloc_guard = MALLOC_PAGESIZE;
384 		break;
385 	case 'j':
386 		if (mopts.def_malloc_junk > 0)
387 			mopts.def_malloc_junk--;
388 		break;
389 	case 'J':
390 		if (mopts.def_malloc_junk < 2)
391 			mopts.def_malloc_junk++;
392 		break;
393 	case 'r':
394 		mopts.malloc_realloc = 0;
395 		break;
396 	case 'R':
397 		mopts.malloc_realloc = 1;
398 		break;
399 	case 'u':
400 		mopts.malloc_freeunmap = 0;
401 		break;
402 	case 'U':
403 		mopts.malloc_freeunmap = 1;
404 		break;
405 #ifdef MALLOC_STATS
406 	case 'v':
407 		mopts.malloc_verbose = 0;
408 		break;
409 	case 'V':
410 		mopts.malloc_verbose = 1;
411 		break;
412 #endif /* MALLOC_STATS */
413 	case 'x':
414 		mopts.malloc_xmalloc = 0;
415 		break;
416 	case 'X':
417 		mopts.malloc_xmalloc = 1;
418 		break;
419 	default:
420 		dprintf(STDERR_FILENO, "malloc() warning: "
421                     "unknown char in MALLOC_OPTIONS\n");
422 		break;
423 	}
424 }
425 
426 static void
427 omalloc_init(void)
428 {
429 	char *p, *q, b[16];
430 	int i, j;
431 	const int mib[2] = { CTL_VM, VM_MALLOC_CONF };
432 	size_t sb;
433 
434 	/*
435 	 * Default options
436 	 */
437 	mopts.malloc_mutexes = 8;
438 	mopts.def_malloc_junk = 1;
439 	mopts.def_maxcache = MALLOC_DEFAULT_CACHE;
440 
441 	for (i = 0; i < 3; i++) {
442 		switch (i) {
443 		case 0:
444 			sb = sizeof(b);
445 			j = sysctl(mib, 2, b, &sb, NULL, 0);
446 			if (j != 0)
447 				continue;
448 			p = b;
449 			break;
450 		case 1:
451 			if (issetugid() == 0)
452 				p = getenv("MALLOC_OPTIONS");
453 			else
454 				continue;
455 			break;
456 		case 2:
457 			p = malloc_options;
458 			break;
459 		default:
460 			p = NULL;
461 		}
462 
463 		for (; p != NULL && *p != '\0'; p++) {
464 			switch (*p) {
465 			case 'S':
466 				for (q = "CFGJ"; *q != '\0'; q++)
467 					omalloc_parseopt(*q);
468 				mopts.def_maxcache = 0;
469 				break;
470 			case 's':
471 				for (q = "cfgj"; *q != '\0'; q++)
472 					omalloc_parseopt(*q);
473 				mopts.def_maxcache = MALLOC_DEFAULT_CACHE;
474 				break;
475 			default:
476 				omalloc_parseopt(*p);
477 				break;
478 			}
479 		}
480 	}
481 
482 #ifdef MALLOC_STATS
483 	if (DO_STATS && (atexit(malloc_exit) == -1)) {
484 		dprintf(STDERR_FILENO, "malloc() warning: atexit(2) failed."
485 		    " Will not be able to dump stats on exit\n");
486 	}
487 #endif
488 
489 	while ((mopts.malloc_canary = arc4random()) == 0)
490 		;
491 	mopts.junk_loc = arc4random();
492 	if (mopts.chunk_canaries)
493 		do {
494 			mopts.chunk_canaries = arc4random();
495 		} while ((u_char)mopts.chunk_canaries == 0 ||
496 		    (u_char)mopts.chunk_canaries == SOME_FREEJUNK);
497 }
498 
499 static void
500 omalloc_poolinit(struct dir_info *d, int mmap_flag)
501 {
502 	int i, j;
503 
504 	d->r = NULL;
505 	d->rbytesused = sizeof(d->rbytes);
506 	d->regions_free = d->regions_total = 0;
507 	for (i = 0; i <= BUCKETS; i++) {
508 		LIST_INIT(&d->chunk_info_list[i]);
509 		for (j = 0; j < MALLOC_CHUNK_LISTS; j++)
510 			LIST_INIT(&d->chunk_dir[i][j]);
511 	}
512 	d->mmap_flag = mmap_flag;
513 	d->malloc_junk = mopts.def_malloc_junk;
514 	d->canary1 = mopts.malloc_canary ^ (u_int32_t)(uintptr_t)d;
515 	d->canary2 = ~d->canary1;
516 }
517 
518 static int
519 omalloc_grow(struct dir_info *d)
520 {
521 	size_t newtotal;
522 	size_t newsize;
523 	size_t mask;
524 	size_t i, oldpsz;
525 	struct region_info *p;
526 
527 	if (d->regions_total > SIZE_MAX / sizeof(struct region_info) / 2)
528 		return 1;
529 
530 	newtotal = d->regions_total == 0 ? MALLOC_INITIAL_REGIONS :
531 	    d->regions_total * 2;
532 	newsize = PAGEROUND(newtotal * sizeof(struct region_info));
533 	mask = newtotal - 1;
534 
535 	/* Don't use cache here, we don't want user uaf touch this */
536 	p = MMAP(newsize, d->mmap_flag);
537 	if (p == MAP_FAILED)
538 		return 1;
539 
540 	STATS_ADD(d->malloc_used, newsize);
541 	STATS_ZERO(d->inserts);
542 	STATS_ZERO(d->insert_collisions);
543 	for (i = 0; i < d->regions_total; i++) {
544 		void *q = d->r[i].p;
545 		if (q != NULL) {
546 			size_t index = hash(q) & mask;
547 			STATS_INC(d->inserts);
548 			while (p[index].p != NULL) {
549 				index = (index - 1) & mask;
550 				STATS_INC(d->insert_collisions);
551 			}
552 			p[index] = d->r[i];
553 		}
554 	}
555 
556 	if (d->regions_total > 0) {
557 		oldpsz = PAGEROUND(d->regions_total * sizeof(struct region_info));
558 		/* clear to avoid meta info ending up in the cache */
559 		unmap(d, d->r, oldpsz, oldpsz);
560 	}
561 	d->regions_free += newtotal - d->regions_total;
562 	d->regions_total = newtotal;
563 	d->r = p;
564 	return 0;
565 }
566 
567 /*
568  * The hashtable uses the assumption that p is never NULL. This holds since
569  * non-MAP_FIXED mappings with hint 0 start at BRKSIZ.
570  */
571 static int
572 insert(struct dir_info *d, void *p, size_t sz, void *f)
573 {
574 	size_t index;
575 	size_t mask;
576 	void *q;
577 
578 	if (d->regions_free * 4 < d->regions_total || d->regions_total == 0) {
579 		if (omalloc_grow(d))
580 			return 1;
581 	}
582 	mask = d->regions_total - 1;
583 	index = hash(p) & mask;
584 	q = d->r[index].p;
585 	STATS_INC(d->inserts);
586 	while (q != NULL) {
587 		index = (index - 1) & mask;
588 		q = d->r[index].p;
589 		STATS_INC(d->insert_collisions);
590 	}
591 	d->r[index].p = p;
592 	d->r[index].size = sz;
593 	STATS_SETF(&d->r[index], f);
594 	d->regions_free--;
595 	return 0;
596 }
597 
598 static struct region_info *
599 find(struct dir_info *d, void *p)
600 {
601 	size_t index;
602 	size_t mask = d->regions_total - 1;
603 	void *q, *r;
604 
605 	if (mopts.malloc_canary != (d->canary1 ^ (u_int32_t)(uintptr_t)d) ||
606 	    d->canary1 != ~d->canary2)
607 		wrterror(d, "internal struct corrupt");
608 	if (d->r == NULL)
609 		return NULL;
610 	p = MASK_POINTER(p);
611 	index = hash(p) & mask;
612 	r = d->r[index].p;
613 	q = MASK_POINTER(r);
614 	STATS_INC(d->finds);
615 	while (q != p && r != NULL) {
616 		index = (index - 1) & mask;
617 		r = d->r[index].p;
618 		q = MASK_POINTER(r);
619 		STATS_INC(d->find_collisions);
620 	}
621 	return (q == p && r != NULL) ? &d->r[index] : NULL;
622 }
623 
624 static void
625 delete(struct dir_info *d, struct region_info *ri)
626 {
627 	/* algorithm R, Knuth Vol III section 6.4 */
628 	size_t mask = d->regions_total - 1;
629 	size_t i, j, r;
630 
631 	if (d->regions_total & (d->regions_total - 1))
632 		wrterror(d, "regions_total not 2^x");
633 	d->regions_free++;
634 	STATS_INC(d->deletes);
635 
636 	i = ri - d->r;
637 	for (;;) {
638 		d->r[i].p = NULL;
639 		d->r[i].size = 0;
640 		j = i;
641 		for (;;) {
642 			i = (i - 1) & mask;
643 			if (d->r[i].p == NULL)
644 				return;
645 			r = hash(d->r[i].p) & mask;
646 			if ((i <= r && r < j) || (r < j && j < i) ||
647 			    (j < i && i <= r))
648 				continue;
649 			d->r[j] = d->r[i];
650 			STATS_INC(d->delete_moves);
651 			break;
652 		}
653 
654 	}
655 }
656 
657 static inline void
658 junk_free(int junk, void *p, size_t sz)
659 {
660 	size_t i, step = 1;
661 	uint64_t *lp = p;
662 
663 	if (junk == 0 || sz == 0)
664 		return;
665 	sz /= sizeof(uint64_t);
666 	if (junk == 1) {
667 		if (sz > MALLOC_PAGESIZE / sizeof(uint64_t))
668 			sz = MALLOC_PAGESIZE / sizeof(uint64_t);
669 		step = sz / 4;
670 		if (step == 0)
671 			step = 1;
672 	}
673 	/* Do not always put the free junk bytes in the same spot.
674 	   There is modulo bias here, but we ignore that. */
675 	for (i = mopts.junk_loc % step; i < sz; i += step)
676 		lp[i] = SOME_FREEJUNK_ULL;
677 }
678 
679 static inline void
680 validate_junk(struct dir_info *pool, void *p, size_t sz)
681 {
682 	size_t i, step = 1;
683 	uint64_t *lp = p;
684 
685 	if (pool->malloc_junk == 0 || sz == 0)
686 		return;
687 	sz /= sizeof(uint64_t);
688 	if (pool->malloc_junk == 1) {
689 		if (sz > MALLOC_PAGESIZE / sizeof(uint64_t))
690 			sz = MALLOC_PAGESIZE / sizeof(uint64_t);
691 		step = sz / 4;
692 		if (step == 0)
693 			step = 1;
694 	}
695 	/* see junk_free */
696 	for (i = mopts.junk_loc % step; i < sz; i += step) {
697 		if (lp[i] != SOME_FREEJUNK_ULL)
698 			wrterror(pool, "write after free %p", p);
699 	}
700 }
701 
702 
703 /*
704  * Cache maintenance.
705  * Opposed to the regular region data structure, the sizes in the
706  * cache are in MALLOC_PAGESIZE units.
707  */
708 static void
709 unmap(struct dir_info *d, void *p, size_t sz, size_t clear)
710 {
711 	size_t psz = sz >> MALLOC_PAGESHIFT;
712 	void *r;
713 	u_short i;
714 	struct smallcache *cache;
715 
716 	if (sz != PAGEROUND(sz) || psz == 0)
717 		wrterror(d, "munmap round");
718 
719 	if (d->bigcache_size > 0 && psz > MAX_SMALLCACHEABLE_SIZE &&
720 	    psz <= MAX_BIGCACHEABLE_SIZE) {
721 		u_short base = getrbyte(d);
722 		u_short j;
723 
724 		/* don't look through all slots */
725 		for (j = 0; j < d->bigcache_size / 4; j++) {
726 			i = (base + j) & (d->bigcache_size - 1);
727 			if (d->bigcache_used <
728 			    BIGCACHE_FILL(d->bigcache_size))  {
729 				if (d->bigcache[i].psize == 0)
730 					break;
731 			} else {
732 				if (d->bigcache[i].psize != 0)
733 					break;
734 			}
735 		}
736 		/* if we didn't find a preferred slot, use random one */
737 		if (d->bigcache[i].psize != 0) {
738 			size_t tmp;
739 
740 			r = d->bigcache[i].page;
741 			d->bigcache_used -= d->bigcache[i].psize;
742 			tmp = d->bigcache[i].psize << MALLOC_PAGESHIFT;
743 			if (!mopts.malloc_freeunmap)
744 				validate_junk(d, r, tmp);
745 			if (munmap(r, tmp))
746 				 wrterror(d, "munmap %p", r);
747 			STATS_SUB(d->malloc_used, tmp);
748 		}
749 
750 		if (clear > 0)
751 			explicit_bzero(p, clear);
752 		if (mopts.malloc_freeunmap) {
753 			if (mprotect(p, sz, PROT_NONE))
754 				wrterror(d, "mprotect %p", r);
755 		} else
756 			junk_free(d->malloc_junk, p, sz);
757 		d->bigcache[i].page = p;
758 		d->bigcache[i].psize = psz;
759 		d->bigcache_used += psz;
760 		return;
761 	}
762 	if (psz > MAX_SMALLCACHEABLE_SIZE || d->smallcache[psz - 1].max == 0) {
763 		if (munmap(p, sz))
764 			wrterror(d, "munmap %p", p);
765 		STATS_SUB(d->malloc_used, sz);
766 		return;
767 	}
768 	cache = &d->smallcache[psz - 1];
769 	if (cache->length == cache->max) {
770 		int fresh;
771 		/* use a random slot */
772 		i = getrbyte(d) & (cache->max - 1);
773 		r = cache->pages[i];
774 		fresh = (uintptr_t)r & 1;
775 		*(uintptr_t*)&r &= ~1ULL;
776 		if (!fresh && !mopts.malloc_freeunmap)
777 			validate_junk(d, r, sz);
778 		if (munmap(r, sz))
779 			wrterror(d, "munmap %p", r);
780 		STATS_SUB(d->malloc_used, sz);
781 		cache->length--;
782 	} else
783 		i = cache->length;
784 
785 	/* fill slot */
786 	if (clear > 0)
787 		explicit_bzero(p, clear);
788 	if (mopts.malloc_freeunmap)
789 		mprotect(p, sz, PROT_NONE);
790 	else
791 		junk_free(d->malloc_junk, p, sz);
792 	cache->pages[i] = p;
793 	cache->length++;
794 }
795 
796 static void *
797 map(struct dir_info *d, size_t sz, int zero_fill)
798 {
799 	size_t psz = sz >> MALLOC_PAGESHIFT;
800 	u_short i;
801 	void *p;
802 	struct smallcache *cache;
803 
804 	if (mopts.malloc_canary != (d->canary1 ^ (u_int32_t)(uintptr_t)d) ||
805 	    d->canary1 != ~d->canary2)
806 		wrterror(d, "internal struct corrupt");
807 	if (sz != PAGEROUND(sz) || psz == 0)
808 		wrterror(d, "map round");
809 
810 
811 	if (d->bigcache_size > 0 && psz > MAX_SMALLCACHEABLE_SIZE &&
812 	    psz <= MAX_BIGCACHEABLE_SIZE) {
813 		size_t base = getrbyte(d);
814 		size_t cached = d->bigcache_used;
815 		ushort j;
816 
817 		for (j = 0; j < d->bigcache_size && cached >= psz; j++) {
818 			i = (j + base) & (d->bigcache_size - 1);
819 			if (d->bigcache[i].psize == psz) {
820 				p = d->bigcache[i].page;
821 				d->bigcache_used -= psz;
822 				d->bigcache[i].page = NULL;
823 				d->bigcache[i].psize = 0;
824 
825 				if (!mopts.malloc_freeunmap)
826 					validate_junk(d, p, sz);
827 				if (mopts.malloc_freeunmap)
828 					mprotect(p, sz, PROT_READ | PROT_WRITE);
829 				if (zero_fill)
830 					memset(p, 0, sz);
831 				else if (mopts.malloc_freeunmap)
832 					junk_free(d->malloc_junk, p, sz);
833 				return p;
834 			}
835 			cached -= d->bigcache[i].psize;
836 		}
837 	}
838 	if (psz <= MAX_SMALLCACHEABLE_SIZE && d->smallcache[psz - 1].max > 0) {
839 		cache = &d->smallcache[psz - 1];
840 		if (cache->length > 0) {
841 			int fresh;
842 			if (cache->length == 1)
843 				p = cache->pages[--cache->length];
844 			else {
845 				i = getrbyte(d) % cache->length;
846 				p = cache->pages[i];
847 				cache->pages[i] = cache->pages[--cache->length];
848 			}
849 			/* check if page was not junked, i.e. "fresh
850 			   we use the lsb of the pointer for that */
851 			fresh = (uintptr_t)p & 1UL;
852 			*(uintptr_t*)&p &= ~1UL;
853 			if (!fresh && !mopts.malloc_freeunmap)
854 				validate_junk(d, p, sz);
855 			if (mopts.malloc_freeunmap)
856 				mprotect(p, sz, PROT_READ | PROT_WRITE);
857 			if (zero_fill)
858 				memset(p, 0, sz);
859 			else if (mopts.malloc_freeunmap)
860 				junk_free(d->malloc_junk, p, sz);
861 			return p;
862 		}
863 		if (psz <= 1) {
864 			p = MMAP(cache->max * sz, d->mmap_flag);
865 			if (p != MAP_FAILED) {
866 				STATS_ADD(d->malloc_used, cache->max * sz);
867 				cache->length = cache->max - 1;
868 				for (i = 0; i < cache->max - 1; i++) {
869 					void *q = (char*)p + i * sz;
870 					cache->pages[i] = q;
871 					/* mark pointer in slot as not junked */
872 					*(uintptr_t*)&cache->pages[i] |= 1UL;
873 				}
874 				if (mopts.malloc_freeunmap)
875 					mprotect(p, (cache->max - 1) * sz,
876 					    PROT_NONE);
877 				p = (char*)p + (cache->max - 1) * sz;
878 				/* zero fill not needed, freshly mmapped */
879 				return p;
880 			}
881 		}
882 
883 	}
884 	p = MMAP(sz, d->mmap_flag);
885 	if (p != MAP_FAILED)
886 		STATS_ADD(d->malloc_used, sz);
887 	/* zero fill not needed */
888 	return p;
889 }
890 
891 static void
892 init_chunk_info(struct dir_info *d, struct chunk_info *p, u_int bucket)
893 {
894 	u_int i;
895 
896 	p->bucket = bucket;
897 	p->total = p->free = MALLOC_PAGESIZE / B2ALLOC(bucket);
898 	p->offset = bucket == 0 ? 0xdead : howmany(p->total, MALLOC_BITS);
899 	p->canary = (u_short)d->canary1;
900 
901 	/* set all valid bits in the bitmap */
902  	i = p->total - 1;
903 	memset(p->bits, 0xff, sizeof(p->bits[0]) * (i / MALLOC_BITS));
904 	p->bits[i / MALLOC_BITS] = (2U << (i % MALLOC_BITS)) - 1;
905 }
906 
907 static struct chunk_info *
908 alloc_chunk_info(struct dir_info *d, u_int bucket)
909 {
910 	struct chunk_info *p;
911 
912 	if (LIST_EMPTY(&d->chunk_info_list[bucket])) {
913 		const size_t chunk_pages = 64;
914 		size_t size, count, i;
915 		char *q;
916 
917 		count = MALLOC_PAGESIZE / B2ALLOC(bucket);
918 
919 		size = howmany(count, MALLOC_BITS);
920 		size = sizeof(struct chunk_info) + (size - 1) * sizeof(u_short);
921 		if (mopts.chunk_canaries)
922 			size += count * sizeof(u_short);
923 		size = _ALIGN(size);
924 		count = MALLOC_PAGESIZE / size;
925 
926 		/* Don't use cache here, we don't want user uaf touch this */
927 		if (d->chunk_pages_used == chunk_pages ||
928 		     d->chunk_pages == NULL) {
929 			q = MMAP(MALLOC_PAGESIZE * chunk_pages, d->mmap_flag);
930 			if (q == MAP_FAILED)
931 				return NULL;
932 			d->chunk_pages = q;
933 			d->chunk_pages_used = 0;
934 			STATS_ADD(d->malloc_used, MALLOC_PAGESIZE *
935 			    chunk_pages);
936 		}
937 		q = (char *)d->chunk_pages + d->chunk_pages_used *
938 		    MALLOC_PAGESIZE;
939 		d->chunk_pages_used++;
940 
941 		for (i = 0; i < count; i++, q += size) {
942 			p = (struct chunk_info *)q;
943 			LIST_INSERT_HEAD(&d->chunk_info_list[bucket], p, entries);
944 		}
945 	}
946 	p = LIST_FIRST(&d->chunk_info_list[bucket]);
947 	LIST_REMOVE(p, entries);
948 	if (p->total == 0)
949 		init_chunk_info(d, p, bucket);
950 	return p;
951 }
952 
953 /*
954  * Allocate a page of chunks
955  */
956 static struct chunk_info *
957 omalloc_make_chunks(struct dir_info *d, u_int bucket, u_int listnum)
958 {
959 	struct chunk_info *bp;
960 	void *pp;
961 
962 	/* Allocate a new bucket */
963 	pp = map(d, MALLOC_PAGESIZE, 0);
964 	if (pp == MAP_FAILED)
965 		return NULL;
966 
967 	/* memory protect the page allocated in the malloc(0) case */
968 	if (bucket == 0 && mprotect(pp, MALLOC_PAGESIZE, PROT_NONE) == -1)
969 		goto err;
970 
971 	bp = alloc_chunk_info(d, bucket);
972 	if (bp == NULL)
973 		goto err;
974 	bp->page = pp;
975 
976 	if (insert(d, (void *)((uintptr_t)pp | (bucket + 1)), (uintptr_t)bp,
977 	    NULL))
978 		goto err;
979 	LIST_INSERT_HEAD(&d->chunk_dir[bucket][listnum], bp, entries);
980 
981 	if (bucket > 0 && d->malloc_junk != 0)
982 		memset(pp, SOME_FREEJUNK, MALLOC_PAGESIZE);
983 
984 	return bp;
985 
986 err:
987 	unmap(d, pp, MALLOC_PAGESIZE, 0);
988 	return NULL;
989 }
990 
991 #if defined(__GNUC__) && __GNUC__ < 4
992 static inline unsigned int
993 lb(u_int x)
994 {
995 #if defined(__m88k__)
996 	__asm__ __volatile__ ("ff1 %0, %0" : "=r" (x) : "0" (x));
997 	return x;
998 #else
999 	/* portable version */
1000 	unsigned int count = 0;
1001 	while ((x & (1U << (sizeof(int) * CHAR_BIT - 1))) == 0) {
1002 		count++;
1003 		x <<= 1;
1004 	}
1005 	return (sizeof(int) * CHAR_BIT - 1) - count;
1006 #endif
1007 }
1008 #else
1009 /* using built-in function version */
1010 static inline unsigned int
1011 lb(u_int x)
1012 {
1013 	/* I need an extension just for integer-length (: */
1014 	return (sizeof(int) * CHAR_BIT - 1) - __builtin_clz(x);
1015 }
1016 #endif
1017 
1018 /* https://pvk.ca/Blog/2015/06/27/linear-log-bucketing-fast-versatile-simple/
1019    via Tony Finch */
1020 static inline unsigned int
1021 bin_of(unsigned int size)
1022 {
1023 	const unsigned int linear = 6;
1024 	const unsigned int subbin = 2;
1025 
1026 	unsigned int mask, range, rounded, sub_index, rounded_size;
1027 	unsigned int n_bits, shift;
1028 
1029 	n_bits = lb(size | (1U << linear));
1030 	shift = n_bits - subbin;
1031 	mask = (1ULL << shift) - 1;
1032 	rounded = size + mask; /* XXX: overflow. */
1033 	sub_index = rounded >> shift;
1034 	range = n_bits - linear;
1035 
1036 	rounded_size = rounded & ~mask;
1037 	return rounded_size;
1038 }
1039 
1040 static inline u_short
1041 find_bucket(u_short size)
1042 {
1043 	/* malloc(0) is special */
1044 	if (size == 0)
1045 		return 0;
1046 	if (size < MALLOC_MINSIZE)
1047 		size = MALLOC_MINSIZE;
1048 	if (mopts.def_maxcache != 0)
1049 		size = bin_of(size);
1050 	return howmany(size, MALLOC_MINSIZE);
1051 }
1052 
1053 static void
1054 fill_canary(char *ptr, size_t sz, size_t allocated)
1055 {
1056 	size_t check_sz = allocated - sz;
1057 
1058 	if (check_sz > CHUNK_CHECK_LENGTH)
1059 		check_sz = CHUNK_CHECK_LENGTH;
1060 	memset(ptr + sz, mopts.chunk_canaries, check_sz);
1061 }
1062 
1063 /*
1064  * Allocate a chunk
1065  */
1066 static void *
1067 malloc_bytes(struct dir_info *d, size_t size, void *f)
1068 {
1069 	u_int i, r, bucket, listnum;
1070 	size_t k;
1071 	u_short	*lp;
1072 	struct chunk_info *bp;
1073 	void *p;
1074 
1075 	if (mopts.malloc_canary != (d->canary1 ^ (u_int32_t)(uintptr_t)d) ||
1076 	    d->canary1 != ~d->canary2)
1077 		wrterror(d, "internal struct corrupt");
1078 
1079 	bucket = find_bucket(size);
1080 
1081 	r = ((u_int)getrbyte(d) << 8) | getrbyte(d);
1082 	listnum = r % MALLOC_CHUNK_LISTS;
1083 
1084 	/* If it's empty, make a page more of that size chunks */
1085 	if ((bp = LIST_FIRST(&d->chunk_dir[bucket][listnum])) == NULL) {
1086 		bp = omalloc_make_chunks(d, bucket, listnum);
1087 		if (bp == NULL)
1088 			return NULL;
1089 	}
1090 
1091 	if (bp->canary != (u_short)d->canary1)
1092 		wrterror(d, "chunk info corrupted");
1093 
1094 	/* bias, as bp->total is not a power of 2 */
1095 	i = (r / MALLOC_CHUNK_LISTS) % bp->total;
1096 
1097 	/* potentially start somewhere in a short */
1098 	lp = &bp->bits[i / MALLOC_BITS];
1099 	if (*lp) {
1100 		int j = i % MALLOC_BITS; /* j must be signed */
1101 		k = ffs(*lp >> j);
1102 		if (k != 0) {
1103 			k += j - 1;
1104 			goto found;
1105 		}
1106 	}
1107 	/* no bit halfway, go to next full short */
1108 	i /= MALLOC_BITS;
1109 	for (;;) {
1110 		if (++i >= howmany(bp->total, MALLOC_BITS))
1111 			i = 0;
1112 		lp = &bp->bits[i];
1113 		if (*lp) {
1114 			k = ffs(*lp) - 1;
1115 			break;
1116 		}
1117 	}
1118 found:
1119 	if (i == 0 && k == 0 && DO_STATS) {
1120 		struct region_info *r = find(d, bp->page);
1121 		STATS_SETF(r, f);
1122 	}
1123 
1124 	*lp ^= 1 << k;
1125 
1126 	/* If there are no more free, remove from free-list */
1127 	if (--bp->free == 0)
1128 		LIST_REMOVE(bp, entries);
1129 
1130 	/* Adjust to the real offset of that chunk */
1131 	k += (lp - bp->bits) * MALLOC_BITS;
1132 
1133 	if (mopts.chunk_canaries && size > 0)
1134 		bp->bits[bp->offset + k] = size;
1135 
1136 	k *= B2ALLOC(bp->bucket);
1137 
1138 	p = (char *)bp->page + k;
1139 	if (bp->bucket > 0) {
1140 		validate_junk(d, p, B2SIZE(bp->bucket));
1141 		if (mopts.chunk_canaries)
1142 			fill_canary(p, size, B2SIZE(bp->bucket));
1143 	}
1144 	return p;
1145 }
1146 
1147 static void
1148 validate_canary(struct dir_info *d, u_char *ptr, size_t sz, size_t allocated)
1149 {
1150 	size_t check_sz = allocated - sz;
1151 	u_char *p, *q;
1152 
1153 	if (check_sz > CHUNK_CHECK_LENGTH)
1154 		check_sz = CHUNK_CHECK_LENGTH;
1155 	p = ptr + sz;
1156 	q = p + check_sz;
1157 
1158 	while (p < q) {
1159 		if (*p != (u_char)mopts.chunk_canaries && *p != SOME_JUNK) {
1160 			wrterror(d, "canary corrupted %p %#tx@%#zx%s",
1161 			    ptr, p - ptr, sz,
1162 			    *p == SOME_FREEJUNK ? " (double free?)" : "");
1163 		}
1164 		p++;
1165 	}
1166 }
1167 
1168 static uint32_t
1169 find_chunknum(struct dir_info *d, struct chunk_info *info, void *ptr, int check)
1170 {
1171 	uint32_t chunknum;
1172 
1173 	if (info->canary != (u_short)d->canary1)
1174 		wrterror(d, "chunk info corrupted");
1175 
1176 	/* Find the chunk number on the page */
1177 	chunknum = ((uintptr_t)ptr & MALLOC_PAGEMASK) / B2ALLOC(info->bucket);
1178 
1179 	if ((uintptr_t)ptr & (MALLOC_MINSIZE - 1))
1180 		wrterror(d, "modified chunk-pointer %p", ptr);
1181 	if (info->bits[chunknum / MALLOC_BITS] &
1182 	    (1U << (chunknum % MALLOC_BITS)))
1183 		wrterror(d, "double free %p", ptr);
1184 	if (check && info->bucket > 0) {
1185 		validate_canary(d, ptr, info->bits[info->offset + chunknum],
1186 		    B2SIZE(info->bucket));
1187 	}
1188 	return chunknum;
1189 }
1190 
1191 /*
1192  * Free a chunk, and possibly the page it's on, if the page becomes empty.
1193  */
1194 static void
1195 free_bytes(struct dir_info *d, struct region_info *r, void *ptr)
1196 {
1197 	struct chunk_head *mp;
1198 	struct chunk_info *info;
1199 	uint32_t chunknum;
1200 	uint32_t listnum;
1201 
1202 	info = (struct chunk_info *)r->size;
1203 	chunknum = find_chunknum(d, info, ptr, 0);
1204 
1205 	if (chunknum == 0)
1206 		STATS_SETF(r, NULL);
1207 
1208 	info->bits[chunknum / MALLOC_BITS] |= 1U << (chunknum % MALLOC_BITS);
1209 	info->free++;
1210 
1211 	if (info->free == 1) {
1212 		/* Page became non-full */
1213 		listnum = getrbyte(d) % MALLOC_CHUNK_LISTS;
1214 		mp = &d->chunk_dir[info->bucket][listnum];
1215 		LIST_INSERT_HEAD(mp, info, entries);
1216 		return;
1217 	}
1218 
1219 	if (info->free != info->total)
1220 		return;
1221 
1222 	LIST_REMOVE(info, entries);
1223 
1224 	if (info->bucket == 0 && !mopts.malloc_freeunmap)
1225 		mprotect(info->page, MALLOC_PAGESIZE, PROT_READ | PROT_WRITE);
1226 	unmap(d, info->page, MALLOC_PAGESIZE, 0);
1227 
1228 	delete(d, r);
1229 	mp = &d->chunk_info_list[info->bucket];
1230 	LIST_INSERT_HEAD(mp, info, entries);
1231 }
1232 
1233 
1234 
1235 static void *
1236 omalloc(struct dir_info *pool, size_t sz, int zero_fill, void *f)
1237 {
1238 	void *p;
1239 	size_t psz;
1240 
1241 	if (sz > MALLOC_MAXCHUNK) {
1242 		if (sz >= SIZE_MAX - mopts.malloc_guard - MALLOC_PAGESIZE) {
1243 			errno = ENOMEM;
1244 			return NULL;
1245 		}
1246 		sz += mopts.malloc_guard;
1247 		psz = PAGEROUND(sz);
1248 		p = map(pool, psz, zero_fill);
1249 		if (p == MAP_FAILED) {
1250 			errno = ENOMEM;
1251 			return NULL;
1252 		}
1253 		if (insert(pool, p, sz, f)) {
1254 			unmap(pool, p, psz, 0);
1255 			errno = ENOMEM;
1256 			return NULL;
1257 		}
1258 		if (mopts.malloc_guard) {
1259 			if (mprotect((char *)p + psz - mopts.malloc_guard,
1260 			    mopts.malloc_guard, PROT_NONE))
1261 				wrterror(pool, "mprotect");
1262 			STATS_ADD(pool->malloc_guarded, mopts.malloc_guard);
1263 		}
1264 
1265 		if (MALLOC_MOVE_COND(sz)) {
1266 			/* fill whole allocation */
1267 			if (pool->malloc_junk == 2)
1268 				memset(p, SOME_JUNK, psz - mopts.malloc_guard);
1269 			/* shift towards the end */
1270 			p = MALLOC_MOVE(p, sz);
1271 			/* fill zeros if needed and overwritten above */
1272 			if (zero_fill && pool->malloc_junk == 2)
1273 				memset(p, 0, sz - mopts.malloc_guard);
1274 		} else {
1275 			if (pool->malloc_junk == 2) {
1276 				if (zero_fill)
1277 					memset((char *)p + sz -
1278 					    mopts.malloc_guard, SOME_JUNK,
1279 					    psz - sz);
1280 				else
1281 					memset(p, SOME_JUNK,
1282 					    psz - mopts.malloc_guard);
1283 			} else if (mopts.chunk_canaries)
1284 				fill_canary(p, sz - mopts.malloc_guard,
1285 				    psz - mopts.malloc_guard);
1286 		}
1287 
1288 	} else {
1289 		/* takes care of SOME_JUNK */
1290 		p = malloc_bytes(pool, sz, f);
1291 		if (zero_fill && p != NULL && sz > 0)
1292 			memset(p, 0, sz);
1293 	}
1294 
1295 	return p;
1296 }
1297 
1298 /*
1299  * Common function for handling recursion.  Only
1300  * print the error message once, to avoid making the problem
1301  * potentially worse.
1302  */
1303 static void
1304 malloc_recurse(struct dir_info *d)
1305 {
1306 	static int noprint;
1307 
1308 	if (noprint == 0) {
1309 		noprint = 1;
1310 		wrterror(d, "recursive call");
1311 	}
1312 	d->active--;
1313 	_MALLOC_UNLOCK(d->mutex);
1314 	errno = EDEADLK;
1315 }
1316 
1317 void
1318 _malloc_init(int from_rthreads)
1319 {
1320 	u_int i, j, nmutexes;
1321 	struct dir_info *d;
1322 
1323 	_MALLOC_LOCK(1);
1324 	if (!from_rthreads && mopts.malloc_pool[1]) {
1325 		_MALLOC_UNLOCK(1);
1326 		return;
1327 	}
1328 	if (!mopts.malloc_canary) {
1329 		char *p;
1330 		size_t sz, d_avail;
1331 
1332 		omalloc_init();
1333 		/*
1334 		 * Allocate dir_infos with a guard page on either side. Also
1335 		 * randomise offset inside the page at which the dir_infos
1336 		 * lay (subject to alignment by 1 << MALLOC_MINSHIFT)
1337 		 */
1338 		sz = mopts.malloc_mutexes * sizeof(*d) + 2 * MALLOC_PAGESIZE;
1339 		if ((p = MMAPNONE(sz, 0)) == MAP_FAILED)
1340 			wrterror(NULL, "malloc_init mmap1 failed");
1341 		if (mprotect(p + MALLOC_PAGESIZE, mopts.malloc_mutexes * sizeof(*d),
1342 		    PROT_READ | PROT_WRITE))
1343 			wrterror(NULL, "malloc_init mprotect1 failed");
1344 		if (mimmutable(p, sz))
1345 			wrterror(NULL, "malloc_init mimmutable1 failed");
1346 		d_avail = (((mopts.malloc_mutexes * sizeof(*d) + MALLOC_PAGEMASK) &
1347 		    ~MALLOC_PAGEMASK) - (mopts.malloc_mutexes * sizeof(*d))) >>
1348 		    MALLOC_MINSHIFT;
1349 		d = (struct dir_info *)(p + MALLOC_PAGESIZE +
1350 		    (arc4random_uniform(d_avail) << MALLOC_MINSHIFT));
1351 		STATS_ADD(d[1].malloc_used, sz);
1352 		for (i = 0; i < mopts.malloc_mutexes; i++)
1353 			mopts.malloc_pool[i] = &d[i];
1354 		mopts.internal_funcs = 1;
1355 		if (((uintptr_t)&malloc_readonly & MALLOC_PAGEMASK) == 0) {
1356 			if (mprotect(&malloc_readonly, sizeof(malloc_readonly),
1357 			    PROT_READ))
1358 				wrterror(NULL, "malloc_init mprotect r/o failed");
1359 			if (mimmutable(&malloc_readonly, sizeof(malloc_readonly)))
1360 				wrterror(NULL, "malloc_init mimmutable r/o failed");
1361 		}
1362 	}
1363 
1364 	nmutexes = from_rthreads ? mopts.malloc_mutexes : 2;
1365 	for (i = 0; i < nmutexes; i++) {
1366 		d = mopts.malloc_pool[i];
1367 		d->malloc_mt = from_rthreads;
1368 		if (d->canary1 == ~d->canary2)
1369 			continue;
1370 		if (i == 0) {
1371 			omalloc_poolinit(d, MAP_CONCEAL);
1372 			d->malloc_junk = 2;
1373 			d->bigcache_size = 0;
1374 			for (j = 0; j < MAX_SMALLCACHEABLE_SIZE; j++)
1375 				d->smallcache[j].max = 0;
1376 		} else {
1377 			size_t sz = 0;
1378 
1379 			omalloc_poolinit(d, 0);
1380 			d->malloc_junk = mopts.def_malloc_junk;
1381 			d->bigcache_size = mopts.def_maxcache;
1382 			for (j = 0; j < MAX_SMALLCACHEABLE_SIZE; j++) {
1383 				d->smallcache[j].max =
1384 				    mopts.def_maxcache >> (j / 8);
1385 				sz += d->smallcache[j].max * sizeof(void *);
1386 			}
1387 			sz += d->bigcache_size * sizeof(struct bigcache);
1388 			if (sz > 0) {
1389 				void *p = MMAP(sz, 0);
1390 				if (p == MAP_FAILED)
1391 					wrterror(NULL,
1392 					    "malloc_init mmap2 failed");
1393 				if (mimmutable(p, sz))
1394 					wrterror(NULL, "malloc_init mimmutable2 failed");
1395 				for (j = 0; j < MAX_SMALLCACHEABLE_SIZE; j++) {
1396 					d->smallcache[j].pages = p;
1397 					p = (char *)p + d->smallcache[j].max *
1398 					    sizeof(void *);
1399 				}
1400 				d->bigcache = p;
1401 			}
1402 		}
1403 		d->mutex = i;
1404 	}
1405 
1406 	_MALLOC_UNLOCK(1);
1407 }
1408 DEF_STRONG(_malloc_init);
1409 
1410 #define PROLOGUE(p, fn)			\
1411 	d = (p); 			\
1412 	if (d == NULL) { 		\
1413 		_malloc_init(0);	\
1414 		d = (p);		\
1415 	}				\
1416 	_MALLOC_LOCK(d->mutex);		\
1417 	d->func = fn;			\
1418 	if (d->active++) {		\
1419 		malloc_recurse(d);	\
1420 		return NULL;		\
1421 	}				\
1422 
1423 #define EPILOGUE()				\
1424 	d->active--;				\
1425 	_MALLOC_UNLOCK(d->mutex);		\
1426 	if (r == NULL && mopts.malloc_xmalloc)	\
1427 		wrterror(d, "out of memory");	\
1428 	if (r != NULL)				\
1429 		errno = saved_errno;		\
1430 
1431 void *
1432 malloc(size_t size)
1433 {
1434 	void *r;
1435 	struct dir_info *d;
1436 	int saved_errno = errno;
1437 
1438 	PROLOGUE(getpool(), "malloc")
1439 	r = omalloc(d, size, 0, CALLER);
1440 	EPILOGUE()
1441 	return r;
1442 }
1443 DEF_STRONG(malloc);
1444 
1445 void *
1446 malloc_conceal(size_t size)
1447 {
1448 	void *r;
1449 	struct dir_info *d;
1450 	int saved_errno = errno;
1451 
1452 	PROLOGUE(mopts.malloc_pool[0], "malloc_conceal")
1453 	r = omalloc(d, size, 0, CALLER);
1454 	EPILOGUE()
1455 	return r;
1456 }
1457 DEF_WEAK(malloc_conceal);
1458 
1459 static struct region_info *
1460 findpool(void *p, struct dir_info *argpool, struct dir_info **foundpool,
1461     char **saved_function)
1462 {
1463 	struct dir_info *pool = argpool;
1464 	struct region_info *r = find(pool, p);
1465 
1466 	STATS_INC(pool->pool_searches);
1467 	if (r == NULL) {
1468 		u_int i, nmutexes;
1469 
1470 		nmutexes = mopts.malloc_pool[1]->malloc_mt ? mopts.malloc_mutexes : 2;
1471 		STATS_INC(pool->other_pool);
1472 		for (i = 1; i < nmutexes; i++) {
1473 			u_int j = (argpool->mutex + i) & (nmutexes - 1);
1474 
1475 			pool->active--;
1476 			_MALLOC_UNLOCK(pool->mutex);
1477 			pool = mopts.malloc_pool[j];
1478 			_MALLOC_LOCK(pool->mutex);
1479 			pool->active++;
1480 			r = find(pool, p);
1481 			if (r != NULL) {
1482 				*saved_function = pool->func;
1483 				pool->func = argpool->func;
1484 				break;
1485 			}
1486 		}
1487 		if (r == NULL)
1488 			wrterror(argpool, "bogus pointer (double free?) %p", p);
1489 	}
1490 	*foundpool = pool;
1491 	return r;
1492 }
1493 
1494 static void
1495 ofree(struct dir_info **argpool, void *p, int clear, int check, size_t argsz)
1496 {
1497 	struct region_info *r;
1498 	struct dir_info *pool;
1499 	char *saved_function;
1500 	size_t sz;
1501 
1502 	r = findpool(p, *argpool, &pool, &saved_function);
1503 
1504 	REALSIZE(sz, r);
1505 	if (pool->mmap_flag) {
1506 		clear = 1;
1507 		if (!check) {
1508 			argsz = sz;
1509 			if (sz > MALLOC_MAXCHUNK)
1510 				argsz -= mopts.malloc_guard;
1511 		}
1512 	}
1513 	if (check) {
1514 		if (sz <= MALLOC_MAXCHUNK) {
1515 			if (mopts.chunk_canaries && sz > 0) {
1516 				struct chunk_info *info =
1517 				    (struct chunk_info *)r->size;
1518 				uint32_t chunknum =
1519 				    find_chunknum(pool, info, p, 0);
1520 
1521 				if (info->bits[info->offset + chunknum] < argsz)
1522 					wrterror(pool, "recorded size %hu"
1523 					    " < %zu",
1524 					    info->bits[info->offset + chunknum],
1525 					    argsz);
1526 			} else {
1527 				if (sz < argsz)
1528 					wrterror(pool, "chunk size %zu < %zu",
1529 					    sz, argsz);
1530 			}
1531 		} else if (sz - mopts.malloc_guard < argsz) {
1532 			wrterror(pool, "recorded size %zu < %zu",
1533 			    sz - mopts.malloc_guard, argsz);
1534 		}
1535 	}
1536 	if (sz > MALLOC_MAXCHUNK) {
1537 		if (!MALLOC_MOVE_COND(sz)) {
1538 			if (r->p != p)
1539 				wrterror(pool, "bogus pointer %p", p);
1540 			if (mopts.chunk_canaries)
1541 				validate_canary(pool, p,
1542 				    sz - mopts.malloc_guard,
1543 				    PAGEROUND(sz - mopts.malloc_guard));
1544 		} else {
1545 			/* shifted towards the end */
1546 			if (p != MALLOC_MOVE(r->p, sz))
1547 				wrterror(pool, "bogus moved pointer %p", p);
1548 			p = r->p;
1549 		}
1550 		if (mopts.malloc_guard) {
1551 			if (sz < mopts.malloc_guard)
1552 				wrterror(pool, "guard size");
1553 			if (!mopts.malloc_freeunmap) {
1554 				if (mprotect((char *)p + PAGEROUND(sz) -
1555 				    mopts.malloc_guard, mopts.malloc_guard,
1556 				    PROT_READ | PROT_WRITE))
1557 					wrterror(pool, "mprotect");
1558 			}
1559 			STATS_SUB(pool->malloc_guarded, mopts.malloc_guard);
1560 		}
1561 		unmap(pool, p, PAGEROUND(sz), clear ? argsz : 0);
1562 		delete(pool, r);
1563 	} else {
1564 		void *tmp;
1565 		u_int i;
1566 
1567 		/* Validate and optionally canary check */
1568 		struct chunk_info *info = (struct chunk_info *)r->size;
1569 		if (B2SIZE(info->bucket) != sz)
1570 			wrterror(pool, "internal struct corrupt");
1571 		find_chunknum(pool, info, p, mopts.chunk_canaries);
1572 
1573 		if (mopts.malloc_freecheck) {
1574 			for (i = 0; i <= MALLOC_DELAYED_CHUNK_MASK; i++) {
1575 				tmp = pool->delayed_chunks[i];
1576 				if (tmp == p)
1577 					wrterror(pool,
1578 					    "double free %p", p);
1579 				if (tmp != NULL) {
1580 					size_t tmpsz;
1581 
1582 					r = find(pool, tmp);
1583 					if (r == NULL)
1584 						wrterror(pool,
1585 						    "bogus pointer ("
1586 						    "double free?) %p", tmp);
1587 					REALSIZE(tmpsz, r);
1588 					validate_junk(pool, tmp, tmpsz);
1589 				}
1590 			}
1591 		}
1592 
1593 		if (clear && argsz > 0)
1594 			explicit_bzero(p, argsz);
1595 		junk_free(pool->malloc_junk, p, sz);
1596 
1597 		i = getrbyte(pool) & MALLOC_DELAYED_CHUNK_MASK;
1598 		tmp = p;
1599 		p = pool->delayed_chunks[i];
1600 		if (tmp == p)
1601 			wrterror(pool, "double free %p", p);
1602 		pool->delayed_chunks[i] = tmp;
1603 		if (p != NULL) {
1604 			r = find(pool, p);
1605 			if (r == NULL)
1606 				wrterror(pool,
1607 				    "bogus pointer (double free?) %p", p);
1608 			if (!mopts.malloc_freecheck) {
1609 				REALSIZE(sz, r);
1610 				validate_junk(pool, p, sz);
1611 			}
1612 			free_bytes(pool, r, p);
1613 		}
1614 	}
1615 
1616 	if (*argpool != pool) {
1617 		pool->func = saved_function;
1618 		*argpool = pool;
1619 	}
1620 }
1621 
1622 void
1623 free(void *ptr)
1624 {
1625 	struct dir_info *d;
1626 	int saved_errno = errno;
1627 
1628 	/* This is legal. */
1629 	if (ptr == NULL)
1630 		return;
1631 
1632 	d = getpool();
1633 	if (d == NULL)
1634 		wrterror(d, "free() called before allocation");
1635 	_MALLOC_LOCK(d->mutex);
1636 	d->func = "free";
1637 	if (d->active++) {
1638 		malloc_recurse(d);
1639 		return;
1640 	}
1641 	ofree(&d, ptr, 0, 0, 0);
1642 	d->active--;
1643 	_MALLOC_UNLOCK(d->mutex);
1644 	errno = saved_errno;
1645 }
1646 DEF_STRONG(free);
1647 
1648 static void
1649 freezero_p(void *ptr, size_t sz)
1650 {
1651 	explicit_bzero(ptr, sz);
1652 	free(ptr);
1653 }
1654 
1655 void
1656 freezero(void *ptr, size_t sz)
1657 {
1658 	struct dir_info *d;
1659 	int saved_errno = errno;
1660 
1661 	/* This is legal. */
1662 	if (ptr == NULL)
1663 		return;
1664 
1665 	if (!mopts.internal_funcs) {
1666 		freezero_p(ptr, sz);
1667 		return;
1668 	}
1669 
1670 	d = getpool();
1671 	if (d == NULL)
1672 		wrterror(d, "freezero() called before allocation");
1673 	_MALLOC_LOCK(d->mutex);
1674 	d->func = "freezero";
1675 	if (d->active++) {
1676 		malloc_recurse(d);
1677 		return;
1678 	}
1679 	ofree(&d, ptr, 1, 1, sz);
1680 	d->active--;
1681 	_MALLOC_UNLOCK(d->mutex);
1682 	errno = saved_errno;
1683 }
1684 DEF_WEAK(freezero);
1685 
1686 static void *
1687 orealloc(struct dir_info **argpool, void *p, size_t newsz, void *f)
1688 {
1689 	struct region_info *r;
1690 	struct dir_info *pool;
1691 	char *saved_function;
1692 	struct chunk_info *info;
1693 	size_t oldsz, goldsz, gnewsz;
1694 	void *q, *ret;
1695 	uint32_t chunknum;
1696 	int forced;
1697 
1698 	if (p == NULL)
1699 		return omalloc(*argpool, newsz, 0, f);
1700 
1701 	if (newsz >= SIZE_MAX - mopts.malloc_guard - MALLOC_PAGESIZE) {
1702 		errno = ENOMEM;
1703 		return  NULL;
1704 	}
1705 
1706 	r = findpool(p, *argpool, &pool, &saved_function);
1707 
1708 	REALSIZE(oldsz, r);
1709 	if (oldsz <= MALLOC_MAXCHUNK) {
1710 		if (DO_STATS || mopts.chunk_canaries) {
1711 			info = (struct chunk_info *)r->size;
1712 			chunknum = find_chunknum(pool, info, p, 0);
1713 		}
1714 	}
1715 
1716 	goldsz = oldsz;
1717 	if (oldsz > MALLOC_MAXCHUNK) {
1718 		if (oldsz < mopts.malloc_guard)
1719 			wrterror(pool, "guard size");
1720 		oldsz -= mopts.malloc_guard;
1721 	}
1722 
1723 	gnewsz = newsz;
1724 	if (gnewsz > MALLOC_MAXCHUNK)
1725 		gnewsz += mopts.malloc_guard;
1726 
1727 	forced = mopts.malloc_realloc || pool->mmap_flag;
1728 	if (newsz > MALLOC_MAXCHUNK && oldsz > MALLOC_MAXCHUNK && !forced) {
1729 		/* First case: from n pages sized allocation to m pages sized
1730 		   allocation, m > n */
1731 		size_t roldsz = PAGEROUND(goldsz);
1732 		size_t rnewsz = PAGEROUND(gnewsz);
1733 
1734 		if (rnewsz < roldsz && rnewsz > roldsz / 2 &&
1735 		    roldsz - rnewsz < mopts.def_maxcache * MALLOC_PAGESIZE &&
1736 		    !mopts.malloc_guard) {
1737 
1738 			ret = p;
1739 			goto done;
1740 		}
1741 
1742 		if (rnewsz > roldsz) {
1743 			/* try to extend existing region */
1744 			if (!mopts.malloc_guard) {
1745 				void *hint = (char *)r->p + roldsz;
1746 				size_t needed = rnewsz - roldsz;
1747 
1748 				STATS_INC(pool->cheap_realloc_tries);
1749 				q = MMAPA(hint, needed, MAP_FIXED | __MAP_NOREPLACE | pool->mmap_flag);
1750 				if (q == hint) {
1751 					STATS_ADD(pool->malloc_used, needed);
1752 					if (pool->malloc_junk == 2)
1753 						memset(q, SOME_JUNK, needed);
1754 					r->size = gnewsz;
1755 					if (r->p != p) {
1756 						/* old pointer is moved */
1757 						memmove(r->p, p, oldsz);
1758 						p = r->p;
1759 					}
1760 					if (mopts.chunk_canaries)
1761 						fill_canary(p, newsz,
1762 						    PAGEROUND(newsz));
1763 					STATS_SETF(r, f);
1764 					STATS_INC(pool->cheap_reallocs);
1765 					ret = p;
1766 					goto done;
1767 				}
1768 			}
1769 		} else if (rnewsz < roldsz) {
1770 			/* shrink number of pages */
1771 			if (mopts.malloc_guard) {
1772 				if (mprotect((char *)r->p + rnewsz -
1773 				    mopts.malloc_guard, mopts.malloc_guard,
1774 				    PROT_NONE))
1775 					wrterror(pool, "mprotect");
1776 			}
1777 			if (munmap((char *)r->p + rnewsz, roldsz - rnewsz))
1778 				wrterror(pool, "munmap %p", (char *)r->p +
1779 				    rnewsz);
1780 			STATS_SUB(pool->malloc_used, roldsz - rnewsz);
1781 			r->size = gnewsz;
1782 			if (MALLOC_MOVE_COND(gnewsz)) {
1783 				void *pp = MALLOC_MOVE(r->p, gnewsz);
1784 				memmove(pp, p, newsz);
1785 				p = pp;
1786 			} else if (mopts.chunk_canaries)
1787 				fill_canary(p, newsz, PAGEROUND(newsz));
1788 			STATS_SETF(r, f);
1789 			ret = p;
1790 			goto done;
1791 		} else {
1792 			/* number of pages remains the same */
1793 			void *pp = r->p;
1794 
1795 			r->size = gnewsz;
1796 			if (MALLOC_MOVE_COND(gnewsz))
1797 				pp = MALLOC_MOVE(r->p, gnewsz);
1798 			if (p != pp) {
1799 				memmove(pp, p, oldsz < newsz ? oldsz : newsz);
1800 				p = pp;
1801 			}
1802 			if (p == r->p) {
1803 				if (newsz > oldsz && pool->malloc_junk == 2)
1804 					memset((char *)p + newsz, SOME_JUNK,
1805 					    rnewsz - mopts.malloc_guard -
1806 					    newsz);
1807 				if (mopts.chunk_canaries)
1808 					fill_canary(p, newsz, PAGEROUND(newsz));
1809 			}
1810 			STATS_SETF(r, f);
1811 			ret = p;
1812 			goto done;
1813 		}
1814 	}
1815 	if (oldsz <= MALLOC_MAXCHUNK && oldsz > 0 &&
1816 	    newsz <= MALLOC_MAXCHUNK && newsz > 0 &&
1817 	    !forced && find_bucket(newsz) == find_bucket(oldsz)) {
1818 		/* do not reallocate if new size fits good in existing chunk */
1819 		if (pool->malloc_junk == 2)
1820 			memset((char *)p + newsz, SOME_JUNK, oldsz - newsz);
1821 		if (mopts.chunk_canaries) {
1822 			info->bits[info->offset + chunknum] = newsz;
1823 			fill_canary(p, newsz, B2SIZE(info->bucket));
1824 		}
1825 		if (DO_STATS && chunknum == 0)
1826 			STATS_SETF(r, f);
1827 		ret = p;
1828 	} else if (newsz != oldsz || forced) {
1829 		/* create new allocation */
1830 		q = omalloc(pool, newsz, 0, f);
1831 		if (q == NULL) {
1832 			ret = NULL;
1833 			goto done;
1834 		}
1835 		if (newsz != 0 && oldsz != 0)
1836 			memcpy(q, p, oldsz < newsz ? oldsz : newsz);
1837 		ofree(&pool, p, 0, 0, 0);
1838 		ret = q;
1839 	} else {
1840 		/* oldsz == newsz */
1841 		if (newsz != 0)
1842 			wrterror(pool, "realloc internal inconsistency");
1843 		if (DO_STATS && chunknum == 0)
1844 			STATS_SETF(r, f);
1845 		ret = p;
1846 	}
1847 done:
1848 	if (*argpool != pool) {
1849 		pool->func = saved_function;
1850 		*argpool = pool;
1851 	}
1852 	return ret;
1853 }
1854 
1855 void *
1856 realloc(void *ptr, size_t size)
1857 {
1858 	struct dir_info *d;
1859 	void *r;
1860 	int saved_errno = errno;
1861 
1862 	PROLOGUE(getpool(), "realloc")
1863 	r = orealloc(&d, ptr, size, CALLER);
1864 	EPILOGUE()
1865 	return r;
1866 }
1867 DEF_STRONG(realloc);
1868 
1869 /*
1870  * This is sqrt(SIZE_MAX+1), as s1*s2 <= SIZE_MAX
1871  * if both s1 < MUL_NO_OVERFLOW and s2 < MUL_NO_OVERFLOW
1872  */
1873 #define MUL_NO_OVERFLOW	(1UL << (sizeof(size_t) * 4))
1874 
1875 void *
1876 calloc(size_t nmemb, size_t size)
1877 {
1878 	struct dir_info *d;
1879 	void *r;
1880 	int saved_errno = errno;
1881 
1882 	PROLOGUE(getpool(), "calloc")
1883 	if ((nmemb >= MUL_NO_OVERFLOW || size >= MUL_NO_OVERFLOW) &&
1884 	    nmemb > 0 && SIZE_MAX / nmemb < size) {
1885 		d->active--;
1886 		_MALLOC_UNLOCK(d->mutex);
1887 		if (mopts.malloc_xmalloc)
1888 			wrterror(d, "out of memory");
1889 		errno = ENOMEM;
1890 		return NULL;
1891 	}
1892 
1893 	size *= nmemb;
1894 	r = omalloc(d, size, 1, CALLER);
1895 	EPILOGUE()
1896 	return r;
1897 }
1898 DEF_STRONG(calloc);
1899 
1900 void *
1901 calloc_conceal(size_t nmemb, size_t size)
1902 {
1903 	struct dir_info *d;
1904 	void *r;
1905 	int saved_errno = errno;
1906 
1907 	PROLOGUE(mopts.malloc_pool[0], "calloc_conceal")
1908 	if ((nmemb >= MUL_NO_OVERFLOW || size >= MUL_NO_OVERFLOW) &&
1909 	    nmemb > 0 && SIZE_MAX / nmemb < size) {
1910 		d->active--;
1911 		_MALLOC_UNLOCK(d->mutex);
1912 		if (mopts.malloc_xmalloc)
1913 			wrterror(d, "out of memory");
1914 		errno = ENOMEM;
1915 		return NULL;
1916 	}
1917 
1918 	size *= nmemb;
1919 	r = omalloc(d, size, 1, CALLER);
1920 	EPILOGUE()
1921 	return r;
1922 }
1923 DEF_WEAK(calloc_conceal);
1924 
1925 static void *
1926 orecallocarray(struct dir_info **argpool, void *p, size_t oldsize,
1927     size_t newsize, void *f)
1928 {
1929 	struct region_info *r;
1930 	struct dir_info *pool;
1931 	char *saved_function;
1932 	void *newptr;
1933 	size_t sz;
1934 
1935 	if (p == NULL)
1936 		return omalloc(*argpool, newsize, 1, f);
1937 
1938 	if (oldsize == newsize)
1939 		return p;
1940 
1941 	r = findpool(p, *argpool, &pool, &saved_function);
1942 
1943 	REALSIZE(sz, r);
1944 	if (sz <= MALLOC_MAXCHUNK) {
1945 		if (mopts.chunk_canaries && sz > 0) {
1946 			struct chunk_info *info = (struct chunk_info *)r->size;
1947 			uint32_t chunknum = find_chunknum(pool, info, p, 0);
1948 
1949 			if (info->bits[info->offset + chunknum] != oldsize)
1950 				wrterror(pool, "recorded size %hu != %zu",
1951 				    info->bits[info->offset + chunknum],
1952 				    oldsize);
1953 		} else {
1954 			if (sz < oldsize)
1955 				wrterror(pool, "chunk size %zu < %zu",
1956 				    sz, oldsize);
1957 		}
1958 	} else {
1959 		if (sz - mopts.malloc_guard < oldsize)
1960 			wrterror(pool, "recorded size %zu < %zu",
1961 			    sz - mopts.malloc_guard, oldsize);
1962 		if (oldsize < (sz - mopts.malloc_guard) / 2)
1963 			wrterror(pool, "recorded size %zu inconsistent with %zu",
1964 			    sz - mopts.malloc_guard, oldsize);
1965 	}
1966 
1967 	newptr = omalloc(pool, newsize, 0, f);
1968 	if (newptr == NULL)
1969 		goto done;
1970 
1971 	if (newsize > oldsize) {
1972 		memcpy(newptr, p, oldsize);
1973 		memset((char *)newptr + oldsize, 0, newsize - oldsize);
1974 	} else
1975 		memcpy(newptr, p, newsize);
1976 
1977 	ofree(&pool, p, 1, 0, oldsize);
1978 
1979 done:
1980 	if (*argpool != pool) {
1981 		pool->func = saved_function;
1982 		*argpool = pool;
1983 	}
1984 
1985 	return newptr;
1986 }
1987 
1988 static void *
1989 recallocarray_p(void *ptr, size_t oldnmemb, size_t newnmemb, size_t size)
1990 {
1991 	size_t oldsize, newsize;
1992 	void *newptr;
1993 
1994 	if (ptr == NULL)
1995 		return calloc(newnmemb, size);
1996 
1997 	if ((newnmemb >= MUL_NO_OVERFLOW || size >= MUL_NO_OVERFLOW) &&
1998 	    newnmemb > 0 && SIZE_MAX / newnmemb < size) {
1999 		errno = ENOMEM;
2000 		return NULL;
2001 	}
2002 	newsize = newnmemb * size;
2003 
2004 	if ((oldnmemb >= MUL_NO_OVERFLOW || size >= MUL_NO_OVERFLOW) &&
2005 	    oldnmemb > 0 && SIZE_MAX / oldnmemb < size) {
2006 		errno = EINVAL;
2007 		return NULL;
2008 	}
2009 	oldsize = oldnmemb * size;
2010 
2011 	/*
2012 	 * Don't bother too much if we're shrinking just a bit,
2013 	 * we do not shrink for series of small steps, oh well.
2014 	 */
2015 	if (newsize <= oldsize) {
2016 		size_t d = oldsize - newsize;
2017 
2018 		if (d < oldsize / 2 && d < MALLOC_PAGESIZE) {
2019 			memset((char *)ptr + newsize, 0, d);
2020 			return ptr;
2021 		}
2022 	}
2023 
2024 	newptr = malloc(newsize);
2025 	if (newptr == NULL)
2026 		return NULL;
2027 
2028 	if (newsize > oldsize) {
2029 		memcpy(newptr, ptr, oldsize);
2030 		memset((char *)newptr + oldsize, 0, newsize - oldsize);
2031 	} else
2032 		memcpy(newptr, ptr, newsize);
2033 
2034 	explicit_bzero(ptr, oldsize);
2035 	free(ptr);
2036 
2037 	return newptr;
2038 }
2039 
2040 void *
2041 recallocarray(void *ptr, size_t oldnmemb, size_t newnmemb, size_t size)
2042 {
2043 	struct dir_info *d;
2044 	size_t oldsize = 0, newsize;
2045 	void *r;
2046 	int saved_errno = errno;
2047 
2048 	if (!mopts.internal_funcs)
2049 		return recallocarray_p(ptr, oldnmemb, newnmemb, size);
2050 
2051 	PROLOGUE(getpool(), "recallocarray")
2052 
2053 	if ((newnmemb >= MUL_NO_OVERFLOW || size >= MUL_NO_OVERFLOW) &&
2054 	    newnmemb > 0 && SIZE_MAX / newnmemb < size) {
2055 		d->active--;
2056 		_MALLOC_UNLOCK(d->mutex);
2057 		if (mopts.malloc_xmalloc)
2058 			wrterror(d, "out of memory");
2059 		errno = ENOMEM;
2060 		return NULL;
2061 	}
2062 	newsize = newnmemb * size;
2063 
2064 	if (ptr != NULL) {
2065 		if ((oldnmemb >= MUL_NO_OVERFLOW || size >= MUL_NO_OVERFLOW) &&
2066 		    oldnmemb > 0 && SIZE_MAX / oldnmemb < size) {
2067 			d->active--;
2068 			_MALLOC_UNLOCK(d->mutex);
2069 			errno = EINVAL;
2070 			return NULL;
2071 		}
2072 		oldsize = oldnmemb * size;
2073 	}
2074 
2075 	r = orecallocarray(&d, ptr, oldsize, newsize, CALLER);
2076 	EPILOGUE()
2077 	return r;
2078 }
2079 DEF_WEAK(recallocarray);
2080 
2081 static void *
2082 mapalign(struct dir_info *d, size_t alignment, size_t sz, int zero_fill)
2083 {
2084 	char *p, *q;
2085 
2086 	if (alignment < MALLOC_PAGESIZE || ((alignment - 1) & alignment) != 0)
2087 		wrterror(d, "mapalign bad alignment");
2088 	if (sz != PAGEROUND(sz))
2089 		wrterror(d, "mapalign round");
2090 
2091 	/* Allocate sz + alignment bytes of memory, which must include a
2092 	 * subrange of size bytes that is properly aligned.  Unmap the
2093 	 * other bytes, and then return that subrange.
2094 	 */
2095 
2096 	/* We need sz + alignment to fit into a size_t. */
2097 	if (alignment > SIZE_MAX - sz)
2098 		return MAP_FAILED;
2099 
2100 	p = map(d, sz + alignment, zero_fill);
2101 	if (p == MAP_FAILED)
2102 		return MAP_FAILED;
2103 	q = (char *)(((uintptr_t)p + alignment - 1) & ~(alignment - 1));
2104 	if (q != p) {
2105 		if (munmap(p, q - p))
2106 			wrterror(d, "munmap %p", p);
2107 	}
2108 	if (munmap(q + sz, alignment - (q - p)))
2109 		wrterror(d, "munmap %p", q + sz);
2110 	STATS_SUB(d->malloc_used, alignment);
2111 
2112 	return q;
2113 }
2114 
2115 static void *
2116 omemalign(struct dir_info *pool, size_t alignment, size_t sz, int zero_fill,
2117     void *f)
2118 {
2119 	size_t psz;
2120 	void *p;
2121 
2122 	/* If between half a page and a page, avoid MALLOC_MOVE. */
2123 	if (sz > MALLOC_MAXCHUNK && sz < MALLOC_PAGESIZE)
2124 		sz = MALLOC_PAGESIZE;
2125 	if (alignment <= MALLOC_PAGESIZE) {
2126 		size_t pof2;
2127 		/*
2128 		 * max(size, alignment) rounded up to power of 2 is enough
2129 		 * to assure the requested alignment. Large regions are
2130 		 * always page aligned.
2131 		 */
2132 		if (sz < alignment)
2133 			sz = alignment;
2134 		if (sz < MALLOC_PAGESIZE) {
2135 			pof2 = MALLOC_MINSIZE;
2136 			while (pof2 < sz)
2137 				pof2 <<= 1;
2138 		} else
2139 			pof2 = sz;
2140 		return omalloc(pool, pof2, zero_fill, f);
2141 	}
2142 
2143 	if (sz >= SIZE_MAX - mopts.malloc_guard - MALLOC_PAGESIZE) {
2144 		errno = ENOMEM;
2145 		return NULL;
2146 	}
2147 
2148 	if (sz < MALLOC_PAGESIZE)
2149 		sz = MALLOC_PAGESIZE;
2150 	sz += mopts.malloc_guard;
2151 	psz = PAGEROUND(sz);
2152 
2153 	p = mapalign(pool, alignment, psz, zero_fill);
2154 	if (p == MAP_FAILED) {
2155 		errno = ENOMEM;
2156 		return NULL;
2157 	}
2158 
2159 	if (insert(pool, p, sz, f)) {
2160 		unmap(pool, p, psz, 0);
2161 		errno = ENOMEM;
2162 		return NULL;
2163 	}
2164 
2165 	if (mopts.malloc_guard) {
2166 		if (mprotect((char *)p + psz - mopts.malloc_guard,
2167 		    mopts.malloc_guard, PROT_NONE))
2168 			wrterror(pool, "mprotect");
2169 		STATS_ADD(pool->malloc_guarded, mopts.malloc_guard);
2170 	}
2171 
2172 	if (pool->malloc_junk == 2) {
2173 		if (zero_fill)
2174 			memset((char *)p + sz - mopts.malloc_guard,
2175 			    SOME_JUNK, psz - sz);
2176 		else
2177 			memset(p, SOME_JUNK, psz - mopts.malloc_guard);
2178 	} else if (mopts.chunk_canaries)
2179 		fill_canary(p, sz - mopts.malloc_guard,
2180 		    psz - mopts.malloc_guard);
2181 
2182 	return p;
2183 }
2184 
2185 int
2186 posix_memalign(void **memptr, size_t alignment, size_t size)
2187 {
2188 	struct dir_info *d;
2189 	int res, saved_errno = errno;
2190 	void *r;
2191 
2192 	/* Make sure that alignment is a large enough power of 2. */
2193 	if (((alignment - 1) & alignment) != 0 || alignment < sizeof(void *))
2194 		return EINVAL;
2195 
2196 	d = getpool();
2197 	if (d == NULL) {
2198 		_malloc_init(0);
2199 		d = getpool();
2200 	}
2201 	_MALLOC_LOCK(d->mutex);
2202 	d->func = "posix_memalign";
2203 	if (d->active++) {
2204 		malloc_recurse(d);
2205 		goto err;
2206 	}
2207 	r = omemalign(d, alignment, size, 0, CALLER);
2208 	d->active--;
2209 	_MALLOC_UNLOCK(d->mutex);
2210 	if (r == NULL) {
2211 		if (mopts.malloc_xmalloc)
2212 			wrterror(d, "out of memory");
2213 		goto err;
2214 	}
2215 	errno = saved_errno;
2216 	*memptr = r;
2217 	return 0;
2218 
2219 err:
2220 	res = errno;
2221 	errno = saved_errno;
2222 	return res;
2223 }
2224 DEF_STRONG(posix_memalign);
2225 
2226 void *
2227 aligned_alloc(size_t alignment, size_t size)
2228 {
2229 	struct dir_info *d;
2230 	int saved_errno = errno;
2231 	void *r;
2232 
2233 	/* Make sure that alignment is a positive power of 2. */
2234 	if (((alignment - 1) & alignment) != 0 || alignment == 0) {
2235 		errno = EINVAL;
2236 		return NULL;
2237 	};
2238 	/* Per spec, size should be a multiple of alignment */
2239 	if ((size & (alignment - 1)) != 0) {
2240 		errno = EINVAL;
2241 		return NULL;
2242 	}
2243 
2244 	PROLOGUE(getpool(), "aligned_alloc")
2245 	r = omemalign(d, alignment, size, 0, CALLER);
2246 	EPILOGUE()
2247 	return r;
2248 }
2249 DEF_STRONG(aligned_alloc);
2250 
2251 #ifdef MALLOC_STATS
2252 
2253 static void
2254 ulog(const char *format, ...)
2255 {
2256 	va_list ap;
2257 	static char* buf;
2258 	static size_t filled;
2259 	int len;
2260 
2261 	if (buf == NULL)
2262 		buf = MMAP(KTR_USER_MAXLEN, 0);
2263 	if (buf == MAP_FAILED)
2264 		return;
2265 
2266 	va_start(ap, format);
2267 	len = vsnprintf(buf + filled, KTR_USER_MAXLEN - filled, format, ap);
2268 	va_end(ap);
2269 	if (len < 0)
2270 		return;
2271 	if (len > KTR_USER_MAXLEN - filled)
2272 		len = KTR_USER_MAXLEN - filled;
2273 	filled += len;
2274 	if (filled > 0) {
2275 		if (filled == KTR_USER_MAXLEN || buf[filled - 1] == '\n') {
2276 			utrace("malloc", buf, filled);
2277 			filled = 0;
2278 		}
2279 	}
2280 }
2281 
2282 struct malloc_leak {
2283 	void *f;
2284 	size_t total_size;
2285 	int count;
2286 };
2287 
2288 struct leaknode {
2289 	RBT_ENTRY(leaknode) entry;
2290 	struct malloc_leak d;
2291 };
2292 
2293 static inline int
2294 leakcmp(const struct leaknode *e1, const struct leaknode *e2)
2295 {
2296 	return e1->d.f < e2->d.f ? -1 : e1->d.f > e2->d.f;
2297 }
2298 
2299 RBT_HEAD(leaktree, leaknode);
2300 RBT_PROTOTYPE(leaktree, leaknode, entry, leakcmp);
2301 RBT_GENERATE(leaktree, leaknode, entry, leakcmp);
2302 
2303 static void
2304 putleakinfo(struct leaktree *leaks, void *f, size_t sz, int cnt)
2305 {
2306 	struct leaknode key, *p;
2307 	static struct leaknode *page;
2308 	static unsigned int used;
2309 
2310 	if (cnt == 0 || page == MAP_FAILED)
2311 		return;
2312 
2313 	key.d.f = f;
2314 	p = RBT_FIND(leaktree, leaks, &key);
2315 	if (p == NULL) {
2316 		if (page == NULL ||
2317 		    used >= MALLOC_PAGESIZE / sizeof(struct leaknode)) {
2318 			page = MMAP(MALLOC_PAGESIZE, 0);
2319 			if (page == MAP_FAILED)
2320 				return;
2321 			used = 0;
2322 		}
2323 		p = &page[used++];
2324 		p->d.f = f;
2325 		p->d.total_size = sz * cnt;
2326 		p->d.count = cnt;
2327 		RBT_INSERT(leaktree, leaks, p);
2328 	} else {
2329 		p->d.total_size += sz * cnt;
2330 		p->d.count += cnt;
2331 	}
2332 }
2333 
2334 static void
2335 dump_leaks(struct leaktree *leaks)
2336 {
2337 	struct leaknode *p;
2338 
2339 	ulog("Leak report:\n");
2340 	ulog("                 f     sum      #    avg\n");
2341 
2342 	RBT_FOREACH(p, leaktree, leaks) {
2343 		Dl_info info;
2344 		const char *caller = p->d.f;
2345 		const char *object = ".";
2346 
2347 		if (caller != NULL) {
2348 			if (dladdr(p->d.f, &info) != 0) {
2349 				caller -= (uintptr_t)info.dli_fbase;
2350 				object = info.dli_fname;
2351 			}
2352 		}
2353 		ulog("%18p %7zu %6u %6zu addr2line -e %s %p\n",
2354 		    p->d.f, p->d.total_size, p->d.count,
2355 		    p->d.total_size / p->d.count,
2356 		    object, caller);
2357 	}
2358 }
2359 
2360 static void
2361 dump_chunk(struct leaktree* leaks, struct chunk_info *p, void *f,
2362     int fromfreelist)
2363 {
2364 	while (p != NULL) {
2365 		if (mopts.malloc_verbose)
2366 			ulog("chunk %18p %18p %4zu %d/%d\n",
2367 			    p->page, ((p->bits[0] & 1) ? NULL : f),
2368 			    B2SIZE(p->bucket), p->free, p->total);
2369 		if (!fromfreelist) {
2370 			size_t sz =  B2SIZE(p->bucket);
2371 			if (p->bits[0] & 1)
2372 				putleakinfo(leaks, NULL, sz, p->total -
2373 				    p->free);
2374 			else {
2375 				putleakinfo(leaks, f, sz, 1);
2376 				putleakinfo(leaks, NULL, sz,
2377 				    p->total - p->free - 1);
2378 			}
2379 			break;
2380 		}
2381 		p = LIST_NEXT(p, entries);
2382 		if (mopts.malloc_verbose && p != NULL)
2383 			ulog("       ->");
2384 	}
2385 }
2386 
2387 static void
2388 dump_free_chunk_info(struct dir_info *d, struct leaktree *leaks)
2389 {
2390 	int i, j, count;
2391 	struct chunk_info *p;
2392 
2393 	ulog("Free chunk structs:\n");
2394 	ulog("Bkt) #CI                     page"
2395 	    "                  f size free/n\n");
2396 	for (i = 0; i <= BUCKETS; i++) {
2397 		count = 0;
2398 		LIST_FOREACH(p, &d->chunk_info_list[i], entries)
2399 			count++;
2400 		for (j = 0; j < MALLOC_CHUNK_LISTS; j++) {
2401 			p = LIST_FIRST(&d->chunk_dir[i][j]);
2402 			if (p == NULL && count == 0)
2403 				continue;
2404 			if (j == 0)
2405 				ulog("%3d) %3d ", i, count);
2406 			else
2407 				ulog("         ");
2408 			if (p != NULL)
2409 				dump_chunk(leaks, p, NULL, 1);
2410 			else
2411 				ulog(".\n");
2412 		}
2413 	}
2414 
2415 }
2416 
2417 static void
2418 dump_free_page_info(struct dir_info *d)
2419 {
2420 	struct smallcache *cache;
2421 	size_t i, total = 0;
2422 
2423 	ulog("Cached in small cache:\n");
2424 	for (i = 0; i < MAX_SMALLCACHEABLE_SIZE; i++) {
2425 		cache = &d->smallcache[i];
2426 		if (cache->length != 0)
2427 			ulog("%zu(%u): %u = %zu\n", i + 1, cache->max,
2428 			    cache->length, cache->length * (i + 1));
2429 		total += cache->length * (i + 1);
2430 	}
2431 
2432 	ulog("Cached in big cache: %zu/%zu\n", d->bigcache_used,
2433 	    d->bigcache_size);
2434 	for (i = 0; i < d->bigcache_size; i++) {
2435 		if (d->bigcache[i].psize != 0)
2436 			ulog("%zu: %zu\n", i, d->bigcache[i].psize);
2437 		total += d->bigcache[i].psize;
2438 	}
2439 	ulog("Free pages cached: %zu\n", total);
2440 }
2441 
2442 static void
2443 malloc_dump1(int poolno, struct dir_info *d, struct leaktree *leaks)
2444 {
2445 	size_t i, realsize;
2446 
2447 	if (mopts.malloc_verbose) {
2448 		ulog("Malloc dir of %s pool %d at %p\n", __progname, poolno, d);
2449 		ulog("MT=%d J=%d Fl=%x\n", d->malloc_mt, d->malloc_junk,
2450 		    d->mmap_flag);
2451 		ulog("Region slots free %zu/%zu\n",
2452 			d->regions_free, d->regions_total);
2453 		ulog("Finds %zu/%zu\n", d->finds, d->find_collisions);
2454 		ulog("Inserts %zu/%zu\n", d->inserts, d->insert_collisions);
2455 		ulog("Deletes %zu/%zu\n", d->deletes, d->delete_moves);
2456 		ulog("Cheap reallocs %zu/%zu\n",
2457 		    d->cheap_reallocs, d->cheap_realloc_tries);
2458 		ulog("Other pool searches %zu/%zu\n",
2459 		    d->other_pool, d->pool_searches);
2460 		ulog("In use %zu\n", d->malloc_used);
2461 		ulog("Guarded %zu\n", d->malloc_guarded);
2462 		dump_free_chunk_info(d, leaks);
2463 		dump_free_page_info(d);
2464 		ulog("Hash table:\n");
2465 		ulog("slot)  hash d  type               page                  "
2466 		    "f size [free/n]\n");
2467 	}
2468 	for (i = 0; i < d->regions_total; i++) {
2469 		if (d->r[i].p != NULL) {
2470 			size_t h = hash(d->r[i].p) &
2471 			    (d->regions_total - 1);
2472 			if (mopts.malloc_verbose)
2473 				ulog("%4zx) #%4zx %zd ",
2474 			        i, h, h - i);
2475 			REALSIZE(realsize, &d->r[i]);
2476 			if (realsize > MALLOC_MAXCHUNK) {
2477 				putleakinfo(leaks, d->r[i].f, realsize, 1);
2478 				if (mopts.malloc_verbose)
2479 					ulog("pages %18p %18p %zu\n", d->r[i].p,
2480 				        d->r[i].f, realsize);
2481 			} else
2482 				dump_chunk(leaks,
2483 				    (struct chunk_info *)d->r[i].size,
2484 				    d->r[i].f, 0);
2485 		}
2486 	}
2487 	if (mopts.malloc_verbose)
2488 		ulog("\n");
2489 }
2490 
2491 static void
2492 malloc_dump0(int poolno, struct dir_info *pool, struct leaktree *leaks)
2493 {
2494 	int i;
2495 	void *p;
2496 	struct region_info *r;
2497 
2498 	if (pool == NULL || pool->r == NULL)
2499 		return;
2500 	for (i = 0; i < MALLOC_DELAYED_CHUNK_MASK + 1; i++) {
2501 		p = pool->delayed_chunks[i];
2502 		if (p == NULL)
2503 			continue;
2504 		r = find(pool, p);
2505 		if (r == NULL)
2506 			wrterror(pool, "bogus pointer in malloc_dump %p", p);
2507 		free_bytes(pool, r, p);
2508 		pool->delayed_chunks[i] = NULL;
2509 	}
2510 	malloc_dump1(poolno, pool, leaks);
2511 }
2512 
2513 void
2514 malloc_dump(void)
2515 {
2516 	int i;
2517 	int saved_errno = errno;
2518 
2519 	/* XXX leak when run multiple times */
2520 	struct leaktree leaks = RBT_INITIALIZER(&leaks);
2521 
2522 	for (i = 0; i < mopts.malloc_mutexes; i++)
2523 		malloc_dump0(i, mopts.malloc_pool[i], &leaks);
2524 
2525 	dump_leaks(&leaks);
2526 	ulog("\n");
2527 	errno = saved_errno;
2528 }
2529 DEF_WEAK(malloc_dump);
2530 
2531 static void
2532 malloc_exit(void)
2533 {
2534 	int save_errno = errno;
2535 
2536 	ulog("******** Start dump %s *******\n", __progname);
2537 	ulog("M=%u I=%d F=%d U=%d J=%d R=%d X=%d C=%d cache=%u "
2538 	    "G=%zu\n",
2539 	    mopts.malloc_mutexes,
2540 	    mopts.internal_funcs, mopts.malloc_freecheck,
2541 	    mopts.malloc_freeunmap, mopts.def_malloc_junk,
2542 	    mopts.malloc_realloc, mopts.malloc_xmalloc,
2543 	    mopts.chunk_canaries, mopts.def_maxcache,
2544 	    mopts.malloc_guard);
2545 
2546 	malloc_dump();
2547 	ulog("******** End dump %s *******\n", __progname);
2548 	errno = save_errno;
2549 }
2550 
2551 #endif /* MALLOC_STATS */
2552