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