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