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