git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@6415 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Damien Doligez 2004-06-16 16:58:46 +00:00
parent 477942df0e
commit fae0bc9d9b
4 changed files with 13 additions and 11 deletions

View File

@ -23,7 +23,9 @@ let preprocess sourcefile =
None -> sourcefile
| Some pp ->
let tmpfile = Filename.temp_file "camlpp" "" in
let comm = Printf.sprintf "%s %s > %s" pp sourcefile tmpfile in
let comm = Printf.sprintf "%s %s > %s"
pp (Filename.quote sourcefile) tmpfile
in
if Ccomp.command comm <> 0 then begin
Misc.remove_file tmpfile;
raise Error;

View File

@ -78,4 +78,4 @@ let catch_break on =
(* OCaml version string, must be in the format described in sys.mli. *)
let ocaml_version = "3.07+21 (2004-06-14)";;
let ocaml_version = "3.07+22 (2004-06-16)";;

View File

@ -22,7 +22,7 @@ open Misc
open Parsetree
(* User programs must not use identifiers that start with these prefixes. *)
let idprefix = "__ocaml_prof";;
let idprefix = "__ocaml_prof_";;
let modprefix = "OCAML__prof_";;
@ -88,10 +88,10 @@ let add_incr_counter modul (kind,pos) =
| Close -> fprintf !outchan ")";
| Open ->
fprintf !outchan
"(%sArray.set %s_cnt_%s %d \
(%sPervasives.succ (%sArray.get %s_cnt_%s %d)); "
modprefix idprefix modul !prof_counter
modprefix modprefix idprefix modul !prof_counter;
"(%sArray.set %s_cnt %d \
(%sPervasives.succ (%sArray.get %s_cnt %d)); "
modprefix idprefix !prof_counter
modprefix modprefix idprefix !prof_counter;
incr prof_counter;
;;
@ -132,12 +132,12 @@ let init_rewrite modes mod_name =
if !instr_mode then begin
fprintf !outchan "module %sArray = Array;; " modprefix;
fprintf !outchan "module %sPervasives = Pervasives;; " modprefix;
fprintf !outchan "let %s_cnt_%s = Array.create 0000000" idprefix mod_name;
fprintf !outchan "let %s_cnt = Array.create 0000000" idprefix;
pos_len := pos_out !outchan;
fprintf !outchan
" 0;; Profiling.counters := \
(\"%s\", (\"%s\", %s_cnt_%s)) :: !Profiling.counters;; "
mod_name modes idprefix mod_name
(\"%s\", (\"%s\", %s_cnt)) :: !Profiling.counters;; "
mod_name modes idprefix;
end
let final_rewrite add_function =

View File

@ -25,7 +25,7 @@ let command cmdline =
let run_command cmdline = ignore(command cmdline)
(* Build @responsefile to work around Windows limitations on
command-length line *)
command-line length *)
let build_diversion lst =
let (responsefile, oc) = Filename.open_temp_file "camlresp" "" in
List.iter