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