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