malloc.c revision 1.91
1/*	$OpenBSD: malloc.c,v 1.91 2008/06/13 21:18:42 otto Exp $	*/
2
3/*
4 * ----------------------------------------------------------------------------
5 * "THE BEER-WARE LICENSE" (Revision 42):
6 * <phk@FreeBSD.ORG> wrote this file.  As long as you retain this notice you
7 * can do whatever you want with this stuff. If we meet some day, and you think
8 * this stuff is worth it, you can buy me a beer in return.   Poul-Henning Kamp
9 * ----------------------------------------------------------------------------
10 */
11
12/*
13 * Defining MALLOC_EXTRA_SANITY will enable extra checks which are
14 * related to internal conditions and consistency in malloc.c. This has
15 * a noticeable runtime performance hit, and generally will not do you
16 * any good unless you fiddle with the internals of malloc or want
17 * to catch random pointer corruption as early as possible.
18 */
19#ifndef	MALLOC_EXTRA_SANITY
20#undef	MALLOC_EXTRA_SANITY
21#endif
22
23/*
24 * Defining MALLOC_STATS will enable you to call malloc_dump() and set
25 * the [dD] options in the MALLOC_OPTIONS environment variable.
26 * It has no run-time performance hit, but does pull in stdio...
27 */
28#ifndef	MALLOC_STATS
29#undef	MALLOC_STATS
30#endif
31
32/*
33 * What to use for Junk.  This is the byte value we use to fill with
34 * when the 'J' option is enabled.
35 */
36#define SOME_JUNK	0xd0	/* as in "Duh" :-) */
37
38#include <sys/types.h>
39#include <sys/time.h>
40#include <sys/resource.h>
41#include <sys/param.h>
42#include <sys/mman.h>
43#include <sys/uio.h>
44#include <stdio.h>
45#include <stdlib.h>
46#include <string.h>
47#include <unistd.h>
48#include <fcntl.h>
49#include <limits.h>
50#include <errno.h>
51#include <err.h>
52
53#include "thread_private.h"
54
55/*
56 * The basic parameters you can tweak.
57 *
58 * malloc_pageshift	pagesize = 1 << malloc_pageshift
59 *			It's probably best if this is the native
60 *			page size, but it shouldn't have to be.
61 *
62 * malloc_minsize	minimum size of an allocation in bytes.
63 *			If this is too small it's too much work
64 *			to manage them.  This is also the smallest
65 *			unit of alignment used for the storage
66 *			returned by malloc/realloc.
67 *
68 */
69
70#if defined(__sparc__)
71#define	malloc_pageshift	13U
72#endif /* __sparc__ */
73
74#ifndef malloc_pageshift
75#define malloc_pageshift	(PGSHIFT)
76#endif
77
78#ifndef malloc_minsize
79#define malloc_minsize			16UL
80#endif
81
82#if !defined(malloc_pagesize)
83#define malloc_pagesize			(1UL<<malloc_pageshift)
84#endif
85
86/* How many bits per u_long in the bitmap */
87#define	MALLOC_BITS	(NBBY * sizeof(u_long))
88
89
90/*
91 * No user serviceable parts behind this point.
92 *
93 * This structure describes a page worth of chunks.
94 */
95struct pginfo {
96	struct pginfo	*next;	/* next on the free list */
97	void		*page;	/* Pointer to the page */
98	u_short		size;	/* size of this page's chunks */
99	u_short		shift;	/* How far to shift for this size chunks */
100	u_short		free;	/* How many free chunks */
101	u_short		total;	/* How many chunk */
102	u_long		bits[(malloc_pagesize / malloc_minsize) / MALLOC_BITS];/* Which chunks are free */
103};
104
105/*
106 * This structure describes a number of free pages.
107 */
108struct pgfree {
109	struct pgfree	*next;	/* next run of free pages */
110	struct pgfree	*prev;	/* prev run of free pages */
111	void		*page;	/* pointer to free pages */
112	void		*pdir;	/* pointer to the base page's dir */
113	size_t		size;	/* number of bytes free */
114};
115
116/*
117 * Magic values to put in the page_directory
118 */
119#define MALLOC_NOT_MINE	((struct pginfo*) 0)
120#define MALLOC_FREE	((struct pginfo*) 1)
121#define MALLOC_FIRST	((struct pginfo*) 2)
122#define MALLOC_FOLLOW	((struct pginfo*) 3)
123#define MALLOC_MAGIC	((struct pginfo*) 4)
124
125#if ((1UL<<malloc_pageshift) != malloc_pagesize)
126#error	"(1UL<<malloc_pageshift) != malloc_pagesize"
127#endif
128
129#ifndef malloc_maxsize
130#define malloc_maxsize			((malloc_pagesize)>>1)
131#endif
132
133/* A mask for the offset inside a page. */
134#define malloc_pagemask	((malloc_pagesize)-1)
135
136#define	pageround(foo)	(((foo) + (malloc_pagemask)) & ~malloc_pagemask)
137#define	ptr2index(foo)	(((u_long)(foo) >> malloc_pageshift)+malloc_pageshift)
138#define	index2ptr(idx)	((void*)(((idx)-malloc_pageshift)<<malloc_pageshift))
139
140/* Set when initialization has been done */
141static unsigned int	malloc_started;
142
143/* Number of free pages we cache */
144static unsigned int	malloc_cache = 16;
145
146/* Structure used for linking discrete directory pages. */
147struct pdinfo {
148	struct pginfo	**base;
149	struct pdinfo	*prev;
150	struct pdinfo	*next;
151	u_long		dirnum;
152};
153static struct pdinfo *last_dir;	/* Caches to the last and previous */
154static struct pdinfo *prev_dir;	/* referenced directory pages. */
155
156static size_t	pdi_off;
157static u_long	pdi_mod;
158#define	PD_IDX(num)	((num) / (malloc_pagesize/sizeof(struct pginfo *)))
159#define	PD_OFF(num)	((num) & ((malloc_pagesize/sizeof(struct pginfo *))-1))
160#define	PI_IDX(index)	((index) / pdi_mod)
161#define	PI_OFF(index)	((index) % pdi_mod)
162
163/* The last index in the page directory we care about */
164static u_long	last_index;
165
166/* Pointer to page directory. Allocated "as if with" malloc */
167static struct pginfo **page_dir;
168
169/* Free pages line up here */
170static struct pgfree free_list;
171
172/* Abort(), user doesn't handle problems. */
173static int	malloc_abort = 2;
174
175/* Are we trying to die ? */
176static int	suicide;
177
178#ifdef MALLOC_STATS
179/* dump statistics */
180static int	malloc_stats;
181#endif
182
183/* avoid outputting warnings? */
184static int	malloc_silent;
185
186/* always realloc ? */
187static int	malloc_realloc;
188
189/* mprotect free pages PROT_NONE? */
190static int	malloc_freeprot;
191
192/* use guard pages after allocations? */
193static size_t	malloc_guard = 0;
194static size_t	malloc_guarded;
195/* align pointers to end of page? */
196static int	malloc_ptrguard;
197
198static int	malloc_hint;
199
200/* xmalloc behaviour ? */
201static int	malloc_xmalloc;
202
203/* zero fill ? */
204static int	malloc_zero;
205
206/* junk fill ? */
207static int	malloc_junk;
208
209#ifdef __FreeBSD__
210/* utrace ? */
211static int	malloc_utrace;
212
213struct ut {
214	void		*p;
215	size_t		s;
216	void		*r;
217};
218
219void		utrace(struct ut *, int);
220
221#define UTRACE(a, b, c) \
222	if (malloc_utrace) \
223		{struct ut u; u.p=a; u.s = b; u.r=c; utrace(&u, sizeof u);}
224#else				/* !__FreeBSD__ */
225#define UTRACE(a,b,c)
226#endif
227
228/* Status of malloc. */
229static int	malloc_active;
230
231/* Allocated memory. */
232static size_t	malloc_used;
233
234/* My last break. */
235static caddr_t	malloc_brk;
236
237/* One location cache for free-list holders. */
238static struct pgfree *px;
239
240/* Compile-time options. */
241char		*malloc_options;
242
243/* Name of the current public function. */
244static char	*malloc_func;
245
246#define MMAP(size) \
247	mmap((void *)0, (size), PROT_READ|PROT_WRITE, MAP_ANON|MAP_PRIVATE, \
248	    -1, (off_t)0)
249
250/*
251 * Necessary function declarations.
252 */
253static void	*imalloc(size_t size);
254static void	ifree(void *ptr);
255static void	*irealloc(void *ptr, size_t size);
256static void	*malloc_bytes(size_t size);
257
258static struct pginfo *pginfo_list;
259
260static struct pgfree *pgfree_list;
261
262static struct pgfree *
263alloc_pgfree(void)
264{
265	struct pgfree *p;
266	int i;
267
268	if (pgfree_list == NULL) {
269		p = MMAP(malloc_pagesize);
270		if (p == MAP_FAILED)
271			return NULL;
272		for (i = 0; i < malloc_pagesize / sizeof(*p); i++) {
273			p[i].next = pgfree_list;
274			pgfree_list = &p[i];
275		}
276	}
277	p = pgfree_list;
278	pgfree_list = p->next;
279	memset(p, 0, sizeof *p);
280	return p;
281}
282
283static struct pginfo *
284alloc_pginfo(void)
285{
286	struct pginfo *p;
287	int i;
288
289	if (pginfo_list == NULL) {
290		p = MMAP(malloc_pagesize);
291		if (p == MAP_FAILED)
292			return NULL;
293		for (i = 0; i < malloc_pagesize / sizeof(*p); i++) {
294			p[i].next = pginfo_list;
295			pginfo_list = &p[i];
296		}
297	}
298	p = pginfo_list;
299	pginfo_list = p->next;
300	memset(p, 0, sizeof *p);
301	return p;
302}
303
304static void
305put_pgfree(struct pgfree *p)
306{
307	p->next = pgfree_list;
308	pgfree_list = p;
309}
310
311static void
312put_pginfo(struct pginfo *p)
313{
314	p->next = pginfo_list;
315	pginfo_list = p;
316}
317
318/*
319 * Function for page directory lookup.
320 */
321static int
322pdir_lookup(u_long index, struct pdinfo ** pdi)
323{
324	struct pdinfo	*spi;
325	u_long		pidx = PI_IDX(index);
326
327	if (last_dir != NULL && PD_IDX(last_dir->dirnum) == pidx)
328		*pdi = last_dir;
329	else if (prev_dir != NULL && PD_IDX(prev_dir->dirnum) == pidx)
330		*pdi = prev_dir;
331	else if (last_dir != NULL && prev_dir != NULL) {
332		if ((PD_IDX(last_dir->dirnum) > pidx) ?
333		    (PD_IDX(last_dir->dirnum) - pidx) :
334		    (pidx - PD_IDX(last_dir->dirnum))
335		    < (PD_IDX(prev_dir->dirnum) > pidx) ?
336		    (PD_IDX(prev_dir->dirnum) - pidx) :
337		    (pidx - PD_IDX(prev_dir->dirnum)))
338			*pdi = last_dir;
339		else
340			*pdi = prev_dir;
341
342		if (PD_IDX((*pdi)->dirnum) > pidx) {
343			for (spi = (*pdi)->prev;
344			    spi != NULL && PD_IDX(spi->dirnum) > pidx;
345			    spi = spi->prev)
346				*pdi = spi;
347			if (spi != NULL)
348				*pdi = spi;
349		} else
350			for (spi = (*pdi)->next;
351			    spi != NULL && PD_IDX(spi->dirnum) <= pidx;
352			    spi = spi->next)
353				*pdi = spi;
354	} else {
355		*pdi = (struct pdinfo *) ((caddr_t) page_dir + pdi_off);
356		for (spi = *pdi;
357		    spi != NULL && PD_IDX(spi->dirnum) <= pidx;
358		    spi = spi->next)
359			*pdi = spi;
360	}
361
362	return ((PD_IDX((*pdi)->dirnum) == pidx) ? 0 :
363	    (PD_IDX((*pdi)->dirnum) > pidx) ? 1 : -1);
364}
365
366#ifdef MALLOC_STATS
367void
368malloc_dump(int fd)
369{
370	char		buf[1024];
371	struct pginfo	**pd;
372	struct pgfree	*pf;
373	struct pdinfo	*pi;
374	u_long		j;
375
376	pd = page_dir;
377	pi = (struct pdinfo *) ((caddr_t) pd + pdi_off);
378
379	/* print out all the pages */
380	for (j = 0; j <= last_index;) {
381		snprintf(buf, sizeof buf, "%08lx %5lu ", j << malloc_pageshift, j);
382		write(fd, buf, strlen(buf));
383		if (pd[PI_OFF(j)] == MALLOC_NOT_MINE) {
384			for (j++; j <= last_index && pd[PI_OFF(j)] == MALLOC_NOT_MINE;) {
385				if (!PI_OFF(++j)) {
386					if ((pi = pi->next) == NULL ||
387					    PD_IDX(pi->dirnum) != PI_IDX(j))
388						break;
389					pd = pi->base;
390					j += pdi_mod;
391				}
392			}
393			j--;
394			snprintf(buf, sizeof buf, ".. %5lu not mine\n", j);
395			write(fd, buf, strlen(buf));
396		} else if (pd[PI_OFF(j)] == MALLOC_FREE) {
397			for (j++; j <= last_index && pd[PI_OFF(j)] == MALLOC_FREE;) {
398				if (!PI_OFF(++j)) {
399					if ((pi = pi->next) == NULL ||
400					    PD_IDX(pi->dirnum) != PI_IDX(j))
401						break;
402					pd = pi->base;
403					j += pdi_mod;
404				}
405			}
406			j--;
407			snprintf(buf, sizeof buf, ".. %5lu free\n", j);
408			write(fd, buf, strlen(buf));
409		} else if (pd[PI_OFF(j)] == MALLOC_FIRST) {
410			for (j++; j <= last_index && pd[PI_OFF(j)] == MALLOC_FOLLOW;) {
411				if (!PI_OFF(++j)) {
412					if ((pi = pi->next) == NULL ||
413					    PD_IDX(pi->dirnum) != PI_IDX(j))
414						break;
415					pd = pi->base;
416					j += pdi_mod;
417				}
418			}
419			j--;
420			snprintf(buf, sizeof buf, ".. %5lu in use\n", j);
421			write(fd, buf, strlen(buf));
422		} else if (pd[PI_OFF(j)] < MALLOC_MAGIC) {
423			snprintf(buf, sizeof buf, "(%p)\n", pd[PI_OFF(j)]);
424			write(fd, buf, strlen(buf));
425		} else {
426			snprintf(buf, sizeof buf, "%p %d (of %d) x %d @ %p --> %p\n",
427			    pd[PI_OFF(j)], pd[PI_OFF(j)]->free,
428			    pd[PI_OFF(j)]->total, pd[PI_OFF(j)]->size,
429			    pd[PI_OFF(j)]->page, pd[PI_OFF(j)]->next);
430			write(fd, buf, strlen(buf));
431		}
432		if (!PI_OFF(++j)) {
433			if ((pi = pi->next) == NULL)
434				break;
435			pd = pi->base;
436			j += (1 + PD_IDX(pi->dirnum) - PI_IDX(j)) * pdi_mod;
437		}
438	}
439
440	for (pf = free_list.next; pf; pf = pf->next) {
441		snprintf(buf, sizeof buf, "Free: @%p [%p...%p[ %ld ->%p <-%p\n",
442		    pf, pf->page, (char *)pf->page + pf->size,
443		    pf->size, pf->prev, pf->next);
444		write(fd, buf, strlen(buf));
445		if (pf == pf->next) {
446			snprintf(buf, sizeof buf, "Free_list loops\n");
447			write(fd, buf, strlen(buf));
448			break;
449		}
450	}
451
452	/* print out various info */
453	snprintf(buf, sizeof buf, "Minsize\t%lu\n", malloc_minsize);
454	write(fd, buf, strlen(buf));
455	snprintf(buf, sizeof buf, "Maxsize\t%lu\n", malloc_maxsize);
456	write(fd, buf, strlen(buf));
457	snprintf(buf, sizeof buf, "Pagesize\t%lu\n", malloc_pagesize);
458	write(fd, buf, strlen(buf));
459	snprintf(buf, sizeof buf, "Pageshift\t%u\n", malloc_pageshift);
460	write(fd, buf, strlen(buf));
461	snprintf(buf, sizeof buf, "In use\t%lu\n", (u_long) malloc_used);
462	write(fd, buf, strlen(buf));
463	snprintf(buf, sizeof buf, "Guarded\t%lu\n", (u_long) malloc_guarded);
464	write(fd, buf, strlen(buf));
465}
466#endif /* MALLOC_STATS */
467
468extern char	*__progname;
469
470static void
471wrterror(char *p)
472{
473	char		*q = " error: ";
474	struct iovec	iov[5];
475
476	iov[0].iov_base = __progname;
477	iov[0].iov_len = strlen(__progname);
478	iov[1].iov_base = malloc_func;
479	iov[1].iov_len = strlen(malloc_func);
480	iov[2].iov_base = q;
481	iov[2].iov_len = strlen(q);
482	iov[3].iov_base = p;
483	iov[3].iov_len = strlen(p);
484	iov[4].iov_base = "\n";
485	iov[4].iov_len = 1;
486	writev(STDERR_FILENO, iov, 5);
487
488	suicide = 1;
489#ifdef MALLOC_STATS
490	if (malloc_stats)
491		malloc_dump(STDERR_FILENO);
492#endif /* MALLOC_STATS */
493	malloc_active--;
494	if (malloc_abort)
495		abort();
496}
497
498static void
499wrtwarning(char *p)
500{
501	char		*q = " warning: ";
502	struct iovec	iov[5];
503
504	if (malloc_abort)
505		wrterror(p);
506	else if (malloc_silent)
507		return;
508
509	iov[0].iov_base = __progname;
510	iov[0].iov_len = strlen(__progname);
511	iov[1].iov_base = malloc_func;
512	iov[1].iov_len = strlen(malloc_func);
513	iov[2].iov_base = q;
514	iov[2].iov_len = strlen(q);
515	iov[3].iov_base = p;
516	iov[3].iov_len = strlen(p);
517	iov[4].iov_base = "\n";
518	iov[4].iov_len = 1;
519
520	writev(STDERR_FILENO, iov, 5);
521}
522
523#ifdef MALLOC_STATS
524static void
525malloc_exit(void)
526{
527	char	*q = "malloc() warning: Couldn't dump stats\n";
528	int	save_errno = errno, fd;
529
530	fd = open("malloc.out", O_RDWR|O_APPEND);
531	if (fd != -1) {
532		malloc_dump(fd);
533		close(fd);
534	} else
535		write(STDERR_FILENO, q, strlen(q));
536	errno = save_errno;
537}
538#endif /* MALLOC_STATS */
539
540/*
541 * Allocate a number of pages from the OS
542 */
543static void *
544map_pages(size_t pages)
545{
546	struct pdinfo	*pi, *spi;
547	struct pginfo	**pd;
548	u_long		idx, pidx, lidx;
549	caddr_t		result, tail;
550	u_long		index, lindex;
551	void 		*pdregion = NULL;
552	size_t		dirs, cnt;
553
554	pages <<= malloc_pageshift;
555	result = MMAP(pages + malloc_guard);
556	if (result == MAP_FAILED) {
557#ifdef MALLOC_EXTRA_SANITY
558		wrtwarning("(ES): map_pages fails");
559#endif /* MALLOC_EXTRA_SANITY */
560		errno = ENOMEM;
561		return (NULL);
562	}
563	index = ptr2index(result);
564	tail = result + pages + malloc_guard;
565	lindex = ptr2index(tail) - 1;
566	if (malloc_guard)
567		mprotect(result + pages, malloc_guard, PROT_NONE);
568
569	pidx = PI_IDX(index);
570	lidx = PI_IDX(lindex);
571
572	if (tail > malloc_brk) {
573		malloc_brk = tail;
574		last_index = lindex;
575	}
576
577	dirs = lidx - pidx;
578
579	/* Insert directory pages, if needed. */
580	if (pdir_lookup(index, &pi) != 0)
581		dirs++;
582
583	if (dirs > 0) {
584		pdregion = MMAP(malloc_pagesize * dirs);
585		if (pdregion == MAP_FAILED) {
586			munmap(result, tail - result);
587#ifdef MALLOC_EXTRA_SANITY
588		wrtwarning("(ES): map_pages fails");
589#endif
590			errno = ENOMEM;
591			return (NULL);
592		}
593	}
594
595	cnt = 0;
596	for (idx = pidx, spi = pi; idx <= lidx; idx++) {
597		if (pi == NULL || PD_IDX(pi->dirnum) != idx) {
598			pd = (struct pginfo **)((char *)pdregion +
599			    cnt * malloc_pagesize);
600			cnt++;
601			memset(pd, 0, malloc_pagesize);
602			pi = (struct pdinfo *) ((caddr_t) pd + pdi_off);
603			pi->base = pd;
604			pi->prev = spi;
605			pi->next = spi->next;
606			pi->dirnum = idx * (malloc_pagesize /
607			    sizeof(struct pginfo *));
608
609			if (spi->next != NULL)
610				spi->next->prev = pi;
611			spi->next = pi;
612		}
613		if (idx > pidx && idx < lidx) {
614			pi->dirnum += pdi_mod;
615		} else if (idx == pidx) {
616			if (pidx == lidx) {
617				pi->dirnum += (u_long)(tail - result) >>
618				    malloc_pageshift;
619			} else {
620				pi->dirnum += pdi_mod - PI_OFF(index);
621			}
622		} else {
623			pi->dirnum += PI_OFF(ptr2index(tail - 1)) + 1;
624		}
625#ifdef MALLOC_EXTRA_SANITY
626		if (PD_OFF(pi->dirnum) > pdi_mod || PD_IDX(pi->dirnum) > idx) {
627			wrterror("(ES): pages directory overflow");
628			errno = EFAULT;
629			return (NULL);
630		}
631#endif /* MALLOC_EXTRA_SANITY */
632		if (idx == pidx && pi != last_dir) {
633			prev_dir = last_dir;
634			last_dir = pi;
635		}
636		spi = pi;
637		pi = spi->next;
638	}
639#ifdef MALLOC_EXTRA_SANITY
640	if (cnt > dirs)
641		wrtwarning("(ES): cnt > dirs");
642#endif /* MALLOC_EXTRA_SANITY */
643	if (cnt < dirs)
644		munmap((char *)pdregion + cnt * malloc_pagesize,
645		    (dirs - cnt) * malloc_pagesize);
646
647	return (result);
648}
649
650/*
651 * Initialize the world
652 */
653static void
654malloc_init(void)
655{
656	char		*p, b[64];
657	int		i, j, save_errno = errno;
658
659#ifdef MALLOC_EXTRA_SANITY
660	malloc_junk = 1;
661#endif /* MALLOC_EXTRA_SANITY */
662
663	for (i = 0; i < 3; i++) {
664		switch (i) {
665		case 0:
666			j = readlink("/etc/malloc.conf", b, sizeof b - 1);
667			if (j <= 0)
668				continue;
669			b[j] = '\0';
670			p = b;
671			break;
672		case 1:
673			if (issetugid() == 0)
674				p = getenv("MALLOC_OPTIONS");
675			else
676				continue;
677			break;
678		case 2:
679			p = malloc_options;
680			break;
681		default:
682			p = NULL;
683		}
684
685		for (; p != NULL && *p != '\0'; p++) {
686			switch (*p) {
687			case '>':
688				malloc_cache <<= 1;
689				break;
690			case '<':
691				malloc_cache >>= 1;
692				break;
693			case 'a':
694				malloc_abort = 0;
695				break;
696			case 'A':
697				malloc_abort = 1;
698				break;
699#ifdef MALLOC_STATS
700			case 'd':
701				malloc_stats = 0;
702				break;
703			case 'D':
704				malloc_stats = 1;
705				break;
706#endif /* MALLOC_STATS */
707			case 'f':
708				malloc_freeprot = 0;
709				break;
710			case 'F':
711				malloc_freeprot = 1;
712				break;
713			case 'g':
714				malloc_guard = 0;
715				break;
716			case 'G':
717				malloc_guard = malloc_pagesize;
718				break;
719			case 'h':
720				malloc_hint = 0;
721				break;
722			case 'H':
723				malloc_hint = 1;
724				break;
725			case 'j':
726				malloc_junk = 0;
727				break;
728			case 'J':
729				malloc_junk = 1;
730				break;
731			case 'n':
732				malloc_silent = 0;
733				break;
734			case 'N':
735				malloc_silent = 1;
736				break;
737			case 'p':
738				malloc_ptrguard = 0;
739				break;
740			case 'P':
741				malloc_ptrguard = 1;
742				break;
743			case 'r':
744				malloc_realloc = 0;
745				break;
746			case 'R':
747				malloc_realloc = 1;
748				break;
749#ifdef __FreeBSD__
750			case 'u':
751				malloc_utrace = 0;
752				break;
753			case 'U':
754				malloc_utrace = 1;
755				break;
756#endif /* __FreeBSD__ */
757			case 'x':
758				malloc_xmalloc = 0;
759				break;
760			case 'X':
761				malloc_xmalloc = 1;
762				break;
763			case 'z':
764				malloc_zero = 0;
765				break;
766			case 'Z':
767				malloc_zero = 1;
768				break;
769			default:
770				j = malloc_abort;
771				malloc_abort = 0;
772				wrtwarning("unknown char in MALLOC_OPTIONS");
773				malloc_abort = j;
774				break;
775			}
776		}
777	}
778
779	UTRACE(0, 0, 0);
780
781	/*
782	 * We want junk in the entire allocation, and zero only in the part
783	 * the user asked for.
784	 */
785	if (malloc_zero)
786		malloc_junk = 1;
787
788#ifdef MALLOC_STATS
789	if (malloc_stats && (atexit(malloc_exit) == -1))
790		wrtwarning("atexit(2) failed."
791		    "  Will not be able to dump malloc stats on exit");
792#endif /* MALLOC_STATS */
793
794	/* Allocate one page for the page directory. */
795	page_dir = (struct pginfo **)MMAP(malloc_pagesize);
796
797	if (page_dir == MAP_FAILED) {
798		wrterror("mmap(2) failed, check limits");
799		errno = ENOMEM;
800		return;
801	}
802	pdi_off = (malloc_pagesize - sizeof(struct pdinfo)) & ~(malloc_minsize - 1);
803	pdi_mod = pdi_off / sizeof(struct pginfo *);
804
805	last_dir = (struct pdinfo *) ((caddr_t) page_dir + pdi_off);
806	last_dir->base = page_dir;
807	last_dir->prev = last_dir->next = NULL;
808	last_dir->dirnum = malloc_pageshift;
809
810	/* Been here, done that. */
811	malloc_started++;
812
813	/* Recalculate the cache size in bytes, and make sure it's nonzero. */
814	if (!malloc_cache)
815		malloc_cache++;
816	malloc_cache <<= malloc_pageshift;
817	errno = save_errno;
818}
819
820/*
821 * Allocate a number of complete pages
822 */
823static void *
824malloc_pages(size_t size)
825{
826	void		*p, *tp;
827	int		i;
828	struct pginfo	**pd;
829	struct pdinfo	*pi;
830	u_long		pidx, index;
831	struct pgfree	*pf, *delay_free = NULL;
832
833	size = pageround(size) + malloc_guard;
834
835	p = NULL;
836	/* Look for free pages before asking for more */
837	for (pf = free_list.next; pf; pf = pf->next) {
838
839#ifdef MALLOC_EXTRA_SANITY
840		if (pf->size & malloc_pagemask) {
841			wrterror("(ES): junk length entry on free_list");
842			errno = EFAULT;
843			return (NULL);
844		}
845		if (!pf->size) {
846			wrterror("(ES): zero length entry on free_list");
847			errno = EFAULT;
848			return (NULL);
849		}
850		if (pf->page > (pf->page + pf->size)) {
851			wrterror("(ES): sick entry on free_list");
852			errno = EFAULT;
853			return (NULL);
854		}
855		if ((pi = pf->pdir) == NULL) {
856			wrterror("(ES): invalid page directory on free-list");
857			errno = EFAULT;
858			return (NULL);
859		}
860		if ((pidx = PI_IDX(ptr2index(pf->page))) != PD_IDX(pi->dirnum)) {
861			wrterror("(ES): directory index mismatch on free-list");
862			errno = EFAULT;
863			return (NULL);
864		}
865		pd = pi->base;
866		if (pd[PI_OFF(ptr2index(pf->page))] != MALLOC_FREE) {
867			wrterror("(ES): non-free first page on free-list");
868			errno = EFAULT;
869			return (NULL);
870		}
871		pidx = PI_IDX(ptr2index((pf->page) + (pf->size)) - 1);
872		for (pi = pf->pdir; pi != NULL && PD_IDX(pi->dirnum) < pidx;
873		    pi = pi->next)
874			;
875		if (pi == NULL || PD_IDX(pi->dirnum) != pidx) {
876			wrterror("(ES): last page not referenced in page directory");
877			errno = EFAULT;
878			return (NULL);
879		}
880		pd = pi->base;
881		if (pd[PI_OFF(ptr2index((pf->page) + (pf->size)) - 1)] != MALLOC_FREE) {
882			wrterror("(ES): non-free last page on free-list");
883			errno = EFAULT;
884			return (NULL);
885		}
886#endif /* MALLOC_EXTRA_SANITY */
887
888		if (pf->size < size)
889			continue;
890
891		if (pf->size == size) {
892			p = pf->page;
893			pi = pf->pdir;
894			if (pf->next != NULL)
895				pf->next->prev = pf->prev;
896			pf->prev->next = pf->next;
897			delay_free = pf;
898			break;
899		}
900		p = pf->page;
901		pf->page = (char *) pf->page + size;
902		pf->size -= size;
903		pidx = PI_IDX(ptr2index(pf->page));
904		for (pi = pf->pdir; pi != NULL && PD_IDX(pi->dirnum) < pidx;
905		    pi = pi->next)
906			;
907		if (pi == NULL || PD_IDX(pi->dirnum) != pidx) {
908			wrterror("(ES): hole in directories");
909			errno = EFAULT;
910			return (NULL);
911		}
912		tp = pf->pdir;
913		pf->pdir = pi;
914		pi = tp;
915		break;
916	}
917
918	size -= malloc_guard;
919
920#ifdef MALLOC_EXTRA_SANITY
921	if (p != NULL && pi != NULL) {
922		pidx = PD_IDX(pi->dirnum);
923		pd = pi->base;
924	}
925	if (p != NULL && pd[PI_OFF(ptr2index(p))] != MALLOC_FREE) {
926		wrterror("(ES): allocated non-free page on free-list");
927		errno = EFAULT;
928		return (NULL);
929	}
930#endif /* MALLOC_EXTRA_SANITY */
931
932	if (p != NULL && (malloc_guard || malloc_freeprot))
933		mprotect(p, size, PROT_READ | PROT_WRITE);
934
935	size >>= malloc_pageshift;
936
937	/* Map new pages */
938	if (p == NULL)
939		p = map_pages(size);
940
941	if (p != NULL) {
942		index = ptr2index(p);
943		pidx = PI_IDX(index);
944		pdir_lookup(index, &pi);
945#ifdef MALLOC_EXTRA_SANITY
946		if (pi == NULL || PD_IDX(pi->dirnum) != pidx) {
947			wrterror("(ES): mapped pages not found in directory");
948			errno = EFAULT;
949			return (NULL);
950		}
951#endif /* MALLOC_EXTRA_SANITY */
952		if (pi != last_dir) {
953			prev_dir = last_dir;
954			last_dir = pi;
955		}
956		pd = pi->base;
957		pd[PI_OFF(index)] = MALLOC_FIRST;
958		for (i = 1; i < size; i++) {
959			if (!PI_OFF(index + i)) {
960				pidx++;
961				pi = pi->next;
962#ifdef MALLOC_EXTRA_SANITY
963				if (pi == NULL || PD_IDX(pi->dirnum) != pidx) {
964					wrterror("(ES): hole in mapped pages directory");
965					errno = EFAULT;
966					return (NULL);
967				}
968#endif /* MALLOC_EXTRA_SANITY */
969				pd = pi->base;
970			}
971			pd[PI_OFF(index + i)] = MALLOC_FOLLOW;
972		}
973		if (malloc_guard) {
974			if (!PI_OFF(index + i)) {
975				pidx++;
976				pi = pi->next;
977#ifdef MALLOC_EXTRA_SANITY
978				if (pi == NULL || PD_IDX(pi->dirnum) != pidx) {
979					wrterror("(ES): hole in mapped pages directory");
980					errno = EFAULT;
981					return (NULL);
982				}
983#endif /* MALLOC_EXTRA_SANITY */
984				pd = pi->base;
985			}
986			pd[PI_OFF(index + i)] = MALLOC_FIRST;
987		}
988		malloc_used += size << malloc_pageshift;
989		malloc_guarded += malloc_guard;
990
991		if (malloc_junk)
992			memset(p, SOME_JUNK, size << malloc_pageshift);
993	}
994	if (delay_free) {
995		if (px == NULL)
996			px = delay_free;
997		else
998			put_pgfree(delay_free);
999	}
1000	return (p);
1001}
1002
1003/*
1004 * Allocate a page of fragments
1005 */
1006
1007static int
1008malloc_make_chunks(int bits)
1009{
1010	struct pginfo	*bp, **pd;
1011	struct pdinfo	*pi;
1012#ifdef	MALLOC_EXTRA_SANITY
1013	u_long		pidx;
1014#endif	/* MALLOC_EXTRA_SANITY */
1015	void		*pp;
1016	long		i, k;
1017
1018	/* Allocate a new bucket */
1019	pp = malloc_pages((size_t)malloc_pagesize);
1020	if (pp == NULL)
1021		return (0);
1022
1023	/* Find length of admin structure */
1024
1025	/* Don't waste more than two chunks on this */
1026
1027	/*
1028	 * If we are to allocate a memory protected page for the malloc(0)
1029	 * case (when bits=0), it must be from a different page than the
1030	 * pginfo page.
1031	 * --> Treat it like the big chunk alloc, get a second data page.
1032	 */
1033	bp = alloc_pginfo();
1034	if (bp == NULL) {
1035		ifree(pp);
1036		return (0);
1037	}
1038
1039	/* memory protect the page allocated in the malloc(0) case */
1040	if (bits == 0) {
1041		bp->size = 0;
1042		bp->shift = 1;
1043		i = malloc_minsize - 1;
1044		while (i >>= 1)
1045			bp->shift++;
1046		bp->total = bp->free = malloc_pagesize >> bp->shift;
1047		bp->page = pp;
1048
1049		k = mprotect(pp, malloc_pagesize, PROT_NONE);
1050		if (k < 0) {
1051			ifree(pp);
1052			put_pginfo(bp);
1053			return (0);
1054		}
1055	} else {
1056		bp->size = (1UL << bits);
1057		bp->shift = bits;
1058		bp->total = bp->free = malloc_pagesize >> bits;
1059		bp->page = pp;
1060	}
1061
1062	/* set all valid bits in the bitmap */
1063	k = bp->total;
1064	i = 0;
1065
1066	/* Do a bunch at a time */
1067	for (; (k - i) >= MALLOC_BITS; i += MALLOC_BITS)
1068		bp->bits[i / MALLOC_BITS] = ~0UL;
1069
1070	for (; i < k; i++)
1071		bp->bits[i / MALLOC_BITS] |= 1UL << (i % MALLOC_BITS);
1072
1073	pdir_lookup(ptr2index(pp), &pi);
1074#ifdef MALLOC_EXTRA_SANITY
1075	pidx = PI_IDX(ptr2index(pp));
1076	if (pi == NULL || PD_IDX(pi->dirnum) != pidx) {
1077		wrterror("(ES): mapped pages not found in directory");
1078		errno = EFAULT;
1079		return (0);
1080	}
1081#endif /* MALLOC_EXTRA_SANITY */
1082	if (pi != last_dir) {
1083		prev_dir = last_dir;
1084		last_dir = pi;
1085	}
1086	pd = pi->base;
1087	pd[PI_OFF(ptr2index(pp))] = bp;
1088
1089	bp->next = page_dir[bits];
1090	page_dir[bits] = bp;
1091
1092	/* MALLOC_UNLOCK */
1093	return (1);
1094}
1095
1096/*
1097 * Allocate a fragment
1098 */
1099static void *
1100malloc_bytes(size_t size)
1101{
1102	int		i, j;
1103	size_t		k;
1104	u_long		u, *lp;
1105	struct pginfo	*bp;
1106
1107	/* Don't bother with anything less than this */
1108	/* unless we have a malloc(0) requests */
1109	if (size != 0 && size < malloc_minsize)
1110		size = malloc_minsize;
1111
1112	/* Find the right bucket */
1113	if (size == 0)
1114		j = 0;
1115	else {
1116		j = 1;
1117		i = size - 1;
1118		while (i >>= 1)
1119			j++;
1120	}
1121
1122	/* If it's empty, make a page more of that size chunks */
1123	if (page_dir[j] == NULL && !malloc_make_chunks(j))
1124		return (NULL);
1125
1126	bp = page_dir[j];
1127
1128	/* Find first word of bitmap which isn't empty */
1129	for (lp = bp->bits; !*lp; lp++);
1130
1131	/* Find that bit, and tweak it */
1132	u = 1;
1133	k = 0;
1134	while (!(*lp & u)) {
1135		u += u;
1136		k++;
1137	}
1138
1139	if (malloc_guard) {
1140		/* Walk to a random position. */
1141		i = arc4random_uniform(bp->free);
1142		while (i > 0) {
1143			u += u;
1144			k++;
1145			if (k >= MALLOC_BITS) {
1146				lp++;
1147				u = 1;
1148				k = 0;
1149			}
1150#ifdef MALLOC_EXTRA_SANITY
1151			if (lp - bp->bits > (bp->total - 1) / MALLOC_BITS) {
1152				wrterror("chunk overflow");
1153				errno = EFAULT;
1154				return (NULL);
1155			}
1156#endif /* MALLOC_EXTRA_SANITY */
1157			if (*lp & u)
1158				i--;
1159		}
1160	}
1161	*lp ^= u;
1162
1163	/* If there are no more free, remove from free-list */
1164	if (!--bp->free) {
1165		page_dir[j] = bp->next;
1166		bp->next = NULL;
1167	}
1168	/* Adjust to the real offset of that chunk */
1169	k += (lp - bp->bits) * MALLOC_BITS;
1170	k <<= bp->shift;
1171
1172	if (malloc_junk && bp->size != 0)
1173		memset((char *)bp->page + k, SOME_JUNK, (size_t)bp->size);
1174
1175	return ((u_char *) bp->page + k);
1176}
1177
1178/*
1179 * Magic so that malloc(sizeof(ptr)) is near the end of the page.
1180 */
1181#define	PTR_GAP		(malloc_pagesize - sizeof(void *))
1182#define	PTR_SIZE	(sizeof(void *))
1183#define	PTR_ALIGNED(p)	(((unsigned long)p & malloc_pagemask) == PTR_GAP)
1184
1185/*
1186 * Allocate a piece of memory
1187 */
1188static void *
1189imalloc(size_t size)
1190{
1191	void		*result;
1192	int		ptralloc = 0;
1193
1194	if (!malloc_started)
1195		malloc_init();
1196
1197	if (suicide)
1198		abort();
1199
1200	/* does not matter if alloc_pgfree() fails */
1201	if (px == NULL)
1202		px = alloc_pgfree();
1203
1204	if (malloc_ptrguard && size == PTR_SIZE) {
1205		ptralloc = 1;
1206		size = malloc_pagesize;
1207	}
1208	if ((size + malloc_pagesize) < size) {	/* Check for overflow */
1209		result = NULL;
1210		errno = ENOMEM;
1211	} else if (size <= malloc_maxsize)
1212		result = malloc_bytes(size);
1213	else
1214		result = malloc_pages(size);
1215
1216	if (malloc_abort == 1 && result == NULL)
1217		wrterror("allocation failed");
1218
1219	if (malloc_zero && result != NULL)
1220		memset(result, 0, size);
1221
1222	if (result && ptralloc)
1223		return ((char *) result + PTR_GAP);
1224	return (result);
1225}
1226
1227/*
1228 * Change the size of an allocation.
1229 */
1230static void *
1231irealloc(void *ptr, size_t size)
1232{
1233	void		*p;
1234	size_t		osize;
1235	u_long		index, i;
1236	struct pginfo	**mp;
1237	struct pginfo	**pd;
1238	struct pdinfo	*pi;
1239#ifdef	MALLOC_EXTRA_SANITY
1240	u_long		pidx;
1241#endif	/* MALLOC_EXTRA_SANITY */
1242
1243	if (suicide)
1244		abort();
1245
1246	if (!malloc_started) {
1247		wrtwarning("malloc() has never been called");
1248		return (NULL);
1249	}
1250	if (malloc_ptrguard && PTR_ALIGNED(ptr)) {
1251		if (size <= PTR_SIZE)
1252			return (ptr);
1253
1254		p = imalloc(size);
1255		if (p)
1256			memcpy(p, ptr, PTR_SIZE);
1257		ifree(ptr);
1258		return (p);
1259	}
1260	index = ptr2index(ptr);
1261
1262	if (index < malloc_pageshift) {
1263		wrtwarning("junk pointer, too low to make sense");
1264		return (NULL);
1265	}
1266	if (index > last_index) {
1267		wrtwarning("junk pointer, too high to make sense");
1268		return (NULL);
1269	}
1270	pdir_lookup(index, &pi);
1271#ifdef MALLOC_EXTRA_SANITY
1272	pidx = PI_IDX(index);
1273	if (pi == NULL || PD_IDX(pi->dirnum) != pidx) {
1274		wrterror("(ES): mapped pages not found in directory");
1275		errno = EFAULT;
1276		return (NULL);
1277	}
1278#endif /* MALLOC_EXTRA_SANITY */
1279	if (pi != last_dir) {
1280		prev_dir = last_dir;
1281		last_dir = pi;
1282	}
1283	pd = pi->base;
1284	mp = &pd[PI_OFF(index)];
1285
1286	if (*mp == MALLOC_FIRST) {	/* Page allocation */
1287
1288		/* Check the pointer */
1289		if ((u_long) ptr & malloc_pagemask) {
1290			wrtwarning("modified (page-) pointer");
1291			return (NULL);
1292		}
1293		/* Find the size in bytes */
1294		i = index;
1295		if (!PI_OFF(++i)) {
1296			pi = pi->next;
1297			if (pi != NULL && PD_IDX(pi->dirnum) != PI_IDX(i))
1298				pi = NULL;
1299			if (pi != NULL)
1300				pd = pi->base;
1301		}
1302		for (osize = malloc_pagesize;
1303		    pi != NULL && pd[PI_OFF(i)] == MALLOC_FOLLOW;) {
1304			osize += malloc_pagesize;
1305			if (!PI_OFF(++i)) {
1306				pi = pi->next;
1307				if (pi != NULL && PD_IDX(pi->dirnum) != PI_IDX(i))
1308					pi = NULL;
1309				if (pi != NULL)
1310					pd = pi->base;
1311			}
1312		}
1313
1314		if (!malloc_realloc && size <= osize &&
1315		    size > osize - malloc_pagesize) {
1316			if (malloc_junk)
1317				memset((char *)ptr + size, SOME_JUNK, osize - size);
1318			return (ptr);	/* ..don't do anything else. */
1319		}
1320	} else if (*mp >= MALLOC_MAGIC) {	/* Chunk allocation */
1321
1322		/* Check the pointer for sane values */
1323		if ((u_long) ptr & ((1UL << ((*mp)->shift)) - 1)) {
1324			wrtwarning("modified (chunk-) pointer");
1325			return (NULL);
1326		}
1327		/* Find the chunk index in the page */
1328		i = ((u_long) ptr & malloc_pagemask) >> (*mp)->shift;
1329
1330		/* Verify that it isn't a free chunk already */
1331		if ((*mp)->bits[i / MALLOC_BITS] & (1UL << (i % MALLOC_BITS))) {
1332			wrtwarning("chunk is already free");
1333			return (NULL);
1334		}
1335		osize = (*mp)->size;
1336
1337		if (!malloc_realloc && size <= osize &&
1338		    (size > osize / 2 || osize == malloc_minsize)) {
1339			if (malloc_junk)
1340				memset((char *) ptr + size, SOME_JUNK, osize - size);
1341			return (ptr);	/* ..don't do anything else. */
1342		}
1343	} else {
1344		wrtwarning("irealloc: pointer to wrong page");
1345		return (NULL);
1346	}
1347
1348	p = imalloc(size);
1349
1350	if (p != NULL) {
1351		/* copy the lesser of the two sizes, and free the old one */
1352		/* Don't move from/to 0 sized region !!! */
1353		if (osize != 0 && size != 0) {
1354			if (osize < size)
1355				memcpy(p, ptr, osize);
1356			else
1357				memcpy(p, ptr, size);
1358		}
1359		ifree(ptr);
1360	}
1361	return (p);
1362}
1363
1364/*
1365 * Free a sequence of pages
1366 */
1367static void
1368free_pages(void *ptr, u_long index, struct pginfo * info)
1369{
1370	u_long		i, pidx, lidx;
1371	size_t		l, cachesize = 0;
1372	struct pginfo	**pd;
1373	struct pdinfo	*pi, *spi;
1374	struct pgfree	*pf, *pt = NULL;
1375	caddr_t		tail;
1376
1377	if (info == MALLOC_FREE) {
1378		wrtwarning("page is already free");
1379		return;
1380	}
1381	if (info != MALLOC_FIRST) {
1382		wrtwarning("free_pages: pointer to wrong page");
1383		return;
1384	}
1385	if ((u_long) ptr & malloc_pagemask) {
1386		wrtwarning("modified (page-) pointer");
1387		return;
1388	}
1389	/* Count how many pages and mark them free at the same time */
1390	pidx = PI_IDX(index);
1391	pdir_lookup(index, &pi);
1392#ifdef MALLOC_EXTRA_SANITY
1393	if (pi == NULL || PD_IDX(pi->dirnum) != pidx) {
1394		wrterror("(ES): mapped pages not found in directory");
1395		errno = EFAULT;
1396		return;
1397	}
1398#endif /* MALLOC_EXTRA_SANITY */
1399
1400	spi = pi;		/* Save page index for start of region. */
1401
1402	pd = pi->base;
1403	pd[PI_OFF(index)] = MALLOC_FREE;
1404	i = 1;
1405	if (!PI_OFF(index + i)) {
1406		pi = pi->next;
1407		if (pi == NULL || PD_IDX(pi->dirnum) != PI_IDX(index + i))
1408			pi = NULL;
1409		else
1410			pd = pi->base;
1411	}
1412	while (pi != NULL && pd[PI_OFF(index + i)] == MALLOC_FOLLOW) {
1413		pd[PI_OFF(index + i)] = MALLOC_FREE;
1414		i++;
1415		if (!PI_OFF(index + i)) {
1416			if ((pi = pi->next) == NULL ||
1417			    PD_IDX(pi->dirnum) != PI_IDX(index + i))
1418				pi = NULL;
1419			else
1420				pd = pi->base;
1421		}
1422	}
1423
1424	l = i << malloc_pageshift;
1425
1426	if (malloc_junk)
1427		memset(ptr, SOME_JUNK, l);
1428
1429	malloc_used -= l;
1430	malloc_guarded -= malloc_guard;
1431	if (malloc_guard) {
1432#ifdef MALLOC_EXTRA_SANITY
1433		if (pi == NULL || PD_IDX(pi->dirnum) != PI_IDX(index + i)) {
1434			wrterror("(ES): hole in mapped pages directory");
1435			errno = EFAULT;
1436			return;
1437		}
1438#endif /* MALLOC_EXTRA_SANITY */
1439		pd[PI_OFF(index + i)] = MALLOC_FREE;
1440		l += malloc_guard;
1441	}
1442	tail = (caddr_t)ptr + l;
1443
1444	if (malloc_hint)
1445		madvise(ptr, l, MADV_FREE);
1446
1447	if (malloc_freeprot)
1448		mprotect(ptr, l, PROT_NONE);
1449
1450	/* Add to free-list. */
1451	if (px == NULL && (px = alloc_pgfree()) == NULL)
1452		goto not_return;
1453	px->page = ptr;
1454	px->pdir = spi;
1455	px->size = l;
1456
1457	if (free_list.next == NULL) {
1458		/* Nothing on free list, put this at head. */
1459		px->next = NULL;
1460		px->prev = &free_list;
1461		free_list.next = px;
1462		pf = px;
1463		px = NULL;
1464	} else {
1465		/*
1466		 * Find the right spot, leave pf pointing to the modified
1467		 * entry.
1468		 */
1469
1470		/* Race ahead here, while calculating cache size. */
1471		for (pf = free_list.next;
1472		    (caddr_t)ptr > ((caddr_t)pf->page + pf->size)
1473		    && pf->next != NULL;
1474		    pf = pf->next)
1475			cachesize += pf->size;
1476
1477		/* Finish cache size calculation. */
1478		pt = pf;
1479		while (pt) {
1480			cachesize += pt->size;
1481			pt = pt->next;
1482		}
1483
1484		if ((caddr_t)pf->page > tail) {
1485			/* Insert before entry */
1486			px->next = pf;
1487			px->prev = pf->prev;
1488			pf->prev = px;
1489			px->prev->next = px;
1490			pf = px;
1491			px = NULL;
1492		} else if (((caddr_t)pf->page + pf->size) == ptr) {
1493			/* Append to the previous entry. */
1494			cachesize -= pf->size;
1495			pf->size += l;
1496			if (pf->next != NULL &&
1497			    pf->next->page == ((caddr_t)pf->page + pf->size)) {
1498				/* And collapse the next too. */
1499				pt = pf->next;
1500				pf->size += pt->size;
1501				pf->next = pt->next;
1502				if (pf->next != NULL)
1503					pf->next->prev = pf;
1504			}
1505		} else if (pf->page == tail) {
1506			/* Prepend to entry. */
1507			cachesize -= pf->size;
1508			pf->size += l;
1509			pf->page = ptr;
1510			pf->pdir = spi;
1511		} else if (pf->next == NULL) {
1512			/* Append at tail of chain. */
1513			px->next = NULL;
1514			px->prev = pf;
1515			pf->next = px;
1516			pf = px;
1517			px = NULL;
1518		} else {
1519			wrterror("freelist is destroyed");
1520			errno = EFAULT;
1521			return;
1522		}
1523	}
1524
1525	if (pf->pdir != last_dir) {
1526		prev_dir = last_dir;
1527		last_dir = pf->pdir;
1528	}
1529
1530	/* Return something to OS ? */
1531	if (pf->size > (malloc_cache - cachesize)) {
1532
1533		/*
1534		 * Keep the cache intact.  Notice that the '>' above guarantees that
1535		 * the pf will always have at least one page afterwards.
1536		 */
1537		if (munmap((char *) pf->page + (malloc_cache - cachesize),
1538		    pf->size - (malloc_cache - cachesize)) != 0)
1539			goto not_return;
1540		tail = (caddr_t)pf->page + pf->size;
1541		lidx = ptr2index(tail) - 1;
1542		pf->size = malloc_cache - cachesize;
1543
1544		index = ptr2index((caddr_t)pf->page + pf->size);
1545
1546		pidx = PI_IDX(index);
1547		if (prev_dir != NULL && PD_IDX(prev_dir->dirnum) >= pidx)
1548			prev_dir = NULL;	/* Will be wiped out below ! */
1549
1550		for (pi = pf->pdir; pi != NULL && PD_IDX(pi->dirnum) < pidx;
1551		    pi = pi->next)
1552			;
1553
1554		spi = pi;
1555		if (pi != NULL && PD_IDX(pi->dirnum) == pidx) {
1556			pd = pi->base;
1557
1558			for (i = index; i <= lidx;) {
1559				if (pd[PI_OFF(i)] != MALLOC_NOT_MINE) {
1560					pd[PI_OFF(i)] = MALLOC_NOT_MINE;
1561#ifdef MALLOC_EXTRA_SANITY
1562					if (!PD_OFF(pi->dirnum)) {
1563						wrterror("(ES): pages directory underflow");
1564						errno = EFAULT;
1565						return;
1566					}
1567#endif /* MALLOC_EXTRA_SANITY */
1568					pi->dirnum--;
1569				}
1570#ifdef MALLOC_EXTRA_SANITY
1571				else
1572					wrtwarning("(ES): page already unmapped");
1573#endif /* MALLOC_EXTRA_SANITY */
1574				i++;
1575				if (!PI_OFF(i)) {
1576					/*
1577					 * If no page in that dir, free
1578					 * directory page.
1579					 */
1580					if (!PD_OFF(pi->dirnum)) {
1581						/* Remove from list. */
1582						if (spi == pi)
1583							spi = pi->prev;
1584						if (pi->prev != NULL)
1585							pi->prev->next = pi->next;
1586						if (pi->next != NULL)
1587							pi->next->prev = pi->prev;
1588						pi = pi->next;
1589						munmap(pd, malloc_pagesize);
1590					} else
1591						pi = pi->next;
1592					if (pi == NULL ||
1593					    PD_IDX(pi->dirnum) != PI_IDX(i))
1594						break;
1595					pd = pi->base;
1596				}
1597			}
1598			if (pi && !PD_OFF(pi->dirnum)) {
1599				/* Resulting page dir is now empty. */
1600				/* Remove from list. */
1601				if (spi == pi)	/* Update spi only if first. */
1602					spi = pi->prev;
1603				if (pi->prev != NULL)
1604					pi->prev->next = pi->next;
1605				if (pi->next != NULL)
1606					pi->next->prev = pi->prev;
1607				pi = pi->next;
1608				munmap(pd, malloc_pagesize);
1609			}
1610		}
1611		if (pi == NULL && malloc_brk == tail) {
1612			/* Resize down the malloc upper boundary. */
1613			last_index = index - 1;
1614			malloc_brk = index2ptr(index);
1615		}
1616
1617		/* XXX: We could realloc/shrink the pagedir here I guess. */
1618		if (pf->size == 0) {	/* Remove from free-list as well. */
1619			if (px)
1620				put_pgfree(px);
1621			if ((px = pf->prev) != &free_list) {
1622				if (pi == NULL && last_index == (index - 1)) {
1623					if (spi == NULL) {
1624						malloc_brk = NULL;
1625						i = 11;
1626					} else {
1627						pd = spi->base;
1628						if (PD_IDX(spi->dirnum) < pidx)
1629							index =
1630							    ((PD_IDX(spi->dirnum) + 1) *
1631							    pdi_mod) - 1;
1632						for (pi = spi, i = index;
1633						    pd[PI_OFF(i)] == MALLOC_NOT_MINE;
1634						    i--) {
1635#ifdef MALLOC_EXTRA_SANITY
1636							if (!PI_OFF(i)) {
1637								pi = pi->prev;
1638								if (pi == NULL || i == 0)
1639									break;
1640								pd = pi->base;
1641								i = (PD_IDX(pi->dirnum) + 1) * pdi_mod;
1642							}
1643#endif /* MALLOC_EXTRA_SANITY */
1644						}
1645						malloc_brk = index2ptr(i + 1);
1646					}
1647					last_index = i;
1648				}
1649				if ((px->next = pf->next) != NULL)
1650					px->next->prev = px;
1651			} else {
1652				if ((free_list.next = pf->next) != NULL)
1653					free_list.next->prev = &free_list;
1654			}
1655			px = pf;
1656			last_dir = prev_dir;
1657			prev_dir = NULL;
1658		}
1659	}
1660not_return:
1661	if (pt != NULL)
1662		put_pgfree(pt);
1663}
1664
1665/*
1666 * Free a chunk, and possibly the page it's on, if the page becomes empty.
1667 */
1668
1669/* ARGSUSED */
1670static void
1671free_bytes(void *ptr)
1672{
1673	u_int8_t __arc4_getbyte(void);
1674	struct pginfo	**mp, **pd, *info;
1675	struct pdinfo	*pi;
1676#ifdef	MALLOC_EXTRA_SANITY
1677	u_long		pidx;
1678#endif	/* MALLOC_EXTRA_SANITY */
1679	u_long		index;
1680	void		*vp;
1681	long		i;
1682	void *tmpptr;
1683	unsigned int tmpidx;
1684	/* pointers that we will want to free at some future time */
1685	static void *chunk_buffer[16];
1686
1687
1688	/* delay return, returning a random something from before instead */
1689	tmpidx = __arc4_getbyte() % 16;
1690	tmpptr = chunk_buffer[tmpidx];
1691	chunk_buffer[tmpidx] = ptr;
1692	ptr = tmpptr;
1693	if (!ptr)
1694		return;
1695
1696	index = ptr2index(ptr);
1697
1698	pdir_lookup(index, &pi);
1699	if (pi != last_dir) {
1700		prev_dir = last_dir;
1701		last_dir = pi;
1702	}
1703	pd = pi->base;
1704	info = pd[PI_OFF(index)];
1705
1706
1707	/* Find the chunk number on the page */
1708	i = ((u_long) ptr & malloc_pagemask) >> info->shift;
1709
1710	if ((u_long) ptr & ((1UL << (info->shift)) - 1)) {
1711		wrtwarning("modified (chunk-) pointer");
1712		return;
1713	}
1714	if (info->bits[i / MALLOC_BITS] & (1UL << (i % MALLOC_BITS))) {
1715		wrtwarning("chunk is already free");
1716		return;
1717	}
1718	if (malloc_junk && info->size != 0)
1719		memset(ptr, SOME_JUNK, (size_t)info->size);
1720
1721	info->bits[i / MALLOC_BITS] |= 1UL << (i % MALLOC_BITS);
1722	info->free++;
1723
1724	if (info->size != 0)
1725		mp = page_dir + info->shift;
1726	else
1727		mp = page_dir;
1728
1729	if (info->free == 1) {
1730		/* Page became non-full */
1731
1732		/* Insert in address order */
1733		while (*mp != NULL && (*mp)->next != NULL &&
1734		    (*mp)->next->page < info->page)
1735			mp = &(*mp)->next;
1736		info->next = *mp;
1737		*mp = info;
1738		return;
1739	}
1740	if (info->free != info->total)
1741		return;
1742
1743	/* Find & remove this page in the queue */
1744	while (*mp != info) {
1745		mp = &((*mp)->next);
1746#ifdef MALLOC_EXTRA_SANITY
1747		if (!*mp) {
1748			wrterror("(ES): Not on queue");
1749			errno = EFAULT;
1750			return;
1751		}
1752#endif /* MALLOC_EXTRA_SANITY */
1753	}
1754	*mp = info->next;
1755
1756	/* Free the page & the info structure if need be */
1757	pdir_lookup(ptr2index(info->page), &pi);
1758#ifdef MALLOC_EXTRA_SANITY
1759	pidx = PI_IDX(ptr2index(info->page));
1760	if (pi == NULL || PD_IDX(pi->dirnum) != pidx) {
1761		wrterror("(ES): mapped pages not found in directory");
1762		errno = EFAULT;
1763		return;
1764	}
1765#endif /* MALLOC_EXTRA_SANITY */
1766	if (pi != last_dir) {
1767		prev_dir = last_dir;
1768		last_dir = pi;
1769	}
1770	pd = pi->base;
1771	pd[PI_OFF(ptr2index(info->page))] = MALLOC_FIRST;
1772
1773	/* If the page was mprotected, unprotect it before releasing it */
1774	if (info->size == 0)
1775		mprotect(info->page, malloc_pagesize, PROT_READ | PROT_WRITE);
1776
1777	vp = info->page;
1778	put_pginfo(info);
1779	ifree(vp);
1780}
1781
1782static void
1783ifree(void *ptr)
1784{
1785	struct pginfo	*info, **pd;
1786	u_long		index;
1787#ifdef	MALLOC_EXTRA_SANITY
1788	u_long		pidx;
1789#endif	/* MALLOC_EXTRA_SANITY */
1790	struct pdinfo	*pi;
1791
1792	if (!malloc_started) {
1793		wrtwarning("malloc() has never been called");
1794		return;
1795	}
1796	/* If we're already sinking, don't make matters any worse. */
1797	if (suicide)
1798		return;
1799
1800	if (malloc_ptrguard && PTR_ALIGNED(ptr))
1801		ptr = (char *)ptr - PTR_GAP;
1802
1803	index = ptr2index(ptr);
1804
1805	if (index < malloc_pageshift) {
1806		warnx("(%p)", ptr);
1807		wrtwarning("ifree: junk pointer, too low to make sense");
1808		return;
1809	}
1810	if (index > last_index) {
1811		warnx("(%p)", ptr);
1812		wrtwarning("ifree: junk pointer, too high to make sense");
1813		return;
1814	}
1815
1816	pdir_lookup(index, &pi);
1817#ifdef MALLOC_EXTRA_SANITY
1818	pidx = PI_IDX(index);
1819	if (pi == NULL || PD_IDX(pi->dirnum) != pidx) {
1820		wrterror("(ES): mapped pages not found in directory");
1821		errno = EFAULT;
1822		return;
1823	}
1824#endif /* MALLOC_EXTRA_SANITY */
1825	if (pi != last_dir) {
1826		prev_dir = last_dir;
1827		last_dir = pi;
1828	}
1829	pd = pi->base;
1830	info = pd[PI_OFF(index)];
1831
1832	if (info < MALLOC_MAGIC)
1833		free_pages(ptr, index, info);
1834	else
1835		free_bytes(ptr);
1836
1837	/* does not matter if alloc_pgfree fails */
1838	if (px == NULL)
1839		px = alloc_pgfree();
1840
1841	return;
1842}
1843
1844/*
1845 * Common function for handling recursion.  Only
1846 * print the error message once, to avoid making the problem
1847 * potentially worse.
1848 */
1849static void
1850malloc_recurse(void)
1851{
1852	static int	noprint;
1853
1854	if (noprint == 0) {
1855		noprint = 1;
1856		wrtwarning("recursive call");
1857	}
1858	malloc_active--;
1859	_MALLOC_UNLOCK();
1860	errno = EDEADLK;
1861}
1862
1863/*
1864 * These are the public exported interface routines.
1865 */
1866void *
1867malloc(size_t size)
1868{
1869	void		*r;
1870
1871	_MALLOC_LOCK();
1872	malloc_func = " in malloc():";
1873	if (malloc_active++) {
1874		malloc_recurse();
1875		return (NULL);
1876	}
1877	r = imalloc(size);
1878	UTRACE(0, size, r);
1879	malloc_active--;
1880	_MALLOC_UNLOCK();
1881	if (malloc_xmalloc && r == NULL) {
1882		wrterror("out of memory");
1883		errno = ENOMEM;
1884	}
1885	return (r);
1886}
1887
1888void
1889free(void *ptr)
1890{
1891	/* This is legal. XXX quick path */
1892	if (ptr == NULL)
1893		return;
1894
1895	_MALLOC_LOCK();
1896	malloc_func = " in free():";
1897	if (malloc_active++) {
1898		malloc_recurse();
1899		return;
1900	}
1901	ifree(ptr);
1902	UTRACE(ptr, 0, 0);
1903	malloc_active--;
1904	_MALLOC_UNLOCK();
1905	return;
1906}
1907
1908void *
1909realloc(void *ptr, size_t size)
1910{
1911	void		*r;
1912
1913	_MALLOC_LOCK();
1914	malloc_func = " in realloc():";
1915	if (malloc_active++) {
1916		malloc_recurse();
1917		return (NULL);
1918	}
1919
1920	if (ptr == NULL)
1921		r = imalloc(size);
1922	else
1923		r = irealloc(ptr, size);
1924
1925	UTRACE(ptr, size, r);
1926	malloc_active--;
1927	_MALLOC_UNLOCK();
1928	if (malloc_xmalloc && r == NULL) {
1929		wrterror("out of memory");
1930		errno = ENOMEM;
1931	}
1932	return (r);
1933}
1934