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