xref: /openbsd-src/lib/libc/stdlib/malloc.c (revision 11f78e4420fedc7328b2013f27ee5520479f974e)
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.59 2003/08/04 16:51:49 jfb 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/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 
52 #include "thread_private.h"
53 
54 /*
55  * The basic parameters you can tweak.
56  *
57  * malloc_pageshift	pagesize = 1 << malloc_pageshift
58  *			It's probably best if this is the native
59  *			page size, but it shouldn't have to be.
60  *
61  * malloc_minsize	minimum size of an allocation in bytes.
62  *			If this is too small it's too much work
63  *			to manage them.  This is also the smallest
64  *			unit of alignment used for the storage
65  *			returned by malloc/realloc.
66  *
67  */
68 
69 #if defined(__OpenBSD__) && defined(__sparc__)
70 #   define    malloc_pageshift	13U
71 #endif /* __OpenBSD__ */
72 
73 /*
74  * No user serviceable parts behind this point.
75  *
76  * This structure describes a page worth of chunks.
77  */
78 
79 struct pginfo {
80     struct pginfo	*next;	/* next on the free list */
81     void		*page;	/* Pointer to the page */
82     u_short		size;	/* size of this page's chunks */
83     u_short		shift;	/* How far to shift for this size chunks */
84     u_short		free;	/* How many free chunks */
85     u_short		total;	/* How many chunk */
86     u_long		bits[1]; /* Which chunks are free */
87 };
88 
89 /*
90  * This structure describes a number of free pages.
91  */
92 
93 struct pgfree {
94     struct pgfree	*next;	/* next run of free pages */
95     struct pgfree	*prev;	/* prev run of free pages */
96     void		*page;	/* pointer to free pages */
97     void		*end;	/* pointer to end of free pages */
98     u_long		size;	/* number of bytes free */
99 };
100 
101 /*
102  * How many bits per u_long in the bitmap.
103  * Change only if not 8 bits/byte
104  */
105 #define	MALLOC_BITS	(8*sizeof(u_long))
106 
107 /*
108  * Magic values to put in the page_directory
109  */
110 #define MALLOC_NOT_MINE	((struct pginfo*) 0)
111 #define MALLOC_FREE	((struct pginfo*) 1)
112 #define MALLOC_FIRST	((struct pginfo*) 2)
113 #define MALLOC_FOLLOW	((struct pginfo*) 3)
114 #define MALLOC_MAGIC	((struct pginfo*) 4)
115 
116 #ifndef malloc_pageshift
117 #define malloc_pageshift		(PGSHIFT)
118 #endif
119 
120 #ifndef malloc_minsize
121 #define malloc_minsize			16U
122 #endif
123 
124 #ifndef malloc_pageshift
125 #error	"malloc_pageshift undefined"
126 #endif
127 
128 #if !defined(malloc_pagesize)
129 #define malloc_pagesize			(1UL<<malloc_pageshift)
130 #endif
131 
132 #if ((1UL<<malloc_pageshift) != malloc_pagesize)
133 #error	"(1UL<<malloc_pageshift) != malloc_pagesize"
134 #endif
135 
136 #ifndef malloc_maxsize
137 #define malloc_maxsize			((malloc_pagesize)>>1)
138 #endif
139 
140 /* A mask for the offset inside a page.  */
141 #define malloc_pagemask	((malloc_pagesize)-1)
142 
143 #define pageround(foo) (((foo) + (malloc_pagemask))&(~(malloc_pagemask)))
144 #define ptr2index(foo) (((u_long)(foo) >> malloc_pageshift)-malloc_origo)
145 
146 /* fd of /dev/zero */
147 #ifdef USE_DEV_ZERO
148 static int fdzero;
149 #define	MMAP_FD	fdzero
150 #define INIT_MMAP() \
151 	{ if ((fdzero=open("/dev/zero", O_RDWR, 0000)) == -1) \
152 	    wrterror("open of /dev/zero"); }
153 #else
154 #define MMAP_FD (-1)
155 #define INIT_MMAP()
156 #endif
157 
158 /* Set when initialization has been done */
159 static unsigned int malloc_started;
160 
161 /* Number of free pages we cache */
162 static unsigned int malloc_cache = 16;
163 
164 /* The offset from pagenumber to index into the page directory */
165 static u_long malloc_origo;
166 
167 /* The last index in the page directory we care about */
168 static u_long last_index;
169 
170 /* Pointer to page directory. Allocated "as if with" malloc */
171 static struct	pginfo **page_dir;
172 
173 /* How many slots in the page directory */
174 static size_t	malloc_ninfo;
175 
176 /* Free pages line up here */
177 static struct pgfree free_list;
178 
179 /* Abort(), user doesn't handle problems.  */
180 static int malloc_abort;
181 
182 /* Are we trying to die ?  */
183 static int suicide;
184 
185 #ifdef MALLOC_STATS
186 /* dump statistics */
187 static int malloc_stats;
188 #endif
189 
190 /* avoid outputting warnings?  */
191 static int malloc_silent;
192 
193 /* always realloc ?  */
194 static int malloc_realloc;
195 
196 #if defined(__FreeBSD__) || (defined(__OpenBSD__) && defined(MADV_FREE))
197 /* pass the kernel a hint on free pages ?  */
198 static int malloc_hint;
199 #endif
200 
201 /* xmalloc behaviour ?  */
202 static int malloc_xmalloc;
203 
204 /* zero fill ?  */
205 static int malloc_zero;
206 
207 /* junk fill ?  */
208 static int malloc_junk;
209 
210 #ifdef __FreeBSD__
211 /* utrace ?  */
212 static int malloc_utrace;
213 
214 struct ut { void *p; size_t s; void *r; };
215 
216 void utrace(struct ut *, int);
217 
218 #define UTRACE(a, b, c) \
219 	if (malloc_utrace) \
220 		{struct ut u; u.p=a; u.s = b; u.r=c; utrace(&u, sizeof u);}
221 #else /* !__FreeBSD__ */
222 #define UTRACE(a,b,c)
223 #endif
224 
225 /* my last break. */
226 static void *malloc_brk;
227 
228 /* one location cache for free-list holders */
229 static struct pgfree *px;
230 
231 /* compile-time options */
232 char *malloc_options;
233 
234 /* Name of the current public function */
235 static char *malloc_func;
236 
237 /* Macro for mmap */
238 #define MMAP(size) \
239 	mmap((void *)0, (size), PROT_READ|PROT_WRITE, MAP_ANON|MAP_PRIVATE, \
240 	    MMAP_FD, (off_t)0)
241 
242 /*
243  * Necessary function declarations
244  */
245 static int extend_pgdir(u_long index);
246 static void *imalloc(size_t size);
247 static void ifree(void *ptr);
248 static void *irealloc(void *ptr, size_t size);
249 static void *malloc_bytes(size_t size);
250 
251 #ifdef MALLOC_STATS
252 void
253 malloc_dump(FILE *fd)
254 {
255     struct pginfo **pd;
256     struct pgfree *pf;
257     int j;
258 
259     pd = page_dir;
260 
261     /* print out all the pages */
262     for(j=0;j<=last_index;j++) {
263 	fprintf(fd, "%08lx %5d ", (j+malloc_origo) << malloc_pageshift, j);
264 	if (pd[j] == MALLOC_NOT_MINE) {
265 	    for(j++;j<=last_index && pd[j] == MALLOC_NOT_MINE;j++)
266 		;
267 	    j--;
268 	    fprintf(fd, ".. %5d not mine\n",	j);
269 	} else if (pd[j] == MALLOC_FREE) {
270 	    for(j++;j<=last_index && pd[j] == MALLOC_FREE;j++)
271 		;
272 	    j--;
273 	    fprintf(fd, ".. %5d free\n", j);
274 	} else if (pd[j] == MALLOC_FIRST) {
275 	    for(j++;j<=last_index && pd[j] == MALLOC_FOLLOW;j++)
276 		;
277 	    j--;
278 	    fprintf(fd, ".. %5d in use\n", j);
279 	} else if (pd[j] < MALLOC_MAGIC) {
280 	    fprintf(fd, "(%p)\n", pd[j]);
281 	} else {
282 	    fprintf(fd, "%p %d (of %d) x %d @ %p --> %p\n",
283 		pd[j], pd[j]->free, pd[j]->total,
284 		pd[j]->size, pd[j]->page, pd[j]->next);
285 	}
286     }
287 
288     for(pf=free_list.next; pf; pf=pf->next) {
289 	fprintf(fd, "Free: @%p [%p...%p[ %ld ->%p <-%p\n",
290 		pf, pf->page, pf->end, pf->size, pf->prev, pf->next);
291 	if (pf == pf->next) {
292 		fprintf(fd, "Free_list loops.\n");
293 		break;
294 	}
295     }
296 
297     /* print out various info */
298     fprintf(fd, "Minsize\t%d\n", malloc_minsize);
299     fprintf(fd, "Maxsize\t%d\n", malloc_maxsize);
300     fprintf(fd, "Pagesize\t%lu\n", (u_long)malloc_pagesize);
301     fprintf(fd, "Pageshift\t%d\n", malloc_pageshift);
302     fprintf(fd, "FirstPage\t%ld\n", malloc_origo);
303     fprintf(fd, "LastPage\t%ld %lx\n", last_index+malloc_pageshift,
304 	(last_index + malloc_pageshift) << malloc_pageshift);
305     fprintf(fd, "Break\t%ld\n", (u_long)sbrk(0) >> malloc_pageshift);
306 }
307 #endif /* MALLOC_STATS */
308 
309 extern char *__progname;
310 
311 static void
312 wrterror(char *p)
313 {
314     char *q = " error: ";
315     struct iovec iov[4];
316 
317     iov[0].iov_base = __progname;
318     iov[0].iov_len = strlen(__progname);
319     iov[1].iov_base = malloc_func;
320     iov[1].iov_len = strlen(malloc_func);
321     iov[2].iov_base = q;
322     iov[2].iov_len = strlen(q);
323     iov[3].iov_base = p;
324     iov[3].iov_len = strlen(p);
325     writev(STDERR_FILENO, iov, 4);
326 
327     suicide = 1;
328 #ifdef MALLOC_STATS
329     if (malloc_stats)
330 	malloc_dump(stderr);
331 #endif /* MALLOC_STATS */
332     abort();
333 }
334 
335 static void
336 wrtwarning(char *p)
337 {
338     char *q = " warning: ";
339     struct iovec iov[4];
340 
341     if (malloc_abort)
342 	wrterror(p);
343     else if (malloc_silent)
344 	return;
345 
346     iov[0].iov_base = __progname;
347     iov[0].iov_len = strlen(__progname);
348     iov[1].iov_base = malloc_func;
349     iov[1].iov_len = strlen(malloc_func);
350     iov[2].iov_base = q;
351     iov[2].iov_len = strlen(q);
352     iov[3].iov_base = p;
353     iov[3].iov_len = strlen(p);
354     writev(STDERR_FILENO, iov, 4);
355 }
356 
357 #ifdef MALLOC_STATS
358 static void
359 malloc_exit(void)
360 {
361     FILE *fd = fopen("malloc.out", "a");
362     char *q = "malloc() warning: Couldn't dump stats.\n";
363     if (fd != NULL) {
364         malloc_dump(fd);
365         fclose(fd);
366     } else
367         write(STDERR_FILENO, q, strlen(q));
368 }
369 #endif /* MALLOC_STATS */
370 
371 
372 /*
373  * Allocate a number of pages from the OS
374  */
375 static void *
376 map_pages(size_t pages)
377 {
378     caddr_t result, tail;
379 
380     result = (caddr_t)pageround((u_long)sbrk(0));
381     pages <<= malloc_pageshift;
382     if (pages > SIZE_T_MAX - (size_t)result) {
383 #ifdef MALLOC_EXTRA_SANITY
384 	wrtwarning("(ES): overflow in map_pages fails\n");
385 #endif /* MALLOC_EXTRA_SANITY */
386 	errno = ENOMEM;
387 	return (NULL);
388     }
389     tail = result + pages;
390 
391     if (brk(tail) == (char *)-1) {
392 #ifdef MALLOC_EXTRA_SANITY
393 	wrtwarning("(ES): map_pages fails\n");
394 #endif /* MALLOC_EXTRA_SANITY */
395 	return (NULL);
396     }
397 
398     last_index = ptr2index(tail) - 1;
399     malloc_brk = tail;
400 
401     if ((last_index+1) >= malloc_ninfo && !extend_pgdir(last_index))
402 	return (NULL);
403 
404     return (result);
405 }
406 
407 /*
408  * Extend page directory
409  */
410 static int
411 extend_pgdir(u_long index)
412 {
413     struct  pginfo **new, **old;
414     size_t i, oldlen;
415 
416     /* Make it this many pages */
417     i = index * sizeof *page_dir;
418     i /= malloc_pagesize;
419     i += 2;
420 
421     /* remember the old mapping size */
422     oldlen = malloc_ninfo * sizeof *page_dir;
423 
424     /*
425      * NOTE: we allocate new pages and copy the directory rather than tempt
426      * fate by trying to "grow" the region.. There is nothing to prevent
427      * us from accidently re-mapping space that's been allocated by our caller
428      * via dlopen() or other mmap().
429      *
430      * The copy problem is not too bad, as there is 4K of page index per
431      * 4MB of malloc arena.
432      *
433      * We can totally avoid the copy if we open a file descriptor to associate
434      * the anon mappings with.  Then, when we remap the pages at the new
435      * address, the old pages will be "magically" remapped..  But this means
436      * keeping open a "secret" file descriptor.....
437      */
438 
439     /* Get new pages */
440     new = (struct pginfo**) MMAP(i * malloc_pagesize);
441     if (new == MAP_FAILED)
442 	return (0);
443 
444     /* Copy the old stuff */
445     memcpy(new, page_dir,
446 	    malloc_ninfo * sizeof *page_dir);
447 
448     /* register the new size */
449     malloc_ninfo = i * malloc_pagesize / sizeof *page_dir;
450 
451     /* swap the pointers */
452     old = page_dir;
453     page_dir = new;
454 
455     /* Now free the old stuff */
456     munmap(old, oldlen);
457     return (1);
458 }
459 
460 /*
461  * Initialize the world
462  */
463 static void
464 malloc_init(void)
465 {
466     char *p, b[64];
467     int i, j;
468     int save_errno = errno;
469 
470     _MALLOC_LOCK_INIT();
471 
472     INIT_MMAP();
473 
474 #ifdef MALLOC_EXTRA_SANITY
475     malloc_junk = 1;
476 #endif /* MALLOC_EXTRA_SANITY */
477 
478     for (i = 0; i < 3; i++) {
479 	if (i == 0) {
480 	    j = readlink("/etc/malloc.conf", b, sizeof b - 1);
481 	    if (j <= 0)
482 		continue;
483 	    b[j] = '\0';
484 	    p = b;
485 	} else if (i == 1) {
486 	    if (issetugid() == 0)
487 		p = getenv("MALLOC_OPTIONS");
488 	    else
489 		continue;
490 	} else if (i == 2) {
491 	    p = malloc_options;
492 	}
493 	for (; p != NULL && *p != '\0'; p++) {
494 	    switch (*p) {
495 		case '>': malloc_cache   <<= 1; break;
496 		case '<': malloc_cache   >>= 1; break;
497 		case 'a': malloc_abort   = 0; break;
498 		case 'A': malloc_abort   = 1; break;
499 #ifdef MALLOC_STATS
500 		case 'd': malloc_stats   = 0; break;
501 		case 'D': malloc_stats   = 1; break;
502 #endif /* MALLOC_STATS */
503 #if defined(__FreeBSD__) || (defined(__OpenBSD__) && defined(MADV_FREE))
504 		case 'h': malloc_hint    = 0; break;
505 		case 'H': malloc_hint    = 1; break;
506 #endif /* __FreeBSD__ */
507 		case 'r': malloc_realloc = 0; break;
508 		case 'R': malloc_realloc = 1; break;
509 		case 'j': malloc_junk    = 0; break;
510 		case 'J': malloc_junk    = 1; break;
511 		case 'n': malloc_silent  = 0; break;
512 		case 'N': malloc_silent  = 1; break;
513 #ifdef __FreeBSD__
514 		case 'u': malloc_utrace  = 0; break;
515 		case 'U': malloc_utrace  = 1; break;
516 #endif /* __FreeBSD__ */
517 		case 'x': malloc_xmalloc = 0; break;
518 		case 'X': malloc_xmalloc = 1; break;
519 		case 'z': malloc_zero    = 0; break;
520 		case 'Z': malloc_zero    = 1; break;
521 		default:
522 		    j = malloc_abort;
523 		    malloc_abort = 0;
524 		    wrtwarning("unknown char in MALLOC_OPTIONS\n");
525 		    malloc_abort = j;
526 		    break;
527 	    }
528 	}
529     }
530 
531     UTRACE(0, 0, 0);
532 
533     /*
534      * We want junk in the entire allocation, and zero only in the part
535      * the user asked for.
536      */
537     if (malloc_zero)
538 	malloc_junk=1;
539 
540 #ifdef MALLOC_STATS
541     if (malloc_stats && (atexit(malloc_exit) == -1))
542 		wrtwarning("atexit(2) failed.  Will not be able to dump malloc stats on exit.\n");
543 #endif /* MALLOC_STATS */
544 
545     /* Allocate one page for the page directory */
546     page_dir = (struct pginfo **) MMAP(malloc_pagesize);
547 
548     if (page_dir == MAP_FAILED)
549 	wrterror("mmap(2) failed, check limits.\n");
550 
551     /*
552      * We need a maximum of malloc_pageshift buckets, steal these from the
553      * front of the page_directory;
554      */
555     malloc_origo = ((u_long)pageround((u_long)sbrk(0))) >> malloc_pageshift;
556     malloc_origo -= malloc_pageshift;
557 
558     malloc_ninfo = malloc_pagesize / sizeof *page_dir;
559 
560     /* Been here, done that */
561     malloc_started++;
562 
563     /* Recalculate the cache size in bytes, and make sure it's nonzero */
564 
565     if (!malloc_cache)
566 	malloc_cache++;
567 
568     malloc_cache <<= malloc_pageshift;
569 
570     /*
571      * This is a nice hack from Kaleb Keithly (kaleb@x.org).
572      * We can sbrk(2) further back when we keep this on a low address.
573      */
574     px = (struct pgfree *) imalloc (sizeof *px);
575     errno = save_errno;
576 }
577 
578 /*
579  * Allocate a number of complete pages
580  */
581 static void *
582 malloc_pages(size_t size)
583 {
584     void *p, *delay_free = NULL;
585     int i;
586     struct pgfree *pf;
587     u_long index;
588 
589     size = pageround(size);
590 
591     p = NULL;
592     /* Look for free pages before asking for more */
593     for(pf = free_list.next; pf; pf = pf->next) {
594 
595 #ifdef MALLOC_EXTRA_SANITY
596 	if (pf->size & malloc_pagemask)
597 	    wrterror("(ES): junk length entry on free_list\n");
598 	if (!pf->size)
599 	    wrterror("(ES): zero length entry on free_list\n");
600 	if (pf->page == pf->end)
601 	    wrterror("(ES): zero entry on free_list\n");
602 	if (pf->page > pf->end)
603 	    wrterror("(ES): sick entry on free_list\n");
604 	if ((void*)pf->page >= (void*)sbrk(0))
605 	    wrterror("(ES): entry on free_list past brk\n");
606 	if (page_dir[ptr2index(pf->page)] != MALLOC_FREE)
607 	    wrterror("(ES): non-free first page on free-list\n");
608 	if (page_dir[ptr2index(pf->end)-1] != MALLOC_FREE)
609 	    wrterror("(ES): non-free last page on free-list\n");
610 #endif /* MALLOC_EXTRA_SANITY */
611 
612 	if (pf->size < size)
613 	    continue;
614 
615 	if (pf->size == size) {
616 	    p = pf->page;
617 	    if (pf->next != NULL)
618 		    pf->next->prev = pf->prev;
619 	    pf->prev->next = pf->next;
620 	    delay_free = pf;
621 	    break;
622 	}
623 
624 	p = pf->page;
625 	pf->page = (char *)pf->page + size;
626 	pf->size -= size;
627 	break;
628     }
629 
630 #ifdef MALLOC_EXTRA_SANITY
631     if (p != NULL && page_dir[ptr2index(p)] != MALLOC_FREE)
632 	wrterror("(ES): allocated non-free page on free-list\n");
633 #endif /* MALLOC_EXTRA_SANITY */
634 
635     size >>= malloc_pageshift;
636 
637     /* Map new pages */
638     if (p == NULL)
639 	p = map_pages(size);
640 
641     if (p != NULL) {
642 
643 	index = ptr2index(p);
644 	page_dir[index] = MALLOC_FIRST;
645 	for (i=1;i<size;i++)
646 	    page_dir[index+i] = MALLOC_FOLLOW;
647 
648 	if (malloc_junk)
649 	    memset(p, SOME_JUNK, size << malloc_pageshift);
650     }
651 
652     if (delay_free) {
653 	if (px == NULL)
654 	    px = delay_free;
655 	else
656 	    ifree(delay_free);
657     }
658 
659     return (p);
660 }
661 
662 /*
663  * Allocate a page of fragments
664  */
665 
666 static __inline__ int
667 malloc_make_chunks(int bits)
668 {
669     struct  pginfo *bp;
670     void *pp;
671     int i, k, l;
672 
673     /* Allocate a new bucket */
674     pp = malloc_pages((size_t)malloc_pagesize);
675     if (pp == NULL)
676 	return (0);
677 
678     /* Find length of admin structure */
679     l = sizeof *bp - sizeof(u_long);
680     l += sizeof(u_long) *
681 	(((malloc_pagesize >> bits)+MALLOC_BITS-1) / MALLOC_BITS);
682 
683     /* Don't waste more than two chunks on this */
684     /*
685      * If we are to allocate a memory protected page for the malloc(0)
686      * case (when bits=0), it must be from a different page than the
687      * pginfo page.
688      * --> Treat it like the big chunk alloc, get a second data page.
689      */
690     if (bits != 0 && (1UL<<(bits)) <= l+l) {
691 	bp = (struct  pginfo *)pp;
692     } else {
693 	bp = (struct  pginfo *)imalloc(l);
694 	if (bp == NULL) {
695 	    ifree(pp);
696 	    return (0);
697 	}
698     }
699 
700     /* memory protect the page allocated in the malloc(0) case */
701     if (bits == 0) {
702 
703 	bp->size = 0;
704 	bp->shift = 1;
705 	i = malloc_minsize-1;
706 	while (i >>= 1)
707 	    bp->shift++;
708 	bp->total = bp->free = malloc_pagesize >> bp->shift;
709 	bp->page = pp;
710 
711 	k = mprotect(pp, malloc_pagesize, PROT_NONE);
712 	if (k < 0) {
713 	    ifree(pp);
714 	    ifree(bp);
715 	    return (0);
716 	}
717     } else {
718 	bp->size = (1UL<<bits);
719 	bp->shift = bits;
720 	bp->total = bp->free = malloc_pagesize >> bits;
721 	bp->page = pp;
722     }
723 
724     /* set all valid bits in the bitmap */
725     k = bp->total;
726     i = 0;
727 
728     /* Do a bunch at a time */
729     for(;k-i >= MALLOC_BITS; i += MALLOC_BITS)
730 	bp->bits[i / MALLOC_BITS] = ~0UL;
731 
732     for(; i < k; i++)
733         bp->bits[i/MALLOC_BITS] |= 1UL<<(i%MALLOC_BITS);
734 
735     if (bp == bp->page) {
736 	/* Mark the ones we stole for ourselves */
737 	for(i=0;l > 0;i++) {
738 	    bp->bits[i/MALLOC_BITS] &= ~(1UL<<(i%MALLOC_BITS));
739 	    bp->free--;
740 	    bp->total--;
741 	    l -= (1 << bits);
742 	}
743     }
744 
745     /* MALLOC_LOCK */
746 
747     page_dir[ptr2index(pp)] = bp;
748 
749     bp->next = page_dir[bits];
750     page_dir[bits] = bp;
751 
752     /* MALLOC_UNLOCK */
753 
754     return (1);
755 }
756 
757 /*
758  * Allocate a fragment
759  */
760 static void *
761 malloc_bytes(size_t size)
762 {
763     int i,j;
764     u_long u;
765     struct  pginfo *bp;
766     int k;
767     u_long *lp;
768 
769     /* Don't bother with anything less than this */
770     /* unless we have a malloc(0) requests */
771     if (size != 0 && size < malloc_minsize)
772 	size = malloc_minsize;
773 
774     /* Find the right bucket */
775     if (size == 0)
776 	j=0;
777     else {
778 	j = 1;
779 	i = size-1;
780 	while (i >>= 1)
781 	    j++;
782     }
783 
784     /* If it's empty, make a page more of that size chunks */
785     if (page_dir[j] == NULL && !malloc_make_chunks(j))
786 	return (NULL);
787 
788     bp = page_dir[j];
789 
790     /* Find first word of bitmap which isn't empty */
791     for (lp = bp->bits; !*lp; lp++)
792 	;
793 
794     /* Find that bit, and tweak it */
795     u = 1;
796     k = 0;
797     while (!(*lp & u)) {
798 	u += u;
799 	k++;
800     }
801     *lp ^= u;
802 
803     /* If there are no more free, remove from free-list */
804     if (!--bp->free) {
805 	page_dir[j] = bp->next;
806 	bp->next = NULL;
807     }
808 
809     /* Adjust to the real offset of that chunk */
810     k += (lp-bp->bits)*MALLOC_BITS;
811     k <<= bp->shift;
812 
813     if (malloc_junk && bp->size != 0)
814 	memset((char *)bp->page + k, SOME_JUNK, bp->size);
815 
816     return ((u_char *)bp->page + k);
817 }
818 
819 /*
820  * Allocate a piece of memory
821  */
822 static void *
823 imalloc(size_t size)
824 {
825     void *result;
826 
827     if (!malloc_started)
828 	malloc_init();
829 
830     if (suicide)
831 	abort();
832 
833     if ((size + malloc_pagesize) < size) {     /* Check for overflow */
834 	result = NULL;
835 	errno = ENOMEM;
836     }
837     else if (size <= malloc_maxsize)
838 	result =  malloc_bytes(size);
839     else
840 	result =  malloc_pages(size);
841 
842     if (malloc_abort && result == NULL)
843 	wrterror("allocation failed.\n");
844 
845     if (malloc_zero && result != NULL)
846 	memset(result, 0, size);
847 
848     return (result);
849 }
850 
851 /*
852  * Change the size of an allocation.
853  */
854 static void *
855 irealloc(void *ptr, size_t size)
856 {
857     void *p;
858     u_long osize, index;
859     struct pginfo **mp;
860     int i;
861 
862     if (suicide)
863 	abort();
864 
865     if (!malloc_started) {
866 	wrtwarning("malloc() has never been called.\n");
867 	return (NULL);
868     }
869 
870     index = ptr2index(ptr);
871 
872     if (index < malloc_pageshift) {
873 	wrtwarning("junk pointer, too low to make sense.\n");
874 	return (NULL);
875     }
876 
877     if (index > last_index) {
878 	wrtwarning("junk pointer, too high to make sense.\n");
879 	return (NULL);
880     }
881 
882     mp = &page_dir[index];
883 
884     if (*mp == MALLOC_FIRST) {			/* Page allocation */
885 
886 	/* Check the pointer */
887 	if ((u_long)ptr & malloc_pagemask) {
888 	    wrtwarning("modified (page-) pointer.\n");
889 	    return (NULL);
890 	}
891 
892 	/* Find the size in bytes */
893 	for (osize = malloc_pagesize; *(++mp) == MALLOC_FOLLOW;)
894 	    osize += malloc_pagesize;
895 
896         if (!malloc_realloc &&			/* Unless we have to, */
897 	  size <= osize &&			/* .. or are too small, */
898 	  size > (osize - malloc_pagesize)) {	/* .. or can free a page, */
899 	    if (malloc_junk)
900 		memset((char *)ptr + size, SOME_JUNK, osize-size);
901 	    return (ptr);			/* ..don't do anything else. */
902 	}
903 
904     } else if (*mp >= MALLOC_MAGIC) {		/* Chunk allocation */
905 
906 	/* Check the pointer for sane values */
907 	if ((u_long)ptr & ((1UL<<((*mp)->shift))-1)) {
908 	    wrtwarning("modified (chunk-) pointer.\n");
909 	    return (NULL);
910 	}
911 
912 	/* Find the chunk index in the page */
913 	i = ((u_long)ptr & malloc_pagemask) >> (*mp)->shift;
914 
915 	/* Verify that it isn't a free chunk already */
916         if ((*mp)->bits[i/MALLOC_BITS] & (1UL<<(i%MALLOC_BITS))) {
917 	    wrtwarning("chunk is already free.\n");
918 	    return (NULL);
919 	}
920 
921 	osize = (*mp)->size;
922 
923 	if (!malloc_realloc &&		/* Unless we have to, */
924 	  size <= osize &&		/* ..or are too small, */
925 	  (size > osize/2 ||		/* ..or could use a smaller size, */
926 	  osize == malloc_minsize)) {	/* ..(if there is one) */
927 	    if (malloc_junk)
928 		memset((char *)ptr + size, SOME_JUNK, osize-size);
929 	    return (ptr);		/* ..don't do anything else. */
930 	}
931 
932     } else {
933 	wrtwarning("pointer to wrong page.\n");
934 	return (NULL);
935     }
936 
937     p = imalloc(size);
938 
939     if (p != NULL) {
940 	/* copy the lesser of the two sizes, and free the old one */
941 	/* Don't move from/to 0 sized region !!! */
942 	if (osize != 0 && size != 0) {
943 	    if (osize < size)
944 		memcpy(p, ptr, osize);
945 	    else
946 		memcpy(p, ptr, size);
947 	}
948 	ifree(ptr);
949     }
950     return (p);
951 }
952 
953 /*
954  * Free a sequence of pages
955  */
956 
957 static __inline__ void
958 free_pages(void *ptr, int index, struct pginfo *info)
959 {
960     int i;
961     struct pgfree *pf, *pt=NULL;
962     u_long l;
963     void *tail;
964 
965     if (info == MALLOC_FREE) {
966 	wrtwarning("page is already free.\n");
967 	return;
968     }
969 
970     if (info != MALLOC_FIRST) {
971 	wrtwarning("pointer to wrong page.\n");
972 	return;
973     }
974 
975     if ((u_long)ptr & malloc_pagemask) {
976 	wrtwarning("modified (page-) pointer.\n");
977 	return;
978     }
979 
980     /* Count how many pages and mark them free at the same time */
981     page_dir[index] = MALLOC_FREE;
982     for (i = 1; page_dir[index+i] == MALLOC_FOLLOW; i++)
983 	page_dir[index + i] = MALLOC_FREE;
984 
985     l = i << malloc_pageshift;
986 
987     if (malloc_junk)
988 	memset(ptr, SOME_JUNK, l);
989 
990 #if defined(__FreeBSD__) || (defined(__OpenBSD__) && defined(MADV_FREE))
991     if (malloc_hint)
992 	madvise(ptr, l, MADV_FREE);
993 #endif
994 
995     tail = (char *)ptr+l;
996 
997     /* add to free-list */
998     if (px == NULL)
999 	px = imalloc(sizeof *px);	/* This cannot fail... */
1000     px->page = ptr;
1001     px->end =  tail;
1002     px->size = l;
1003 
1004     if (free_list.next == NULL) {
1005 
1006 	/* Nothing on free list, put this at head */
1007 	px->next = free_list.next;
1008 	px->prev = &free_list;
1009 	free_list.next = px;
1010 	pf = px;
1011 	px = NULL;
1012 
1013     } else {
1014 
1015 	/* Find the right spot, leave pf pointing to the modified entry. */
1016 
1017 	for(pf = free_list.next; pf->end < ptr && pf->next != NULL;
1018 	    pf = pf->next)
1019 	    ; /* Race ahead here */
1020 
1021 	if (pf->page > tail) {
1022 	    /* Insert before entry */
1023 	    px->next = pf;
1024 	    px->prev = pf->prev;
1025 	    pf->prev = px;
1026 	    px->prev->next = px;
1027 	    pf = px;
1028 	    px = NULL;
1029 	} else if (pf->end == ptr ) {
1030 	    /* Append to the previous entry */
1031 	    pf->end = (char *)pf->end + l;
1032 	    pf->size += l;
1033 	    if (pf->next != NULL && pf->end == pf->next->page ) {
1034 		/* And collapse the next too. */
1035 		pt = pf->next;
1036 		pf->end = pt->end;
1037 		pf->size += pt->size;
1038 		pf->next = pt->next;
1039 		if (pf->next != NULL)
1040 		    pf->next->prev = pf;
1041 	    }
1042 	} else if (pf->page == tail) {
1043 	    /* Prepend to entry */
1044 	    pf->size += l;
1045 	    pf->page = ptr;
1046 	} else if (pf->next == NULL) {
1047 	    /* Append at tail of chain */
1048 	    px->next = NULL;
1049 	    px->prev = pf;
1050 	    pf->next = px;
1051 	    pf = px;
1052 	    px = NULL;
1053 	} else {
1054 	    wrterror("freelist is destroyed.\n");
1055 	}
1056     }
1057 
1058     /* Return something to OS ? */
1059     if (pf->next == NULL &&			/* If we're the last one, */
1060       pf->size > malloc_cache &&		/* ..and the cache is full, */
1061       pf->end == malloc_brk &&			/* ..and none behind us, */
1062       malloc_brk == sbrk(0)) {			/* ..and it's OK to do... */
1063 
1064 	/*
1065 	 * Keep the cache intact.  Notice that the '>' above guarantees that
1066 	 * the pf will always have at least one page afterwards.
1067 	 */
1068 	pf->end = (char *)pf->page + malloc_cache;
1069 	pf->size = malloc_cache;
1070 
1071 	brk(pf->end);
1072 	malloc_brk = pf->end;
1073 
1074 	index = ptr2index(pf->end);
1075 
1076 	for(i=index;i <= last_index;)
1077 	    page_dir[i++] = MALLOC_NOT_MINE;
1078 
1079 	last_index = index - 1;
1080 
1081 	/* XXX: We could realloc/shrink the pagedir here I guess. */
1082     }
1083     if (pt != NULL)
1084 	ifree(pt);
1085 }
1086 
1087 /*
1088  * Free a chunk, and possibly the page it's on, if the page becomes empty.
1089  */
1090 
1091 /* ARGSUSED */
1092 static __inline__ void
1093 free_bytes(void *ptr, int index, struct pginfo *info)
1094 {
1095     int i;
1096     struct pginfo **mp;
1097     void *vp;
1098 
1099     /* Find the chunk number on the page */
1100     i = ((u_long)ptr & malloc_pagemask) >> info->shift;
1101 
1102     if ((u_long)ptr & ((1UL<<(info->shift))-1)) {
1103 	wrtwarning("modified (chunk-) pointer.\n");
1104 	return;
1105     }
1106 
1107     if (info->bits[i/MALLOC_BITS] & (1UL<<(i%MALLOC_BITS))) {
1108 	wrtwarning("chunk is already free.\n");
1109 	return;
1110     }
1111 
1112     if (malloc_junk && info->size != 0)
1113 	memset(ptr, SOME_JUNK, info->size);
1114 
1115     info->bits[i/MALLOC_BITS] |= 1UL<<(i%MALLOC_BITS);
1116     info->free++;
1117 
1118     if (info->size != 0)
1119 	mp = page_dir + info->shift;
1120     else
1121 	mp = page_dir;
1122 
1123     if (info->free == 1) {
1124 
1125 	/* Page became non-full */
1126 
1127 	/* Insert in address order */
1128 	while (*mp && (*mp)->next && (*mp)->next->page < info->page)
1129 	    mp = &(*mp)->next;
1130 	info->next = *mp;
1131 	*mp = info;
1132 	return;
1133     }
1134 
1135     if (info->free != info->total)
1136 	return;
1137 
1138     /* Find & remove this page in the queue */
1139     while (*mp != info) {
1140 	mp = &((*mp)->next);
1141 #ifdef MALLOC_EXTRA_SANITY
1142 	if (!*mp)
1143 		wrterror("(ES): Not on queue\n");
1144 #endif /* MALLOC_EXTRA_SANITY */
1145     }
1146     *mp = info->next;
1147 
1148     /* Free the page & the info structure if need be */
1149     page_dir[ptr2index(info->page)] = MALLOC_FIRST;
1150 
1151     /* If the page was mprotected, unprotect it before releasing it */
1152     if (info->size == 0) {
1153 	mprotect(info->page, malloc_pagesize, PROT_READ|PROT_WRITE);
1154 	/* Do we have to care if mprotect succeeds here ? */
1155     }
1156 
1157     vp = info->page;		/* Order is important ! */
1158     if(vp != (void*)info)
1159 	ifree(info);
1160     ifree(vp);
1161 }
1162 
1163 static void
1164 ifree(void *ptr)
1165 {
1166     struct pginfo *info;
1167     int index;
1168 
1169     /* This is legal */
1170     if (ptr == NULL)
1171 	return;
1172 
1173     if (!malloc_started) {
1174 	wrtwarning("malloc() has never been called.\n");
1175 	return;
1176     }
1177 
1178     /* If we're already sinking, don't make matters any worse. */
1179     if (suicide)
1180 	return;
1181 
1182     index = ptr2index(ptr);
1183 
1184     if (index < malloc_pageshift) {
1185 	wrtwarning("junk pointer, too low to make sense.\n");
1186 	return;
1187     }
1188 
1189     if (index > last_index) {
1190 	wrtwarning("junk pointer, too high to make sense.\n");
1191 	return;
1192     }
1193 
1194     info = page_dir[index];
1195 
1196     if (info < MALLOC_MAGIC)
1197         free_pages(ptr, index, info);
1198     else
1199 	free_bytes(ptr, index, info);
1200     return;
1201 }
1202 
1203 /*
1204  * These are the public exported interface routines.
1205  */
1206 
1207 static int malloc_active;
1208 
1209 void *
1210 malloc(size_t size)
1211 {
1212     register void *r;
1213 
1214     malloc_func = " in malloc():";
1215     _MALLOC_LOCK();
1216     if (malloc_active++) {
1217 	wrtwarning("recursive call.\n");
1218         malloc_active--;
1219 	_MALLOC_UNLOCK();
1220 	return (NULL);
1221     }
1222     r = imalloc(size);
1223     UTRACE(0, size, r);
1224     malloc_active--;
1225     _MALLOC_UNLOCK();
1226     if (malloc_xmalloc && r == NULL)
1227 	wrterror("out of memory.\n");
1228     return (r);
1229 }
1230 
1231 void
1232 free(void *ptr)
1233 {
1234     malloc_func = " in free():";
1235     _MALLOC_LOCK();
1236     if (malloc_active++) {
1237 	wrtwarning("recursive call.\n");
1238         malloc_active--;
1239 	_MALLOC_UNLOCK();
1240 	return;
1241     }
1242     ifree(ptr);
1243     UTRACE(ptr, 0, 0);
1244     malloc_active--;
1245     _MALLOC_UNLOCK();
1246     return;
1247 }
1248 
1249 void *
1250 realloc(void *ptr, size_t size)
1251 {
1252     register void *r;
1253 
1254     malloc_func = " in realloc():";
1255     _MALLOC_LOCK();
1256     if (malloc_active++) {
1257 	wrtwarning("recursive call.\n");
1258         malloc_active--;
1259 	_MALLOC_UNLOCK();
1260 	return (NULL);
1261     }
1262     if (ptr == NULL) {
1263 	r = imalloc(size);
1264     } else {
1265         r = irealloc(ptr, size);
1266     }
1267     UTRACE(ptr, size, r);
1268     malloc_active--;
1269     _MALLOC_UNLOCK();
1270     if (malloc_xmalloc && r == NULL)
1271 	wrterror("out of memory.\n");
1272     return (r);
1273 }
1274