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