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