summaryrefslogtreecommitdiffstats
path: root/stdlib/gc.ml
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/gc.ml')
-rw-r--r--stdlib/gc.ml47
1 files changed, 47 insertions, 0 deletions
diff --git a/stdlib/gc.ml b/stdlib/gc.ml
new file mode 100644
index 000000000..78065fdd8
--- /dev/null
+++ b/stdlib/gc.ml
@@ -0,0 +1,47 @@
+type stat = {
+ minor_words : int;
+ promoted_words : int;
+ major_words : int;
+ minor_collections : int;
+ major_collections : int;
+ heap_size : int;
+ heap_chunks : int;
+ live_words : int;
+ live_blocks : int;
+ free_words : int;
+ free_blocks : int;
+ largest_free : int;
+ fragments : int
+}
+
+type control = {
+ mutable minor_heap_size : int;
+ mutable major_heap_increment : int;
+ mutable space_overhead : int;
+ mutable verbose : bool
+}
+
+external stat : unit -> stat = "gc_stat"
+external get : unit -> control = "gc_get"
+external set : control -> unit = "gc_set"
+external minor : unit -> unit = "gc_minor"
+external major : unit -> unit = "gc_major"
+external full_major : unit -> unit = "gc_full_major"
+
+open Printf
+
+let print_stat c =
+ let st = stat () in
+ fprintf c "minor_words: %d\n" st.minor_words;
+ fprintf c "promoted_words: %d\n" st.promoted_words;
+ fprintf c "major_words: %d\n" st.major_words;
+ fprintf c "minor_collections: %d\n" st.minor_collections;
+ fprintf c "major_collections: %d\n" st.major_collections;
+ fprintf c "heap_size: %d\n" st.heap_size;
+ fprintf c "heap_chunks: %d\n" st.heap_chunks;
+ fprintf c "live_words: %d\n" st.live_words;
+ fprintf c "live_blocks: %d\n" st.live_blocks;
+ fprintf c "free_words: %d\n" st.free_words;
+ fprintf c "free_blocks: %d\n" st.free_blocks;
+ fprintf c "largest_free: %d\n" st.largest_free;
+ fprintf c "fragments: %d\n" st.fragments