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