1 /* ``Licensed under the Apache License, Version 2.0 (the "License");
2  * you may not use this file except in compliance with the License.
3  * You may obtain a copy of the License at
4  *
5  *     http://www.apache.org/licenses/LICENSE-2.0
6  *
7  * Unless required by applicable law or agreed to in writing, software
8  * distributed under the License is distributed on an "AS IS" BASIS,
9  * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
10  * See the License for the specific language governing permissions and
11  * limitations under the License.
12  *
13  * The Initial Developer of the Original Code is Ericsson Utvecklings AB.
14  * Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
15  * AB. All Rights Reserved.''
16  *
17  *     $Id$
18  */
19 
20 
21 /*
22  * Description:
23  *
24  * Author: 	Rickard Green
25  */
26 
27 /* Headers to include ... */
28 
29 #ifdef HAVE_CONFIG_H
30 #	include "config.h"
31 #endif
32 
33 #include "erl_memory_trace_block_table.h"
34 #include <errno.h>
35 
36 #undef HARD_DEBUG
37 #undef REALLY_HARD_DEBUG
38 #ifdef DEBUG
39 #  define HARD_DEBUG 0
40 #  define REALLY_HARD_DEBUG 0
41 #else
42 #  define HARD_DEBUG 0
43 #  define REALLY_HARD_DEBUG 0
44 #endif
45 
46 /* Some system specific defines ... */
47 #if defined(__WIN32__) && !defined(__GNUC__)
48 #	define INLINE __forceinline
49 #else
50 #	ifdef __GNUC__
51 #		define INLINE __inline__
52 #	else
53 #		define INLINE
54 #	endif
55 #endif
56 
57 /* Our own assert() ... */
58 #ifdef DEBUG
59 #define ASSERT(A) ((void) ((A) ? 1 : assert_failed(__FILE__, __LINE__, #A)))
60 #include <stdio.h>
assert_failed(char * f,int l,char * a)61 static int assert_failed(char *f, int l, char *a)
62 {
63     fprintf(stderr, "%s:%d: Assertion failed: %s\n", f, l, a);
64     abort();
65     return 0;
66 }
67 
68 #else
69 #define ASSERT(A) ((void) 1)
70 #endif
71 
72 
73 #define EMTBT_BLOCKS_PER_POOL 1000
74 
75 typedef struct emtbt_block_pool_ {
76     struct emtbt_block_pool_ *next;
77     emtbt_block blocks[1];
78 } emtbt_block_pool;
79 
80 struct emtbt_table_ {
81     void * (*alloc)(size_t);
82     void * (*realloc)(void *, size_t);
83     void   (*free)(void *);
84     int is_64_bit;
85     int no_blocks;
86     int no_of_buckets;
87     int max_used_buckets;
88     int min_used_buckets;
89     int used_buckets;
90     int current_size_index;
91     emtbt_block *blocks;
92     emtbt_block ** buckets;
93 
94 
95     /* Fixed size allocation of blocks */
96     emtbt_block_pool *block_pools;
97     emtbt_block *free_blocks;
98     int blocks_per_pool;
99 
100 };
101 
102 
103 static emtbt_block null_blk = {0};
104 
105 /* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *\
106  * Block table                                                             *
107  *                                                                         *
108 \*                                                                         */
109 
110 #if HARD_DEBUG
111 static void check_table(emtbt_table *table);
112 #endif
113 
114 static emtbt_block *
block_alloc_new_pool(emtbt_table * tab)115 block_alloc_new_pool(emtbt_table *tab)
116 {
117     size_t size;
118     emtbt_block_pool *poolp;
119 
120     size = sizeof(emtbt_block_pool) - sizeof(emtbt_block);
121     size += tab->blocks_per_pool*sizeof(emtbt_block);
122 
123     poolp = (*tab->alloc)(size);
124 
125     if (poolp) {
126 	int i;
127 	emtbt_block *blks;
128 
129 	poolp->next = tab->block_pools;
130 	tab->block_pools = poolp;
131 
132 	blks = (emtbt_block *) poolp->blocks;
133 
134 	for (i = 1; i < tab->blocks_per_pool - 1; i++)
135 	    blks[i].next = &blks[i + 1];
136 	blks[tab->blocks_per_pool - 1].next = NULL;
137 	tab->free_blocks = &blks[1];
138 
139 	return &blks[0];
140     }
141     return NULL;
142 }
143 
144 static INLINE emtbt_block *
block_alloc(emtbt_table * tab)145 block_alloc(emtbt_table *tab)
146 {
147     emtbt_block *res;
148 #if HARD_DEBUG
149     check_table(tab);
150 #endif
151 
152     if (tab->free_blocks) {
153 	res = tab->free_blocks;
154 	tab->free_blocks = tab->free_blocks->next;
155     }
156     else {
157 	res = block_alloc_new_pool(tab);
158     }
159 
160 #ifdef DEBUG
161     res->next = ((emtbt_block *) 0xfffffff0);
162     res->prev = ((emtbt_block *) 0xfffffff0);
163     res->bucket = ((emtbt_block **) 0xfffffff0);
164 #endif
165 
166 #if HARD_DEBUG
167     check_table(tab);
168 #endif
169 
170     return res;
171 }
172 
173 static INLINE void
block_free(emtbt_table * tab,emtbt_block * bp)174 block_free(emtbt_table *tab, emtbt_block *bp)
175 {
176 
177 #if HARD_DEBUG
178     check_table(tab);
179 #endif
180 
181     bp->next = tab->free_blocks;
182     tab->free_blocks = bp;
183 
184 #if HARD_DEBUG
185     check_table(tab);
186 #endif
187 
188 
189 }
190 
191 #define PRIME0 ((usgnd_int_32) 268438039)
192 #define PRIME1 ((usgnd_int_32) 268440479)
193 #define PRIME2 ((usgnd_int_32) 268439161)
194 #define PRIME3 ((usgnd_int_32) 268437017)
195 
196 #define MK_HASH(H, P, IS64)						\
197 do {									\
198     (H) = (P) & 0xff;							\
199     (H) *= PRIME0;							\
200     (H) += ((P) >> 8) & 0xff;						\
201     (H) *= PRIME1;							\
202     (H) += ((P) >> 16) & 0xff;						\
203     (H) *= PRIME2;							\
204     (H) += ((P) >> 24) & 0xff;						\
205     (H) *= PRIME3;							\
206     if ((IS64)) {							\
207 	(H) += ((P) >> 32) & 0xff;					\
208 	(H) *= PRIME0;							\
209 	(H) += ((P) >> 40) & 0xff;					\
210 	(H) *= PRIME1;							\
211 	(H) += ((P) >> 48) & 0xff;					\
212 	(H) *= PRIME2;							\
213 	(H) += ((P) >> 56) & 0xff;					\
214 	(H) *= PRIME3;							\
215     }									\
216 } while (0)
217 
218 static const int table_sizes[] = {
219     3203,
220     4813,
221     6421,
222     9643,
223     12853,
224     19289,
225     25717,
226     51437,
227     102877,
228     205759,
229     411527,
230     823117,
231     1646237,
232     3292489,
233     6584983,
234     13169977,
235     26339969,
236     52679969
237 };
238 
239 #if HARD_DEBUG
240 
241 static void
check_table(emtbt_table * table)242 check_table(emtbt_table *table)
243 {
244     int no_blocks;
245     emtbt_block *block, *prev_block;
246 
247     no_blocks = 0;
248     block = table->blocks;
249     ASSERT(!block || !block->prev);
250     prev_block = NULL;
251     while (block) {
252 	usgnd_int_32 hash;
253 	MK_HASH(hash, block->pointer, table->is_64_bit);
254 	ASSERT(hash == block->hash);
255 	ASSERT(block->bucket - table->buckets
256 	       == hash % table->no_of_buckets);
257 	ASSERT(!prev_block || prev_block == block->prev);
258 	prev_block = block;
259 	block = block->next;
260 	no_blocks++;
261 	ASSERT(table->no_blocks >= no_blocks);
262     }
263 
264     ASSERT(table->no_blocks == no_blocks);
265 
266 #if REALLY_HARD_DEBUG
267     {
268 	int i;
269 	for (i = 0; i < table->no_of_buckets; i++) {
270 	    int bucket_end_found;
271 	    emtbt_block **bucket;
272 	    if (!table->buckets[i])
273 		continue;
274 	    bucket_end_found = 0;
275 	    bucket = &table->buckets[i];
276 	    for (block = table->blocks; block; block = block->next) {
277 		if (block->bucket == bucket) {
278 		    if (!block->prev || block->prev->bucket != bucket)
279 			ASSERT(*bucket == block);
280 		    if (!block->next || block->next->bucket != bucket)
281 			bucket_end_found++;
282 		}
283 	    }
284 	    ASSERT(bucket_end_found);
285 	}
286     }
287 #endif
288 
289 }
290 
291 #endif
292 
293 static INLINE void
link_block(emtbt_table * table,emtbt_block ** bucket,emtbt_block * block)294 link_block(emtbt_table *table, emtbt_block **bucket, emtbt_block *block)
295 {
296     ASSERT(bucket);
297 
298     block->bucket = bucket;
299     if (*bucket) {
300 	block->next = *bucket;
301 	block->prev = (*bucket)->prev;
302 	if (block->prev)
303 	    block->prev->next = block;
304 	else
305 	    table->blocks = block;
306 	block->next->prev = block;
307     }
308     else {
309 	block->next = table->blocks;
310 	block->prev = NULL;
311 	if (table->blocks)
312 	    table->blocks->prev = block;
313 	table->blocks = block;
314 	table->used_buckets++;
315 
316     }
317     *bucket = block;
318     table->no_blocks++;
319 
320 #if HARD_DEBUG
321     check_table(table);
322 #endif
323 
324 }
325 
326 static int
resize_table(emtbt_table * table,int new_no_of_buckets)327 resize_table(emtbt_table *table, int new_no_of_buckets)
328 {
329 #ifdef DEBUG
330     int org_no_blocks;
331 #endif
332     int i;
333     emtbt_block *block;
334     emtbt_block **buckets;
335 
336     if (new_no_of_buckets < table->no_of_buckets) {
337 	/* shrink never fails */
338 	buckets = (emtbt_block **) (*table->realloc)(table->buckets,
339 						     (sizeof(emtbt_block *)
340 						      * new_no_of_buckets));
341 	if (!buckets)
342 	    return 1;
343     }
344     else if (new_no_of_buckets > table->no_of_buckets) {
345 	(*table->free)((void *) table->buckets);
346 	buckets = (emtbt_block **) (*table->alloc)((sizeof(emtbt_block *)
347 						    * new_no_of_buckets));
348 	if (!buckets)
349 	    return 0;
350     }
351     else
352 	return 1;
353 
354     table->buckets = buckets;
355     table->no_of_buckets = new_no_of_buckets;
356     table->max_used_buckets = (4*new_no_of_buckets)/5;
357     table->min_used_buckets = new_no_of_buckets/5;
358     table->used_buckets = 0;
359 
360 #ifdef DEBUG
361     org_no_blocks = table->no_blocks;
362 #endif
363 
364     table->no_blocks = 0;
365 
366 
367     for (i = 0; i < new_no_of_buckets; i++)
368 	buckets[i] = NULL;
369 
370     block = table->blocks;
371     table->blocks = NULL;
372 
373     while (block) {
374 	emtbt_block *next_block = block->next;
375 	link_block(table,&table->buckets[block->hash%new_no_of_buckets],block);
376 	block = next_block;
377     }
378 
379     ASSERT(org_no_blocks == table->no_blocks);
380 
381     return 1;
382 }
383 
384 static INLINE int
grow_table(emtbt_table * table)385 grow_table(emtbt_table *table)
386 {
387     if (table->current_size_index < sizeof(table_sizes)/sizeof(int)) {
388 	int new_size;
389 	table->current_size_index++;
390 	new_size = table_sizes[table->current_size_index];
391 	ASSERT(new_size > 0);
392 	return resize_table(table, new_size);
393     }
394     return 1;
395 }
396 
397 static INLINE void
shrink_table(emtbt_table * table)398 shrink_table(emtbt_table *table)
399 {
400     if (table->current_size_index > 0) {
401 	int new_size;
402 	table->current_size_index--;
403 	new_size = table_sizes[table->current_size_index];
404 	ASSERT(new_size > 0);
405 	(void) resize_table(table, new_size);
406     }
407 }
408 
409 static INLINE emtbt_block *
peek_block(emtbt_table * table,usgnd_int_max ptr)410 peek_block(emtbt_table *table, usgnd_int_max ptr)
411 {
412     emtbt_block **bucket;
413     emtbt_block *block;
414     usgnd_int_32 hash;
415 
416     MK_HASH(hash, ptr, table->is_64_bit);
417 
418     bucket = &table->buckets[hash % table->no_of_buckets];
419     block = *bucket;
420     if (!block)
421 	return NULL;
422 
423     while (block->bucket == bucket) {
424 	ASSERT(block);
425 	if (block->pointer == ptr)
426 	    return block;
427 	if (!block->next)
428 	    break;
429 	block = block->next;
430     }
431     return NULL;
432 }
433 
434 static INLINE int
insert_block(emtbt_table * table,emtbt_block * block)435 insert_block(emtbt_table *table, emtbt_block *block)
436 {
437     emtbt_block **bucket;
438     emtbt_block *tmp_block;
439     usgnd_int_32 hash;
440     usgnd_int_max p;
441 
442 #if HARD_DEBUG
443     check_table(table);
444 #endif
445 
446     if (table->used_buckets >= table->max_used_buckets) {
447 	if(!grow_table(table))
448 	    return -1;
449     }
450 
451     p = block->pointer;
452 
453     MK_HASH(hash, p, table->is_64_bit);
454     block->hash = hash;
455 
456     bucket = &table->buckets[hash % table->no_of_buckets];
457     tmp_block = *bucket;
458     if (tmp_block) {
459 	while (tmp_block->bucket == bucket) {
460 	    if (tmp_block->pointer == p)
461 		return 0;
462 	    if (!tmp_block->next)
463 		break;
464 	    tmp_block = tmp_block->next;
465 	}
466     }
467 
468     link_block(table, bucket, block);
469 
470     ASSERT(block == peek_block(table, p));
471 
472 
473     return 1;
474 }
475 
476 static INLINE void
delete_block(emtbt_table * table,emtbt_block * block)477 delete_block(emtbt_table *table, emtbt_block *block)
478 {
479     emtbt_block **bucket;
480 
481     if (!block)
482 	return;
483 
484 #if HARD_DEBUG
485     check_table(table);
486 #endif
487 
488     bucket = block->bucket;
489     ASSERT(bucket);
490 
491     if (block->prev)
492 	block->prev->next = block->next;
493     else
494 	table->blocks = block->next;
495 
496     if (block->next)
497 	block->next->prev = block->prev;
498 
499     if (block == *bucket) {
500 	ASSERT(!block->prev || block->prev->bucket != bucket);
501 	if (block->next && block->next->bucket == bucket)
502 	    *bucket = block->next;
503 	else {
504 	    ASSERT(table->used_buckets > 0);
505 	    *bucket = NULL;
506 	    table->used_buckets--;
507 	}
508     }
509 #ifdef DEBUG
510 
511     block->next = ((emtbt_block *) 0xfffffff0);
512     block->prev = ((emtbt_block *) 0xfffffff0);
513     block->bucket = ((emtbt_block **) 0xfffffff0);
514 #endif
515 
516     ASSERT(table->no_blocks > 0);
517     table->no_blocks--;
518 
519     if (table->used_buckets < table->min_used_buckets)
520 	shrink_table(table);
521 
522 #if HARD_DEBUG
523     check_table(table);
524 #endif
525 
526 }
527 
528 static INLINE emtbt_block *
fetch_block(emtbt_table * table,usgnd_int_max ptr)529 fetch_block(emtbt_table *table, usgnd_int_max ptr)
530 {
531     emtbt_block *block;
532 
533     block = peek_block(table, ptr);
534     delete_block(table, block);
535     return block;
536 }
537 
538 
emtbt_error_string(int error)539 const char *emtbt_error_string(int error)
540 {
541     switch (error) {
542     case EMTBT_ALLOC_XBLK_ERROR:
543 	return "Allocation to an already existing block";
544     case EMTBT_REALLOC_NOBLK_ERROR:
545 	return "Reallocation of non-existing block";
546     case EMTBT_REALLOC_XBLK_ERROR:
547 	return "Reallocation to an already existing block";
548     case EMTBT_REALLOC_BLK_TYPE_MISMATCH:
549 	return "Block types mismatch when reallocating";
550     case EMTBT_FREE_NOBLK_ERROR:
551 	return "Deallocation of non-existing block";
552     case EMTBT_FREE_BLK_TYPE_MISMATCH:
553 	return "Block types mismatch when deallocating";
554     case EMTBT_INTERNAL_ERROR:
555 	return "Block table internal error";
556     default:
557 	return NULL;
558     }
559 
560 
561 }
562 
563 
564 emtbt_table *
emtbt_new_table(int is_64_bit,void * (* alloc)(size_t),void * (* realloc)(void *,size_t),void (* free)(void *))565 emtbt_new_table(int is_64_bit,
566 		void * (*alloc)(size_t),
567 		void * (*realloc)(void *, size_t),
568 		void   (*free)(void *))
569 {
570     emtbt_table *tab = (*alloc)(sizeof(emtbt_table));
571     if (tab) {
572 	tab->alloc = alloc;
573 	tab->realloc = realloc;
574 	tab->free = free;
575 	tab->is_64_bit = is_64_bit;
576 	tab->no_blocks = 0;
577 	tab->no_of_buckets = 0;
578 	tab->max_used_buckets = 0;
579 	tab->min_used_buckets = 0;
580 	tab->used_buckets = 0;
581 	tab->current_size_index = 0;
582 	tab->blocks = NULL;
583 	tab->buckets = NULL;
584 
585 	tab->block_pools = NULL;
586 	tab->free_blocks = NULL;
587 	tab->blocks_per_pool = EMTBT_BLOCKS_PER_POOL;
588 
589     }
590     return tab;
591 }
592 
593 void
emtbt_destroy_table(emtbt_table * tab)594 emtbt_destroy_table(emtbt_table *tab)
595 {
596     void (*freep)(void *);
597     emtbt_block_pool *poolp1, *poolp2;
598 
599     freep = tab->free;
600 
601     /* Free block pools */
602     poolp1 = tab->block_pools;
603     while (poolp1) {
604 	poolp2 = poolp1;
605 	poolp1 = poolp1->next;
606 	(*freep)((void *) poolp2);
607     }
608 
609     if (tab->buckets)
610 	(*freep)((void *) tab->buckets);
611 
612     (*freep)((void *) tab);
613 }
614 
615 
616 #define CP_BLK(TO, FROM)						\
617 do {									\
618     (TO)->time.secs	= (FROM)->time.secs;				\
619     (TO)->time.usecs	= (FROM)->time.usecs;				\
620     (TO)->type		= (FROM)->type;					\
621     (TO)->pointer	= (FROM)->pointer;				\
622     (TO)->size		= (FROM)->size;					\
623 } while (0)
624 
625 int
emtbt_alloc_op(emtbt_table * tab,emtp_operation * op)626 emtbt_alloc_op(emtbt_table *tab, emtp_operation *op)
627 {
628     int res;
629     emtbt_block *blk;
630 
631     blk = block_alloc(tab);
632     if (!blk)
633 	return ENOMEM;
634 
635     blk->time.secs	= op->time.secs;
636     blk->time.usecs	= op->time.usecs;
637     blk->type		= op->u.block.type;
638     blk->pointer	= op->u.block.new_ptr;
639     blk->size		= op->u.block.new_size;
640 
641     res = insert_block(tab, blk);
642     if (res < 0)
643 	return ENOMEM;
644     else if (res == 0)
645 	return EMTBT_ALLOC_XBLK_ERROR;
646     return 0;
647 }
648 
649 int
emtbt_realloc_op(emtbt_table * tab,emtp_operation * op,emtbt_block * old_blk)650 emtbt_realloc_op(emtbt_table *tab, emtp_operation *op, emtbt_block *old_blk)
651 {
652     int res;
653     emtbt_block *blk;
654 
655     if (!op->u.block.new_size) {
656 	/* freed block */
657 
658 	blk = fetch_block(tab, op->u.block.prev_ptr);
659 	if (!blk)
660 	    return EMTBT_REALLOC_NOBLK_ERROR;
661 
662 	CP_BLK(old_blk, blk);
663 	block_free(tab, blk);
664     }
665     else {
666 
667 	if (!op->u.block.new_ptr) {
668 	    /* failed operation */
669 	    if (!op->u.block.prev_ptr)
670 		CP_BLK(old_blk, &null_blk);
671 	    else {
672 		blk = peek_block(tab, op->u.block.prev_ptr);
673 		if (!blk)
674 		    return EMTBT_REALLOC_NOBLK_ERROR;
675 		CP_BLK(old_blk, blk);
676 #if 0
677 		if (blk->type != op->u.block.type)
678 		    return EMTBT_REALLOC_BLK_TYPE_MISMATCH;
679 #endif
680 	    }
681 	}
682 	else if (!op->u.block.prev_ptr) {
683 	    /* new block */
684 
685 	    CP_BLK(old_blk, &null_blk);
686 	    blk = block_alloc(tab);
687 	    if (!blk)
688 		return ENOMEM;
689 	    blk->type		= op->u.block.type;
690 	    blk->pointer	= op->u.block.new_ptr;
691 	    blk->time.secs	= op->time.secs;
692 	    blk->time.usecs	= op->time.usecs;
693 	    blk->size		= op->u.block.new_size;
694 
695 	    res = insert_block(tab, blk);
696 	    if (res < 0)
697 		return ENOMEM;
698 	    else if (res == 0)
699 		return EMTBT_REALLOC_XBLK_ERROR;
700 	}
701 	else if (op->u.block.new_ptr == op->u.block.prev_ptr) {
702 	    /* resized block */
703 	    blk = peek_block(tab, op->u.block.prev_ptr);
704 	    if (!blk)
705 		return EMTBT_REALLOC_NOBLK_ERROR;
706 	    CP_BLK(old_blk, blk);
707 	    blk->time.secs	= op->time.secs;
708 	    blk->time.usecs	= op->time.usecs;
709 	    blk->size		= op->u.block.new_size;
710 #if 0
711 	    if (blk->type != op->u.block.type)
712 		return EMTBT_REALLOC_BLK_TYPE_MISMATCH;
713 #endif
714 	}
715 	else {
716 	    /* moved block */
717 	    blk = fetch_block(tab, op->u.block.prev_ptr);
718 	    if (!blk)
719 		return EMTBT_REALLOC_NOBLK_ERROR;
720 	    CP_BLK(old_blk, blk);
721 	    blk->time.secs	= op->time.secs;
722 	    blk->time.usecs	= op->time.usecs;
723 	    blk->pointer 	= op->u.block.new_ptr;
724 	    blk->size		= op->u.block.new_size;
725 	    res = insert_block(tab, blk);
726 	    if (res < 0)
727 		return ENOMEM;
728 	    else if (res == 0)
729 		return EMTBT_REALLOC_XBLK_ERROR;
730 #if 0
731 	    if (blk->type != op->u.block.type)
732 		return EMTBT_REALLOC_BLK_TYPE_MISMATCH;
733 #endif
734 	}
735     }
736     return 0;
737 
738 }
739 
740 
741 int
emtbt_free_op(emtbt_table * tab,emtp_operation * op,emtbt_block * old_blk)742 emtbt_free_op(emtbt_table *tab, emtp_operation *op, emtbt_block *old_blk)
743 {
744     emtbt_block *blk;
745 
746     if (!op->u.block.prev_ptr)
747 	CP_BLK(old_blk, &null_blk);
748     else {
749 
750 	blk = fetch_block(tab, op->u.block.prev_ptr);
751 	if (!blk)
752 	    return EMTBT_FREE_NOBLK_ERROR;
753 
754 	CP_BLK(old_blk, blk);
755 	block_free(tab, blk);
756 #if 0
757 	if (blk->type != op->u.block.type)
758 	    return EMTBT_FREE_BLK_TYPE_MISMATCH;
759 #endif
760     }
761     return 0;
762 }
763