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