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