BSD 4_4 release
[unix-history] / usr / src / lib / libc / stdlib / malloc.c
index f71e0f2..ea8f092 100644 (file)
@@ -1,6 +1,39 @@
-#ifndef lint
-static char sccsid[] = "@(#)malloc.c   4.4 (Berkeley) %G%";
-#endif
+/*
+ * Copyright (c) 1983, 1993
+ *     The Regents of the University of California.  All rights reserved.
+ *
+ * Redistribution and use in source and binary forms, with or without
+ * modification, are permitted provided that the following conditions
+ * are met:
+ * 1. Redistributions of source code must retain the above copyright
+ *    notice, this list of conditions and the following disclaimer.
+ * 2. Redistributions in binary form must reproduce the above copyright
+ *    notice, this list of conditions and the following disclaimer in the
+ *    documentation and/or other materials provided with the distribution.
+ * 3. All advertising materials mentioning features or use of this software
+ *    must display the following acknowledgement:
+ *     This product includes software developed by the University of
+ *     California, Berkeley and its contributors.
+ * 4. Neither the name of the University nor the names of its contributors
+ *    may be used to endorse or promote products derived from this software
+ *    without specific prior written permission.
+ *
+ * THIS SOFTWARE IS PROVIDED BY THE REGENTS AND CONTRIBUTORS ``AS IS'' AND
+ * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
+ * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
+ * ARE DISCLAIMED.  IN NO EVENT SHALL THE REGENTS OR CONTRIBUTORS BE LIABLE
+ * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
+ * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
+ * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
+ * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
+ * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
+ * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
+ * SUCH DAMAGE.
+ */
+
+#if defined(LIBC_SCCS) && !defined(lint)
+static char sccsid[] = "@(#)malloc.c   8.1 (Berkeley) 6/4/93";
+#endif /* LIBC_SCCS and not lint */
 
 /*
  * malloc.c (Caltech) 2/21/82
 
 /*
  * malloc.c (Caltech) 2/21/82
@@ -9,23 +42,29 @@ static char sccsid[] = "@(#)malloc.c 4.4 (Berkeley) %G%";
  * This is a very fast storage allocator.  It allocates blocks of a small 
  * number of different sizes, and keeps free lists of each size.  Blocks that
  * don't exactly fit are passed up to the next larger size.  In this 
  * This is a very fast storage allocator.  It allocates blocks of a small 
  * number of different sizes, and keeps free lists of each size.  Blocks that
  * don't exactly fit are passed up to the next larger size.  In this 
- * implementation, the available sizes are 2^n-4 (or 2^n-12) bytes long.
- * This is designed for use in a program that uses vast quantities of memory,
- * but bombs when it runs out. 
+ * implementation, the available sizes are 2^n-4 (or 2^n-10) bytes long.
+ * This is designed for use in a virtual memory environment.
  */
 
 #include <sys/types.h>
  */
 
 #include <sys/types.h>
+#include <stdlib.h>
+#include <string.h>
+#include <unistd.h>
 
 #define        NULL 0
 
 
 #define        NULL 0
 
