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