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