+static void morecore();
+static int findbucket();
+
 /*
  * The overhead on a block is at least 4 bytes.  When free, this space
  * contains a pointer to the next free block, and the bottom two bits must
  * be zero.  When in use, the first byte is set to MAGIC, and the second
  * byte is the size index.  The remaining bytes are for alignment.
 /*
  * The overhead on a block is at least 4 bytes.  When free, this space
  * contains a pointer to the next free block, and the bottom two bits must
  * be zero.  When in use, the first byte is set to MAGIC, and the second
  * byte is the size index.  The remaining bytes are for alignment.
- * If range checking is enabled and the size of the block fits
- * in two bytes, then the top two bytes hold the size of the requested block
- * plus the range checking words, and the header word MINUS ONE.
+ * If range checking is enabled then a second word holds the size of the
+ * requested block, less 1, rounded up to a multiple of sizeof(RMAGIC).
+ * The order of elements is critical: ov_magic must overlay the low order
+ * bits of ov_next, and ov_magic can not be a valid ov_next bit pattern.
  */
 union  overhead {
        union   overhead *ov_next;      /* when free */
  */
 union  overhead {
        union   overhead *ov_next;      /* when free */
@@ -33,20 +72,21 @@ union       overhead {
                u_char  ovu_magic;      /* magic number */
                u_char  ovu_index;      /* bucket # */
 #ifdef RCHECK
                u_char  ovu_magic;      /* magic number */
                u_char  ovu_index;      /* bucket # */
 #ifdef RCHECK
-               u_short ovu_size;       /* actual block size */
-               u_int   ovu_rmagic;     /* range magic number */
+               u_short ovu_rmagic;     /* range magic number */
+               u_int   ovu_size;       /* actual block size */
 #endif
        } ovu;
 #define        ov_magic        ovu.ovu_magic
 #define        ov_index        ovu.ovu_index
 #endif
        } ovu;
 #define        ov_magic        ovu.ovu_magic
 #define        ov_index        ovu.ovu_index
-#define        ov_size         ovu.ovu_size
 #define        ov_rmagic       ovu.ovu_rmagic
 #define        ov_rmagic       ovu.ovu_rmagic
+#define        ov_size         ovu.ovu_size
 };
 
 };
 
-#define        MAGIC           0xff            /* magic # on accounting info */
-#define RMAGIC         0x55555555      /* magic # on range info */
+#define        MAGIC           0xef            /* magic # on accounting info */
+#define RMAGIC         0x5555          /* magic # on range info */
+
 #ifdef RCHECK
 #ifdef RCHECK
-#define        RSLOP           sizeof (u_int)
+#define        RSLOP           sizeof (u_short)
 #else
 #define        RSLOP           0
 #endif
 #else
 #define        RSLOP           0
 #endif
@@ -60,6 +100,9 @@ union        overhead {
 static union overhead *nextf[NBUCKETS];
 extern char *sbrk();
 
 static union overhead *nextf[NBUCKETS];
 extern char *sbrk();
 
+static int pagesz;                     /* page size */
+static int pagebucket;                 /* page size bucket */
+
 #ifdef MSTATS
 /*
  * nmalloc[i] is the difference between the number of mallocs and frees
 #ifdef MSTATS
 /*
  * nmalloc[i] is the difference between the number of mallocs and frees
@@ -69,52 +112,88 @@ static     u_int nmalloc[NBUCKETS];
 #include <stdio.h>
 #endif
 
 #include <stdio.h>
 #endif
 
-#ifdef debug
-#define        ASSERT(p)   if (!(p)) botch("p"); else
+#if defined(DEBUG) || defined(RCHECK)
+#define        ASSERT(p)   if (!(p)) botch("p")
+#include <stdio.h>
 static
 botch(s)
        char *s;
 {
 static
 botch(s)
        char *s;
 {
-
-       printf("assertion botched: %s\n", s);
+       fprintf(stderr, "\r\nassertion botched: %s\r\n", s);
+       (void) fflush(stderr);          /* just in case user buffered it */
        abort();
 }
 #else
 #define        ASSERT(p)
 #endif
 
        abort();
 }
 #else
 #define        ASSERT(p)
 #endif
 
-char *
+void *
 malloc(nbytes)
 malloc(nbytes)
