~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/tools/c_src/erl_memory_trace_block_table.c

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

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