summaryrefslogtreecommitdiff
path: root/stdlib/gc.ml
diff options
context:
space:
mode:
authorKC Sivaramakrishnan <kc@kcsrk.info>2018-03-09 09:38:20 +0000
committerKC Sivaramakrishnan <kc@kcsrk.info>2018-03-09 09:38:20 +0000
commit99441b55e1ef6576c414a6a0d5e5bbb365f0cf1a (patch)
tree84e8a9c5ba38e0e8b0a96281123856bc67409efd /stdlib/gc.ml
parentefac34a4822f578a04a97b82c65ca86860658b18 (diff)
downloadocaml-99441b55e1ef6576c414a6a0d5e5bbb365f0cf1a.tar.gz
Promote to 4.04.2 => bootstrap succeeded
Diffstat (limited to 'stdlib/gc.ml')
-rw-r--r--stdlib/gc.ml93
1 files changed, 54 insertions, 39 deletions
diff --git a/stdlib/gc.ml b/stdlib/gc.ml
index 8276ecedc7..0083c7885b 100644
--- a/stdlib/gc.ml
+++ b/stdlib/gc.ml
@@ -1,15 +1,17 @@
-(***********************************************************************)
+(**************************************************************************)
(* *)
(* OCaml *)
(* *)
(* Damien Doligez, projet Para, INRIA Rocquencourt *)
(* *)
(* Copyright 1996 Institut National de Recherche en Informatique et *)
-(* en Automatique. All rights reserved. This file is distributed *)
-(* under the terms of the GNU Library General Public License, with *)
-(* the special exception on linking described in file ../LICENSE. *)
+(* en Automatique. *)
(* *)
-(***********************************************************************)
+(* All rights reserved. This file is distributed under the terms of *)
+(* the GNU Lesser General Public License version 2.1, with the *)
+(* special exception on linking described in the file LICENSE. *)
+(* *)
+(**************************************************************************)
type stat = {
minor_words : float;
@@ -28,7 +30,7 @@ type stat = {
compactions : int;
top_heap_words : int;
stack_size : int;
-};;
+}
type control = {
mutable minor_heap_size : int;
@@ -38,64 +40,77 @@ type control = {
mutable max_overhead : int;
mutable stack_limit : int;
mutable allocation_policy : int;
-};;
+ window_size : int;
+}
-external stat : unit -> stat = "caml_gc_stat";;
-external quick_stat : unit -> stat = "caml_gc_quick_stat";;
-external counters : unit -> (float * float * float) = "caml_gc_counters";;
-external get : unit -> control = "caml_gc_get";;
-external set : control -> unit = "caml_gc_set";;
-external minor : unit -> unit = "caml_gc_minor";;
-external major_slice : int -> int = "caml_gc_major_slice";;
-external major : unit -> unit = "caml_gc_major";;
-external full_major : unit -> unit = "caml_gc_full_major";;
-external compact : unit -> unit = "caml_gc_compaction";;
+external stat : unit -> stat = "caml_gc_stat"
+external quick_stat : unit -> stat = "caml_gc_quick_stat"
+external counters : unit -> (float * float * float) = "caml_gc_counters"
+external minor_words : unit -> (float [@unboxed])
+ = "caml_gc_minor_words" "caml_gc_minor_words_unboxed" [@@noalloc]
+external get : unit -> control = "caml_gc_get"
+external set : control -> unit = "caml_gc_set"
+external minor : unit -> unit = "caml_gc_minor"
+external major_slice : int -> int = "caml_gc_major_slice"
+external major : unit -> unit = "caml_gc_major"
+external full_major : unit -> unit = "caml_gc_full_major"
+external compact : unit -> unit = "caml_gc_compaction"
+external get_minor_free : unit -> int = "caml_get_minor_free" [@@noalloc]
+external get_bucket : int -> int = "caml_get_major_bucket" [@@noalloc]
+external get_credit : unit -> int = "caml_get_major_credit" [@@noalloc]
+external huge_fallback_count : unit -> int = "caml_gc_huge_fallback_count"
-open Printf;;
+open Printf
let print_stat c =
let st = stat () in
- fprintf c "minor_words: %.0f\n" st.minor_words;
- fprintf c "promoted_words: %.0f\n" st.promoted_words;
- fprintf c "major_words: %.0f\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_words: %d\n" st.heap_words;
- fprintf c "heap_chunks: %d\n" st.heap_chunks;
- fprintf c "top_heap_words: %d\n" st.top_heap_words;
- fprintf c "live_words: %d\n" st.live_words;
+ fprintf c "compactions: %d\n" st.compactions;
+ fprintf c "\n";
+ let l1 = String.length (sprintf "%.0f" st.minor_words) in
+ fprintf c "minor_words: %*.0f\n" l1 st.minor_words;
+ fprintf c "promoted_words: %*.0f\n" l1 st.promoted_words;
+ fprintf c "major_words: %*.0f\n" l1 st.major_words;
+ fprintf c "\n";
+ let l2 = String.length (sprintf "%d" st.top_heap_words) in
+ fprintf c "top_heap_words: %*d\n" l2 st.top_heap_words;
+ fprintf c "heap_words: %*d\n" l2 st.heap_words;
+ fprintf c "live_words: %*d\n" l2 st.live_words;
+ fprintf c "free_words: %*d\n" l2 st.free_words;
+ fprintf c "largest_free: %*d\n" l2 st.largest_free;
+ fprintf c "fragments: %*d\n" l2 st.fragments;
+ fprintf c "\n";
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;
- fprintf c "compactions: %d\n" st.compactions;
-;;
+ fprintf c "heap_chunks: %d\n" st.heap_chunks
+
let allocated_bytes () =
let (mi, pro, ma) = counters () in
(mi +. ma -. pro) *. float_of_int (Sys.word_size / 8)
-;;
-external finalise : ('a -> unit) -> 'a -> unit = "caml_final_register";;
-external finalise_release : unit -> unit = "caml_final_release";;
external promote_to : 'a -> 'b -> 'a = "caml_obj_promote_to"
+external finalise : ('a -> unit) -> 'a -> unit = "caml_final_register"
+external finalise_last : (unit -> unit) -> 'a -> unit =
+ "caml_final_register_called_without_value"
+external finalise_release : unit -> unit = "caml_final_release"
-type alarm = bool ref;;
-type alarm_rec = {active : alarm; f : unit -> unit};;
+type alarm = bool ref
+type alarm_rec = {active : alarm; f : unit -> unit}
let rec call_alarm arec =
if !(arec.active) then begin
finalise call_alarm arec;
arec.f ();
- end;
-;;
+ end
+
let create_alarm f =
let arec = { active = ref true; f = f } in
finalise call_alarm arec;
arec.active
-;;
-let delete_alarm a = a := false;;
+
+let delete_alarm a = a := false