xref: /openbsd-src/lib/libc/stdlib/malloc.c (revision d13be5d47e4149db2549a9828e244d59dbc43f15)
1 /*	$OpenBSD: malloc.c,v 1.139 2011/07/12 14:43:42 otto Exp $	*/
2 /*
3  * Copyright (c) 2008 Otto Moerbeek <otto@drijf.net>
4  *
5  * Permission to use, copy, modify, and distribute this software for any
6  * purpose with or without fee is hereby granted, provided that the above
7  * copyright notice and this permission notice appear in all copies.
8  *
9  * THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES
10  * WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF
11  * MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR
12  * ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES
13  * WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN
14  * ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF
15  * OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.
16  */
17 
18 /*
19  * Parts of this code, mainly the sub page sized chunk management code is
20  * derived from the malloc implementation with the following license:
21  */
22 /*
23  * ----------------------------------------------------------------------------
24  * "THE BEER-WARE LICENSE" (Revision 42):
25  * <phk@FreeBSD.ORG> wrote this file.  As long as you retain this notice you
26  * can do whatever you want with this stuff. If we meet some day, and you think
27  * this stuff is worth it, you can buy me a beer in return.  Poul-Henning Kamp
28  * ----------------------------------------------------------------------------
29  */
30 
31 /* #define MALLOC_STATS */
32 
33 #include <sys/types.h>
34 #include <sys/param.h>
35 #include <sys/queue.h>
36 #include <sys/mman.h>
37 #include <sys/uio.h>
38 #include <errno.h>
39 #include <stdint.h>
40 #include <stdlib.h>
41 #include <string.h>
42 #include <stdio.h>
43 #include <unistd.h>
44 
45 #ifdef MALLOC_STATS
46 #include <sys/tree.h>
47 #include <fcntl.h>
48 #endif
49 
50 #include "thread_private.h"
51 
52 #if defined(__sparc__) && !defined(__sparcv9__)
53 #define MALLOC_PAGESHIFT	(13U)
54 #elif defined(__mips64__)
55 #define MALLOC_PAGESHIFT	(14U)
56 #else
57 #define MALLOC_PAGESHIFT	(PGSHIFT)
58 #endif
59 
60 #define MALLOC_MINSHIFT		4
61 #define MALLOC_MAXSHIFT		(MALLOC_PAGESHIFT - 1)
62 #define MALLOC_PAGESIZE		(1UL << MALLOC_PAGESHIFT)
63 #define MALLOC_MINSIZE		(1UL << MALLOC_MINSHIFT)
64 #define MALLOC_PAGEMASK		(MALLOC_PAGESIZE - 1)
65 #define MASK_POINTER(p)		((void *)(((uintptr_t)(p)) & ~MALLOC_PAGEMASK))
66 
67 #define MALLOC_MAXCHUNK		(1 << MALLOC_MAXSHIFT)
68 #define MALLOC_MAXCACHE		256
69 #define MALLOC_DELAYED_CHUNKS	15	/* max of getrnibble() */
70 #define MALLOC_INITIAL_REGIONS	512
71 #define MALLOC_DEFAULT_CACHE	64
72 
73 /*
74  * When the P option is active, we move allocations between half a page
75  * and a whole page towards the end, subject to alignment constraints.
76  * This is the extra headroom we allow. Set to zero to be the most
77  * strict.
78  */
79 #define MALLOC_LEEWAY		0
80 
81 #define PAGEROUND(x)  (((x) + (MALLOC_PAGEMASK)) & ~MALLOC_PAGEMASK)
82 
83 /*
84  * What to use for Junk.  This is the byte value we use to fill with
85  * when the 'J' option is enabled. Use SOME_JUNK right after alloc,
86  * and SOME_FREEJUNK right before free.
87  */
88 #define SOME_JUNK		0xd0	/* as in "Duh" :-) */
89 #define SOME_FREEJUNK		0xdf
90 
91 #define MMAP(sz)	mmap(NULL, (size_t)(sz), PROT_READ | PROT_WRITE, \
92     MAP_ANON | MAP_PRIVATE, -1, (off_t) 0)
93 
94 #define MMAPA(a,sz)	mmap((a), (size_t)(sz), PROT_READ | PROT_WRITE, \
95     MAP_ANON | MAP_PRIVATE, -1, (off_t) 0)
96 
97 struct region_info {
98 	void *p;		/* page; low bits used to mark chunks */
99 	uintptr_t size;		/* size for pages, or chunk_info pointer */
100 #ifdef MALLOC_STATS
101 	void *f;		/* where allocated from */
102 #endif
103 };
104 
105 LIST_HEAD(chunk_head, chunk_info);
106 
107 struct dir_info {
108 	u_int32_t canary1;
109 	struct region_info *r;		/* region slots */
110 	size_t regions_total;		/* number of region slots */
111 	size_t regions_free;		/* number of free slots */
112 					/* list of free chunk info structs */
113 	struct chunk_head chunk_info_list;
114 					/* lists of chunks with free slots */
115 	struct chunk_head chunk_dir[MALLOC_MAXSHIFT + 1];
116 	size_t free_regions_size;	/* free pages cached */
117 					/* free pages cache */
118 	struct region_info free_regions[MALLOC_MAXCACHE];
119 					/* delayed free chunk slots */
120 	void *delayed_chunks[MALLOC_DELAYED_CHUNKS + 1];
121 	u_short chunk_start;
122 #ifdef MALLOC_STATS
123 	size_t inserts;
124 	size_t insert_collisions;
125 	size_t finds;
126 	size_t find_collisions;
127 	size_t deletes;
128 	size_t delete_moves;
129 	size_t cheap_realloc_tries;
130 	size_t cheap_reallocs;
131 #define STATS_INC(x) ((x)++)
132 #define STATS_ZERO(x) ((x) = 0)
133 #define STATS_SETF(x,y) ((x)->f = (y))
134 #else
135 #define STATS_INC(x)	/* nothing */
136 #define STATS_ZERO(x)	/* nothing */
137 #define STATS_SETF(x,y)	/* nothing */
138 #endif /* MALLOC_STATS */
139 	u_int32_t canary2;
140 };
141 #define DIR_INFO_RSZ	((sizeof(struct dir_info) + MALLOC_PAGEMASK) & \
142 			~MALLOC_PAGEMASK)
143 
144 /*
145  * This structure describes a page worth of chunks.
146  *
147  * How many bits per u_short in the bitmap
148  */
149 #define MALLOC_BITS		(NBBY * sizeof(u_short))
150 struct chunk_info {
151 	LIST_ENTRY(chunk_info) entries;
152 	void *page;			/* pointer to the page */
153 	u_int32_t canary;
154 	u_short size;			/* size of this page's chunks */
155 	u_short shift;			/* how far to shift for this size */
156 	u_short free;			/* how many free chunks */
157 	u_short total;			/* how many chunk */
158 					/* which chunks are free */
159 	u_short bits[(MALLOC_PAGESIZE / MALLOC_MINSIZE) / MALLOC_BITS];
160 };
161 
162 struct malloc_readonly {
163 	struct dir_info *g_pool;	/* Main bookkeeping information */
164 	int	malloc_abort;		/* abort() on error */
165 	int	malloc_freeprot;	/* mprotect free pages PROT_NONE? */
166 	int	malloc_hint;		/* call madvice on free pages?  */
167 	int	malloc_junk;		/* junk fill? */
168 	int	malloc_move;		/* move allocations to end of page? */
169 	int	malloc_realloc;		/* always realloc? */
170 	int	malloc_xmalloc;		/* xmalloc behaviour? */
171 	int	malloc_zero;		/* zero fill? */
172 	size_t	malloc_guard;		/* use guard pages after allocations? */
173 	u_int	malloc_cache;		/* free pages we cache */
174 #ifdef MALLOC_STATS
175 	int	malloc_stats;		/* dump statistics at end */
176 #endif
177 	u_int32_t malloc_canary;	/* Matched against ones in g_pool */
178 };
179 
180 /* This object is mapped PROT_READ after initialisation to prevent tampering */
181 static union {
182 	struct malloc_readonly mopts;
183 	u_char _pad[MALLOC_PAGESIZE];
184 } malloc_readonly __attribute__((aligned(MALLOC_PAGESIZE)));
185 #define mopts	malloc_readonly.mopts
186 #define g_pool	mopts.g_pool
187 
188 char		*malloc_options;	/* compile-time options */
189 
190 static char	*malloc_func;		/* current function */
191 static int	malloc_active;		/* status of malloc */
192 
193 static size_t	malloc_guarded;		/* bytes used for guards */
194 static size_t	malloc_used;		/* bytes allocated */
195 
196 static size_t rnibblesused;		/* random nibbles used */
197 static u_char rbytes[512];		/* random bytes */
198 static u_char getrnibble(void);
199 
200 extern char	*__progname;
201 
202 #ifdef MALLOC_STATS
203 void malloc_dump(int);
204 static void malloc_exit(void);
205 #define CALLER	__builtin_return_address(0)
206 #else
207 #define CALLER	NULL
208 #endif
209 
210 /* low bits of r->p determine size: 0 means >= page size and p->size holding
211  *  real size, otherwise r->size is a shift count, or 1 for malloc(0)
212  */
213 #define REALSIZE(sz, r) 					\
214 	(sz) = (uintptr_t)(r)->p & MALLOC_PAGEMASK,		\
215 	(sz) = ((sz) == 0 ? (r)->size : ((sz) == 1 ? 0 : (1 << ((sz)-1))))
216 
217 static inline size_t
218 hash(void *p)
219 {
220 	size_t sum;
221 	union {
222 		uintptr_t p;
223 		unsigned short a[sizeof(void *) / sizeof(short)];
224 	} u;
225 	u.p = (uintptr_t)p >> MALLOC_PAGESHIFT;
226 	sum = u.a[0];
227 	sum = (sum << 7) - sum + u.a[1];
228 #ifdef __LP64__
229 	sum = (sum << 7) - sum + u.a[2];
230 	sum = (sum << 7) - sum + u.a[3];
231 #endif
232 	return sum;
233 }
234 
235 static void
236 wrterror(char *msg, void *p)
237 {
238 	char		*q = " error: ";
239 	struct iovec	iov[6];
240 	char		buf[20];
241 	int		saved_errno = errno;
242 
243 	iov[0].iov_base = __progname;
244 	iov[0].iov_len = strlen(__progname);
245 	iov[1].iov_base = malloc_func;
246 	iov[1].iov_len = strlen(malloc_func);
247 	iov[2].iov_base = q;
248 	iov[2].iov_len = strlen(q);
249 	iov[3].iov_base = msg;
250 	iov[3].iov_len = strlen(msg);
251 	iov[4].iov_base = buf;
252 	if (p == NULL)
253 		iov[4].iov_len = 0;
254 	else {
255 		snprintf(buf, sizeof(buf), " %p", p);
256 		iov[4].iov_len = strlen(buf);
257 	}
258 	iov[5].iov_base = "\n";
259 	iov[5].iov_len = 1;
260 	writev(STDERR_FILENO, iov, 6);
261 
262 #ifdef MALLOC_STATS
263 	if (mopts.malloc_stats)
264 		malloc_dump(STDERR_FILENO);
265 #endif /* MALLOC_STATS */
266 
267 	errno = saved_errno;
268 	if (mopts.malloc_abort)
269 		abort();
270 }
271 
272 static void
273 rbytes_init(void)
274 {
275 	arc4random_buf(rbytes, sizeof(rbytes));
276 	rnibblesused = 0;
277 }
278 
279 static inline u_char
280 getrnibble(void)
281 {
282 	u_char x;
283 
284 	if (rnibblesused >= 2 * sizeof(rbytes))
285 		rbytes_init();
286 	x = rbytes[rnibblesused++ / 2];
287 	return (rnibblesused & 1 ? x & 0xf : x >> 4);
288 }
289 
290 /*
291  * Cache maintenance. We keep at most malloc_cache pages cached.
292  * If the cache is becoming full, unmap pages in the cache for real,
293  * and then add the region to the cache
294  * Opposed to the regular region data structure, the sizes in the
295  * cache are in MALLOC_PAGESIZE units.
296  */
297 static void
298 unmap(struct dir_info *d, void *p, size_t sz)
299 {
300 	size_t psz = sz >> MALLOC_PAGESHIFT;
301 	size_t rsz, tounmap;
302 	struct region_info *r;
303 	u_int i, offset;
304 
305 	if (sz != PAGEROUND(sz)) {
306 		wrterror("munmap round", NULL);
307 		return;
308 	}
309 
310 	if (psz > mopts.malloc_cache) {
311 		if (munmap(p, sz))
312 			wrterror("munmap", p);
313 		malloc_used -= sz;
314 		return;
315 	}
316 	tounmap = 0;
317 	rsz = mopts.malloc_cache - d->free_regions_size;
318 	if (psz > rsz)
319 		tounmap = psz - rsz;
320 	offset = getrnibble();
321 	for (i = 0; tounmap > 0 && i < mopts.malloc_cache; i++) {
322 		r = &d->free_regions[(i + offset) & (mopts.malloc_cache - 1)];
323 		if (r->p != NULL) {
324 			rsz = r->size << MALLOC_PAGESHIFT;
325 			if (munmap(r->p, rsz))
326 				wrterror("munmap", r->p);
327 			r->p = NULL;
328 			if (tounmap > r->size)
329 				tounmap -= r->size;
330 			else
331 				tounmap = 0;
332 			d->free_regions_size -= r->size;
333 			r->size = 0;
334 			malloc_used -= rsz;
335 		}
336 	}
337 	if (tounmap > 0)
338 		wrterror("malloc cache underflow", NULL);
339 	for (i = 0; i < mopts.malloc_cache; i++) {
340 		r = &d->free_regions[i];
341 		if (r->p == NULL) {
342 			if (mopts.malloc_hint)
343 				madvise(p, sz, MADV_FREE);
344 			if (mopts.malloc_freeprot)
345 				mprotect(p, sz, PROT_NONE);
346 			r->p = p;
347 			r->size = psz;
348 			d->free_regions_size += psz;
349 			break;
350 		}
351 	}
352 	if (i == mopts.malloc_cache)
353 		wrterror("malloc free slot lost", NULL);
354 	if (d->free_regions_size > mopts.malloc_cache)
355 		wrterror("malloc cache overflow", NULL);
356 }
357 
358 static void
359 zapcacheregion(struct dir_info *d, void *p)
360 {
361 	u_int i;
362 	struct region_info *r;
363 	size_t rsz;
364 
365 	for (i = 0; i < mopts.malloc_cache; i++) {
366 		r = &d->free_regions[i];
367 		if (r->p == p) {
368 			rsz = r->size << MALLOC_PAGESHIFT;
369 			if (munmap(r->p, rsz))
370 				wrterror("munmap", r->p);
371 			r->p = NULL;
372 			d->free_regions_size -= r->size;
373 			r->size = 0;
374 			malloc_used -= rsz;
375 		}
376 	}
377 }
378 
379 static void *
380 map(struct dir_info *d, size_t sz, int zero_fill)
381 {
382 	size_t psz = sz >> MALLOC_PAGESHIFT;
383 	struct region_info *r, *big = NULL;
384 	u_int i, offset;
385 	void *p;
386 
387 	if (mopts.malloc_canary != (d->canary1 ^ (u_int32_t)(uintptr_t)d) ||
388 	    d->canary1 != ~d->canary2)
389 		wrterror("internal struct corrupt", NULL);
390 	if (sz != PAGEROUND(sz)) {
391 		wrterror("map round", NULL);
392 		return NULL;
393 	}
394 	if (psz > d->free_regions_size) {
395 		p = MMAP(sz);
396 		if (p != MAP_FAILED)
397 			malloc_used += sz;
398 		/* zero fill not needed */
399 		return p;
400 	}
401 	offset = getrnibble();
402 	for (i = 0; i < mopts.malloc_cache; i++) {
403 		r = &d->free_regions[(i + offset) & (mopts.malloc_cache - 1)];
404 		if (r->p != NULL) {
405 			if (r->size == psz) {
406 				p = r->p;
407 				if (mopts.malloc_freeprot)
408 					mprotect(p, sz, PROT_READ | PROT_WRITE);
409 				if (mopts.malloc_hint)
410 					madvise(p, sz, MADV_NORMAL);
411 				r->p = NULL;
412 				r->size = 0;
413 				d->free_regions_size -= psz;
414 				if (zero_fill)
415 					memset(p, 0, sz);
416 				else if (mopts.malloc_junk &&
417 				    mopts.malloc_freeprot)
418 					memset(p, SOME_FREEJUNK, sz);
419 				return p;
420 			} else if (r->size > psz)
421 				big = r;
422 		}
423 	}
424 	if (big != NULL) {
425 		r = big;
426 		p = (char *)r->p + ((r->size - psz) << MALLOC_PAGESHIFT);
427 		if (mopts.malloc_freeprot)
428 			mprotect(p, sz, PROT_READ | PROT_WRITE);
429 		if (mopts.malloc_hint)
430 			madvise(p, sz, MADV_NORMAL);
431 		r->size -= psz;
432 		d->free_regions_size -= psz;
433 		if (zero_fill)
434 			memset(p, 0, sz);
435 		else if (mopts.malloc_junk && mopts.malloc_freeprot)
436 			memset(p, SOME_FREEJUNK, sz);
437 		return p;
438 	}
439 	p = MMAP(sz);
440 	if (p != MAP_FAILED)
441 		malloc_used += sz;
442 	if (d->free_regions_size > mopts.malloc_cache)
443 		wrterror("malloc cache", NULL);
444 	/* zero fill not needed */
445 	return p;
446 }
447 
448 /*
449  * Initialize a dir_info, which should have been cleared by caller
450  */
451 static int
452 omalloc_init(struct dir_info **dp)
453 {
454 	char *p, b[64];
455 	int i, j;
456 	size_t d_avail, regioninfo_size;
457 	struct dir_info *d;
458 
459 	rbytes_init();
460 
461 	/*
462 	 * Default options
463 	 */
464 	mopts.malloc_abort = 1;
465 	mopts.malloc_move = 1;
466 	mopts.malloc_cache = MALLOC_DEFAULT_CACHE;
467 
468 	for (i = 0; i < 3; i++) {
469 		switch (i) {
470 		case 0:
471 			j = readlink("/etc/malloc.conf", b, sizeof b - 1);
472 			if (j <= 0)
473 				continue;
474 			b[j] = '\0';
475 			p = b;
476 			break;
477 		case 1:
478 			if (issetugid() == 0)
479 				p = getenv("MALLOC_OPTIONS");
480 			else
481 				continue;
482 			break;
483 		case 2:
484 			p = malloc_options;
485 			break;
486 		default:
487 			p = NULL;
488 		}
489 
490 		for (; p != NULL && *p != '\0'; p++) {
491 			switch (*p) {
492 			case '>':
493 				mopts.malloc_cache <<= 1;
494 				if (mopts.malloc_cache > MALLOC_MAXCACHE)
495 					mopts.malloc_cache = MALLOC_MAXCACHE;
496 				break;
497 			case '<':
498 				mopts.malloc_cache >>= 1;
499 				break;
500 			case 'a':
501 				mopts.malloc_abort = 0;
502 				break;
503 			case 'A':
504 				mopts.malloc_abort = 1;
505 				break;
506 #ifdef MALLOC_STATS
507 			case 'd':
508 				mopts.malloc_stats = 0;
509 				break;
510 			case 'D':
511 				mopts.malloc_stats = 1;
512 				break;
513 #endif /* MALLOC_STATS */
514 			case 'f':
515 				mopts.malloc_freeprot = 0;
516 				break;
517 			case 'F':
518 				mopts.malloc_freeprot = 1;
519 				break;
520 			case 'g':
521 				mopts.malloc_guard = 0;
522 				break;
523 			case 'G':
524 				mopts.malloc_guard = MALLOC_PAGESIZE;
525 				break;
526 			case 'h':
527 				mopts.malloc_hint = 0;
528 				break;
529 			case 'H':
530 				mopts.malloc_hint = 1;
531 				break;
532 			case 'j':
533 				mopts.malloc_junk = 0;
534 				break;
535 			case 'J':
536 				mopts.malloc_junk = 1;
537 				break;
538 			case 'n':
539 			case 'N':
540 				break;
541 			case 'p':
542 				mopts.malloc_move = 0;
543 				break;
544 			case 'P':
545 				mopts.malloc_move = 1;
546 				break;
547 			case 'r':
548 				mopts.malloc_realloc = 0;
549 				break;
550 			case 'R':
551 				mopts.malloc_realloc = 1;
552 				break;
553 			case 's':
554 				mopts.malloc_freeprot = mopts.malloc_junk = 0;
555 				mopts.malloc_guard = 0;
556 				mopts.malloc_cache = MALLOC_DEFAULT_CACHE;
557 				break;
558 			case 'S':
559 				mopts.malloc_freeprot = mopts.malloc_junk = 1;
560 				mopts.malloc_guard = MALLOC_PAGESIZE;
561 				mopts.malloc_cache = 0;
562 				break;
563 			case 'x':
564 				mopts.malloc_xmalloc = 0;
565 				break;
566 			case 'X':
567 				mopts.malloc_xmalloc = 1;
568 				break;
569 			case 'z':
570 				mopts.malloc_zero = 0;
571 				break;
572 			case 'Z':
573 				mopts.malloc_zero = 1;
574 				break;
575 			default: {
576 				static const char q[] = "malloc() warning: "
577 				    "unknown char in MALLOC_OPTIONS\n";
578 				write(STDERR_FILENO, q, sizeof(q) - 1);
579 				break;
580 			}
581 			}
582 		}
583 	}
584 
585 	/*
586 	 * We want junk in the entire allocation, and zero only in the part
587 	 * the user asked for.
588 	 */
589 	if (mopts.malloc_zero)
590 		mopts.malloc_junk = 1;
591 
592 #ifdef MALLOC_STATS
593 	if (mopts.malloc_stats && (atexit(malloc_exit) == -1)) {
594 		static const char q[] = "malloc() warning: atexit(2) failed."
595 		    " Will not be able to dump stats on exit\n";
596 		write(STDERR_FILENO, q, sizeof(q) - 1);
597 	}
598 #endif /* MALLOC_STATS */
599 
600 	while ((mopts.malloc_canary = arc4random()) == 0)
601 		;
602 
603 	/*
604 	 * Allocate dir_info with a guard page on either side. Also
605 	 * randomise offset inside the page at which the dir_info
606 	 * lies (subject to alignment by 1 << MALLOC_MINSHIFT)
607 	 */
608 	if ((p = MMAP(DIR_INFO_RSZ + (MALLOC_PAGESIZE * 2))) == MAP_FAILED)
609 		return -1;
610 	mprotect(p, MALLOC_PAGESIZE, PROT_NONE);
611 	mprotect(p + MALLOC_PAGESIZE + DIR_INFO_RSZ,
612 	    MALLOC_PAGESIZE, PROT_NONE);
613 	d_avail = (DIR_INFO_RSZ - sizeof(*d)) >> MALLOC_MINSHIFT;
614 	d = (struct dir_info *)(p + MALLOC_PAGESIZE +
615 	    (arc4random_uniform(d_avail) << MALLOC_MINSHIFT));
616 
617 	d->regions_free = d->regions_total = MALLOC_INITIAL_REGIONS;
618 	regioninfo_size = d->regions_total * sizeof(struct region_info);
619 	d->r = MMAP(regioninfo_size);
620 	if (d->r == MAP_FAILED) {
621 		wrterror("malloc init mmap failed", NULL);
622 		d->regions_total = 0;
623 		return 1;
624 	}
625 	LIST_INIT(&d->chunk_info_list);
626 	for (i = 0; i <= MALLOC_MAXSHIFT; i++)
627 		LIST_INIT(&d->chunk_dir[i]);
628 	malloc_used += regioninfo_size;
629 	d->canary1 = mopts.malloc_canary ^ (u_int32_t)(uintptr_t)d;
630 	d->canary2 = ~d->canary1;
631 
632 	*dp = d;
633 
634 	/*
635 	 * Options have been set and will never be reset.
636 	 * Prevent further tampering with them.
637 	 */
638 	if (((uintptr_t)&malloc_readonly & MALLOC_PAGEMASK) == 0)
639 		mprotect(&malloc_readonly, sizeof(malloc_readonly), PROT_READ);
640 
641 	return 0;
642 }
643 
644 static int
645 omalloc_grow(struct dir_info *d)
646 {
647 	size_t newtotal;
648 	size_t newsize;
649 	size_t mask;
650 	size_t i;
651 	struct region_info *p;
652 
653 	if (d->regions_total > SIZE_MAX / sizeof(struct region_info) / 2 )
654 		return 1;
655 
656 	newtotal = d->regions_total * 2;
657 	newsize = newtotal * sizeof(struct region_info);
658 	mask = newtotal - 1;
659 
660 	p = MMAP(newsize);
661 	if (p == MAP_FAILED)
662 		return 1;
663 
664 	malloc_used += newsize;
665 	memset(p, 0, newsize);
666 	STATS_ZERO(d->inserts);
667 	STATS_ZERO(d->insert_collisions);
668 	for (i = 0; i < d->regions_total; i++) {
669 		void *q = d->r[i].p;
670 		if (q != NULL) {
671 			size_t index = hash(q) & mask;
672 			STATS_INC(d->inserts);
673 			while (p[index].p != NULL) {
674 				index = (index - 1) & mask;
675 				STATS_INC(d->insert_collisions);
676 			}
677 			p[index] = d->r[i];
678 		}
679 	}
680 	/* avoid pages containing meta info to end up in cache */
681 	if (munmap(d->r, d->regions_total * sizeof(struct region_info)))
682 		wrterror("munmap", d->r);
683 	else
684 		malloc_used -= d->regions_total * sizeof(struct region_info);
685 	d->regions_free = d->regions_free + d->regions_total;
686 	d->regions_total = newtotal;
687 	d->r = p;
688 	return 0;
689 }
690 
691 static struct chunk_info *
692 alloc_chunk_info(struct dir_info *d)
693 {
694 	struct chunk_info *p;
695 	int i;
696 
697 	if (LIST_EMPTY(&d->chunk_info_list)) {
698 		p = MMAP(MALLOC_PAGESIZE);
699 		if (p == MAP_FAILED)
700 			return NULL;
701 		malloc_used += MALLOC_PAGESIZE;
702 		for (i = 0; i < MALLOC_PAGESIZE / sizeof(*p); i++)
703 			LIST_INSERT_HEAD(&d->chunk_info_list, &p[i], entries);
704 	}
705 	p = LIST_FIRST(&d->chunk_info_list);
706 	LIST_REMOVE(p, entries);
707 	memset(p, 0, sizeof *p);
708 	p->canary = d->canary1;
709 	return p;
710 }
711 
712 static int
713 insert(struct dir_info *d, void *p, size_t sz, void *f)
714 {
715 	size_t index;
716 	size_t mask;
717 	void *q;
718 
719 	if (d->regions_free * 4 < d->regions_total) {
720 		if (omalloc_grow(d))
721 			return 1;
722 	}
723 	mask = d->regions_total - 1;
724 	index = hash(p) & mask;
725 	q = d->r[index].p;
726 	STATS_INC(d->inserts);
727 	while (q != NULL) {
728 		index = (index - 1) & mask;
729 		q = d->r[index].p;
730 		STATS_INC(d->insert_collisions);
731 	}
732 	d->r[index].p = p;
733 	d->r[index].size = sz;
734 #ifdef MALLOC_STATS
735 	d->r[index].f = f;
736 #endif
737 	d->regions_free--;
738 	return 0;
739 }
740 
741 static struct region_info *
742 find(struct dir_info *d, void *p)
743 {
744 	size_t index;
745 	size_t mask = d->regions_total - 1;
746 	void *q, *r;
747 
748 	if (mopts.malloc_canary != (d->canary1 ^ (u_int32_t)(uintptr_t)d) ||
749 	    d->canary1 != ~d->canary2)
750 		wrterror("internal struct corrupt", NULL);
751 	p = MASK_POINTER(p);
752 	index = hash(p) & mask;
753 	r = d->r[index].p;
754 	q = MASK_POINTER(r);
755 	STATS_INC(d->finds);
756 	while (q != p && r != NULL) {
757 		index = (index - 1) & mask;
758 		r = d->r[index].p;
759 		q = MASK_POINTER(r);
760 		STATS_INC(d->find_collisions);
761 	}
762 	return q == p ? &d->r[index] : NULL;
763 }
764 
765 static void
766 delete(struct dir_info *d, struct region_info *ri)
767 {
768 	/* algorithm R, Knuth Vol III section 6.4 */
769 	size_t mask = d->regions_total - 1;
770 	size_t i, j, r;
771 
772 	if (d->regions_total & (d->regions_total - 1))
773 		wrterror("regions_total not 2^x", NULL);
774 	d->regions_free++;
775 	STATS_INC(g_pool->deletes);
776 
777 	i = ri - d->r;
778 	for (;;) {
779 		d->r[i].p = NULL;
780 		d->r[i].size = 0;
781 		j = i;
782 		for (;;) {
783 			i = (i - 1) & mask;
784 			if (d->r[i].p == NULL)
785 				return;
786 			r = hash(d->r[i].p) & mask;
787 			if ((i <= r && r < j) || (r < j && j < i) ||
788 			    (j < i && i <= r))
789 				continue;
790 			d->r[j] = d->r[i];
791 			STATS_INC(g_pool->delete_moves);
792 			break;
793 		}
794 
795 	}
796 }
797 
798 /*
799  * Allocate a page of chunks
800  */
801 static struct chunk_info *
802 omalloc_make_chunks(struct dir_info *d, int bits)
803 {
804 	struct chunk_info *bp;
805 	void		*pp;
806 	long		i, k;
807 
808 	/* Allocate a new bucket */
809 	pp = map(d, MALLOC_PAGESIZE, 0);
810 	if (pp == MAP_FAILED)
811 		return NULL;
812 
813 	bp = alloc_chunk_info(d);
814 	if (bp == NULL) {
815 		unmap(d, pp, MALLOC_PAGESIZE);
816 		return NULL;
817 	}
818 
819 	/* memory protect the page allocated in the malloc(0) case */
820 	if (bits == 0) {
821 		bp->size = 0;
822 		bp->shift = 1;
823 		i = MALLOC_MINSIZE - 1;
824 		while (i >>= 1)
825 			bp->shift++;
826 		bp->total = bp->free = MALLOC_PAGESIZE >> bp->shift;
827 		bp->page = pp;
828 
829 		k = mprotect(pp, MALLOC_PAGESIZE, PROT_NONE);
830 		if (k < 0) {
831 			unmap(d, pp, MALLOC_PAGESIZE);
832 			LIST_INSERT_HEAD(&d->chunk_info_list, bp, entries);
833 			return NULL;
834 		}
835 	} else {
836 		bp->size = 1U << bits;
837 		bp->shift = bits;
838 		bp->total = bp->free = MALLOC_PAGESIZE >> bits;
839 		bp->page = pp;
840 	}
841 
842 	/* set all valid bits in the bitmap */
843 	k = bp->total;
844 	i = 0;
845 
846 	/* Do a bunch at a time */
847 	for (; (k - i) >= MALLOC_BITS; i += MALLOC_BITS)
848 		bp->bits[i / MALLOC_BITS] = (u_short)~0U;
849 
850 	for (; i < k; i++)
851 		bp->bits[i / MALLOC_BITS] |= (u_short)1U << (i % MALLOC_BITS);
852 
853 	LIST_INSERT_HEAD(&d->chunk_dir[bits], bp, entries);
854 
855 	bits++;
856 	if ((uintptr_t)pp & bits)
857 		wrterror("pp & bits", pp);
858 
859 	insert(d, (void *)((uintptr_t)pp | bits), (uintptr_t)bp, NULL);
860 	return bp;
861 }
862 
863 
864 /*
865  * Allocate a chunk
866  */
867 static void *
868 malloc_bytes(struct dir_info *d, size_t size, void *f)
869 {
870 	int		i, j;
871 	size_t		k;
872 	u_short		u, *lp;
873 	struct chunk_info *bp;
874 
875 	if (mopts.malloc_canary != (d->canary1 ^ (u_int32_t)(uintptr_t)d) ||
876 	    d->canary1 != ~d->canary2)
877 		wrterror("internal struct corrupt", NULL);
878 	/* Don't bother with anything less than this */
879 	/* unless we have a malloc(0) requests */
880 	if (size != 0 && size < MALLOC_MINSIZE)
881 		size = MALLOC_MINSIZE;
882 
883 	/* Find the right bucket */
884 	if (size == 0)
885 		j = 0;
886 	else {
887 		j = MALLOC_MINSHIFT;
888 		i = (size - 1) >> (MALLOC_MINSHIFT - 1);
889 		while (i >>= 1)
890 			j++;
891 	}
892 
893 	/* If it's empty, make a page more of that size chunks */
894 	if (LIST_EMPTY(&d->chunk_dir[j])) {
895 		bp = omalloc_make_chunks(d, j);
896 		if (bp == NULL)
897 			return NULL;
898 	} else
899 		bp = LIST_FIRST(&d->chunk_dir[j]);
900 
901 	if (bp->canary != d->canary1)
902 		wrterror("chunk info corrupted", NULL);
903 
904 	i = d->chunk_start;
905 	if (bp->free > 1)
906 		i += getrnibble();
907 	if (i >= bp->total)
908 		i &= bp->total - 1;
909 	for (;;) {
910 		for (;;) {
911 			lp = &bp->bits[i / MALLOC_BITS];
912 			if (!*lp) {
913 				i += MALLOC_BITS;
914 				i &= ~(MALLOC_BITS - 1);
915 				if (i >= bp->total)
916 					i = 0;
917 			} else
918 				break;
919 		}
920 		k = i % MALLOC_BITS;
921 		u = 1 << k;
922 		if (*lp & u)
923 			break;
924 		if (++i >= bp->total)
925 			i = 0;
926 	}
927 	d->chunk_start += i + 1;
928 #ifdef MALLOC_STATS
929 	if (i == 0) {
930 		struct region_info *r = find(d, bp->page);
931 		r->f = f;
932 	}
933 #endif
934 
935 	*lp ^= u;
936 
937 	/* If there are no more free, remove from free-list */
938 	if (!--bp->free)
939 		LIST_REMOVE(bp, entries);
940 
941 	/* Adjust to the real offset of that chunk */
942 	k += (lp - bp->bits) * MALLOC_BITS;
943 	k <<= bp->shift;
944 
945 	if (mopts.malloc_junk && bp->size > 0)
946 		memset((char *)bp->page + k, SOME_JUNK, bp->size);
947 	return ((char *)bp->page + k);
948 }
949 
950 
951 /*
952  * Free a chunk, and possibly the page it's on, if the page becomes empty.
953  */
954 static void
955 free_bytes(struct dir_info *d, struct region_info *r, void *ptr)
956 {
957 	struct chunk_head *mp;
958 	struct chunk_info *info;
959 	long i;
960 
961 	info = (struct chunk_info *)r->size;
962 	if (info->canary != d->canary1)
963 		wrterror("chunk info corrupted", NULL);
964 
965 	/* Find the chunk number on the page */
966 	i = ((uintptr_t)ptr & MALLOC_PAGEMASK) >> info->shift;
967 
968 	if ((uintptr_t)ptr & ((1U << (info->shift)) - 1)) {
969 		wrterror("modified chunk-pointer", ptr);
970 		return;
971 	}
972 	if (info->bits[i / MALLOC_BITS] & (1U << (i % MALLOC_BITS))) {
973 		wrterror("chunk is already free", ptr);
974 		return;
975 	}
976 
977 	info->bits[i / MALLOC_BITS] |= 1U << (i % MALLOC_BITS);
978 	info->free++;
979 
980 	if (info->size != 0)
981 		mp = d->chunk_dir + info->shift;
982 	else
983 		mp = d->chunk_dir;
984 
985 	if (info->free == 1) {
986 		/* Page became non-full */
987 		LIST_INSERT_HEAD(mp, info, entries);
988 		return;
989 	}
990 	if (info->free != info->total)
991 		return;
992 
993 	LIST_REMOVE(info, entries);
994 
995 	if (info->size == 0 && !mopts.malloc_freeprot)
996 		mprotect(info->page, MALLOC_PAGESIZE, PROT_READ | PROT_WRITE);
997 	unmap(d, info->page, MALLOC_PAGESIZE);
998 
999 	delete(d, r);
1000 	LIST_INSERT_HEAD(&d->chunk_info_list, info, entries);
1001 }
1002 
1003 
1004 
1005 static void *
1006 omalloc(size_t sz, int zero_fill, void *f)
1007 {
1008 	void *p;
1009 	size_t psz;
1010 
1011 	if (sz > MALLOC_MAXCHUNK) {
1012 		if (sz >= SIZE_MAX - mopts.malloc_guard - MALLOC_PAGESIZE) {
1013 			errno = ENOMEM;
1014 			return NULL;
1015 		}
1016 		sz += mopts.malloc_guard;
1017 		psz = PAGEROUND(sz);
1018 		p = map(g_pool, psz, zero_fill);
1019 		if (p == MAP_FAILED) {
1020 			errno = ENOMEM;
1021 			return NULL;
1022 		}
1023 		if (insert(g_pool, p, sz, f)) {
1024 			unmap(g_pool, p, psz);
1025 			errno = ENOMEM;
1026 			return NULL;
1027 		}
1028 		if (mopts.malloc_guard) {
1029 			if (mprotect((char *)p + psz - mopts.malloc_guard,
1030 			    mopts.malloc_guard, PROT_NONE))
1031 				wrterror("mprotect", NULL);
1032 			malloc_guarded += mopts.malloc_guard;
1033 		}
1034 
1035 		if (mopts.malloc_move &&
1036 		    sz - mopts.malloc_guard < MALLOC_PAGESIZE -
1037 		    MALLOC_LEEWAY) {
1038 			/* fill whole allocation */
1039 			if (mopts.malloc_junk)
1040 				memset(p, SOME_JUNK, psz - mopts.malloc_guard);
1041 			/* shift towards the end */
1042 			p = ((char *)p) + ((MALLOC_PAGESIZE - MALLOC_LEEWAY -
1043 			    (sz - mopts.malloc_guard)) & ~(MALLOC_MINSIZE-1));
1044 			/* fill zeros if needed and overwritten above */
1045 			if (zero_fill && mopts.malloc_junk)
1046 				memset(p, 0, sz - mopts.malloc_guard);
1047 		} else {
1048 			if (mopts.malloc_junk) {
1049 				if (zero_fill)
1050 					memset((char *)p + sz - mopts.malloc_guard,
1051 					    SOME_JUNK, psz - sz);
1052 				else
1053 					memset(p, SOME_JUNK,
1054 					    psz - mopts.malloc_guard);
1055 			}
1056 		}
1057 
1058 	} else {
1059 		/* takes care of SOME_JUNK */
1060 		p = malloc_bytes(g_pool, sz, f);
1061 		if (zero_fill && p != NULL && sz > 0)
1062 			memset(p, 0, sz);
1063 	}
1064 
1065 	return p;
1066 }
1067 
1068 /*
1069  * Common function for handling recursion.  Only
1070  * print the error message once, to avoid making the problem
1071  * potentially worse.
1072  */
1073 static void
1074 malloc_recurse(void)
1075 {
1076 	static int noprint;
1077 
1078 	if (noprint == 0) {
1079 		noprint = 1;
1080 		wrterror("recursive call", NULL);
1081 	}
1082 	malloc_active--;
1083 	_MALLOC_UNLOCK();
1084 	errno = EDEADLK;
1085 }
1086 
1087 static int
1088 malloc_init(void)
1089 {
1090 	if (omalloc_init(&g_pool)) {
1091 		_MALLOC_UNLOCK();
1092 		if (mopts.malloc_xmalloc)
1093 			wrterror("out of memory", NULL);
1094 		errno = ENOMEM;
1095 		return -1;
1096 	}
1097 	return 0;
1098 }
1099 
1100 void *
1101 malloc(size_t size)
1102 {
1103 	void *r;
1104 	int saved_errno = errno;
1105 
1106 	_MALLOC_LOCK();
1107 	malloc_func = " in malloc():";
1108 	if (g_pool == NULL) {
1109 		if (malloc_init() != 0)
1110 			return NULL;
1111 	}
1112 	if (malloc_active++) {
1113 		malloc_recurse();
1114 		return NULL;
1115 	}
1116 	r = omalloc(size, mopts.malloc_zero, CALLER);
1117 	malloc_active--;
1118 	_MALLOC_UNLOCK();
1119 	if (r == NULL && mopts.malloc_xmalloc) {
1120 		wrterror("out of memory", NULL);
1121 		errno = ENOMEM;
1122 	}
1123 	if (r != NULL)
1124 		errno = saved_errno;
1125 	return r;
1126 }
1127 
1128 static void
1129 ofree(void *p)
1130 {
1131 	struct region_info *r;
1132 	size_t sz;
1133 
1134 	r = find(g_pool, p);
1135 	if (r == NULL) {
1136 		wrterror("bogus pointer (double free?)", p);
1137 		return;
1138 	}
1139 	REALSIZE(sz, r);
1140 	if (sz > MALLOC_MAXCHUNK) {
1141 		if (sz - mopts.malloc_guard >= MALLOC_PAGESIZE -
1142 		    MALLOC_LEEWAY) {
1143 			if (r->p != p) {
1144 				wrterror("bogus pointer", p);
1145 				return;
1146 			}
1147 		} else {
1148 #if notyetbecause_of_realloc
1149 			/* shifted towards the end */
1150 			if (p != ((char *)r->p) + ((MALLOC_PAGESIZE -
1151 			    MALLOC_MINSIZE - sz - mopts.malloc_guard) &
1152 			    ~(MALLOC_MINSIZE-1))) {
1153 			}
1154 #endif
1155 			p = r->p;
1156 		}
1157 		if (mopts.malloc_guard) {
1158 			if (sz < mopts.malloc_guard)
1159 				wrterror("guard size", NULL);
1160 			if (!mopts.malloc_freeprot) {
1161 				if (mprotect((char *)p + PAGEROUND(sz) -
1162 				    mopts.malloc_guard, mopts.malloc_guard,
1163 				    PROT_READ | PROT_WRITE))
1164 					wrterror("mprotect", NULL);
1165 			}
1166 			malloc_guarded -= mopts.malloc_guard;
1167 		}
1168 		if (mopts.malloc_junk && !mopts.malloc_freeprot)
1169 			memset(p, SOME_FREEJUNK,
1170 			    PAGEROUND(sz) - mopts.malloc_guard);
1171 		unmap(g_pool, p, PAGEROUND(sz));
1172 		delete(g_pool, r);
1173 	} else {
1174 		void *tmp;
1175 		int i;
1176 
1177 		if (mopts.malloc_junk && sz > 0)
1178 			memset(p, SOME_FREEJUNK, sz);
1179 		if (!mopts.malloc_freeprot) {
1180 			i = getrnibble();
1181 			tmp = p;
1182 			p = g_pool->delayed_chunks[i];
1183 			g_pool->delayed_chunks[i] = tmp;
1184 		}
1185 		if (p != NULL) {
1186 			r = find(g_pool, p);
1187 			if (r == NULL) {
1188 				wrterror("bogus pointer (double free?)", p);
1189 				return;
1190 			}
1191 			free_bytes(g_pool, r, p);
1192 		}
1193 	}
1194 }
1195 
1196 void
1197 free(void *ptr)
1198 {
1199 	int saved_errno = errno;
1200 
1201 	/* This is legal. */
1202 	if (ptr == NULL)
1203 		return;
1204 
1205 	_MALLOC_LOCK();
1206 	malloc_func = " in free():";
1207 	if (g_pool == NULL) {
1208 		_MALLOC_UNLOCK();
1209 		wrterror("free() called before allocation", NULL);
1210 		return;
1211 	}
1212 	if (malloc_active++) {
1213 		malloc_recurse();
1214 		return;
1215 	}
1216 	ofree(ptr);
1217 	malloc_active--;
1218 	_MALLOC_UNLOCK();
1219 	errno = saved_errno;
1220 }
1221 
1222 
1223 static void *
1224 orealloc(void *p, size_t newsz, void *f)
1225 {
1226 	struct region_info *r;
1227 	size_t oldsz, goldsz, gnewsz;
1228 	void *q;
1229 
1230 	if (p == NULL)
1231 		return omalloc(newsz, 0, f);
1232 
1233 	r = find(g_pool, p);
1234 	if (r == NULL) {
1235 		wrterror("bogus pointer (double free?)", p);
1236 		return NULL;
1237 	}
1238 	if (newsz >= SIZE_MAX - mopts.malloc_guard - MALLOC_PAGESIZE) {
1239 		errno = ENOMEM;
1240 		return NULL;
1241 	}
1242 
1243 	REALSIZE(oldsz, r);
1244 	goldsz = oldsz;
1245 	if (oldsz > MALLOC_MAXCHUNK) {
1246 		if (oldsz < mopts.malloc_guard)
1247 			wrterror("guard size", NULL);
1248 		oldsz -= mopts.malloc_guard;
1249 	}
1250 
1251 	gnewsz = newsz;
1252 	if (gnewsz > MALLOC_MAXCHUNK)
1253 		gnewsz += mopts.malloc_guard;
1254 
1255 	if (newsz > MALLOC_MAXCHUNK && oldsz > MALLOC_MAXCHUNK && p == r->p &&
1256 	    !mopts.malloc_realloc) {
1257 		size_t roldsz = PAGEROUND(goldsz);
1258 		size_t rnewsz = PAGEROUND(gnewsz);
1259 
1260 		if (rnewsz > roldsz) {
1261 			if (!mopts.malloc_guard) {
1262 				STATS_INC(g_pool->cheap_realloc_tries);
1263 				zapcacheregion(g_pool, (char *)p + roldsz);
1264 				q = MMAPA((char *)p + roldsz, rnewsz - roldsz);
1265 				if (q == (char *)p + roldsz) {
1266 					malloc_used += rnewsz - roldsz;
1267 					if (mopts.malloc_junk)
1268 						memset(q, SOME_JUNK,
1269 						    rnewsz - roldsz);
1270 					r->size = newsz;
1271 					STATS_SETF(r, f);
1272 					STATS_INC(g_pool->cheap_reallocs);
1273 					return p;
1274 				} else if (q != MAP_FAILED)
1275 					munmap(q, rnewsz - roldsz);
1276 			}
1277 		} else if (rnewsz < roldsz) {
1278 			if (mopts.malloc_guard) {
1279 				if (mprotect((char *)p + roldsz -
1280 				    mopts.malloc_guard, mopts.malloc_guard,
1281 				    PROT_READ | PROT_WRITE))
1282 					wrterror("mprotect", NULL);
1283 				if (mprotect((char *)p + rnewsz -
1284 				    mopts.malloc_guard, mopts.malloc_guard,
1285 				    PROT_NONE))
1286 					wrterror("mprotect", NULL);
1287 			}
1288 			unmap(g_pool, (char *)p + rnewsz, roldsz - rnewsz);
1289 			r->size = gnewsz;
1290 			STATS_SETF(r, f);
1291 			return p;
1292 		} else {
1293 			if (newsz > oldsz && mopts.malloc_junk)
1294 				memset((char *)p + newsz, SOME_JUNK,
1295 				    rnewsz - mopts.malloc_guard - newsz);
1296 			r->size = gnewsz;
1297 			STATS_SETF(r, f);
1298 			return p;
1299 		}
1300 	}
1301 	if (newsz <= oldsz && newsz > oldsz / 2 && !mopts.malloc_realloc) {
1302 		if (mopts.malloc_junk && newsz > 0)
1303 			memset((char *)p + newsz, SOME_JUNK, oldsz - newsz);
1304 		STATS_SETF(r, f);
1305 		return p;
1306 	} else if (newsz != oldsz || mopts.malloc_realloc) {
1307 		q = omalloc(newsz, 0, f);
1308 		if (q == NULL)
1309 			return NULL;
1310 		if (newsz != 0 && oldsz != 0)
1311 			memcpy(q, p, oldsz < newsz ? oldsz : newsz);
1312 		ofree(p);
1313 		return q;
1314 	} else {
1315 		STATS_SETF(r, f);
1316 		return p;
1317 	}
1318 }
1319 
1320 void *
1321 realloc(void *ptr, size_t size)
1322 {
1323 	void *r;
1324 	int saved_errno = errno;
1325 
1326 	_MALLOC_LOCK();
1327 	malloc_func = " in realloc():";
1328 	if (g_pool == NULL) {
1329 		if (malloc_init() != 0)
1330 			return NULL;
1331 	}
1332 	if (malloc_active++) {
1333 		malloc_recurse();
1334 		return NULL;
1335 	}
1336 	r = orealloc(ptr, size, CALLER);
1337 
1338 	malloc_active--;
1339 	_MALLOC_UNLOCK();
1340 	if (r == NULL && mopts.malloc_xmalloc) {
1341 		wrterror("out of memory", NULL);
1342 		errno = ENOMEM;
1343 	}
1344 	if (r != NULL)
1345 		errno = saved_errno;
1346 	return r;
1347 }
1348 
1349 
1350 #define MUL_NO_OVERFLOW	(1UL << (sizeof(size_t) * 4))
1351 
1352 void *
1353 calloc(size_t nmemb, size_t size)
1354 {
1355 	void *r;
1356 	int saved_errno = errno;
1357 
1358 	_MALLOC_LOCK();
1359 	malloc_func = " in calloc():";
1360 	if (g_pool == NULL) {
1361 		if (malloc_init() != 0)
1362 			return NULL;
1363 	}
1364 	if ((nmemb >= MUL_NO_OVERFLOW || size >= MUL_NO_OVERFLOW) &&
1365 	    nmemb > 0 && SIZE_MAX / nmemb < size) {
1366 		_MALLOC_UNLOCK();
1367 		if (mopts.malloc_xmalloc)
1368 			wrterror("out of memory", NULL);
1369 		errno = ENOMEM;
1370 		return NULL;
1371 	}
1372 
1373 	if (malloc_active++) {
1374 		malloc_recurse();
1375 		return NULL;
1376 	}
1377 
1378 	size *= nmemb;
1379 	r = omalloc(size, 1, CALLER);
1380 
1381 	malloc_active--;
1382 	_MALLOC_UNLOCK();
1383 	if (r == NULL && mopts.malloc_xmalloc) {
1384 		wrterror("out of memory", NULL);
1385 		errno = ENOMEM;
1386 	}
1387 	if (r != NULL)
1388 		errno = saved_errno;
1389 	return r;
1390 }
1391 
1392 int
1393 posix_memalign(void **memptr, size_t alignment, size_t size)
1394 {
1395 	void *result;
1396 
1397 	/* Make sure that alignment is a large enough power of 2. */
1398 	if (((alignment - 1) & alignment) != 0 || alignment < sizeof(void *) ||
1399 	    alignment > MALLOC_PAGESIZE)
1400 		return EINVAL;
1401 
1402 	/*
1403 	 * max(size, alignment) is enough to assure the requested alignment,
1404 	 * since the allocator always allocates power-of-two blocks.
1405 	 */
1406 	if (size < alignment)
1407 		size = alignment;
1408 	result = malloc(size);
1409 
1410 	if (result == NULL)
1411 		return ENOMEM;
1412 
1413 	*memptr = result;
1414 	return 0;
1415 }
1416 
1417 #ifdef MALLOC_STATS
1418 
1419 struct malloc_leak {
1420 	void (*f)();
1421 	size_t total_size;
1422 	int count;
1423 };
1424 
1425 struct leaknode {
1426 	RB_ENTRY(leaknode) entry;
1427 	struct malloc_leak d;
1428 };
1429 
1430 static int
1431 leakcmp(struct leaknode *e1, struct leaknode *e2)
1432 {
1433 	return e1->d.f < e2->d.f ? -1 : e1->d.f > e2->d.f;
1434 }
1435 
1436 static RB_HEAD(leaktree, leaknode) leakhead;
1437 RB_GENERATE_STATIC(leaktree, leaknode, entry, leakcmp)
1438 
1439 static void
1440 putleakinfo(void *f, size_t sz, int cnt)
1441 {
1442 	struct leaknode key, *p;
1443 	static struct leaknode *page;
1444 	static int used;
1445 
1446 	if (cnt == 0)
1447 		return;
1448 
1449 	key.d.f = f;
1450 	p = RB_FIND(leaktree, &leakhead, &key);
1451 	if (p == NULL) {
1452 		if (page == NULL ||
1453 		    used >= MALLOC_PAGESIZE / sizeof(struct leaknode)) {
1454 			page = MMAP(MALLOC_PAGESIZE);
1455 			if (page == MAP_FAILED)
1456 				return;
1457 			used = 0;
1458 		}
1459 		p = &page[used++];
1460 		p->d.f = f;
1461 		p->d.total_size = sz * cnt;
1462 		p->d.count = cnt;
1463 		RB_INSERT(leaktree, &leakhead, p);
1464 	} else {
1465 		p->d.total_size += sz * cnt;
1466 		p->d.count += cnt;
1467 	}
1468 }
1469 
1470 static struct malloc_leak *malloc_leaks;
1471 
1472 static void
1473 dump_leaks(int fd)
1474 {
1475 	struct leaknode *p;
1476 	char buf[64];
1477 	int i = 0;
1478 
1479 	snprintf(buf, sizeof(buf), "Leak report\n");
1480 	write(fd, buf, strlen(buf));
1481 	snprintf(buf, sizeof(buf), "           f     sum      #    avg\n");
1482 	write(fd, buf, strlen(buf));
1483 	/* XXX only one page of summary */
1484 	if (malloc_leaks == NULL)
1485 		malloc_leaks = MMAP(MALLOC_PAGESIZE);
1486 	if (malloc_leaks != MAP_FAILED)
1487 		memset(malloc_leaks, 0, MALLOC_PAGESIZE);
1488 	RB_FOREACH(p, leaktree, &leakhead) {
1489 		snprintf(buf, sizeof(buf), "%12p %7zu %6u %6zu\n", p->d.f,
1490 		    p->d.total_size, p->d.count, p->d.total_size / p->d.count);
1491 		write(fd, buf, strlen(buf));
1492 		if (malloc_leaks == MAP_FAILED ||
1493 		    i >= MALLOC_PAGESIZE / sizeof(struct malloc_leak))
1494 			continue;
1495 		malloc_leaks[i].f = p->d.f;
1496 		malloc_leaks[i].total_size = p->d.total_size;
1497 		malloc_leaks[i].count = p->d.count;
1498 		i++;
1499 	}
1500 }
1501 
1502 static void
1503 dump_chunk(int fd, struct chunk_info *p, void *f, int fromfreelist)
1504 {
1505 	char buf[64];
1506 
1507 	while (p != NULL) {
1508 		snprintf(buf, sizeof(buf), "chunk %12p %12p %4d %d/%d\n",
1509 		    p->page, ((p->bits[0] & 1) ? NULL : f),
1510 		    p->size, p->free, p->total);
1511 		write(fd, buf, strlen(buf));
1512 		if (!fromfreelist) {
1513 			if (p->bits[0] & 1)
1514 				putleakinfo(NULL, p->size, p->total - p->free);
1515 			else {
1516 				putleakinfo(f, p->size, 1);
1517 				putleakinfo(NULL, p->size,
1518 				    p->total - p->free - 1);
1519 			}
1520 			break;
1521 		}
1522 		p = LIST_NEXT(p, entries);
1523 		if (p != NULL) {
1524 			snprintf(buf, sizeof(buf), "    ");
1525 			write(fd, buf, strlen(buf));
1526 		}
1527 	}
1528 }
1529 
1530 static void
1531 dump_free_chunk_info(int fd, struct dir_info *d)
1532 {
1533 	char buf[64];
1534 	int i;
1535 
1536 	snprintf(buf, sizeof(buf), "Free chunk structs:\n");
1537 	write(fd, buf, strlen(buf));
1538 	for (i = 0; i <= MALLOC_MAXSHIFT; i++) {
1539 		struct chunk_info *p = LIST_FIRST(&d->chunk_dir[i]);
1540 		if (p != NULL) {
1541 			snprintf(buf, sizeof(buf), "%2d) ", i);
1542 			write(fd, buf, strlen(buf));
1543 			dump_chunk(fd, p, NULL, 1);
1544 		}
1545 	}
1546 
1547 }
1548 
1549 static void
1550 dump_free_page_info(int fd, struct dir_info *d)
1551 {
1552 	char buf[64];
1553 	int i;
1554 
1555 	snprintf(buf, sizeof(buf), "Free pages cached: %zu\n",
1556 	    d->free_regions_size);
1557 	write(fd, buf, strlen(buf));
1558 	for (i = 0; i < mopts.malloc_cache; i++) {
1559 		if (d->free_regions[i].p != NULL) {
1560 			snprintf(buf, sizeof(buf), "%2d) ", i);
1561 			write(fd, buf, strlen(buf));
1562 			snprintf(buf, sizeof(buf), "free at %p: %zu\n",
1563 			    d->free_regions[i].p, d->free_regions[i].size);
1564 			write(fd, buf, strlen(buf));
1565 		}
1566 	}
1567 }
1568 
1569 static void
1570 malloc_dump1(int fd, struct dir_info *d)
1571 {
1572 	char buf[64];
1573 	size_t i, realsize;
1574 
1575 	snprintf(buf, sizeof(buf), "Malloc dir of %s at %p\n", __progname, d);
1576 	write(fd, buf, strlen(buf));
1577 	if (d == NULL)
1578 		return;
1579 	snprintf(buf, sizeof(buf), "Region slots free %zu/%zu\n",
1580 		d->regions_free, d->regions_total);
1581 	write(fd, buf, strlen(buf));
1582 	snprintf(buf, sizeof(buf), "Finds %zu/%zu\n", d->finds,
1583 	    d->find_collisions);
1584 	write(fd, buf, strlen(buf));
1585 	snprintf(buf, sizeof(buf), "Inserts %zu/%zu\n", d->inserts,
1586 	    d->insert_collisions);
1587 	write(fd, buf, strlen(buf));
1588 	snprintf(buf, sizeof(buf), "Deletes %zu/%zu\n", d->deletes,
1589 	     d->delete_moves);
1590 	write(fd, buf, strlen(buf));
1591 	snprintf(buf, sizeof(buf), "Cheap reallocs %zu/%zu\n",
1592 	    d->cheap_reallocs, d->cheap_realloc_tries);
1593 	write(fd, buf, strlen(buf));
1594 	dump_free_chunk_info(fd, d);
1595 	dump_free_page_info(fd, d);
1596 	snprintf(buf, sizeof(buf),
1597 	    "slot)  hash d  type         page            f size [free/n]\n");
1598 	write(fd, buf, strlen(buf));
1599 	for (i = 0; i < d->regions_total; i++) {
1600 		if (d->r[i].p != NULL) {
1601 			size_t h = hash(d->r[i].p) &
1602 			    (d->regions_total - 1);
1603 			snprintf(buf, sizeof(buf), "%4zx) #%4zx %zd ",
1604 			    i, h, h - i);
1605 			write(fd, buf, strlen(buf));
1606 			REALSIZE(realsize, &d->r[i]);
1607 			if (realsize > MALLOC_MAXCHUNK) {
1608 				putleakinfo(d->r[i].f, realsize, 1);
1609 				snprintf(buf, sizeof(buf),
1610 				    "pages %12p %12p %zu\n", d->r[i].p,
1611 				    d->r[i].f, realsize);
1612 				write(fd, buf, strlen(buf));
1613 			} else
1614 				dump_chunk(fd,
1615 				    (struct chunk_info *)d->r[i].size,
1616 				    d->r[i].f, 0);
1617 		}
1618 	}
1619 	snprintf(buf, sizeof(buf), "In use %zu\n", malloc_used);
1620 	write(fd, buf, strlen(buf));
1621 	snprintf(buf, sizeof(buf), "Guarded %zu\n", malloc_guarded);
1622 	write(fd, buf, strlen(buf));
1623 	dump_leaks(fd);
1624 	write(fd, "\n", 1);
1625 }
1626 
1627 void
1628 malloc_dump(int fd)
1629 {
1630 	int i;
1631 	void *p;
1632 	struct region_info *r;
1633 	int saved_errno = errno;
1634 
1635 	for (i = 0; i <= MALLOC_DELAYED_CHUNKS; i++) {
1636 		p = g_pool->delayed_chunks[i];
1637 		if (p == NULL)
1638 			continue;
1639 		r = find(g_pool, p);
1640 		if (r == NULL)
1641 			wrterror("bogus pointer in malloc_dump", p);
1642 		free_bytes(g_pool, r, p);
1643 		g_pool->delayed_chunks[i] = NULL;
1644 	}
1645 	/* XXX leak when run multiple times */
1646 	RB_INIT(&leakhead);
1647 	malloc_dump1(fd, g_pool);
1648 	errno = saved_errno;
1649 }
1650 
1651 static void
1652 malloc_exit(void)
1653 {
1654 	static const char q[] = "malloc() warning: Couldn't dump stats\n";
1655 	int save_errno = errno, fd;
1656 
1657 	fd = open("malloc.out", O_RDWR|O_APPEND);
1658 	if (fd != -1) {
1659 		malloc_dump(fd);
1660 		close(fd);
1661 	} else
1662 		write(STDERR_FILENO, q, sizeof(q) - 1);
1663 	errno = save_errno;
1664 }
1665 
1666 #endif /* MALLOC_STATS */
1667