-       register unsigned nbytes;
+       size_t nbytes;
 {
 {
-       register union overhead *p;
-       register int bucket = 0;
-       register unsigned shiftr;
+       register union overhead *op;
+       register int bucket, n;
+       register unsigned amt;
 
        /*
 
        /*
-        * Convert amount of memory requested into
-        * closest block size stored in hash buckets
-        * which satisfies request.  Account for
-        * space used per block for accounting.
+        * First time malloc is called, setup page size and
+        * align break pointer so all data will be page aligned.
         */
         */
-       nbytes += sizeof (union overhead) + RSLOP;
-       nbytes = (nbytes + 3) &~ 3; 
-       shiftr = (nbytes - 1) >> 2;
-       /* apart from this loop, this is O(1) */
-       while (shiftr >>= 1)
-               bucket++;
+       if (pagesz == 0) {
+               pagesz = n = getpagesize();
+               op = (union overhead *)sbrk(0);
+               n = n - sizeof (*op) - ((int)op & (n - 1));
+               if (n < 0)
+                       n += pagesz;
+               if (n) {
+                       if (sbrk(n) == (char *)-1)
+                               return (NULL);
+               }
+               bucket = 0;
+               amt = 8;
+               while (pagesz > amt) {
+                       amt <<= 1;
+                       bucket++;
+               }
+               pagebucket = bucket;
+       }
+       /*
+        * Convert amount of memory requested into closest block size
+        * stored in hash buckets which satisfies request.
+        * Account for space used per block for accounting.
+        */
+       if (nbytes <= (n = pagesz - sizeof (*op) - RSLOP)) {
+#ifndef RCHECK
+               amt = 8;        /* size of first bucket */
+               bucket = 0;
+#else
+               amt = 16;       /* size of first bucket */
+               bucket = 1;
+#endif
+               n = -(sizeof (*op) + RSLOP);
+       } else {
+               amt = pagesz;
+               bucket = pagebucket;
+       }
+       while (nbytes > amt + n) {
+               amt <<= 1;
+               if (amt == 0)
+                       return (NULL);
+               bucket++;
+       }
        /*
         * If nothing in hash bucket right now,
         * request more memory from the system.
         */
        /*
         * If nothing in hash bucket right now,
         * request more memory from the system.
         */
-       if (nextf[bucket] == NULL)    
+       if ((op = nextf[bucket]) == NULL) {
                morecore(bucket);
                morecore(bucket);
-       if ((p = (union overhead *)nextf[bucket]) == NULL)
-               return (NULL);
+               if ((op = nextf[bucket]) == NULL)
+                       return (NULL);
+       }
        /* remove from linked list */
        /* remove from linked list */
-       nextf[bucket] = nextf[bucket]->ov_next;
-       p->ov_magic = MAGIC;
-       p->ov_index= bucket;
+       nextf[bucket] = op->ov_next;
+       op->ov_magic = MAGIC;
+       op->ov_index = bucket;
 #ifdef MSTATS
        nmalloc[bucket]++;
 #endif
 #ifdef MSTATS
        nmalloc[bucket]++;
 #endif
@@ -123,68 +202,61 @@ malloc(nbytes)
         * Record allocated size of block and
         * bound space with magic numbers.
         */
         * Record allocated size of block and
         * bound space with magic numbers.
         */
-       p->ov_rmagic = RMAGIC;
-       if (bucket <= 13) {
-               p->ov_size = nbytes - 1;
-               *((u_int *)((caddr_t)p + nbytes - RSLOP)) = RMAGIC;
-       }
+       op->ov_size = (nbytes + RSLOP - 1) & ~(RSLOP - 1);
+       op->ov_rmagic = RMAGIC;
+       *(u_short *)((caddr_t)(op + 1) + op->ov_size) = RMAGIC;
 #endif
 #endif
-       return ((char *)(p + 1));
+       return ((char *)(op + 1));
 }
 
 /*
  * Allocate more memory to the indicated bucket.
  */
 }
 
 /*
  * Allocate more memory to the indicated bucket.
  */
-static
+static void
 morecore(bucket)
 morecore(bucket)
