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