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