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