-       register bucket;
+       int bucket;
 {
        register union overhead *op;
 {
        register union overhead *op;
-       register int rnu;       /* 2^rnu bytes will be requested */
-       register int nblks;     /* become nblks blocks of the desired size */
-       register int siz;
+       register int sz;                /* size of desired block */
+       int amt;                        /* amount to allocate */
+       int nblks;                      /* how many blocks we get */
 
 
-       if (nextf[bucket])
-               return;
        /*
        /*
-        * Insure memory is allocated
-        * on a page boundary.  Should
-        * make getpageize call?
+        * sbrk_size <= 0 only for big, FLUFFY, requests (about
+        * 2^30 bytes on a VAX, I think) or for a negative arg.
         */
         */
-       op = (union overhead *)sbrk(0);
-       if ((int)op & 0x3ff)
-               sbrk(1024 - ((int)op & 0x3ff));
-       /* take 2k unless the block is bigger than that */
-       rnu = (bucket <= 8) ? 11 : bucket + 3;
-       nblks = 1 << (rnu - (bucket + 3));  /* how many blocks to get */
-       if (rnu < bucket)
-               rnu = bucket;
-       op = (union overhead *)sbrk(1 << rnu);
+       sz = 1 << (bucket + 3);
+#ifdef DEBUG
+       ASSERT(sz > 0);
+#else
+       if (sz <= 0)
+               return;
+#endif
+       if (sz < pagesz) {
+               amt = pagesz;
+               nblks = amt / sz;
+       } else {
+               amt = sz + pagesz;
+               nblks = 1;
+       }
+       op = (union overhead *)sbrk(amt);
        /* no more room! */
        if ((int)op == -1)
                return;
        /* no more room! */
        if ((int)op == -1)
                return;
-       /*
-        * Round up to minimum allocation size boundary
-        * and deduct from block count to reflect.
-        */
-       if ((int)op & 7) {
-               op = (union overhead *)(((int)op + 8) &~ 7);
-               nblks--;
-       }
        /*
         * Add new memory allocated to that on
         * free list for this hash bucket.
         */
        nextf[bucket] = op;
        /*
         * Add new memory allocated to that on
         * free list for this hash bucket.
         */
        nextf[bucket] = op;
-       siz = 1 << (bucket + 3);
        while (--nblks > 0) {
        while (--nblks > 0) {
-               op->ov_next = (union overhead *)((caddr_t)op + siz);
-               op = (union overhead *)((caddr_t)op + siz);
+               op->ov_next = (union overhead *)((caddr_t)op + sz);
+               op = (union overhead *)((caddr_t)op + sz);
        }
 }
 
        }
 }
 
+void
 free(cp)
 free(cp)
