Pristine Ack-5.5
[Ack-5.5.git] / lang / cem / libcc.ansi / stdlib / malloc / mal.c
1 /* $Id: mal.c,v 1.5 1994/06/24 11:55:29 ceriel Exp $ */
2 /*
3  * (c) copyright 1987 by the Vrije Universiteit, Amsterdam, The Netherlands.
4  * See the copyright notice in the ACK home directory, in the file "Copyright".
5  */
6 #include        <limits.h>
7 #include        <stdlib.h>
8 #include        "param.h"
9 #include        "impl.h"
10 #include        "check.h"
11 #include        "log.h"
12 #include        "phys.h"
13
14 /*      Malloc space is traversed by N doubly-linked lists of chunks, each
15         containing a couple of house-keeping data addressed as a
16         'mallink' and a piece of useful space, called the block.
17         The N lists are accessed through their starting pointers in
18         free_list[].  Free_list[n] points to a list of chunks between
19         2**(n+LOG_MIN_SIZE) and 2**(n+LOG_MIN_SIZE+1)-1, which means
20         that the smallest chunk is 2**LOG_MIN_SIZE (== MIN_SIZE).
21 */
22
23 #ifdef SYSTEM
24 #include        <system.h>
25 #define SBRK    sys_break
26 #else
27 #define SBRK    _sbrk
28 #define ILL_BREAK               (void *)(-1)    /* funny failure value */
29 #endif
30 extern void *SBRK(int incr);
31 #ifdef STORE
32 #define MAX_STORE       32
33 private do_free(mallink *ml), sell_out(void);
34 privatedata mallink *store[MAX_STORE];
35 #endif /* STORE */
36
37 void *
38 malloc(register size_t n)
39 {check_mallinks("malloc entry");{
40         register mallink *ml;
41         register int min_class;
42
43         if (n == 0) {
44                 return NULL;
45         }
46         if (n < MIN_SIZE) n = align(MIN_SIZE); else n = align(n);
47 #ifdef STORE
48         if (n <= MAX_STORE*MIN_SIZE)    {
49                 /* look in the store first */
50                 register mallink **stp = &store[(n >> LOG_MIN_SIZE) - 1];
51                 
52                 if (ml = *stp)  {
53                         *stp = log_next_of(ml);
54                         set_store(ml, 0);
55                         check_mallinks("malloc fast exit");
56                         assert(! in_store(ml));
57                         return block_of_mallink(ml);
58                 }
59         }
60 #endif /* STORE */
61
62         check_work_empty("malloc, entry");
63
64         /*      Acquire a chunk of at least size n if at all possible;
65                 Try everything.
66         */
67         {
68                 /*      Inline substitution of "smallest".
69                 */
70                 register size_t n1 = n;
71
72                 assert(n1 < (1L << LOG_MAX_SIZE));
73                 min_class = 0;
74
75                 do {
76                         n1 >>= 1;
77                         min_class++;
78                 } while (n1 >= MIN_SIZE);
79         }
80
81         if (min_class >= MAX_FLIST)
82                 return NULL;            /* we don't deal in blocks that big */
83         ml = first_present(min_class);
84         if (ml == MAL_NULL)     {
85                 /*      Try and extend */
86                 register void *p;
87 #define GRABSIZE        4096            /* Power of 2 */
88                 register size_t req =
89                         ((MIN_SIZE<<min_class)+ mallink_size() + GRABSIZE - 1) &
90                                 ~(GRABSIZE-1);
91         
92                 if (!ml_last)   {
93                         /* first align SBRK() */
94                 
95                         p = SBRK(0);
96                         SBRK((int) (align((size_type) p) - (size_type) p));
97                 }
98
99                 /* SBRK takes an int; sorry ... */
100                 if ((int) req < 0) {
101                         p = ILL_BREAK;
102                 } else {
103                         p = SBRK((int)req);
104                 }
105                 if (p == ILL_BREAK) {
106                         req = n + mallink_size();
107                         if ((int) req >= 0) p = SBRK((int)req);
108                 }
109                 if (p == ILL_BREAK)     {
110                         /*      Now this is bad.  The system will not give us
111                                 more memory.  We can only liquidate our store
112                                 and hope it helps.
113                         */
114 #ifdef STORE
115                         sell_out();
116                         ml = first_present(min_class);
117                         if (ml == MAL_NULL)     {
118 #endif /* STORE */
119                                 /* In this emergency we try to locate a suitable
120                                    chunk in the free_list just below the safe
121                                    one; some of these chunks may fit the job.
122                                 */
123                                 ml = search_free_list(min_class - 1, n);
124                                 if (!ml)        /* really out of space */
125                                         return NULL;
126                                 started_working_on(ml);
127                                 unlink_free_chunk(ml);
128                                 check_mallinks("suitable_chunk, forced");
129 #ifdef STORE
130                         }
131                         else started_working_on(ml);
132 #endif /* STORE */
133                 }
134                 else {
135                         assert((size_type)p == align((size_type)p));
136                         ml = create_chunk(p, req);
137                 }
138                 check_mallinks("suitable_chunk, extended");
139         }
140         else started_working_on(ml);
141
142         /* we have a chunk */
143         set_free(ml, 0);
144         calc_checksum(ml);
145         check_mallinks("suitable_chunk, removed");
146         n += mallink_size();
147         if (n + MIN_SIZE <= size_of(ml)) {
148                 truncate(ml, n);
149         }
150         stopped_working_on(ml);
151         check_mallinks("malloc exit");
152         check_work_empty("malloc exit");
153 #ifdef STORE
154         assert(! in_store(ml));
155 #endif
156         return block_of_mallink(ml);
157 }}
158
159 void
160 free(void *addr)
161 {check_mallinks("free entry");{
162         register mallink *ml;
163
164         if (addr == NULL) {
165                 check_mallinks("free(0) very fast exit");
166                 return;
167         }
168
169         ml = mallink_of_block(addr);
170 #ifdef STORE
171
172         if (free_of(ml) || in_store(ml))
173                 return;                         /* user frees free block */
174         if (size_of(ml) <= MAX_STORE*MIN_SIZE)  {
175                 /* return to store */
176                 mallink **stp = &store[(size_of(ml) >> LOG_MIN_SIZE) - 1];
177                 
178                 set_log_next(ml, *stp);
179                 *stp = ml;
180                 set_store(ml, 1);
181                 calc_checksum(ml);
182                 check_mallinks("free fast exit");
183         }
184         else    {
185                 do_free(ml);
186                 check_mallinks("free exit");
187         }
188 }}
189
190 private
191 do_free(register mallink *ml)
192 {{
193 #endif
194
195 #ifndef STORE
196         if (free_of(ml))        return;
197 #endif /* STORE */
198         started_working_on(ml);
199         set_free(ml, 1);
200         calc_checksum(ml);
201         if (! last_mallink(ml)) {
202                 register mallink *next = phys_next_of(ml);
203
204                 if (free_of(next)) coalesce_forw(ml, next);
205         }
206
207         if (! first_mallink(ml)) {
208                 register mallink *prev = phys_prev_of(ml);
209
210                 if (free_of(prev)) {
211                         coalesce_backw(ml, prev);
212                         ml = prev;
213                 }
214         }
215         link_free_chunk(ml);
216         stopped_working_on(ml);
217         check_work_empty("free");
218
219         /* Compile-time checks on param.h */
220         switch (0)      {
221         case MIN_SIZE < OFF_SET * sizeof(mallink):      break;
222         case 1: break;
223         /*      If this statement does not compile due to duplicate case
224                 entry, the minimum size block cannot hold the links for
225                 the free blocks.  Either raise LOG_MIN_SIZE or switch
226                 off NON_STANDARD.
227         */
228         }
229         switch(0)       {
230         case sizeof(void *) != sizeof(size_type):       break;
231         case 1: break;
232         /*      If this statement does not compile due to duplicate
233                 case entry, size_type is not defined correctly.
234                 Redefine and compile again.
235         */
236         }
237 }}
238
239 void *
240 realloc(void *addr, register size_t n)
241 {check_mallinks("realloc entry");{
242         register mallink *ml, *ph_next;
243         register size_type size;
244
245         if (addr == NULL) {
246                 /*      Behave like most Unix realloc's when handed a
247                         null-pointer
248                 */
249                 return malloc(n);
250         }
251         if (n == 0) {
252                 free(addr);
253                 return NULL;
254         }
255         ml = mallink_of_block(addr);
256         if (n < MIN_SIZE) n = align(MIN_SIZE); else n = align(n);
257 #ifdef STORE
258         if (in_store(ml)) {
259                 register mallink *stp = store[(size_of(ml) >> LOG_MIN_SIZE) - 1];
260                 mallink *stp1 = NULL;
261                 while (ml != stp)       {
262                         stp1 = stp;
263                         stp = log_next_of(stp);
264                 }
265                 stp = log_next_of(stp);
266                 if (! stp1) store[(size_of(ml) >> LOG_MIN_SIZE) - 1] = stp;
267                 else set_log_next(stp1, stp);
268                 set_store(ml, 0);
269                 calc_checksum(ml);
270         }
271 #endif
272         if (free_of(ml)) {
273                 unlink_free_chunk(ml);
274                 set_free(ml, 0);                /* user reallocs free block */
275         }
276         started_working_on(ml);
277         size = size_of(ml);
278         if (    /* we can simplify the problem by adding the next chunk: */
279                 n > size &&
280                 !last_mallink(ml) &&
281                 (ph_next = phys_next_of(ml), free_of(ph_next)) &&
282                 n <= size + mallink_size() + size_of(ph_next)
283         )       {
284                 /* add in the physically next chunk */
285                 unlink_free_chunk(ph_next);
286                 combine_chunks(ml, ph_next);
287                 size = size_of(ml);
288                 check_mallinks("realloc, combining");
289         }
290         if (n > size)   {               /* this didn't help */
291                 void *new;
292                 register char *l1, *l2 = addr;
293
294                 stopped_working_on(ml);
295                 if (!(new = l1 = malloc(n))) return NULL;       /* no way */
296                 while (size--) *l1++ = *l2++;
297                 free(addr);
298                 check_work_empty("mv_realloc");
299 #ifdef STORE
300                 assert(! in_store(mallink_of_block(new)));
301 #endif
302                 return new;
303         }
304         /* it helped, but maybe too well */
305         n += mallink_size();
306         if (n + MIN_SIZE <= size_of(ml)) {
307                 truncate(ml, n);
308         }
309         stopped_working_on(ml);
310         check_mallinks("realloc exit");
311         check_work_empty("realloc");
312 #ifdef STORE
313         assert(! in_store(ml));
314 #endif
315         return addr;
316 }}
317
318 void *
319 calloc(size_t nmemb, size_t size)
320 {check_mallinks("calloc entry");{
321         long *l1, *l2;
322         size_t n;
323
324         if (size == 0) return NULL;
325         if (nmemb == 0) return NULL;
326
327         /* Check for overflow on the multiplication. The peephole-optimizer
328          * will eliminate all but one of the possibilities.
329          */
330         if (sizeof(size_t) == sizeof(int)) {
331                 if (UINT_MAX / size < nmemb) return NULL;
332         } else if (sizeof(size_t) == sizeof(long)) {
333                 if (ULONG_MAX / size < nmemb) return NULL;
334         } else return NULL;             /* can't happen, can it ? */
335
336         n = size * nmemb;
337         if (n < MIN_SIZE) n = align(MIN_SIZE); else n = align(n);
338         if (n >= (1L << LOG_MAX_SIZE)) return NULL;
339         l1 = (long *) malloc(n);
340         l2 = l1 + (n / sizeof(long));   /* n is at least long aligned */
341         while ( l2 != l1 ) *--l2 = 0;
342         check_mallinks("calloc exit");
343         check_work_empty("calloc exit");
344         return (void *)l1;
345 }}
346 /*      Auxiliary routines */
347
348 #ifdef STORE
349 private
350 sell_out(void)  {
351         /*      Frees all block in store.
352         */
353         register mallink **stp;
354         
355         for (stp = &store[0]; stp < &store[MAX_STORE]; stp++)   {
356                 register mallink *ml = *stp;
357                 
358                 while (ml)      {
359                         *stp = log_next_of(ml);
360                         set_store(ml, 0);
361                         do_free(ml);
362                         ml = *stp;
363                 }
364         }
365
366 }
367 #endif /* STORE */
368
369 #ifdef  ASSERT
370 public
371 m_assert(const char *fn, int ln)
372 {
373         char ch;
374         
375         while (*fn)
376                 write(2, fn++, 1);
377         write(2, ": malloc assert failed in line ", 31);
378         ch = (ln / 100) + '0'; write(2, &ch, 1); ln %= 100;
379         ch = (ln / 10) + '0'; write(2, &ch, 1); ln %= 10;
380         ch = (ln / 1) + '0'; write(2, &ch, 1);
381         write(2, "\n", 1);
382         maldump(1);
383 }
384 #endif  /* ASSERT */