1997-05-13 07:45:38 -07:00
|
|
|
/***********************************************************************/
|
|
|
|
/* */
|
|
|
|
/* Objective Caml */
|
|
|
|
/* */
|
|
|
|
/* Damien Doligez, projet Para, INRIA Rocquencourt */
|
|
|
|
/* */
|
|
|
|
/* Copyright 1996 Institut National de Recherche en Informatique et */
|
1999-11-17 10:59:06 -08:00
|
|
|
/* en Automatique. All rights reserved. This file is distributed */
|
2001-12-07 05:41:02 -08:00
|
|
|
/* under the terms of the GNU Library General Public License, with */
|
|
|
|
/* the special exception on linking described in file ../LICENSE. */
|
1997-05-13 07:45:38 -07:00
|
|
|
/* */
|
|
|
|
/***********************************************************************/
|
|
|
|
|
|
|
|
/* $Id$ */
|
|
|
|
|
|
|
|
#include <string.h>
|
|
|
|
|
|
|
|
#include "config.h"
|
2000-01-07 08:51:58 -08:00
|
|
|
#include "finalise.h"
|
1997-05-13 07:45:38 -07:00
|
|
|
#include "freelist.h"
|
|
|
|
#include "gc.h"
|
|
|
|
#include "gc_ctrl.h"
|
|
|
|
#include "major_gc.h"
|
|
|
|
#include "memory.h"
|
|
|
|
#include "mlvalues.h"
|
|
|
|
#include "roots.h"
|
|
|
|
#include "weak.h"
|
|
|
|
|
1997-05-21 08:28:15 -07:00
|
|
|
extern unsigned long percent_free; /* major_gc.c */
|
1997-09-02 05:55:01 -07:00
|
|
|
extern void shrink_heap (char *); /* memory.c */
|
1997-05-13 07:45:38 -07:00
|
|
|
|
|
|
|
/* Encoded headers: the color is stored in the 2 least significant bits.
|
|
|
|
(For pointer inversion, we need to distinguish headers from pointers.)
|
|
|
|
s is a Wosize, t is a tag, and c is a color (a two-bit number)
|
|
|
|
|
|
|
|
For the purpose of compaction, "colors" are:
|
|
|
|
0: pointers (direct or inverted)
|
|
|
|
1: integer or (unencoded) infix header
|
|
|
|
2: inverted pointer for infix header
|
|
|
|
3: integer or encoded (noninfix) header
|
1999-11-08 09:31:19 -08:00
|
|
|
|
|
|
|
XXX Should be fixed:
|
|
|
|
XXX The above assumes that all roots are aligned on a 4-byte boundary,
|
|
|
|
XXX which is not always guaranteed by C.
|
|
|
|
XXX (see [register_global_roots] and [init_exceptions])
|
|
|
|
XXX Should be able to fix it to only assume 2-byte alignment.
|
1997-05-13 07:45:38 -07:00
|
|
|
*/
|
|
|
|
#define Make_ehd(s,t,c) (((s) << 10) | (t) << 2 | (c))
|
|
|
|
#define Whsize_ehd(h) Whsize_hd (h)
|
|
|
|
#define Wosize_ehd(h) Wosize_hd (h)
|
|
|
|
#define Tag_ehd(h) (((h) >> 2) & 0xFF)
|
|
|
|
#define Ecolor(w) ((w) & 3)
|
|
|
|
|
|
|
|
typedef unsigned long word;
|
|
|
|
|
1997-09-02 05:55:01 -07:00
|
|
|
static void invert_pointer_at (word *p)
|
1997-05-13 07:45:38 -07:00
|
|
|
{
|
|
|
|
word q = *p;
|
1999-11-08 09:31:19 -08:00
|
|
|
Assert (Ecolor ((long) p) == 0);
|
1997-05-13 07:45:38 -07:00
|
|
|
|
|
|
|
/* Use Ecolor (q) == 0 instead of Is_block (q) because q could be an
|
|
|
|
inverted pointer for an infix header (with Ecolor == 2). */
|
|
|
|
if (Ecolor (q) == 0 && Is_in_heap (q)){
|
|
|
|
switch (Ecolor (Hd_val (q))){
|
|
|
|
case 0:
|
|
|
|
case 3: /* Pointer or header: insert in inverted list. */
|
|
|
|
*p = Hd_val (q);
|
|
|
|
Hd_val (q) = (header_t) p;
|
|
|
|
break;
|
|
|
|
case 1: /* Infix header: make inverted infix list. */
|
|
|
|
/* Double inversion: the last of the inverted infix list points to
|
|
|
|
the next infix header in this block. The last of the last list
|
|
|
|
contains the original block header. */
|
|
|
|
{
|
1997-05-19 08:42:21 -07:00
|
|
|
/* This block as a value. */
|
|
|
|
value val = (value) q - Infix_offset_val (q);
|
|
|
|
/* Get the block header. */
|
|
|
|
word *hp = (word *) Hp_val (val);
|
1999-11-08 09:31:19 -08:00
|
|
|
|
1997-05-19 08:42:21 -07:00
|
|
|
while (Ecolor (*hp) == 0) hp = (word *) *hp;
|
1997-05-13 07:45:38 -07:00
|
|
|
Assert (Ecolor (*hp) == 3);
|
1997-05-19 08:42:21 -07:00
|
|
|
if (Tag_ehd (*hp) == Closure_tag){
|
|
|
|
/* This is the first infix found in this block. */
|
1997-05-13 07:45:38 -07:00
|
|
|
/* Save original header. */
|
1997-05-19 08:42:21 -07:00
|
|
|
*p = *hp;
|
1997-05-13 07:45:38 -07:00
|
|
|
/* Link inverted infix list. */
|
1997-05-19 08:42:21 -07:00
|
|
|
Hd_val (q) = (header_t) ((word) p | 2);
|
|
|
|
/* Change block header's tag to Infix_tag, and change its size
|
1997-05-13 07:45:38 -07:00
|
|
|
to point to the infix list. */
|
1997-05-19 08:42:21 -07:00
|
|
|
*hp = Make_ehd (Wosize_bhsize (q - val), Infix_tag, 3);
|
|
|
|
}else{ Assert (Tag_ehd (*hp) == Infix_tag);
|
|
|
|
/* Point the last of this infix list to the current first infix
|
1997-05-13 07:45:38 -07:00
|
|
|
list of the block. */
|
|
|
|
*p = (word) &Field (val, Wosize_ehd (*hp)) | 1;
|
1997-05-19 08:42:21 -07:00
|
|
|
/* Point the head of this infix list to the above. */
|
|
|
|
Hd_val (q) = (header_t) ((word) p | 2);
|
|
|
|
/* Change block header's size to point to this infix list. */
|
|
|
|
*hp = Make_ehd (Wosize_bhsize (q - val), Infix_tag, 3);
|
|
|
|
}
|
1997-05-13 07:45:38 -07:00
|
|
|
}
|
|
|
|
break;
|
|
|
|
case 2: /* Inverted infix list: insert. */
|
|
|
|
*p = Hd_val (q);
|
|
|
|
Hd_val (q) = (header_t) ((word) p | 2);
|
|
|
|
break;
|
|
|
|
}
|
|
|
|
}
|
|
|
|
}
|
|
|
|
|
1997-09-02 05:55:01 -07:00
|
|
|
static void invert_root (value v, value *p)
|
1997-05-13 07:45:38 -07:00
|
|
|
{
|
|
|
|
invert_pointer_at ((word *) p);
|
|
|
|
}
|
|
|
|
|
|
|
|
static char *compact_fl;
|
|
|
|
|
1997-09-02 05:55:01 -07:00
|
|
|
static void init_compact_allocate (void)
|
1997-05-13 07:45:38 -07:00
|
|
|
{
|
|
|
|
char *ch = heap_start;
|
|
|
|
while (ch != NULL){
|
|
|
|
Chunk_alloc (ch) = 0;
|
|
|
|
ch = Chunk_next (ch);
|
|
|
|
}
|
|
|
|
compact_fl = heap_start;
|
|
|
|
}
|
|
|
|
|
1997-09-02 05:55:01 -07:00
|
|
|
static char *compact_allocate (mlsize_t size)
|
|
|
|
/* in bytes, including header */
|
1997-05-13 07:45:38 -07:00
|
|
|
{
|
|
|
|
char *chunk, *adr;
|
|
|
|
|
|
|
|
while (Chunk_size (compact_fl) - Chunk_alloc (compact_fl) <= Bhsize_wosize (3)
|
1997-05-19 08:42:21 -07:00
|
|
|
&& Chunk_size (Chunk_next (compact_fl))
|
|
|
|
- Chunk_alloc (Chunk_next (compact_fl))
|
1997-05-13 07:45:38 -07:00
|
|
|
<= Bhsize_wosize (3)){
|
|
|
|
compact_fl = Chunk_next (compact_fl);
|
|
|
|
}
|
|
|
|
chunk = compact_fl;
|
|
|
|
while (Chunk_size (chunk) - Chunk_alloc (chunk) < size){
|
|
|
|
chunk = Chunk_next (chunk); Assert (chunk != NULL);
|
|
|
|
}
|
|
|
|
adr = chunk + Chunk_alloc (chunk);
|
|
|
|
Chunk_alloc (chunk) += size;
|
|
|
|
return adr;
|
|
|
|
}
|
|
|
|
|
|
|
|
void compact_heap (void)
|
|
|
|
{
|
|
|
|
char *ch, *chend;
|
|
|
|
Assert (gc_phase == Phase_idle);
|
1998-08-07 11:43:39 -07:00
|
|
|
gc_message (0x10, "Compacting heap...\n", 0);
|
1999-11-08 09:31:19 -08:00
|
|
|
|
|
|
|
#ifdef DEBUG
|
|
|
|
heap_check ();
|
|
|
|
#endif
|
|
|
|
|
1997-05-13 07:45:38 -07:00
|
|
|
/* First pass: encode all noninfix headers. */
|
|
|
|
{
|
|
|
|
ch = heap_start;
|
|
|
|
while (ch != NULL){
|
|
|
|
header_t *p = (header_t *) ch;
|
|
|
|
|
|
|
|
chend = ch + Chunk_size (ch);
|
|
|
|
while ((char *) p < chend){
|
1997-05-19 08:42:21 -07:00
|
|
|
header_t hd = Hd_hp (p);
|
|
|
|
mlsize_t sz = Wosize_hd (hd);
|
|
|
|
|
|
|
|
if (Is_blue_hd (hd)){
|
|
|
|
/* Free object. Give it a string tag. */
|
|
|
|
Hd_hp (p) = Make_ehd (sz, String_tag, 3);
|
|
|
|
}else{ Assert (Is_white_hd (hd));
|
|
|
|
/* Live object. Keep its tag. */
|
1997-05-13 07:45:38 -07:00
|
|
|
Hd_hp (p) = Make_ehd (sz, Tag_hd (hd), 3);
|
1997-05-19 08:42:21 -07:00
|
|
|
}
|
|
|
|
p += Whsize_wosize (sz);
|
1997-05-13 07:45:38 -07:00
|
|
|
}
|
|
|
|
ch = Chunk_next (ch);
|
|
|
|
}
|
|
|
|
}
|
|
|
|
|
|
|
|
|
|
|
|
/* Second pass: invert pointers.
|
|
|
|
Link infix headers in each block in an inverted list of inverted lists.
|
|
|
|
Don't forget roots and weak pointers. */
|
|
|
|
{
|
1998-04-06 09:32:33 -07:00
|
|
|
/* Invert roots first because the threads library needs some heap
|
2000-01-07 08:51:58 -08:00
|
|
|
data structures to find its roots. Fortunately, it doesn't need
|
|
|
|
the headers (see above). */
|
1998-04-06 09:32:33 -07:00
|
|
|
do_roots (invert_root);
|
2000-01-07 08:51:58 -08:00
|
|
|
final_do_weak_roots (invert_root);
|
1998-04-06 09:32:33 -07:00
|
|
|
|
1997-05-13 07:45:38 -07:00
|
|
|
ch = heap_start;
|
|
|
|
while (ch != NULL){
|
|
|
|
word *p = (word *) ch;
|
|
|
|
chend = ch + Chunk_size (ch);
|
|
|
|
|
|
|
|
while ((char *) p < chend){
|
1997-05-19 08:42:21 -07:00
|
|
|
word q = *p;
|
|
|
|
size_t sz, i;
|
|
|
|
tag_t t;
|
|
|
|
word *infixes;
|
|
|
|
|
|
|
|
while (Ecolor (q) == 0) q = * (word *) q;
|
|
|
|
sz = Whsize_ehd (q);
|
|
|
|
t = Tag_ehd (q);
|
|
|
|
|
|
|
|
if (t == Infix_tag){
|
|
|
|
/* Get the original header of this block. */
|
|
|
|
infixes = p + sz;
|
|
|
|
q = *infixes;
|
|
|
|
while (Ecolor (q) != 3) q = * (word *) (q & ~(unsigned long)3);
|
|
|
|
sz = Whsize_ehd (q);
|
|
|
|
t = Tag_ehd (q);
|
|
|
|
}
|
|
|
|
|
|
|
|
if (t < No_scan_tag){
|
|
|
|
for (i = 1; i < sz; i++) invert_pointer_at (&(p[i]));
|
|
|
|
}
|
|
|
|
p += sz;
|
1997-05-13 07:45:38 -07:00
|
|
|
}
|
|
|
|
ch = Chunk_next (ch);
|
|
|
|
}
|
|
|
|
/* Invert weak pointers. */
|
|
|
|
{
|
1997-06-02 05:51:51 -07:00
|
|
|
value *pp = &weak_list_head;
|
|
|
|
value p;
|
1997-05-13 07:45:38 -07:00
|
|
|
word q;
|
|
|
|
size_t sz, i;
|
|
|
|
|
1997-06-02 05:51:51 -07:00
|
|
|
while (1){
|
|
|
|
p = *pp;
|
|
|
|
if (p == (value) NULL) break;
|
1997-05-19 08:42:21 -07:00
|
|
|
q = Hd_val (p);
|
|
|
|
while (Ecolor (q) == 0) q = * (word *) q;
|
|
|
|
sz = Wosize_ehd (q);
|
|
|
|
for (i = 1; i < sz; i++){
|
1997-09-02 06:13:33 -07:00
|
|
|
if (Field (p,i) != 0) invert_pointer_at ((word *) &(Field (p,i)));
|
1997-05-19 08:42:21 -07:00
|
|
|
}
|
1997-09-02 06:13:33 -07:00
|
|
|
invert_pointer_at ((word *) pp);
|
1997-06-02 05:51:51 -07:00
|
|
|
pp = &Field (p, 0);
|
1997-05-13 07:45:38 -07:00
|
|
|
}
|
|
|
|
}
|
|
|
|
}
|
|
|
|
|
|
|
|
|
|
|
|
/* Third pass: reallocate virtually; revert pointers; decode headers.
|
|
|
|
Rebuild infix headers. */
|
|
|
|
{
|
|
|
|
init_compact_allocate ();
|
|
|
|
ch = heap_start;
|
|
|
|
while (ch != NULL){
|
|
|
|
word *p = (word *) ch;
|
|
|
|
|
|
|
|
chend = ch + Chunk_size (ch);
|
|
|
|
while ((char *) p < chend){
|
1997-05-19 08:42:21 -07:00
|
|
|
word q = *p;
|
|
|
|
|
|
|
|
if (Ecolor (q) == 0 || Tag_ehd (q) == Infix_tag){
|
|
|
|
/* There were (normal or infix) pointers to this block. */
|
|
|
|
size_t sz;
|
|
|
|
tag_t t;
|
|
|
|
char *newadr;
|
|
|
|
word *infixes = NULL;
|
|
|
|
|
|
|
|
while (Ecolor (q) == 0) q = * (word *) q;
|
|
|
|
sz = Whsize_ehd (q);
|
|
|
|
t = Tag_ehd (q);
|
|
|
|
|
|
|
|
if (t == Infix_tag){
|
|
|
|
/* Get the original header of this block. */
|
|
|
|
infixes = p + sz;
|
|
|
|
q = *infixes; Assert (Ecolor (q) == 2);
|
|
|
|
while (Ecolor (q) != 3) q = * (word *) (q & ~(unsigned long)3);
|
|
|
|
sz = Whsize_ehd (q);
|
|
|
|
t = Tag_ehd (q);
|
|
|
|
}
|
|
|
|
|
|
|
|
newadr = compact_allocate (Bsize_wsize (sz));
|
|
|
|
q = *p;
|
|
|
|
while (Ecolor (q) == 0){
|
|
|
|
word next = * (word *) q;
|
|
|
|
* (word *) q = (word) Val_hp (newadr);
|
|
|
|
q = next;
|
|
|
|
}
|
2000-01-02 08:10:00 -08:00
|
|
|
*p = Make_header (Wosize_whsize (sz), t, Caml_white);
|
1997-05-19 08:42:21 -07:00
|
|
|
|
|
|
|
if (infixes != NULL){
|
|
|
|
/* Rebuild the infix headers and revert the infix pointers. */
|
|
|
|
while (Ecolor ((word) infixes) != 3){
|
|
|
|
infixes = (word *) ((word) infixes & ~(unsigned long) 3);
|
|
|
|
q = *infixes;
|
|
|
|
while (Ecolor (q) == 2){
|
|
|
|
word next;
|
|
|
|
q = (word) q & ~(unsigned long) 3;
|
|
|
|
next = * (word *) q;
|
|
|
|
* (word *) q = (word) Val_hp ((word *) newadr + (infixes - p));
|
|
|
|
q = next;
|
|
|
|
} Assert (Ecolor (q) == 1 || Ecolor (q) == 3);
|
2000-01-02 08:10:00 -08:00
|
|
|
*infixes = Make_header (infixes - p, Infix_tag, Caml_white);
|
1997-05-19 08:42:21 -07:00
|
|
|
infixes = (word *) q;
|
|
|
|
}
|
|
|
|
}
|
|
|
|
p += sz;
|
|
|
|
}else{ Assert (Ecolor (q) == 3);
|
1997-05-13 07:45:38 -07:00
|
|
|
/* This is guaranteed only if compact_heap was called after a
|
|
|
|
nonincremental major GC: Assert (Tag_ehd (q) == String_tag);
|
|
|
|
*/
|
1997-05-19 08:42:21 -07:00
|
|
|
/* No pointers to the header and no infix header:
|
|
|
|
the object was free. */
|
2000-01-02 08:10:00 -08:00
|
|
|
*p = Make_header (Wosize_ehd (q), Tag_ehd (q), Caml_blue);
|
1997-05-19 08:42:21 -07:00
|
|
|
p += Whsize_ehd (q);
|
|
|
|
}
|
1997-05-13 07:45:38 -07:00
|
|
|
}
|
|
|
|
ch = Chunk_next (ch);
|
|
|
|
}
|
|
|
|
}
|
|
|
|
|
|
|
|
|
|
|
|
/* Fourth pass: reallocate and move objects.
|
|
|
|
Use the exact same allocation algorithm as pass 3. */
|
|
|
|
{
|
|
|
|
init_compact_allocate ();
|
|
|
|
ch = heap_start;
|
|
|
|
while (ch != NULL){
|
|
|
|
word *p = (word *) ch;
|
|
|
|
|
|
|
|
chend = ch + Chunk_size (ch);
|
|
|
|
while ((char *) p < chend){
|
1997-05-19 08:42:21 -07:00
|
|
|
word q = *p;
|
2000-01-02 08:10:00 -08:00
|
|
|
if (Color_hd (q) == Caml_white){
|
1997-05-19 08:42:21 -07:00
|
|
|
size_t sz = Bhsize_hd (q);
|
|
|
|
char *newadr = compact_allocate (sz); Assert (newadr <= (char *)p);
|
2000-10-12 11:05:42 -07:00
|
|
|
memmove (newadr, p, sz);
|
1997-05-19 08:42:21 -07:00
|
|
|
p += Wsize_bsize (sz);
|
|
|
|
}else{
|
2000-01-02 08:10:00 -08:00
|
|
|
Assert (Color_hd (q) == Caml_blue);
|
1997-05-19 08:42:21 -07:00
|
|
|
p += Whsize_hd (q);
|
|
|
|
}
|
1997-05-13 07:45:38 -07:00
|
|
|
}
|
|
|
|
ch = Chunk_next (ch);
|
|
|
|
}
|
|
|
|
}
|
|
|
|
|
|
|
|
/* Shrink the heap if needed. */
|
|
|
|
{
|
|
|
|
/* Find the amount of live data and the unshrinkable free space. */
|
|
|
|
asize_t live = 0;
|
|
|
|
asize_t free = 0;
|
|
|
|
asize_t wanted;
|
|
|
|
|
|
|
|
ch = heap_start;
|
|
|
|
while (ch != NULL){
|
|
|
|
if (Chunk_alloc (ch) != 0){
|
1997-05-19 08:42:21 -07:00
|
|
|
live += Wsize_bsize (Chunk_alloc (ch));
|
|
|
|
free += Wsize_bsize (Chunk_size (ch) - Chunk_alloc (ch));
|
1997-05-13 07:45:38 -07:00
|
|
|
}
|
|
|
|
ch = Chunk_next (ch);
|
|
|
|
}
|
|
|
|
|
|
|
|
/* Add up the empty chunks until there are enough, then remove the
|
|
|
|
other empty chunks. */
|
1997-05-21 08:28:15 -07:00
|
|
|
wanted = percent_free * (live / 100 + 1);
|
1997-05-13 07:45:38 -07:00
|
|
|
ch = heap_start;
|
|
|
|
while (ch != NULL){
|
|
|
|
char *next_chunk = Chunk_next (ch); /* Chunk_next (ch) will be erased */
|
|
|
|
|
|
|
|
if (Chunk_alloc (ch) == 0){
|
1997-05-19 08:42:21 -07:00
|
|
|
if (free < wanted){
|
1997-05-21 08:28:15 -07:00
|
|
|
free += Wsize_bsize (Chunk_size (ch));
|
1997-05-19 08:42:21 -07:00
|
|
|
}else{
|
|
|
|
shrink_heap (ch);
|
|
|
|
}
|
1997-05-13 07:45:38 -07:00
|
|
|
}
|
|
|
|
ch = next_chunk;
|
|
|
|
}
|
|
|
|
}
|
|
|
|
|
|
|
|
/* Rebuild the free list. */
|
|
|
|
{
|
|
|
|
ch = heap_start;
|
|
|
|
fl_reset ();
|
|
|
|
while (ch != NULL){
|
|
|
|
if (Chunk_size (ch) > Chunk_alloc (ch)){
|
1997-05-19 08:42:21 -07:00
|
|
|
header_t *p = (header_t *) (ch + Chunk_alloc (ch));
|
|
|
|
*p = Make_header (Wosize_bhsize (Chunk_size (ch) - Chunk_alloc (ch)),
|
2000-01-02 08:10:00 -08:00
|
|
|
0, Caml_white);
|
1997-05-19 08:42:21 -07:00
|
|
|
fl_merge_block (Bp_hp (p));
|
1997-05-13 07:45:38 -07:00
|
|
|
}
|
|
|
|
ch = Chunk_next (ch);
|
|
|
|
}
|
|
|
|
}
|
|
|
|
++ stat_compactions;
|
1998-08-07 11:43:39 -07:00
|
|
|
gc_message (0x10, "done.\n", 0);
|
1997-05-13 07:45:38 -07:00
|
|
|
}
|
|
|
|
|
1997-05-21 08:28:15 -07:00
|
|
|
unsigned long percent_max;
|
1997-05-13 07:45:38 -07:00
|
|
|
|
1997-09-02 05:55:01 -07:00
|
|
|
void compact_heap_maybe (void)
|
1997-05-13 07:45:38 -07:00
|
|
|
{
|
2002-05-28 09:57:31 -07:00
|
|
|
/* Estimated free words in the heap:
|
|
|
|
FW = fl_size_at_change + 3 * (fl_cur_size - fl_size_at_change)
|
|
|
|
FW = 3 * fl_cur_size - 2 * fl_size_at_change
|
|
|
|
Estimated live words: LW = stat_heap_size - FW
|
|
|
|
Estimated free percentage: FP = 100 * FW / LW
|
|
|
|
We compact the heap if FP > percent_max
|
1997-05-13 07:45:38 -07:00
|
|
|
*/
|
2002-05-28 09:57:31 -07:00
|
|
|
float fw, fp;
|
1997-05-21 08:28:15 -07:00
|
|
|
Assert (gc_phase == Phase_idle);
|
|
|
|
if (percent_max >= 1000000) return;
|
2002-05-28 09:57:31 -07:00
|
|
|
if (stat_major_collections < 5 || stat_heap_chunks < 5) return;
|
|
|
|
|
|
|
|
fw = 3.0 * fl_cur_size - 2.0 * fl_size_at_phase_change;
|
|
|
|
if (fw < 0) fw = fl_cur_size;
|
|
|
|
|
|
|
|
if (fw >= Wsize_bsize (stat_heap_size)){
|
|
|
|
fp = 1000000.0;
|
|
|
|
}else{
|
|
|
|
fp = 100.0 * fw / (Wsize_bsize (stat_heap_size) - fw);
|
|
|
|
if (fp > 1000000.0) fp = 1000000.0;
|
|
|
|
}
|
2002-06-05 05:10:15 -07:00
|
|
|
gc_message (0x200, "FL size at phase change = %lu\n",
|
|
|
|
(unsigned long) fl_size_at_phase_change);
|
2002-05-28 09:57:31 -07:00
|
|
|
gc_message (0x200, "Estimated overhead = %lu%%\n", (unsigned long) fp);
|
|
|
|
if (fp >= percent_max){
|
|
|
|
gc_message (0x200, "Automatic compaction triggered.\n", 0);
|
1997-05-13 07:45:38 -07:00
|
|
|
finish_major_cycle ();
|
2002-05-28 09:57:31 -07:00
|
|
|
|
|
|
|
/* We just did a complete GC, so we can measure the overhead exactly. */
|
|
|
|
fw = fl_cur_size;
|
|
|
|
fp = 100.0 * fw / (Wsize_bsize (stat_heap_size) - fw);
|
|
|
|
gc_message (0x200, "Measured overhead: %lu%%\n", (unsigned long) fp);
|
|
|
|
|
1997-05-13 07:45:38 -07:00
|
|
|
compact_heap ();
|
|
|
|
}
|
|
|
|
}
|