summaryrefslogtreecommitdiff
path: root/src/lib/libc/stdlib/malloc.c
diff options
context:
space:
mode:
Diffstat (limited to 'src/lib/libc/stdlib/malloc.c')
-rw-r--r--src/lib/libc/stdlib/malloc.c1870
1 files changed, 1870 insertions, 0 deletions
diff --git a/src/lib/libc/stdlib/malloc.c b/src/lib/libc/stdlib/malloc.c
new file mode 100644
index 0000000000..028eff2b2d
--- /dev/null
+++ b/src/lib/libc/stdlib/malloc.c
@@ -0,0 +1,1870 @@
1/* $OpenBSD: malloc.c,v 1.83 2006/05/14 19:53:40 otto Exp $ */
2
3/*
4 * ----------------------------------------------------------------------------
5 * "THE BEER-WARE LICENSE" (Revision 42):
6 * <phk@FreeBSD.ORG> wrote this file. As long as you retain this notice you
7 * can do whatever you want with this stuff. If we meet some day, and you think
8 * this stuff is worth it, you can buy me a beer in return. Poul-Henning Kamp
9 * ----------------------------------------------------------------------------
10 */
11
12/*
13 * Defining MALLOC_EXTRA_SANITY will enable extra checks which are
14 * related to internal conditions and consistency in malloc.c. This has
15 * a noticeable runtime performance hit, and generally will not do you
16 * any good unless you fiddle with the internals of malloc or want
17 * to catch random pointer corruption as early as possible.
18 */
19#ifndef MALLOC_EXTRA_SANITY
20#undef MALLOC_EXTRA_SANITY
21#endif
22
23/*
24 * Defining MALLOC_STATS will enable you to call malloc_dump() and set
25 * the [dD] options in the MALLOC_OPTIONS environment variable.
26 * It has no run-time performance hit, but does pull in stdio...
27 */
28#ifndef MALLOC_STATS
29#undef MALLOC_STATS
30#endif
31
32/*
33 * What to use for Junk. This is the byte value we use to fill with
34 * when the 'J' option is enabled.
35 */
36#define SOME_JUNK 0xd0 /* as in "Duh" :-) */
37
38#include <sys/types.h>
39#include <sys/time.h>
40#include <sys/resource.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#include <err.h>
52
53#include "thread_private.h"
54
55/*
56 * The basic parameters you can tweak.
57 *
58 * malloc_pageshift pagesize = 1 << malloc_pageshift
59 * It's probably best if this is the native
60 * page size, but it shouldn't have to be.
61 *
62 * malloc_minsize minimum size of an allocation in bytes.
63 * If this is too small it's too much work
64 * to manage them. This is also the smallest
65 * unit of alignment used for the storage
66 * returned by malloc/realloc.
67 *
68 */
69
70#if defined(__sparc__)
71#define malloc_pageshift 13U
72#endif /* __sparc__ */
73
74#ifndef malloc_pageshift
75#define malloc_pageshift (PGSHIFT)
76#endif
77
78/*
79 * No user serviceable parts behind this point.
80 *
81 * This structure describes a page worth of chunks.
82 */
83struct pginfo {
84 struct pginfo *next; /* next on the free list */
85 void *page; /* Pointer to the page */
86 u_short size; /* size of this page's chunks */
87 u_short shift; /* How far to shift for this size chunks */
88 u_short free; /* How many free chunks */
89 u_short total; /* How many chunk */
90 u_long bits[1];/* Which chunks are free */
91};
92
93/* How many bits per u_long in the bitmap */
94#define MALLOC_BITS (NBBY * sizeof(u_long))
95
96/*
97 * This structure describes a number of free pages.
98 */
99struct pgfree {
100 struct pgfree *next; /* next run of free pages */
101 struct pgfree *prev; /* prev run of free pages */
102 void *page; /* pointer to free pages */
103 void *pdir; /* pointer to the base page's dir */
104 size_t size; /* number of bytes free */
105};
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_minsize
117#define malloc_minsize 16UL
118#endif
119
120#if !defined(malloc_pagesize)
121#define malloc_pagesize (1UL<<malloc_pageshift)
122#endif
123
124#if ((1UL<<malloc_pageshift) != malloc_pagesize)
125#error "(1UL<<malloc_pageshift) != malloc_pagesize"
126#endif
127
128#ifndef malloc_maxsize
129#define malloc_maxsize ((malloc_pagesize)>>1)
130#endif
131
132/* A mask for the offset inside a page. */
133#define malloc_pagemask ((malloc_pagesize)-1)
134
135#define pageround(foo) (((foo) + (malloc_pagemask)) & ~malloc_pagemask)
136#define ptr2index(foo) (((u_long)(foo) >> malloc_pageshift)+malloc_pageshift)
137#define index2ptr(idx) ((void*)(((idx)-malloc_pageshift)<<malloc_pageshift))
138
139/* Set when initialization has been done */
140static unsigned int malloc_started;
141
142/* Number of free pages we cache */
143static unsigned int malloc_cache = 16;
144
145/* Structure used for linking discrete directory pages. */
146struct pdinfo {
147 struct pginfo **base;
148 struct pdinfo *prev;
149 struct pdinfo *next;
150 u_long dirnum;
151};
152static struct pdinfo *last_dir; /* Caches to the last and previous */
153static struct pdinfo *prev_dir; /* referenced directory pages. */
154
155static size_t pdi_off;
156static u_long pdi_mod;
157#define PD_IDX(num) ((num) / (malloc_pagesize/sizeof(struct pginfo *)))
158#define PD_OFF(num) ((num) & ((malloc_pagesize/sizeof(struct pginfo *))-1))
159#define PI_IDX(index) ((index) / pdi_mod)
160#define PI_OFF(index) ((index) % pdi_mod)
161
162/* The last index in the page directory we care about */
163static u_long last_index;
164
165/* Pointer to page directory. Allocated "as if with" malloc */
166static struct pginfo **page_dir;
167
168/* Free pages line up here */
169static struct pgfree free_list;
170
171/* Abort(), user doesn't handle problems. */
172static int malloc_abort = 2;
173
174/* Are we trying to die ? */
175static int suicide;
176
177#ifdef MALLOC_STATS
178/* dump statistics */
179static int malloc_stats;
180#endif
181
182/* avoid outputting warnings? */
183static int malloc_silent;
184
185/* always realloc ? */
186static int malloc_realloc;
187
188/* mprotect free pages PROT_NONE? */
189static int malloc_freeprot;
190
191/* use guard pages after allocations? */
192static size_t malloc_guard = 0;
193static size_t malloc_guarded;
194/* align pointers to end of page? */
195static int malloc_ptrguard;
196
197static int malloc_hint;
198
199/* xmalloc behaviour ? */
200static int malloc_xmalloc;
201
202/* zero fill ? */
203static int malloc_zero;
204
205/* junk fill ? */
206static int malloc_junk;
207
208#ifdef __FreeBSD__
209/* utrace ? */
210static int malloc_utrace;
211
212struct ut {
213 void *p;
214 size_t s;
215 void *r;
216};
217
218void utrace(struct ut *, int);
219
220#define UTRACE(a, b, c) \
221 if (malloc_utrace) \
222 {struct ut u; u.p=a; u.s = b; u.r=c; utrace(&u, sizeof u);}
223#else /* !__FreeBSD__ */
224#define UTRACE(a,b,c)
225#endif
226
227/* Status of malloc. */
228static int malloc_active;
229
230/* Allocated memory. */
231static size_t malloc_used;
232
233/* My last break. */
234static caddr_t malloc_brk;
235
236/* One location cache for free-list holders. */
237static struct pgfree *px;
238
239/* Compile-time options. */
240char *malloc_options;
241
242/* Name of the current public function. */
243static char *malloc_func;
244
245#define MMAP(size) \
246 mmap((void *)0, (size), PROT_READ|PROT_WRITE, MAP_ANON|MAP_PRIVATE, \
247 -1, (off_t)0)
248
249/*
250 * Necessary function declarations.
251 */
252static void *imalloc(size_t size);
253static void ifree(void *ptr);
254static void *irealloc(void *ptr, size_t size);
255static void *malloc_bytes(size_t size);
256
257/*
258 * Function for page directory lookup.
259 */
260static int
261pdir_lookup(u_long index, struct pdinfo ** pdi)
262{
263 struct pdinfo *spi;
264 u_long pidx = PI_IDX(index);
265
266 if (last_dir != NULL && PD_IDX(last_dir->dirnum) == pidx)
267 *pdi = last_dir;
268 else if (prev_dir != NULL && PD_IDX(prev_dir->dirnum) == pidx)
269 *pdi = prev_dir;
270 else if (last_dir != NULL && prev_dir != NULL) {
271 if ((PD_IDX(last_dir->dirnum) > pidx) ?
272 (PD_IDX(last_dir->dirnum) - pidx) :
273 (pidx - PD_IDX(last_dir->dirnum))
274 < (PD_IDX(prev_dir->dirnum) > pidx) ?
275 (PD_IDX(prev_dir->dirnum) - pidx) :
276 (pidx - PD_IDX(prev_dir->dirnum)))
277 *pdi = last_dir;
278 else
279 *pdi = prev_dir;
280
281 if (PD_IDX((*pdi)->dirnum) > pidx) {
282 for (spi = (*pdi)->prev;
283 spi != NULL && PD_IDX(spi->dirnum) > pidx;
284 spi = spi->prev)
285 *pdi = spi;
286 if (spi != NULL)
287 *pdi = spi;
288 } else
289 for (spi = (*pdi)->next;
290 spi != NULL && PD_IDX(spi->dirnum) <= pidx;
291 spi = spi->next)
292 *pdi = spi;
293 } else {
294 *pdi = (struct pdinfo *) ((caddr_t) page_dir + pdi_off);
295 for (spi = *pdi;
296 spi != NULL && PD_IDX(spi->dirnum) <= pidx;
297 spi = spi->next)
298 *pdi = spi;
299 }
300
301 return ((PD_IDX((*pdi)->dirnum) == pidx) ? 0 :
302 (PD_IDX((*pdi)->dirnum) > pidx) ? 1 : -1);
303}
304
305#ifdef MALLOC_STATS
306void
307malloc_dump(int fd)
308{
309 char buf[1024];
310 struct pginfo **pd;
311 struct pgfree *pf;
312 struct pdinfo *pi;
313 u_long j;
314
315 pd = page_dir;
316 pi = (struct pdinfo *) ((caddr_t) pd + pdi_off);
317
318 /* print out all the pages */
319 for (j = 0; j <= last_index;) {
320 snprintf(buf, sizeof buf, "%08lx %5lu ", j << malloc_pageshift, j);
321 write(fd, buf, strlen(buf));
322 if (pd[PI_OFF(j)] == MALLOC_NOT_MINE) {
323 for (j++; j <= last_index && pd[PI_OFF(j)] == MALLOC_NOT_MINE;) {
324 if (!PI_OFF(++j)) {
325 if ((pi = pi->next) == NULL ||
326 PD_IDX(pi->dirnum) != PI_IDX(j))
327 break;
328 pd = pi->base;
329 j += pdi_mod;
330 }
331 }
332 j--;
333 snprintf(buf, sizeof buf, ".. %5lu not mine\n", j);
334 write(fd, buf, strlen(buf));
335 } else if (pd[PI_OFF(j)] == MALLOC_FREE) {
336 for (j++; j <= last_index && pd[PI_OFF(j)] == MALLOC_FREE;) {
337 if (!PI_OFF(++j)) {
338 if ((pi = pi->next) == NULL ||
339 PD_IDX(pi->dirnum) != PI_IDX(j))
340 break;
341 pd = pi->base;
342 j += pdi_mod;
343 }
344 }
345 j--;
346 snprintf(buf, sizeof buf, ".. %5lu free\n", j);
347 write(fd, buf, strlen(buf));
348 } else if (pd[PI_OFF(j)] == MALLOC_FIRST) {
349 for (j++; j <= last_index && pd[PI_OFF(j)] == MALLOC_FOLLOW;) {
350 if (!PI_OFF(++j)) {
351 if ((pi = pi->next) == NULL ||
352 PD_IDX(pi->dirnum) != PI_IDX(j))
353 break;
354 pd = pi->base;
355 j += pdi_mod;
356 }
357 }
358 j--;
359 snprintf(buf, sizeof buf, ".. %5lu in use\n", j);
360 write(fd, buf, strlen(buf));
361 } else if (pd[PI_OFF(j)] < MALLOC_MAGIC) {
362 snprintf(buf, sizeof buf, "(%p)\n", pd[PI_OFF(j)]);
363 write(fd, buf, strlen(buf));
364 } else {
365 snprintf(buf, sizeof buf, "%p %d (of %d) x %d @ %p --> %p\n",
366 pd[PI_OFF(j)], pd[PI_OFF(j)]->free,
367 pd[PI_OFF(j)]->total, pd[PI_OFF(j)]->size,
368 pd[PI_OFF(j)]->page, pd[PI_OFF(j)]->next);
369 write(fd, buf, strlen(buf));
370 }
371 if (!PI_OFF(++j)) {
372 if ((pi = pi->next) == NULL)
373 break;
374 pd = pi->base;
375 j += (1 + PD_IDX(pi->dirnum) - PI_IDX(j)) * pdi_mod;
376 }
377 }
378
379 for (pf = free_list.next; pf; pf = pf->next) {
380 snprintf(buf, sizeof buf, "Free: @%p [%p...%p[ %ld ->%p <-%p\n",
381 pf, pf->page, (char *)pf->page + pf->size,
382 pf->size, pf->prev, pf->next);
383 write(fd, buf, strlen(buf));
384 if (pf == pf->next) {
385 snprintf(buf, sizeof buf, "Free_list loops\n");
386 write(fd, buf, strlen(buf));
387 break;
388 }
389 }
390
391 /* print out various info */
392 snprintf(buf, sizeof buf, "Minsize\t%lu\n", malloc_minsize);
393 write(fd, buf, strlen(buf));
394 snprintf(buf, sizeof buf, "Maxsize\t%lu\n", malloc_maxsize);
395 write(fd, buf, strlen(buf));
396 snprintf(buf, sizeof buf, "Pagesize\t%lu\n", malloc_pagesize);
397 write(fd, buf, strlen(buf));
398 snprintf(buf, sizeof buf, "Pageshift\t%u\n", malloc_pageshift);
399 write(fd, buf, strlen(buf));
400 snprintf(buf, sizeof buf, "In use\t%lu\n", (u_long) malloc_used);
401 write(fd, buf, strlen(buf));
402 snprintf(buf, sizeof buf, "Guarded\t%lu\n", (u_long) malloc_guarded);
403 write(fd, buf, strlen(buf));
404}
405#endif /* MALLOC_STATS */
406
407extern char *__progname;
408
409static void
410wrterror(char *p)
411{
412 char *q = " error: ";
413 struct iovec iov[5];
414
415 iov[0].iov_base = __progname;
416 iov[0].iov_len = strlen(__progname);
417 iov[1].iov_base = malloc_func;
418 iov[1].iov_len = strlen(malloc_func);
419 iov[2].iov_base = q;
420 iov[2].iov_len = strlen(q);
421 iov[3].iov_base = p;
422 iov[3].iov_len = strlen(p);
423 iov[4].iov_base = "\n";
424 iov[4].iov_len = 1;
425 writev(STDERR_FILENO, iov, 5);
426
427 suicide = 1;
428#ifdef MALLOC_STATS
429 if (malloc_stats)
430 malloc_dump(STDERR_FILENO);
431#endif /* MALLOC_STATS */
432 malloc_active--;
433 if (malloc_abort)
434 abort();
435}
436
437static void
438wrtwarning(char *p)
439{
440 char *q = " warning: ";
441 struct iovec iov[5];
442
443 if (malloc_abort)
444 wrterror(p);
445 else if (malloc_silent)
446 return;
447
448 iov[0].iov_base = __progname;
449 iov[0].iov_len = strlen(__progname);
450 iov[1].iov_base = malloc_func;
451 iov[1].iov_len = strlen(malloc_func);
452 iov[2].iov_base = q;
453 iov[2].iov_len = strlen(q);
454 iov[3].iov_base = p;
455 iov[3].iov_len = strlen(p);
456 iov[4].iov_base = "\n";
457 iov[4].iov_len = 1;
458
459 writev(STDERR_FILENO, iov, 5);
460}
461
462#ifdef MALLOC_STATS
463static void
464malloc_exit(void)
465{
466 char *q = "malloc() warning: Couldn't dump stats\n";
467 int save_errno = errno, fd;
468
469 fd = open("malloc.out", O_RDWR|O_APPEND);
470 if (fd != -1) {
471 malloc_dump(fd);
472 close(fd);
473 } else
474 write(STDERR_FILENO, q, strlen(q));
475 errno = save_errno;
476}
477#endif /* MALLOC_STATS */
478
479/*
480 * Allocate a number of pages from the OS
481 */
482static void *
483map_pages(size_t pages)
484{
485 struct pdinfo *pi, *spi;
486 struct pginfo **pd;
487 u_long idx, pidx, lidx;
488 caddr_t result, tail;
489 u_long index, lindex;
490 void *pdregion = NULL;
491 size_t dirs, cnt;
492
493 pages <<= malloc_pageshift;
494 result = MMAP(pages + malloc_guard);
495 if (result == MAP_FAILED) {
496#ifdef MALLOC_EXTRA_SANITY
497 wrtwarning("(ES): map_pages fails");
498#endif /* MALLOC_EXTRA_SANITY */
499 errno = ENOMEM;
500 return (NULL);
501 }
502 index = ptr2index(result);
503 tail = result + pages + malloc_guard;
504 lindex = ptr2index(tail) - 1;
505 if (malloc_guard)
506 mprotect(result + pages, malloc_guard, PROT_NONE);
507
508 pidx = PI_IDX(index);
509 lidx = PI_IDX(lindex);
510
511 if (tail > malloc_brk) {
512 malloc_brk = tail;
513 last_index = lindex;
514 }
515
516 dirs = lidx - pidx;
517
518 /* Insert directory pages, if needed. */
519 if (pdir_lookup(index, &pi) != 0)
520 dirs++;
521
522 if (dirs > 0) {
523 pdregion = MMAP(malloc_pagesize * dirs);
524 if (pdregion == MAP_FAILED) {
525 munmap(result, tail - result);
526#ifdef MALLOC_EXTRA_SANITY
527 wrtwarning("(ES): map_pages fails");
528#endif
529 errno = ENOMEM;
530 return (NULL);
531 }
532 }
533
534 cnt = 0;
535 for (idx = pidx, spi = pi; idx <= lidx; idx++) {
536 if (pi == NULL || PD_IDX(pi->dirnum) != idx) {
537 pd = (struct pginfo **)((char *)pdregion +
538 cnt * malloc_pagesize);
539 cnt++;
540 memset(pd, 0, malloc_pagesize);
541 pi = (struct pdinfo *) ((caddr_t) pd + pdi_off);
542 pi->base = pd;
543 pi->prev = spi;
544 pi->next = spi->next;
545 pi->dirnum = idx * (malloc_pagesize /
546 sizeof(struct pginfo *));
547
548 if (spi->next != NULL)
549 spi->next->prev = pi;
550 spi->next = pi;
551 }
552 if (idx > pidx && idx < lidx) {
553 pi->dirnum += pdi_mod;
554 } else if (idx == pidx) {
555 if (pidx == lidx) {
556 pi->dirnum += (u_long)(tail - result) >>
557 malloc_pageshift;
558 } else {
559 pi->dirnum += pdi_mod - PI_OFF(index);
560 }
561 } else {
562 pi->dirnum += PI_OFF(ptr2index(tail - 1)) + 1;
563 }
564#ifdef MALLOC_EXTRA_SANITY
565 if (PD_OFF(pi->dirnum) > pdi_mod || PD_IDX(pi->dirnum) > idx) {
566 wrterror("(ES): pages directory overflow");
567 errno = EFAULT;
568 return (NULL);
569 }
570#endif /* MALLOC_EXTRA_SANITY */
571 if (idx == pidx && pi != last_dir) {
572 prev_dir = last_dir;
573 last_dir = pi;
574 }
575 spi = pi;
576 pi = spi->next;
577 }
578#ifdef MALLOC_EXTRA_SANITY
579 if (cnt > dirs)
580 wrtwarning("(ES): cnt > dirs");
581#endif /* MALLOC_EXTRA_SANITY */
582 if (cnt < dirs)
583 munmap((char *)pdregion + cnt * malloc_pagesize,
584 (dirs - cnt) * malloc_pagesize);
585
586 return (result);
587}
588
589/*
590 * Initialize the world
591 */
592static void
593malloc_init(void)
594{
595 char *p, b[64];
596 int i, j, save_errno = errno;
597
598 _MALLOC_LOCK_INIT();
599
600#ifdef MALLOC_EXTRA_SANITY
601 malloc_junk = 1;
602#endif /* MALLOC_EXTRA_SANITY */
603
604 for (i = 0; i < 3; i++) {
605 switch (i) {
606 case 0:
607 j = readlink("/etc/malloc.conf", b, sizeof b - 1);
608 if (j <= 0)
609 continue;
610 b[j] = '\0';
611 p = b;
612 break;
613 case 1:
614 if (issetugid() == 0)
615 p = getenv("MALLOC_OPTIONS");
616 else
617 continue;
618 break;
619 case 2:
620 p = malloc_options;
621 break;
622 default:
623 p = NULL;
624 }
625
626 for (; p != NULL && *p != '\0'; p++) {
627 switch (*p) {
628 case '>':
629 malloc_cache <<= 1;
630 break;
631 case '<':
632 malloc_cache >>= 1;
633 break;
634 case 'a':
635 malloc_abort = 0;
636 break;
637 case 'A':
638 malloc_abort = 1;
639 break;
640#ifdef MALLOC_STATS
641 case 'd':
642 malloc_stats = 0;
643 break;
644 case 'D':
645 malloc_stats = 1;
646 break;
647#endif /* MALLOC_STATS */
648 case 'f':
649 malloc_freeprot = 0;
650 break;
651 case 'F':
652 malloc_freeprot = 1;
653 break;
654 case 'g':
655 malloc_guard = 0;
656 break;
657 case 'G':
658 malloc_guard = malloc_pagesize;
659 break;
660 case 'h':
661 malloc_hint = 0;
662 break;
663 case 'H':
664 malloc_hint = 1;
665 break;
666 case 'j':
667 malloc_junk = 0;
668 break;
669 case 'J':
670 malloc_junk = 1;
671 break;
672 case 'n':
673 malloc_silent = 0;
674 break;
675 case 'N':
676 malloc_silent = 1;
677 break;
678 case 'p':
679 malloc_ptrguard = 0;
680 break;
681 case 'P':
682 malloc_ptrguard = 1;
683 break;
684 case 'r':
685 malloc_realloc = 0;
686 break;
687 case 'R':
688 malloc_realloc = 1;
689 break;
690#ifdef __FreeBSD__
691 case 'u':
692 malloc_utrace = 0;
693 break;
694 case 'U':
695 malloc_utrace = 1;
696 break;
697#endif /* __FreeBSD__ */
698 case 'x':
699 malloc_xmalloc = 0;
700 break;
701 case 'X':
702 malloc_xmalloc = 1;
703 break;
704 case 'z':
705 malloc_zero = 0;
706 break;
707 case 'Z':
708 malloc_zero = 1;
709 break;
710 default:
711 j = malloc_abort;
712 malloc_abort = 0;
713 wrtwarning("unknown char in MALLOC_OPTIONS");
714 malloc_abort = j;
715 break;
716 }
717 }
718 }
719
720 UTRACE(0, 0, 0);
721
722 /*
723 * We want junk in the entire allocation, and zero only in the part
724 * the user asked for.
725 */
726 if (malloc_zero)
727 malloc_junk = 1;
728
729#ifdef MALLOC_STATS
730 if (malloc_stats && (atexit(malloc_exit) == -1))
731 wrtwarning("atexit(2) failed."
732 " Will not be able to dump malloc stats on exit");
733#endif /* MALLOC_STATS */
734
735 /* Allocate one page for the page directory. */
736 page_dir = (struct pginfo **)MMAP(malloc_pagesize);
737
738 if (page_dir == MAP_FAILED) {
739 wrterror("mmap(2) failed, check limits");
740 errno = ENOMEM;
741 return;
742 }
743 pdi_off = (malloc_pagesize - sizeof(struct pdinfo)) & ~(malloc_minsize - 1);
744 pdi_mod = pdi_off / sizeof(struct pginfo *);
745
746 last_dir = (struct pdinfo *) ((caddr_t) page_dir + pdi_off);
747 last_dir->base = page_dir;
748 last_dir->prev = last_dir->next = NULL;
749 last_dir->dirnum = malloc_pageshift;
750
751 /* Been here, done that. */
752 malloc_started++;
753
754 /* Recalculate the cache size in bytes, and make sure it's nonzero. */
755 if (!malloc_cache)
756 malloc_cache++;
757 malloc_cache <<= malloc_pageshift;
758 errno = save_errno;
759}
760
761/*
762 * Allocate a number of complete pages
763 */
764static void *
765malloc_pages(size_t size)
766{
767 void *p, *delay_free = NULL, *tp;
768 int i;
769 struct pginfo **pd;
770 struct pdinfo *pi;
771 u_long pidx, index;
772 struct pgfree *pf;
773
774 size = pageround(size) + malloc_guard;
775
776 p = NULL;
777 /* Look for free pages before asking for more */
778 for (pf = free_list.next; pf; pf = pf->next) {
779
780#ifdef MALLOC_EXTRA_SANITY
781 if (pf->size & malloc_pagemask) {
782 wrterror("(ES): junk length entry on free_list");
783 errno = EFAULT;
784 return (NULL);
785 }
786 if (!pf->size) {
787 wrterror("(ES): zero length entry on free_list");
788 errno = EFAULT;
789 return (NULL);
790 }
791 if (pf->page > (pf->page + pf->size)) {
792 wrterror("(ES): sick entry on free_list");
793 errno = EFAULT;
794 return (NULL);
795 }
796 if ((pi = pf->pdir) == NULL) {
797 wrterror("(ES): invalid page directory on free-list");
798 errno = EFAULT;
799 return (NULL);
800 }
801 if ((pidx = PI_IDX(ptr2index(pf->page))) != PD_IDX(pi->dirnum)) {
802 wrterror("(ES): directory index mismatch on free-list");
803 errno = EFAULT;
804 return (NULL);
805 }
806 pd = pi->base;
807 if (pd[PI_OFF(ptr2index(pf->page))] != MALLOC_FREE) {
808 wrterror("(ES): non-free first page on free-list");
809 errno = EFAULT;
810 return (NULL);
811 }
812 pidx = PI_IDX(ptr2index((pf->page) + (pf->size)) - 1);
813 for (pi = pf->pdir; pi != NULL && PD_IDX(pi->dirnum) < pidx;
814 pi = pi->next)
815 ;
816 if (pi == NULL || PD_IDX(pi->dirnum) != pidx) {
817 wrterror("(ES): last page not referenced in page directory");
818 errno = EFAULT;
819 return (NULL);
820 }
821 pd = pi->base;
822 if (pd[PI_OFF(ptr2index((pf->page) + (pf->size)) - 1)] != MALLOC_FREE) {
823 wrterror("(ES): non-free last page on free-list");
824 errno = EFAULT;
825 return (NULL);
826 }
827#endif /* MALLOC_EXTRA_SANITY */
828
829 if (pf->size < size)
830 continue;
831
832 if (pf->size == size) {
833 p = pf->page;
834 pi = pf->pdir;
835 if (pf->next != NULL)
836 pf->next->prev = pf->prev;
837 pf->prev->next = pf->next;
838 delay_free = pf;
839 break;
840 }
841 p = pf->page;
842 pf->page = (char *) pf->page + size;
843 pf->size -= size;
844 pidx = PI_IDX(ptr2index(pf->page));
845 for (pi = pf->pdir; pi != NULL && PD_IDX(pi->dirnum) < pidx;
846 pi = pi->next)
847 ;
848 if (pi == NULL || PD_IDX(pi->dirnum) != pidx) {
849 wrterror("(ES): hole in directories");
850 errno = EFAULT;
851 return (NULL);
852 }
853 tp = pf->pdir;
854 pf->pdir = pi;
855 pi = tp;
856 break;
857 }
858
859 size -= malloc_guard;
860
861#ifdef MALLOC_EXTRA_SANITY
862 if (p != NULL && pi != NULL) {
863 pidx = PD_IDX(pi->dirnum);
864 pd = pi->base;
865 }
866 if (p != NULL && pd[PI_OFF(ptr2index(p))] != MALLOC_FREE) {
867 wrterror("(ES): allocated non-free page on free-list");
868 errno = EFAULT;
869 return (NULL);
870 }
871#endif /* MALLOC_EXTRA_SANITY */
872
873 if (p != NULL && (malloc_guard || malloc_freeprot))
874 mprotect(p, size, PROT_READ | PROT_WRITE);
875
876 size >>= malloc_pageshift;
877
878 /* Map new pages */
879 if (p == NULL)
880 p = map_pages(size);
881
882 if (p != NULL) {
883 index = ptr2index(p);
884 pidx = PI_IDX(index);
885 pdir_lookup(index, &pi);
886#ifdef MALLOC_EXTRA_SANITY
887 if (pi == NULL || PD_IDX(pi->dirnum) != pidx) {
888 wrterror("(ES): mapped pages not found in directory");
889 errno = EFAULT;
890 return (NULL);
891 }
892#endif /* MALLOC_EXTRA_SANITY */
893 if (pi != last_dir) {
894 prev_dir = last_dir;
895 last_dir = pi;
896 }
897 pd = pi->base;
898 pd[PI_OFF(index)] = MALLOC_FIRST;
899 for (i = 1; i < size; i++) {
900 if (!PI_OFF(index + i)) {
901 pidx++;
902 pi = pi->next;
903#ifdef MALLOC_EXTRA_SANITY
904 if (pi == NULL || PD_IDX(pi->dirnum) != pidx) {
905 wrterror("(ES): hole in mapped pages directory");
906 errno = EFAULT;
907 return (NULL);
908 }
909#endif /* MALLOC_EXTRA_SANITY */
910 pd = pi->base;
911 }
912 pd[PI_OFF(index + i)] = MALLOC_FOLLOW;
913 }
914 if (malloc_guard) {
915 if (!PI_OFF(index + i)) {
916 pidx++;
917 pi = pi->next;
918#ifdef MALLOC_EXTRA_SANITY
919 if (pi == NULL || PD_IDX(pi->dirnum) != pidx) {
920 wrterror("(ES): hole in mapped pages directory");
921 errno = EFAULT;
922 return (NULL);
923 }
924#endif /* MALLOC_EXTRA_SANITY */
925 pd = pi->base;
926 }
927 pd[PI_OFF(index + i)] = MALLOC_FIRST;
928 }
929 malloc_used += size << malloc_pageshift;
930 malloc_guarded += malloc_guard;
931
932 if (malloc_junk)
933 memset(p, SOME_JUNK, size << malloc_pageshift);
934 }
935 if (delay_free) {
936 if (px == NULL)
937 px = delay_free;
938 else
939 ifree(delay_free);
940 }
941 return (p);
942}
943
944/*
945 * Allocate a page of fragments
946 */
947
948static __inline__ int
949malloc_make_chunks(int bits)
950{
951 struct pginfo *bp, **pd;
952 struct pdinfo *pi;
953#ifdef MALLOC_EXTRA_SANITY
954 u_long pidx;
955#endif /* MALLOC_EXTRA_SANITY */
956 void *pp;
957 long i, k;
958 size_t l;
959
960 /* Allocate a new bucket */
961 pp = malloc_pages((size_t) malloc_pagesize);
962 if (pp == NULL)
963 return (0);
964
965 /* Find length of admin structure */
966 l = sizeof *bp - sizeof(u_long);
967 l += sizeof(u_long) *
968 (((malloc_pagesize >> bits) + MALLOC_BITS - 1) / MALLOC_BITS);
969
970 /* Don't waste more than two chunks on this */
971
972 /*
973 * If we are to allocate a memory protected page for the malloc(0)
974 * case (when bits=0), it must be from a different page than the
975 * pginfo page.
976 * --> Treat it like the big chunk alloc, get a second data page.
977 */
978 if (bits != 0 && (1UL << (bits)) <= l + l) {
979 bp = (struct pginfo *) pp;
980 } else {
981 bp = (struct pginfo *) imalloc(l);
982 if (bp == NULL) {
983 ifree(pp);
984 return (0);
985 }
986 }
987
988 /* memory protect the page allocated in the malloc(0) case */
989 if (bits == 0) {
990 bp->size = 0;
991 bp->shift = 1;
992 i = malloc_minsize - 1;
993 while (i >>= 1)
994 bp->shift++;
995 bp->total = bp->free = malloc_pagesize >> bp->shift;
996 bp->page = pp;
997
998 k = mprotect(pp, malloc_pagesize, PROT_NONE);
999 if (k < 0) {
1000 ifree(pp);
1001 ifree(bp);
1002 return (0);
1003 }
1004 } else {
1005 bp->size = (1UL << bits);
1006 bp->shift = bits;
1007 bp->total = bp->free = malloc_pagesize >> bits;
1008 bp->page = pp;
1009 }
1010
1011 /* set all valid bits in the bitmap */
1012 k = bp->total;
1013 i = 0;
1014
1015 /* Do a bunch at a time */
1016 for (; (k - i) >= MALLOC_BITS; i += MALLOC_BITS)
1017 bp->bits[i / MALLOC_BITS] = ~0UL;
1018
1019 for (; i < k; i++)
1020 bp->bits[i / MALLOC_BITS] |= 1UL << (i % MALLOC_BITS);
1021
1022 k = (long)l;
1023 if (bp == bp->page) {
1024 /* Mark the ones we stole for ourselves */
1025 for (i = 0; k > 0; i++) {
1026 bp->bits[i / MALLOC_BITS] &= ~(1UL << (i % MALLOC_BITS));
1027 bp->free--;
1028 bp->total--;
1029 k -= (1 << bits);
1030 }
1031 }
1032 /* MALLOC_LOCK */
1033
1034 pdir_lookup(ptr2index(pp), &pi);
1035#ifdef MALLOC_EXTRA_SANITY
1036 pidx = PI_IDX(ptr2index(pp));
1037 if (pi == NULL || PD_IDX(pi->dirnum) != pidx) {
1038 wrterror("(ES): mapped pages not found in directory");
1039 errno = EFAULT;
1040 return (0);
1041 }
1042#endif /* MALLOC_EXTRA_SANITY */
1043 if (pi != last_dir) {
1044 prev_dir = last_dir;
1045 last_dir = pi;
1046 }
1047 pd = pi->base;
1048 pd[PI_OFF(ptr2index(pp))] = bp;
1049
1050 bp->next = page_dir[bits];
1051 page_dir[bits] = bp;
1052
1053 /* MALLOC_UNLOCK */
1054 return (1);
1055}
1056
1057/*
1058 * Allocate a fragment
1059 */
1060static void *
1061malloc_bytes(size_t size)
1062{
1063 int i, j;
1064 size_t k;
1065 u_long u, *lp;
1066 struct pginfo *bp;
1067
1068 /* Don't bother with anything less than this */
1069 /* unless we have a malloc(0) requests */
1070 if (size != 0 && size < malloc_minsize)
1071 size = malloc_minsize;
1072
1073 /* Find the right bucket */
1074 if (size == 0)
1075 j = 0;
1076 else {
1077 j = 1;
1078 i = size - 1;
1079 while (i >>= 1)
1080 j++;
1081 }
1082
1083 /* If it's empty, make a page more of that size chunks */
1084 if (page_dir[j] == NULL && !malloc_make_chunks(j))
1085 return (NULL);
1086
1087 bp = page_dir[j];
1088
1089 /* Find first word of bitmap which isn't empty */
1090 for (lp = bp->bits; !*lp; lp++);
1091
1092 /* Find that bit, and tweak it */
1093 u = 1;
1094 k = 0;
1095 while (!(*lp & u)) {
1096 u += u;
1097 k++;
1098 }
1099
1100 if (malloc_guard) {
1101 /* Walk to a random position. */
1102 i = arc4random() % bp->free;
1103 while (i > 0) {
1104 u += u;
1105 k++;
1106 if (k >= MALLOC_BITS) {
1107 lp++;
1108 u = 1;
1109 k = 0;
1110 }
1111#ifdef MALLOC_EXTRA_SANITY
1112 if (lp - bp->bits > (bp->total - 1) / MALLOC_BITS) {
1113 wrterror("chunk overflow");
1114 errno = EFAULT;
1115 return (NULL);
1116 }
1117#endif /* MALLOC_EXTRA_SANITY */
1118 if (*lp & u)
1119 i--;
1120 }
1121 }
1122 *lp ^= u;
1123
1124 /* If there are no more free, remove from free-list */
1125 if (!--bp->free) {
1126 page_dir[j] = bp->next;
1127 bp->next = NULL;
1128 }
1129 /* Adjust to the real offset of that chunk */
1130 k += (lp - bp->bits) * MALLOC_BITS;
1131 k <<= bp->shift;
1132
1133 if (malloc_junk && bp->size != 0)
1134 memset((char *)bp->page + k, SOME_JUNK, (size_t)bp->size);
1135
1136 return ((u_char *) bp->page + k);
1137}
1138
1139/*
1140 * Magic so that malloc(sizeof(ptr)) is near the end of the page.
1141 */
1142#define PTR_GAP (malloc_pagesize - sizeof(void *))
1143#define PTR_SIZE (sizeof(void *))
1144#define PTR_ALIGNED(p) (((unsigned long)p & malloc_pagemask) == PTR_GAP)
1145
1146/*
1147 * Allocate a piece of memory
1148 */
1149static void *
1150imalloc(size_t size)
1151{
1152 void *result;
1153 int ptralloc = 0;
1154
1155 if (!malloc_started)
1156 malloc_init();
1157
1158 if (suicide)
1159 abort();
1160
1161 /* does not matter if malloc_bytes fails */
1162 if (px == NULL)
1163 px = malloc_bytes(sizeof *px);
1164
1165 if (malloc_ptrguard && size == PTR_SIZE) {
1166 ptralloc = 1;
1167 size = malloc_pagesize;
1168 }
1169 if ((size + malloc_pagesize) < size) { /* Check for overflow */
1170 result = NULL;
1171 errno = ENOMEM;
1172 } else if (size <= malloc_maxsize)
1173 result = malloc_bytes(size);
1174 else
1175 result = malloc_pages(size);
1176
1177 if (malloc_abort == 1 && result == NULL)
1178 wrterror("allocation failed");
1179
1180 if (malloc_zero && result != NULL)
1181 memset(result, 0, size);
1182
1183 if (result && ptralloc)
1184 return ((char *) result + PTR_GAP);
1185 return (result);
1186}
1187
1188/*
1189 * Change the size of an allocation.
1190 */
1191static void *
1192irealloc(void *ptr, size_t size)
1193{
1194 void *p;
1195 size_t osize;
1196 u_long index, i;
1197 struct pginfo **mp;
1198 struct pginfo **pd;
1199 struct pdinfo *pi;
1200#ifdef MALLOC_EXTRA_SANITY
1201 u_long pidx;
1202#endif /* MALLOC_EXTRA_SANITY */
1203
1204 if (suicide)
1205 abort();
1206
1207 if (!malloc_started) {
1208 wrtwarning("malloc() has never been called");
1209 return (NULL);
1210 }
1211 if (malloc_ptrguard && PTR_ALIGNED(ptr)) {
1212 if (size <= PTR_SIZE)
1213 return (ptr);
1214
1215 p = imalloc(size);
1216 if (p)
1217 memcpy(p, ptr, PTR_SIZE);
1218 ifree(ptr);
1219 return (p);
1220 }
1221 index = ptr2index(ptr);
1222
1223 if (index < malloc_pageshift) {
1224 wrtwarning("junk pointer, too low to make sense");
1225 return (NULL);
1226 }
1227 if (index > last_index) {
1228 wrtwarning("junk pointer, too high to make sense");
1229 return (NULL);
1230 }
1231 pdir_lookup(index, &pi);
1232#ifdef MALLOC_EXTRA_SANITY
1233 pidx = PI_IDX(index);
1234 if (pi == NULL || PD_IDX(pi->dirnum) != pidx) {
1235 wrterror("(ES): mapped pages not found in directory");
1236 errno = EFAULT;
1237 return (NULL);
1238 }
1239#endif /* MALLOC_EXTRA_SANITY */
1240 if (pi != last_dir) {
1241 prev_dir = last_dir;
1242 last_dir = pi;
1243 }
1244 pd = pi->base;
1245 mp = &pd[PI_OFF(index)];
1246
1247 if (*mp == MALLOC_FIRST) { /* Page allocation */
1248
1249 /* Check the pointer */
1250 if ((u_long) ptr & malloc_pagemask) {
1251 wrtwarning("modified (page-) pointer");
1252 return (NULL);
1253 }
1254 /* Find the size in bytes */
1255 i = index;
1256 if (!PI_OFF(++i)) {
1257 pi = pi->next;
1258 if (pi != NULL && PD_IDX(pi->dirnum) != PI_IDX(i))
1259 pi = NULL;
1260 if (pi != NULL)
1261 pd = pi->base;
1262 }
1263 for (osize = malloc_pagesize;
1264 pi != NULL && pd[PI_OFF(i)] == MALLOC_FOLLOW;) {
1265 osize += malloc_pagesize;
1266 if (!PI_OFF(++i)) {
1267 pi = pi->next;
1268 if (pi != NULL && PD_IDX(pi->dirnum) != PI_IDX(i))
1269 pi = NULL;
1270 if (pi != NULL)
1271 pd = pi->base;
1272 }
1273 }
1274
1275 if (!malloc_realloc && size <= osize &&
1276 size > osize - malloc_pagesize) {
1277 if (malloc_junk)
1278 memset((char *)ptr + size, SOME_JUNK, osize - size);
1279 return (ptr); /* ..don't do anything else. */
1280 }
1281 } else if (*mp >= MALLOC_MAGIC) { /* Chunk allocation */
1282
1283 /* Check the pointer for sane values */
1284 if ((u_long) ptr & ((1UL << ((*mp)->shift)) - 1)) {
1285 wrtwarning("modified (chunk-) pointer");
1286 return (NULL);
1287 }
1288 /* Find the chunk index in the page */
1289 i = ((u_long) ptr & malloc_pagemask) >> (*mp)->shift;
1290
1291 /* Verify that it isn't a free chunk already */
1292 if ((*mp)->bits[i / MALLOC_BITS] & (1UL << (i % MALLOC_BITS))) {
1293 wrtwarning("chunk is already free");
1294 return (NULL);
1295 }
1296 osize = (*mp)->size;
1297
1298 if (!malloc_realloc && size <= osize &&
1299 (size > osize / 2 || osize == malloc_minsize)) {
1300 if (malloc_junk)
1301 memset((char *) ptr + size, SOME_JUNK, osize - size);
1302 return (ptr); /* ..don't do anything else. */
1303 }
1304 } else {
1305 wrtwarning("irealloc: pointer to wrong page");
1306 return (NULL);
1307 }
1308
1309 p = imalloc(size);
1310
1311 if (p != NULL) {
1312 /* copy the lesser of the two sizes, and free the old one */
1313 /* Don't move from/to 0 sized region !!! */
1314 if (osize != 0 && size != 0) {
1315 if (osize < size)
1316 memcpy(p, ptr, osize);
1317 else
1318 memcpy(p, ptr, size);
1319 }
1320 ifree(ptr);
1321 }
1322 return (p);
1323}
1324
1325/*
1326 * Free a sequence of pages
1327 */
1328static __inline__ void
1329free_pages(void *ptr, u_long index, struct pginfo * info)
1330{
1331 u_long i, pidx, lidx;
1332 size_t l, cachesize = 0;
1333 struct pginfo **pd;
1334 struct pdinfo *pi, *spi;
1335 struct pgfree *pf, *pt = NULL;
1336 caddr_t tail;
1337
1338 if (info == MALLOC_FREE) {
1339 wrtwarning("page is already free");
1340 return;
1341 }
1342 if (info != MALLOC_FIRST) {
1343 wrtwarning("free_pages: pointer to wrong page");
1344 return;
1345 }
1346 if ((u_long) ptr & malloc_pagemask) {
1347 wrtwarning("modified (page-) pointer");
1348 return;
1349 }
1350 /* Count how many pages and mark them free at the same time */
1351 pidx = PI_IDX(index);
1352 pdir_lookup(index, &pi);
1353#ifdef MALLOC_EXTRA_SANITY
1354 if (pi == NULL || PD_IDX(pi->dirnum) != pidx) {
1355 wrterror("(ES): mapped pages not found in directory");
1356 errno = EFAULT;
1357 return;
1358 }
1359#endif /* MALLOC_EXTRA_SANITY */
1360
1361 spi = pi; /* Save page index for start of region. */
1362
1363 pd = pi->base;
1364 pd[PI_OFF(index)] = MALLOC_FREE;
1365 i = 1;
1366 if (!PI_OFF(index + i)) {
1367 pi = pi->next;
1368 if (pi == NULL || PD_IDX(pi->dirnum) != PI_IDX(index + i))
1369 pi = NULL;
1370 else
1371 pd = pi->base;
1372 }
1373 while (pi != NULL && pd[PI_OFF(index + i)] == MALLOC_FOLLOW) {
1374 pd[PI_OFF(index + i)] = MALLOC_FREE;
1375 i++;
1376 if (!PI_OFF(index + i)) {
1377 if ((pi = pi->next) == NULL ||
1378 PD_IDX(pi->dirnum) != PI_IDX(index + i))
1379 pi = NULL;
1380 else
1381 pd = pi->base;
1382 }
1383 }
1384
1385 l = i << malloc_pageshift;
1386
1387 if (malloc_junk)
1388 memset(ptr, SOME_JUNK, l);
1389
1390 malloc_used -= l;
1391 malloc_guarded -= malloc_guard;
1392 if (malloc_guard) {
1393#ifdef MALLOC_EXTRA_SANITY
1394 if (pi == NULL || PD_IDX(pi->dirnum) != PI_IDX(index + i)) {
1395 wrterror("(ES): hole in mapped pages directory");
1396 errno = EFAULT;
1397 return;
1398 }
1399#endif /* MALLOC_EXTRA_SANITY */
1400 pd[PI_OFF(index + i)] = MALLOC_FREE;
1401 l += malloc_guard;
1402 }
1403 tail = (caddr_t)ptr + l;
1404
1405 if (malloc_hint)
1406 madvise(ptr, l, MADV_FREE);
1407
1408 if (malloc_freeprot)
1409 mprotect(ptr, l, PROT_NONE);
1410
1411 /* Add to free-list. */
1412 if (px == NULL && (px = malloc_bytes(sizeof *px)) == NULL)
1413 goto not_return;
1414 px->page = ptr;
1415 px->pdir = spi;
1416 px->size = l;
1417
1418 if (free_list.next == NULL) {
1419 /* Nothing on free list, put this at head. */
1420 px->next = NULL;
1421 px->prev = &free_list;
1422 free_list.next = px;
1423 pf = px;
1424 px = NULL;
1425 } else {
1426 /*
1427 * Find the right spot, leave pf pointing to the modified
1428 * entry.
1429 */
1430
1431 /* Race ahead here, while calculating cache size. */
1432 for (pf = free_list.next;
1433 (caddr_t)ptr > ((caddr_t)pf->page + pf->size)
1434 && pf->next != NULL;
1435 pf = pf->next)
1436 cachesize += pf->size;
1437
1438 /* Finish cache size calculation. */
1439 pt = pf;
1440 while (pt) {
1441 cachesize += pt->size;
1442 pt = pt->next;
1443 }
1444
1445 if ((caddr_t)pf->page > tail) {
1446 /* Insert before entry */
1447 px->next = pf;
1448 px->prev = pf->prev;
1449 pf->prev = px;
1450 px->prev->next = px;
1451 pf = px;
1452 px = NULL;
1453 } else if (((caddr_t)pf->page + pf->size) == ptr) {
1454 /* Append to the previous entry. */
1455 cachesize -= pf->size;
1456 pf->size += l;
1457 if (pf->next != NULL &&
1458 pf->next->page == ((caddr_t)pf->page + pf->size)) {
1459 /* And collapse the next too. */
1460 pt = pf->next;
1461 pf->size += pt->size;
1462 pf->next = pt->next;
1463 if (pf->next != NULL)
1464 pf->next->prev = pf;
1465 }
1466 } else if (pf->page == tail) {
1467 /* Prepend to entry. */
1468 cachesize -= pf->size;
1469 pf->size += l;
1470 pf->page = ptr;
1471 pf->pdir = spi;
1472 } else if (pf->next == NULL) {
1473 /* Append at tail of chain. */
1474 px->next = NULL;
1475 px->prev = pf;
1476 pf->next = px;
1477 pf = px;
1478 px = NULL;
1479 } else {
1480 wrterror("freelist is destroyed");
1481 errno = EFAULT;
1482 return;
1483 }
1484 }
1485
1486 if (pf->pdir != last_dir) {
1487 prev_dir = last_dir;
1488 last_dir = pf->pdir;
1489 }
1490
1491 /* Return something to OS ? */
1492 if (pf->size > (malloc_cache - cachesize)) {
1493
1494 /*
1495 * Keep the cache intact. Notice that the '>' above guarantees that
1496 * the pf will always have at least one page afterwards.
1497 */
1498 if (munmap((char *) pf->page + (malloc_cache - cachesize),
1499 pf->size - (malloc_cache - cachesize)) != 0)
1500 goto not_return;
1501 tail = (caddr_t)pf->page + pf->size;
1502 lidx = ptr2index(tail) - 1;
1503 pf->size = malloc_cache - cachesize;
1504
1505 index = ptr2index((caddr_t)pf->page + pf->size);
1506
1507 pidx = PI_IDX(index);
1508 if (prev_dir != NULL && PD_IDX(prev_dir->dirnum) >= pidx)
1509 prev_dir = NULL; /* Will be wiped out below ! */
1510
1511 for (pi = pf->pdir; pi != NULL && PD_IDX(pi->dirnum) < pidx;
1512 pi = pi->next)
1513 ;
1514
1515 spi = pi;
1516 if (pi != NULL && PD_IDX(pi->dirnum) == pidx) {
1517 pd = pi->base;
1518
1519 for (i = index; i <= lidx;) {
1520 if (pd[PI_OFF(i)] != MALLOC_NOT_MINE) {
1521 pd[PI_OFF(i)] = MALLOC_NOT_MINE;
1522#ifdef MALLOC_EXTRA_SANITY
1523 if (!PD_OFF(pi->dirnum)) {
1524 wrterror("(ES): pages directory underflow");
1525 errno = EFAULT;
1526 return;
1527 }
1528#endif /* MALLOC_EXTRA_SANITY */
1529 pi->dirnum--;
1530 }
1531#ifdef MALLOC_EXTRA_SANITY
1532 else
1533 wrtwarning("(ES): page already unmapped");
1534#endif /* MALLOC_EXTRA_SANITY */
1535 i++;
1536 if (!PI_OFF(i)) {
1537 /*
1538 * If no page in that dir, free
1539 * directory page.
1540 */
1541 if (!PD_OFF(pi->dirnum)) {
1542 /* Remove from list. */
1543 if (spi == pi)
1544 spi = pi->prev;
1545 if (pi->prev != NULL)
1546 pi->prev->next = pi->next;
1547 if (pi->next != NULL)
1548 pi->next->prev = pi->prev;
1549 pi = pi->next;
1550 munmap(pd, malloc_pagesize);
1551 } else
1552 pi = pi->next;
1553 if (pi == NULL ||
1554 PD_IDX(pi->dirnum) != PI_IDX(i))
1555 break;
1556 pd = pi->base;
1557 }
1558 }
1559 if (pi && !PD_OFF(pi->dirnum)) {
1560 /* Resulting page dir is now empty. */
1561 /* Remove from list. */
1562 if (spi == pi) /* Update spi only if first. */
1563 spi = pi->prev;
1564 if (pi->prev != NULL)
1565 pi->prev->next = pi->next;
1566 if (pi->next != NULL)
1567 pi->next->prev = pi->prev;
1568 pi = pi->next;
1569 munmap(pd, malloc_pagesize);
1570 }
1571 }
1572 if (pi == NULL && malloc_brk == tail) {
1573 /* Resize down the malloc upper boundary. */
1574 last_index = index - 1;
1575 malloc_brk = index2ptr(index);
1576 }
1577
1578 /* XXX: We could realloc/shrink the pagedir here I guess. */
1579 if (pf->size == 0) { /* Remove from free-list as well. */
1580 if (px)
1581 ifree(px);
1582 if ((px = pf->prev) != &free_list) {
1583 if (pi == NULL && last_index == (index - 1)) {
1584 if (spi == NULL) {
1585 malloc_brk = NULL;
1586 i = 11;
1587 } else {
1588 pd = spi->base;
1589 if (PD_IDX(spi->dirnum) < pidx)
1590 index =
1591 ((PD_IDX(spi->dirnum) + 1) *
1592 pdi_mod) - 1;
1593 for (pi = spi, i = index;
1594 pd[PI_OFF(i)] == MALLOC_NOT_MINE;
1595 i--)
1596#ifdef MALLOC_EXTRA_SANITY
1597 if (!PI_OFF(i)) {
1598 pi = pi->prev;
1599 if (pi == NULL || i == 0)
1600 break;
1601 pd = pi->base;
1602 i = (PD_IDX(pi->dirnum) + 1) * pdi_mod;
1603 }
1604#else /* !MALLOC_EXTRA_SANITY */
1605 {
1606 }
1607#endif /* MALLOC_EXTRA_SANITY */
1608 malloc_brk = index2ptr(i + 1);
1609 }
1610 last_index = i;
1611 }
1612 if ((px->next = pf->next) != NULL)
1613 px->next->prev = px;
1614 } else {
1615 if ((free_list.next = pf->next) != NULL)
1616 free_list.next->prev = &free_list;
1617 }
1618 px = pf;
1619 last_dir = prev_dir;
1620 prev_dir = NULL;
1621 }
1622 }
1623not_return:
1624 if (pt != NULL)
1625 ifree(pt);
1626}
1627
1628/*
1629 * Free a chunk, and possibly the page it's on, if the page becomes empty.
1630 */
1631
1632/* ARGSUSED */
1633static __inline__ void
1634free_bytes(void *ptr, u_long index, struct pginfo * info)
1635{
1636 struct pginfo **mp, **pd;
1637 struct pdinfo *pi;
1638#ifdef MALLOC_EXTRA_SANITY
1639 u_long pidx;
1640#endif /* MALLOC_EXTRA_SANITY */
1641 void *vp;
1642 long i;
1643
1644 /* Find the chunk number on the page */
1645 i = ((u_long) ptr & malloc_pagemask) >> info->shift;
1646
1647 if ((u_long) ptr & ((1UL << (info->shift)) - 1)) {
1648 wrtwarning("modified (chunk-) pointer");
1649 return;
1650 }
1651 if (info->bits[i / MALLOC_BITS] & (1UL << (i % MALLOC_BITS))) {
1652 wrtwarning("chunk is already free");
1653 return;
1654 }
1655 if (malloc_junk && info->size != 0)
1656 memset(ptr, SOME_JUNK, (size_t)info->size);
1657
1658 info->bits[i / MALLOC_BITS] |= 1UL << (i % MALLOC_BITS);
1659 info->free++;
1660
1661 if (info->size != 0)
1662 mp = page_dir + info->shift;
1663 else
1664 mp = page_dir;
1665
1666 if (info->free == 1) {
1667 /* Page became non-full */
1668
1669 /* Insert in address order */
1670 while (*mp != NULL && (*mp)->next != NULL &&
1671 (*mp)->next->page < info->page)
1672 mp = &(*mp)->next;
1673 info->next = *mp;
1674 *mp = info;
1675 return;
1676 }
1677 if (info->free != info->total)
1678 return;
1679
1680 /* Find & remove this page in the queue */
1681 while (*mp != info) {
1682 mp = &((*mp)->next);
1683#ifdef MALLOC_EXTRA_SANITY
1684 if (!*mp) {
1685 wrterror("(ES): Not on queue");
1686 errno = EFAULT;
1687 return;
1688 }
1689#endif /* MALLOC_EXTRA_SANITY */
1690 }
1691 *mp = info->next;
1692
1693 /* Free the page & the info structure if need be */
1694 pdir_lookup(ptr2index(info->page), &pi);
1695#ifdef MALLOC_EXTRA_SANITY
1696 pidx = PI_IDX(ptr2index(info->page));
1697 if (pi == NULL || PD_IDX(pi->dirnum) != pidx) {
1698 wrterror("(ES): mapped pages not found in directory");
1699 errno = EFAULT;
1700 return;
1701 }
1702#endif /* MALLOC_EXTRA_SANITY */
1703 if (pi != last_dir) {
1704 prev_dir = last_dir;
1705 last_dir = pi;
1706 }
1707 pd = pi->base;
1708 pd[PI_OFF(ptr2index(info->page))] = MALLOC_FIRST;
1709
1710 /* If the page was mprotected, unprotect it before releasing it */
1711 if (info->size == 0)
1712 mprotect(info->page, malloc_pagesize, PROT_READ | PROT_WRITE);
1713
1714 vp = info->page; /* Order is important ! */
1715 if (vp != (void *) info)
1716 ifree(info);
1717 ifree(vp);
1718}
1719
1720static void
1721ifree(void *ptr)
1722{
1723 struct pginfo *info, **pd;
1724 u_long index;
1725#ifdef MALLOC_EXTRA_SANITY
1726 u_long pidx;
1727#endif /* MALLOC_EXTRA_SANITY */
1728 struct pdinfo *pi;
1729
1730 if (!malloc_started) {
1731 wrtwarning("malloc() has never been called");
1732 return;
1733 }
1734 /* If we're already sinking, don't make matters any worse. */
1735 if (suicide)
1736 return;
1737
1738 if (malloc_ptrguard && PTR_ALIGNED(ptr))
1739 ptr = (char *) ptr - PTR_GAP;
1740
1741 index = ptr2index(ptr);
1742
1743 if (index < malloc_pageshift) {
1744 warnx("(%p)", ptr);
1745 wrtwarning("ifree: junk pointer, too low to make sense");
1746 return;
1747 }
1748 if (index > last_index) {
1749 warnx("(%p)", ptr);
1750 wrtwarning("ifree: junk pointer, too high to make sense");
1751 return;
1752 }
1753 pdir_lookup(index, &pi);
1754#ifdef MALLOC_EXTRA_SANITY
1755 pidx = PI_IDX(index);
1756 if (pi == NULL || PD_IDX(pi->dirnum) != pidx) {
1757 wrterror("(ES): mapped pages not found in directory");
1758 errno = EFAULT;
1759 return;
1760 }
1761#endif /* MALLOC_EXTRA_SANITY */
1762 if (pi != last_dir) {
1763 prev_dir = last_dir;
1764 last_dir = pi;
1765 }
1766 pd = pi->base;
1767 info = pd[PI_OFF(index)];
1768
1769 if (info < MALLOC_MAGIC)
1770 free_pages(ptr, index, info);
1771 else
1772 free_bytes(ptr, index, info);
1773
1774 /* does not matter if malloc_bytes fails */
1775 if (px == NULL)
1776 px = malloc_bytes(sizeof *px);
1777
1778 return;
1779}
1780
1781/*
1782 * Common function for handling recursion. Only
1783 * print the error message once, to avoid making the problem
1784 * potentially worse.
1785 */
1786static void
1787malloc_recurse(void)
1788{
1789 static int noprint;
1790
1791 if (noprint == 0) {
1792 noprint = 1;
1793 wrtwarning("recursive call");
1794 }
1795 malloc_active--;
1796 _MALLOC_UNLOCK();
1797 errno = EDEADLK;
1798}
1799
1800/*
1801 * These are the public exported interface routines.
1802 */
1803void *
1804malloc(size_t size)
1805{
1806 void *r;
1807
1808 _MALLOC_LOCK();
1809 malloc_func = " in malloc():";
1810 if (malloc_active++) {
1811 malloc_recurse();
1812 return (NULL);
1813 }
1814 r = imalloc(size);
1815 UTRACE(0, size, r);
1816 malloc_active--;
1817 _MALLOC_UNLOCK();
1818 if (malloc_xmalloc && r == NULL) {
1819 wrterror("out of memory");
1820 errno = ENOMEM;
1821 }
1822 return (r);
1823}
1824
1825void
1826free(void *ptr)
1827{
1828 /* This is legal. XXX quick path */
1829 if (ptr == NULL)
1830 return;
1831
1832 _MALLOC_LOCK();
1833 malloc_func = " in free():";
1834 if (malloc_active++) {
1835 malloc_recurse();
1836 return;
1837 }
1838 ifree(ptr);
1839 UTRACE(ptr, 0, 0);
1840 malloc_active--;
1841 _MALLOC_UNLOCK();
1842 return;
1843}
1844
1845void *
1846realloc(void *ptr, size_t size)
1847{
1848 void *r;
1849
1850 _MALLOC_LOCK();
1851 malloc_func = " in realloc():";
1852 if (malloc_active++) {
1853 malloc_recurse();
1854 return (NULL);
1855 }
1856
1857 if (ptr == NULL)
1858 r = imalloc(size);
1859 else
1860 r = irealloc(ptr, size);
1861
1862 UTRACE(ptr, size, r);
1863 malloc_active--;
1864 _MALLOC_UNLOCK();
1865 if (malloc_xmalloc && r == NULL) {
1866 wrterror("out of memory");
1867 errno = ENOMEM;
1868 }
1869 return (r);
1870}