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