-       char *cp;
+       void *cp;
 {   
        register int size;
        register union overhead *op;
 {   
        register int size;
        register union overhead *op;
@@ -192,7 +264,7 @@ free(cp)
        if (cp == NULL)
                return;
        op = (union overhead *)((caddr_t)cp - sizeof (union overhead));
        if (cp == NULL)
                return;
        op = (union overhead *)((caddr_t)cp - sizeof (union overhead));
-#ifdef debug
+#ifdef DEBUG
        ASSERT(op->ov_magic == MAGIC);          /* make sure it was in use */
 #else
        if (op->ov_magic != MAGIC)
        ASSERT(op->ov_magic == MAGIC);          /* make sure it was in use */
 #else
        if (op->ov_magic != MAGIC)
@@ -200,12 +272,11 @@ free(cp)
 #endif
 #ifdef RCHECK
        ASSERT(op->ov_rmagic == RMAGIC);
 #endif
 #ifdef RCHECK
        ASSERT(op->ov_rmagic == RMAGIC);
-       if (op->ov_index <= 13)
-               ASSERT(*(u_int *)((caddr_t)op + op->ov_size + 1 - RSLOP) == RMAGIC);
+       ASSERT(*(u_short *)((caddr_t)(op + 1) + op->ov_size) == RMAGIC);
 #endif
 #endif
-       ASSERT(op->ov_index < NBUCKETS);
        size = op->ov_index;
        size = op->ov_index;
-       op->ov_next = nextf[size];
+       ASSERT(size < NBUCKETS);
+       op->ov_next = nextf[size];      /* also clobbers ov_magic */
        nextf[size] = op;
 #ifdef MSTATS
        nmalloc[size]--;
        nextf[size] = op;
 #ifdef MSTATS
        nmalloc[size]--;
@@ -219,21 +290,21 @@ free(cp)
  * back.  We have to search all the free lists for the block in order
  * to determine its bucket: 1st we make one pass thru the lists
  * checking only the first block in each; if that fails we search
  * back.  We have to search all the free lists for the block in order
  * to determine its bucket: 1st we make one pass thru the lists
  * checking only the first block in each; if that fails we search
- * ``realloc_srchlen'' blocks in each list for a match (the variable
+ * ``__realloc_srchlen'' blocks in each list for a match (the variable
  * is extern so the caller can modify it).  If that fails we just copy
  * however many bytes was given to realloc() and hope it's not huge.
  */
  * is extern so the caller can modify it).  If that fails we just copy
  * however many bytes was given to realloc() and hope it's not huge.
  */
-int realloc_srchlen = 4;       /* 4 should be plenty, -1 =>'s whole list */
+int __realloc_srchlen = 4;     /* 4 should be plenty, -1 =>'s whole list */
 
 
-char *
+void *
 realloc(cp, nbytes)
 realloc(cp, nbytes)
-       char *cp; 
-       unsigned nbytes;
+       void *cp; 
+       size_t nbytes;
 {   
        register u_int onb;
 {   
        register u_int onb;
+       register int i;
        union overhead *op;
        char *res;
        union overhead *op;
        char *res;
-       register int i;
        int was_alloced = 0;
 
        if (cp == NULL)
        int was_alloced = 0;
 
        if (cp == NULL)
@@ -249,33 +320,45 @@ realloc(cp, nbytes)
                 * Search for the old block of memory on the
                 * free list.  First, check the most common
                 * case (last element free'd), then (this failing)
                 * Search for the old block of memory on the
                 * free list.  First, check the most common
                 * case (last element free'd), then (this failing)
-                * the last ``realloc_srchlen'' items free'd.
+                * the last ``__realloc_srchlen'' items free'd.
                 * If all lookups fail, then assume the size of
                 * the memory block being realloc'd is the
                 * If all lookups fail, then assume the size of
                 * the memory block being realloc'd is the
-                * smallest possible.
+                * largest possible (so that all "nbytes" of new
+                * memory are copied into).  Note that this could cause
+                * a memory fault if the old area was tiny, and the moon
+                * is gibbous.  However, that is very unlikely.
                 */
                if ((i = findbucket(op, 1)) < 0 &&
                 */
                if ((i = findbucket(op, 1)) < 0 &&
-                   (i = findbucket(op, realloc_srchlen)) < 0)
-                       i = 0;
+                   (i = findbucket(op, __realloc_srchlen)) < 0)
+                       i = NBUCKETS;
        }
        }
-       onb = (1 << (i + 3)) - sizeof (*op) - RSLOP;
+       onb = 1 << (i + 3);
+       if (onb < pagesz)
+               onb -= sizeof (*op) + RSLOP;
+       else
+               onb += pagesz - sizeof (*op) - RSLOP;
        /* avoid the copy if same size block */
        /* avoid the copy if same size block */
-       if (was_alloced &&
-           nbytes <= onb && nbytes > (1 << (i + 2)) - sizeof(*op) - RSLOP) {
-#ifdef RCHECK
-               if (i <= 13) {
-                       op->ov_size = nbytes - 1;
-                       *((u_int *)((caddr_t)op + nbytes - RSLOP)) = RMAGIC;
+       if (was_alloced) {
+               if (i) {
+                       i = 1 << (i + 2);
+                       if (i < pagesz)
+                               i -= sizeof (*op) + RSLOP;
+                       else
+                               i += pagesz - sizeof (*op) - RSLOP;
                }
                }
+               if (nbytes <= onb && nbytes > i) {
+#ifdef RCHECK
+                       op->ov_size = (nbytes + RSLOP - 1) & ~(RSLOP - 1);
+                       *(u_short *)((caddr_t)(op + 1) + op->ov_size) = RMAGIC;
 #endif
 #endif
-               return(cp);
+                       return(cp);
+               } else
+                       free(cp);
        }
        if ((res = malloc(nbytes)) == NULL)
                return (NULL);
        }
        if ((res = malloc(nbytes)) == NULL)
                return (NULL);
-       if (cp != res)                  /* common optimization */
+       if (cp != res)          /* common optimization if "compacting" */
                bcopy(cp, res, (nbytes < onb) ? nbytes : onb);
                bcopy(cp, res, (nbytes < onb) ? nbytes : onb);
-       if (was_alloced)
-               free(cp);
        return (res);
 }
 
        return (res);
 }