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