Le module Profiling a ete sorti de la lib standard et mis ici.

Raison: qd on linke en -linkall (e.g. pour le toplevel), on ne veut
pas linker Profiling systematiquement.


git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@442 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Xavier Leroy 1995-11-13 14:25:17 +00:00
parent 0e624a81cb
commit 78a3daa364
5 changed files with 75 additions and 4 deletions

View File

@ -1,5 +1,5 @@
camldep.cmo: ../utils/misc.cmi
camldep.cmx: ../utils/misc.cmx
csldep.cmo: ../utils/misc.cmi
csldep.cmx: ../utils/misc.cmx
cslprof.cmo: ../utils/clflags.cmo ../utils/config.cmi ../parsing/lexer.cmi \
../parsing/location.cmi ../utils/misc.cmi ../parsing/parse.cmi \
../parsing/parsetree.cmi
@ -20,3 +20,5 @@ dumpobj.cmx: ../parsing/asttypes.cmi ../utils/config.cmx \
../utils/tbl.cmx
objinfo.cmo: ../utils/config.cmi ../bytecomp/emitcode.cmi
objinfo.cmx: ../utils/config.cmx ../bytecomp/emitcode.cmx
profiling.cmo: profiling.cmi
profiling.cmx: profiling.cmi

View File

@ -36,12 +36,13 @@ CSLPROF=cslprof.cmo
CSLPROF_IMPORTS=misc.cmo config.cmo clflags.cmo terminfo.cmo \
location.cmo longident.cmo pstream.cmo parser.cmo lexer.cmo parse.cmo
cslprof: $(CSLPROF)
cslprof: $(CSLPROF) profiling.cmo
$(CAMLC) $(LINKFLAGS) -o cslprof $(CSLPROF_IMPORTS) $(CSLPROF)
install::
cp cslprof $(BINDIR)/cslprof
cp cslcp $(BINDIR)/cslcp
cp profiling.cmi profiling.cmo $(LIBDIR)
clean::
rm -f cslprof

View File

@ -1,7 +1,7 @@
#!/bin/sh
toremove=""
cslargs=""
cslargs="profiling.cmo"
profargs=""
while : ; do

51
tools/profiling.ml Normal file
View File

@ -0,0 +1,51 @@
(***********************************************************************)
(* *)
(* Caml Special Light *)
(* *)
(* Damien Doligez and Francois Rouaix, INRIA Rocquencourt *)
(* Ported to Caml Special Light by John Malecki and Xavier Leroy *)
(* *)
(* Copyright 1995 Institut National de Recherche en Informatique et *)
(* Automatique. Distributed only by permission. *)
(* *)
(***********************************************************************)
(* $Id$ *)
(* Run-time library for profiled programs *)
type profiling_counters = (string * (string * int array)) list
let counters = ref ([] : profiling_counters)
exception Bad_profile
let dump_counters () =
begin try
let ic = open_in_bin "cslprof.dump" in
let prevl = (input_value ic : profiling_counters) in
close_in ic;
List.iter2
(fun (curname, (curmodes,curcount)) (prevname, (prevmodes,prevcount)) ->
if curname <> prevname
or curmodes <> prevmodes
or Array.length curcount <> Array.length prevcount
then raise Bad_profile)
!counters prevl;
List.iter2
(fun (curname, (_,curcount)) (prevname, (_,prevcount)) ->
for i = 0 to Array.length curcount - 1 do
curcount.(i) <- curcount.(i) + prevcount.(i)
done)
!counters prevl
with _ -> ()
end;
begin try
let oc = open_out_bin "cslprof.dump" in
output_value oc !counters;
close_out oc
with _ -> ()
end
let _ = at_exit dump_counters

17
tools/profiling.mli Normal file
View File

@ -0,0 +1,17 @@
(***********************************************************************)
(* *)
(* Caml Special Light *)
(* *)
(* Damien Doligez and Francois Rouaix, INRIA Rocquencourt *)
(* Ported to Caml Special Light by John Malecki and Xavier Leroy *)
(* *)
(* Copyright 1995 Institut National de Recherche en Informatique et *)
(* Automatique. Distributed only by permission. *)
(* *)
(***********************************************************************)
(* $Id$ *)
(* Run-time library for profiled programs *)
val counters: (string * (string * int array)) list ref