]> pd.if.org Git - pdclib/blob - functions/stdlib/malloc.c
05fd82ed42acf670969a4ba4a14fcc89f8466177
[pdclib] / functions / stdlib / malloc.c
1 /* $Id$ */
2
3 /* void * malloc( size_t )
4
5    This file is part of the Public Domain C Library (PDCLib).
6    Permission is granted to use, modify, and / or redistribute at will.
7 */
8
9 #include <stdlib.h>
10 #include <stdint.h>
11 #include <stdbool.h>
12
13 #ifndef REGTEST
14
15 #ifndef _PDCLIB_GLUE_H
16 #define _PDCLIB_GLUE_H _PDLIB_GLUE_H
17 #include <_PDCLIB_glue.h>
18 #endif
19
20 /* TODO: Primitive placeholder. Much room for improvement. */
21
22 /* Keeping pointers to the first and the last element of the free list. */
23 struct _PDCLIB_headnode_t _PDCLIB_memlist = { NULL, NULL };
24
25 void * malloc( size_t size )
26 {
27     if ( size == 0 )
28     {
29         return NULL;
30     }
31     if ( size < _PDCLIB_MINALLOC )
32     {
33         size = _PDCLIB_MINALLOC;
34     }
35     {
36     struct _PDCLIB_memnode_t * current = _PDCLIB_memlist.first;
37     struct _PDCLIB_memnode_t * previous = NULL;
38     struct _PDCLIB_memnode_t * firstfit = NULL;
39     struct _PDCLIB_memnode_t * firstfit_previous = NULL;
40     /* Trying exact fit */
41     while ( current != NULL )
42     {
43         if ( current->size == size )
44         {
45             /* Found exact fit, allocate node */
46             if ( previous != NULL )
47             {
48                 /* Node in the middle of the list */
49                 previous->next = current->next;
50             }
51             else
52             {
53                 /* Node is first in list */
54                 _PDCLIB_memlist.first = current->next;
55             }
56             if ( _PDCLIB_memlist.last == current )
57             {
58                 /* Node is last in list */
59                 _PDCLIB_memlist.last = previous;
60             }
61             return (char *)current + sizeof( struct _PDCLIB_memnode_t );
62         }
63         else if ( current->size > size && ( firstfit == NULL || current->size < firstfit->size ) )
64         {
65             /* Remember previous node in case we do not get an exact fit.
66                Note that this is the node *pointing to* the first fit,
67                as we need that for allocating (i.e., changing next pointer).
68             */
69             firstfit_previous = previous;
70             firstfit = current;
71         }
72         /* Skip to next node */
73         previous = current;
74         current = current->next;
75     }
76     /* No exact fit; go for first fit */
77     if ( firstfit != NULL )
78     {
79         bool node_split = false;
80         if ( ( firstfit->size - size ) > ( _PDCLIB_MINALLOC + sizeof( struct _PDCLIB_memnode_t ) ) )
81         {
82             /* Oversized - split into two nodes */
83             struct _PDCLIB_memnode_t * newnode = (struct _PDCLIB_memnode_t *)( (char *)firstfit + sizeof( struct _PDCLIB_memnode_t ) + size );
84             newnode->size = firstfit->size - size - sizeof( struct _PDCLIB_memnode_t );
85             newnode->next = firstfit->next;
86             firstfit->next = newnode;
87             firstfit->size = firstfit->size - newnode->size - sizeof( struct _PDCLIB_memnode_t );
88             node_split = true;
89         }
90         if ( firstfit_previous != NULL )
91         {
92             /* Node in the middle of the list */
93             firstfit_previous->next = firstfit->next;
94         }
95         else
96         {
97             /* Node is first in list */
98             _PDCLIB_memlist.first = firstfit->next;
99         }
100         if ( _PDCLIB_memlist.last == firstfit )
101         {
102             /* Node is last in list */
103             if ( node_split )
104             {
105                 _PDCLIB_memlist.last = firstfit->next;
106             }
107             else
108             {
109                 _PDCLIB_memlist.last = firstfit_previous;
110             }
111         }
112         return (char *)firstfit + sizeof( struct _PDCLIB_memnode_t );
113     }
114     }
115     {
116     /* No fit possible; how many additional pages do we need? */
117     size_t pages = ( ( size + sizeof( struct _PDCLIB_memnode_t ) - 1 ) / _PDCLIB_PAGESIZE ) + 1;
118     /* Allocate more pages */
119     struct _PDCLIB_memnode_t * newnode = (struct _PDCLIB_memnode_t *)_PDCLIB_allocpages( (int)pages );
120     if ( newnode != NULL )
121     {
122         newnode->next = NULL;
123         newnode->size = pages * _PDCLIB_PAGESIZE - sizeof( struct _PDCLIB_memnode_t );
124         if ( ( newnode->size - size ) > ( _PDCLIB_MINALLOC + sizeof( struct _PDCLIB_memnode_t ) ) )
125         {
126             /* Oversized - split into two nodes */
127             struct _PDCLIB_memnode_t * splitnode = (struct _PDCLIB_memnode_t *)( (char *)newnode + sizeof( struct _PDCLIB_memnode_t ) + size );
128             splitnode->size = newnode->size - size - sizeof( struct _PDCLIB_memnode_t );
129             newnode->size = size;
130             /* Add splitted node as last element to free node list */
131             if ( _PDCLIB_memlist.last == NULL )
132             {
133                 _PDCLIB_memlist.first = splitnode;
134             }
135             else
136             {
137                 _PDCLIB_memlist.last->next = splitnode;
138             }
139             splitnode->next = NULL; /* TODO: This is bug #7, uncovered by testdriver yet. */
140             _PDCLIB_memlist.last = splitnode;
141         }
142         return (char *)newnode + sizeof( struct _PDCLIB_memnode_t );
143     }
144     }
145     /* No fit, heap extension not possible - out of memory */
146     return NULL;
147 }
148
149 #endif
150
151
152 #ifdef TEST
153 #include <_PDCLIB_test.h>
154 #include <string.h>
155 #include <stdarg.h>
156 #include <stdio.h>
157
158
159 #ifndef REGTEST
160
161 /* Effective page size, i.e. how many bytes can be allocated and still be on
162    one page of memory.
163 */
164 #define EFFECTIVE _PDCLIB_PAGESIZE - sizeof( struct _PDCLIB_memnode_t )
165 #define MEMTEST( ptr, size ) ( ( ptr = malloc( size ) ) != NULL ) && ( memset( ptr, 0, size ) == ptr )
166
167 char * pages_start = 0;
168 int test_nodes( char const * const, int, ... );
169 void PRINT( char const * const, ... );
170
171 /* This can be enabled to give a dump of node information */
172 #if 0
173 void PRINT( char const * const format, ... )
174 {
175     va_list( ap );
176     va_start( ap, format );
177     vprintf( format, ap );
178 }
179 #else
180 void PRINT( char const * const format, ... )
181 {
182     /* EMPTY */
183 }
184 #endif
185
186 /* Helper function checking number of allocated memory pages and the nodes
187    in the free memory list against expectations.
188 */
189 int test_nodes( char const * const action, int expected_pages, ... )
190 {
191     static int count = 1;
192     int result = 1;
193     PRINT( action );
194     /* Determining the amount of allocated pages */
195     int allocated_pages = ( (intptr_t)_PDCLIB_allocpages( 0 ) - (intptr_t)pages_start ) / _PDCLIB_PAGESIZE;
196     PRINT( "Test #%2d, %d allocated pages", count++, allocated_pages );
197     if ( allocated_pages != expected_pages )
198     {
199         PRINT( " - MISMATCH, expected\n          %d pages\n", expected_pages );
200         result = 0;
201     }
202     else
203     {
204         PRINT( "\n" );
205     }
206     /* Now moving through the free nodes list */
207     va_list( ap );
208     va_start( ap, expected_pages );
209     struct _PDCLIB_memnode_t * tracer = _PDCLIB_memlist.first;
210     int firstnode = 0;
211     int lastnode = 0;
212     while ( tracer != NULL )
213     {
214         /* Data from node */
215         size_t node_location = (char *)tracer - (char *)pages_start;
216         PRINT( "   - node %.4p, size %#.4x", node_location, tracer->size );
217         /* Expected data */
218         size_t expected_location = va_arg( ap, size_t );
219         if ( expected_location == 0 )
220         {
221             PRINT( " - UNEXPECTED NODE\n" );
222             result = 0;
223             continue;
224         }
225         /* Memorizing first and last expected node for later comparison. */
226         if ( firstnode == 0 )
227         {
228             firstnode = expected_location;
229         }
230         lastnode = expected_location;
231         /* Comparing expected node against current node */
232         size_t expected_size = va_arg( ap, size_t );
233         if ( ( node_location != expected_location ) || ( tracer->size != expected_size ) )
234         {
235             PRINT( " - MISMATCH, expected values\n          %.4p       %#.4p\n", expected_location, expected_size );
236             result = 0;
237         }
238         else
239         {
240             PRINT( "\n" );
241         }
242         tracer = tracer->next;
243     }
244     /* Comparing first and last node in memlist against expectations. */
245     PRINT( "   - memlist first: %#.4x - last: %#.4x",
246             ( _PDCLIB_memlist.first == NULL ) ? NULL : (char *)_PDCLIB_memlist.first - (char *)pages_start,
247             ( _PDCLIB_memlist.last == NULL ) ? NULL : (char *)_PDCLIB_memlist.last - (char *)pages_start );
248     if ( ( firstnode != 0 ) && 
249          ( ( ( (char *)_PDCLIB_memlist.first - (char *)pages_start ) != firstnode )
250          || ( ( (char *)_PDCLIB_memlist.last  - (char *)pages_start ) != lastnode ) ) )
251     {
252         PRINT( " - MISMATCH, expected values\n                    %#.4x - last: %#.4x\n", firstnode, lastnode );
253         result = 0;
254     }
255     else
256     {
257         PRINT( "\n" );
258     }
259     PRINT( "\n" );
260     return result;
261 }
262
263 #endif 
264
265 /* Note that this test driver heavily tests *internals* of the implementation
266    above (and of free() and realloc(), too). That means that changes in the
267    implementation must be accompanied with appropriate changes of the test
268    driver. It does *not* make a good regression tester for the implementation,
269    I am afraid, and thus there is no REGTEST equivalent.
270 */
271
272 int main( void )
273 {
274 #ifndef REGTEST
275     void * ptr1, * ptr2, * ptr3, * ptr4, * ptr5, * ptr6, * ptr7, * ptr8, * ptr9, * ptrA, * ptrB, * ptrC;
276
277     pages_start = _PDCLIB_allocpages( 0 );
278     PRINT( "\nEffective is: %#.4x\nsizeof( memnode ) is: %#.2x\n\n", EFFECTIVE, sizeof( struct _PDCLIB_memnode_t ) ); 
279
280     /* Allocating 10 bytes; expecting one page allocation and a node split */
281     TESTCASE( MEMTEST( ptr1, 10 ) );
282     TESTCASE( test_nodes( "Allocating 10 bytes.", 1,
283                sizeof( struct _PDCLIB_memnode_t ) + 10, EFFECTIVE - sizeof( struct _PDCLIB_memnode_t ) - 10,
284                0 ) );
285
286     /* Allocating the rest of the page; expecting no page allocation and assignment of the remaining node */
287     TESTCASE( MEMTEST( ptr2, EFFECTIVE - 10 - sizeof( struct _PDCLIB_memnode_t ) ) );
288     TESTCASE( test_nodes( "Allocating the rest of the page.", 1,
289                0 ) );
290
291     /* Allocating a full page; expecting one page allocation, no node split */
292     TESTCASE( MEMTEST( ptr3, EFFECTIVE ) );
293     TESTCASE( test_nodes( "Allocating a full page.", 2,
294                0 ) );
295
296     /* Allocating *almost* a full page; expecting one page allocation, no node split */
297     TESTCASE( MEMTEST( ptr4, EFFECTIVE - 4 ) );
298     TESTCASE( test_nodes( "Allocating *almost* a full page.", 3,
299                0 ) );
300
301     /* Freeing and re-allocating the "almost" full page; expecting no page allocation, no node split */
302     free( ptr4 );
303     TESTCASE( MEMTEST( ptr5, EFFECTIVE - 4 ) );
304     TESTCASE( ptr4 == ptr5 );
305     TESTCASE( test_nodes( "Freeing and re-allocating the \"almost\" full page.", 3 ) );
306
307     /* Freeing the full page from test #3; expecting a full-sized free node. */
308     free( ptr3 );
309     TESTCASE( test_nodes( "Freeing the full page from test #3.", 3,
310                _PDCLIB_PAGESIZE * 1, EFFECTIVE,
311                0 ) );
312
313     /* Allocating two full pages; expecting two page allocations, no node split */
314     TESTCASE( MEMTEST( ptr3, EFFECTIVE + _PDCLIB_PAGESIZE ) );
315     TESTCASE( test_nodes( "Allocating two full pages.", 5,
316                _PDCLIB_PAGESIZE * 1, EFFECTIVE,
317                0 ) );
318
319     /* Re-allocating to size of 10 bytes; expecting no page allocation, no node split */
320     /* TODO: Shouldn't realloc() split the now much-too-large node? */
321     TESTCASE( realloc( ptr3, 10 ) == ptr3 );
322     TESTCASE( test_nodes( "Re-allocating to size of 10 bytes.", 5,
323                _PDCLIB_PAGESIZE * 1, EFFECTIVE,
324                0 ) );
325
326     /* Re-allocating to size of two full pages; expecting no page allocation, no node split */
327     TESTCASE( realloc( ptr3, EFFECTIVE + _PDCLIB_PAGESIZE ) == ptr3 );
328     TESTCASE( test_nodes( "Re-allocating to size of two full pages.", 5,
329                _PDCLIB_PAGESIZE * 1, EFFECTIVE,
330                0 ) );
331
332     /* Re-allocating to size of three full pages; expecting three page allocation, freeing of two-page node */
333     TESTCASE( realloc( ptr3, EFFECTIVE + _PDCLIB_PAGESIZE * 2 ) != ptr3 );
334     TESTCASE( test_nodes( "Re-allocating to size of three full pages.", 8,
335                _PDCLIB_PAGESIZE * 1, EFFECTIVE,
336                _PDCLIB_PAGESIZE * 3, EFFECTIVE + _PDCLIB_PAGESIZE,
337                0 ) );
338
339     /* Allocating two full pages; expecting allocation of the available two-page node */
340     TESTCASE( MEMTEST( ptr4, EFFECTIVE + _PDCLIB_PAGESIZE ) );
341     TESTCASE( test_nodes( "Allocating two full pages.", 8,
342                _PDCLIB_PAGESIZE * 1, EFFECTIVE,
343                0 ) );
344
345     /* Allocating zero bytes; expecting no change */
346     TESTCASE( ! MEMTEST( ptr6, 0 ) );
347     TESTCASE( test_nodes( "Allocating zero bytes.", 8,
348                _PDCLIB_PAGESIZE * 1, EFFECTIVE,
349                0 ) );
350
351     /* Allocating 4 bytes; expecting upsizing of requestupsizing of size, node split */
352     TESTCASE( MEMTEST( ptr7, 4 ) );
353     TESTCASE( test_nodes( "Allocating 4 bytes.", 8,
354                _PDCLIB_PAGESIZE * 1 + _PDCLIB_MINALLOC + sizeof( struct _PDCLIB_memnode_t ),
355                EFFECTIVE - _PDCLIB_MINALLOC - sizeof( struct _PDCLIB_memnode_t ),
356                0 ) );
357
358     /* Allocating the rest of the page; expecting no page allocation and assignment of the remaining node */
359     TESTCASE( MEMTEST( ptr8, EFFECTIVE - _PDCLIB_MINALLOC - sizeof( struct _PDCLIB_memnode_t ) ) );
360     TESTCASE( test_nodes( "Allocating the rest of the page.", 8, 0 ) );
361
362     /* Freeing the node from the previous test; expecting node to re-appear in free list */
363     free( ptr8 );
364     TESTCASE( test_nodes( "Freeing the node from the previous test.", 8,
365                _PDCLIB_PAGESIZE * 1 + _PDCLIB_MINALLOC + sizeof( struct _PDCLIB_memnode_t ),
366                EFFECTIVE - _PDCLIB_MINALLOC - sizeof( struct _PDCLIB_memnode_t ),
367                0 ) );
368
369     /* Allocating one byte more than available in free node; expecting page allocation */
370     TESTCASE( MEMTEST( ptr8, EFFECTIVE + 1 - _PDCLIB_MINALLOC - sizeof( struct _PDCLIB_memnode_t ) ) );
371     TESTCASE( test_nodes( "Allocating one byte more than available in free node.", 9,
372                _PDCLIB_PAGESIZE * 1 + _PDCLIB_MINALLOC + sizeof( struct _PDCLIB_memnode_t ),
373                EFFECTIVE - _PDCLIB_MINALLOC - sizeof( struct _PDCLIB_memnode_t ),
374                0 ) );
375
376     /* Re-allocating with NULL pointer; expecting no page allocation, no node split */
377     ptr9 = realloc( NULL, EFFECTIVE - _PDCLIB_MINALLOC - sizeof( struct _PDCLIB_memnode_t ) );
378     TESTCASE( ptr9 != NULL );
379     TESTCASE( memset( ptr9, 0, EFFECTIVE - _PDCLIB_MINALLOC - sizeof( struct _PDCLIB_memnode_t ) ) == ptr9 );
380     TESTCASE( test_nodes( "Re-allocating with NULL pointer.", 9, 0 ) );
381
382     /* Allocating a bit more than half a page; expecting page allocation, node split */
383 #define TESTSIZE 3000
384     TESTCASE( MEMTEST( ptrA, TESTSIZE ) );
385     TESTCASE( test_nodes( "Allocating a bit more than half a page.", 10,
386                _PDCLIB_PAGESIZE * 9 + sizeof( struct _PDCLIB_memnode_t ) + TESTSIZE,
387                EFFECTIVE - sizeof( struct _PDCLIB_memnode_t ) - TESTSIZE,
388                0 ) );
389
390     /* Allocating a bit more than half a page; expecting page allocation, node split */
391     TESTCASE( MEMTEST( ptrB, TESTSIZE ) );
392     TESTCASE( test_nodes( "Allocating a bit more than half a page.", 11,
393                _PDCLIB_PAGESIZE * 9 + sizeof( struct _PDCLIB_memnode_t ) + TESTSIZE,
394                EFFECTIVE - sizeof( struct _PDCLIB_memnode_t ) - TESTSIZE,
395                _PDCLIB_PAGESIZE * 10 + sizeof( struct _PDCLIB_memnode_t ) + TESTSIZE,
396                EFFECTIVE - sizeof( struct _PDCLIB_memnode_t ) - TESTSIZE,
397                0 ) );
398
399     /* Allocating a bit more than half a page; expecting page allocation, node split */
400     TESTCASE( MEMTEST( ptrC, TESTSIZE ) );
401     TESTCASE( test_nodes( "Allocating a bit more than half a page.", 12,
402                _PDCLIB_PAGESIZE * 9 + sizeof( struct _PDCLIB_memnode_t ) + TESTSIZE,
403                EFFECTIVE - sizeof( struct _PDCLIB_memnode_t ) - TESTSIZE,
404                _PDCLIB_PAGESIZE * 10 + sizeof( struct _PDCLIB_memnode_t ) + TESTSIZE,
405                EFFECTIVE - sizeof( struct _PDCLIB_memnode_t ) - TESTSIZE,
406                _PDCLIB_PAGESIZE * 11 + sizeof( struct _PDCLIB_memnode_t ) + TESTSIZE,
407                EFFECTIVE - sizeof( struct _PDCLIB_memnode_t ) - TESTSIZE,
408                0 ) );
409
410     /* Freeing the middle node */
411     free( ptrB );
412     TESTCASE( test_nodes( "Freeing the middle node.", 12,
413                _PDCLIB_PAGESIZE * 9 + sizeof( struct _PDCLIB_memnode_t ) + TESTSIZE,
414                EFFECTIVE - sizeof( struct _PDCLIB_memnode_t ) - TESTSIZE,
415                _PDCLIB_PAGESIZE * 10 + sizeof( struct _PDCLIB_memnode_t ) + TESTSIZE,
416                EFFECTIVE - sizeof( struct _PDCLIB_memnode_t ) - TESTSIZE,
417                _PDCLIB_PAGESIZE * 11 + sizeof( struct _PDCLIB_memnode_t ) + TESTSIZE,
418                EFFECTIVE - sizeof( struct _PDCLIB_memnode_t ) - TESTSIZE,
419                _PDCLIB_PAGESIZE * 10,
420                TESTSIZE,
421                0 ) );
422
423 #else
424     puts( " NOTEST malloc() test driver is PDCLib-specific." );
425 #endif
426     return TEST_RESULTS;
427 }
428
429 #endif