1995-08-09 08:06:35 -07:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
2011-07-27 07:17:02 -07:00
|
|
|
(* OCaml *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
1997-10-14 06:17:48 -07:00
|
|
|
(* Damien Doligez, projet Para, INRIA Rocquencourt *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* 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. *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
type stat = {
|
2001-02-05 06:59:24 -08:00
|
|
|
minor_words : float;
|
|
|
|
promoted_words : float;
|
|
|
|
major_words : float;
|
1995-05-04 03:15:53 -07:00
|
|
|
minor_collections : int;
|
|
|
|
major_collections : int;
|
1995-08-08 06:37:34 -07:00
|
|
|
heap_words : int;
|
1995-05-04 03:15:53 -07:00
|
|
|
heap_chunks : int;
|
|
|
|
live_words : int;
|
|
|
|
live_blocks : int;
|
|
|
|
free_words : int;
|
|
|
|
free_blocks : int;
|
|
|
|
largest_free : int;
|
1997-05-13 07:45:38 -07:00
|
|
|
fragments : int;
|
2002-02-01 04:23:58 -08:00
|
|
|
compactions : int;
|
|
|
|
top_heap_words : int;
|
2010-04-27 00:55:08 -07:00
|
|
|
stack_size : int;
|
1997-05-13 07:45:38 -07:00
|
|
|
};;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
type control = {
|
|
|
|
mutable minor_heap_size : int;
|
|
|
|
mutable major_heap_increment : int;
|
|
|
|
mutable space_overhead : int;
|
1998-08-07 11:45:00 -07:00
|
|
|
mutable verbose : int;
|
1997-05-13 07:45:38 -07:00
|
|
|
mutable max_overhead : int;
|
2002-02-01 04:23:58 -08:00
|
|
|
mutable stack_limit : int;
|
2008-12-03 10:09:09 -08:00
|
|
|
mutable allocation_policy : int;
|
1997-05-13 07:45:38 -07:00
|
|
|
};;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2004-01-02 11:23:29 -08:00
|
|
|
external stat : unit -> stat = "caml_gc_stat";;
|
2004-01-30 06:29:04 -08:00
|
|
|
external quick_stat : unit -> stat = "caml_gc_quick_stat";;
|
2004-01-02 11:23:29 -08:00
|
|
|
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";;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1997-05-13 07:45:38 -07:00
|
|
|
open Printf;;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
let print_stat c =
|
|
|
|
let st = stat () in
|
2001-02-05 06:59:24 -08:00
|
|
|
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;
|
1995-05-04 03:15:53 -07:00
|
|
|
fprintf c "minor_collections: %d\n" st.minor_collections;
|
|
|
|
fprintf c "major_collections: %d\n" st.major_collections;
|
1995-08-08 06:37:34 -07:00
|
|
|
fprintf c "heap_words: %d\n" st.heap_words;
|
1995-05-04 03:15:53 -07:00
|
|
|
fprintf c "heap_chunks: %d\n" st.heap_chunks;
|
2002-02-01 04:23:58 -08:00
|
|
|
fprintf c "top_heap_words: %d\n" st.top_heap_words;
|
1995-05-04 03:15:53 -07:00
|
|
|
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;
|
1997-05-13 07:45:38 -07:00
|
|
|
fprintf c "fragments: %d\n" st.fragments;
|
|
|
|
fprintf c "compactions: %d\n" st.compactions;
|
|
|
|
;;
|
1999-11-29 12:02:33 -08:00
|
|
|
|
|
|
|
let allocated_bytes () =
|
2001-02-05 06:59:24 -08:00
|
|
|
let (mi, pro, ma) = counters () in
|
|
|
|
(mi +. ma -. pro) *. float_of_int (Sys.word_size / 8)
|
1999-11-29 12:02:33 -08:00
|
|
|
;;
|
2000-01-07 08:51:58 -08:00
|
|
|
|
2004-01-02 11:23:29 -08:00
|
|
|
external finalise : ('a -> unit) -> 'a -> unit = "caml_final_register";;
|
2004-06-14 06:27:42 -07:00
|
|
|
external finalise_release : unit -> unit = "caml_final_release";;
|
2001-02-05 06:59:24 -08:00
|
|
|
|
|
|
|
|
2002-02-01 04:23:58 -08:00
|
|
|
type alarm = bool ref;;
|
|
|
|
type alarm_rec = {active : alarm; f : unit -> unit};;
|
2001-02-05 06:59:24 -08:00
|
|
|
|
2001-08-28 06:22:24 -07:00
|
|
|
let rec call_alarm arec =
|
|
|
|
if !(arec.active) then begin
|
|
|
|
finalise call_alarm arec;
|
|
|
|
arec.f ();
|
2001-02-05 06:59:24 -08:00
|
|
|
end;
|
|
|
|
;;
|
|
|
|
|
|
|
|
let create_alarm f =
|
2001-08-28 06:22:24 -07:00
|
|
|
let arec = { active = ref true; f = f } in
|
|
|
|
finalise call_alarm arec;
|
2003-08-07 07:17:59 -07:00
|
|
|
arec.active
|
2001-02-05 06:59:24 -08:00
|
|
|
;;
|
|
|
|
|
2001-08-28 06:22:24 -07:00
|
|
|
let delete_alarm a = a := false;;
|