use Timings.source_provenance in more places

master
Thomas Refis 2015-12-31 10:57:42 +00:00
parent ca789ede10
commit cae2a7e53c
7 changed files with 29 additions and 29 deletions

View File

@ -100,7 +100,7 @@ let compile_genfuns ppf f =
| _ -> ())
(Cmmgen.generic_functions true [Compilenv.current_unit_infos ()])
let compile_unit ~sourcefile asm_filename keep_asm obj_filename gen =
let compile_unit ~source_provenance asm_filename keep_asm obj_filename gen =
let create_asm = keep_asm || not !Emitaux.binary_backend_available in
Emitaux.create_asm_file := create_asm;
try
@ -114,7 +114,7 @@ let compile_unit ~sourcefile asm_filename keep_asm obj_filename gen =
raise exn
end;
let assemble_result =
Timings.(time (Assemble sourcefile))
Timings.(time (Assemble source_provenance))
(Proc.assemble_file asm_filename) obj_filename
in
if assemble_result <> 0
@ -124,12 +124,12 @@ let compile_unit ~sourcefile asm_filename keep_asm obj_filename gen =
remove_file obj_filename;
raise exn
let gen_implementation ?toplevel ~sourcefile ppf (size, lam) =
let gen_implementation ?toplevel ~source_provenance ppf (size, lam) =
Emit.begin_assembly ();
Timings.(time (Clambda sourcefile)) (Closure.intro size) lam
Timings.(time (Clambda source_provenance)) (Closure.intro size) lam
++ clambda_dump_if ppf
++ Timings.(time (Cmm sourcefile)) (Cmmgen.compunit size)
++ Timings.(time (Compile_phrases sourcefile))
++ Timings.(time (Cmm source_provenance)) (Cmmgen.compunit size)
++ Timings.(time (Compile_phrases source_provenance))
(List.iter (compile_phrase ppf))
++ (fun () -> ());
(match toplevel with None -> () | Some f -> compile_genfuns ppf f);
@ -147,14 +147,14 @@ let gen_implementation ?toplevel ~sourcefile ppf (size, lam) =
);
Emit.end_assembly ()
let compile_implementation ?toplevel ~sourcefile prefixname ppf (size, lam) =
let compile_implementation ?toplevel ~source_provenance prefixname ppf (size, lam) =
let asmfile =
if !keep_asm_file || !Emitaux.binary_backend_available
then prefixname ^ ext_asm
else Filename.temp_file "camlasm" ext_asm
in
compile_unit sourcefile asmfile !keep_asm_file (prefixname ^ ext_obj)
(fun () -> gen_implementation ?toplevel ~sourcefile ppf (size, lam))
compile_unit ~source_provenance asmfile !keep_asm_file (prefixname ^ ext_obj)
(fun () -> gen_implementation ?toplevel ~source_provenance ppf (size, lam))
(* Error report *)

View File

@ -14,7 +14,7 @@
val compile_implementation :
?toplevel:(string -> bool) ->
sourcefile:string ->
source_provenance:Timings.source_provenance ->
string -> Format.formatter -> int * Lambda.lambda -> unit
val compile_phrase :
Format.formatter -> Cmm.phrase -> unit
@ -25,6 +25,6 @@ val report_error: Format.formatter -> error -> unit
val compile_unit:
sourcefile:string ->
source_provenance:Timings.source_provenance ->
string(*asm file*) -> bool(*keep asm*) ->
string(*obj file*) -> (unit -> unit) -> unit

View File

@ -268,7 +268,7 @@ let link_shared ppf objfiles output_name =
then output_name ^ ".startup" ^ ext_asm
else Filename.temp_file "camlstartup" ext_asm in
let startup_obj = output_name ^ ".startup" ^ ext_obj in
Asmgen.compile_unit ~sourcefile:"startup"
Asmgen.compile_unit ~source_provenance:Timings.Startup
startup !Clflags.keep_startup_file startup_obj
(fun () ->
make_shared_startup_file ppf
@ -327,7 +327,7 @@ let link ppf objfiles output_name =
then output_name ^ ".startup" ^ ext_asm
else Filename.temp_file "camlstartup" ext_asm in
let startup_obj = Filename.temp_file "camlstartup" ext_obj in
Asmgen.compile_unit ~sourcefile:"startup"
Asmgen.compile_unit ~source_provenance:Timings.Startup
startup !Clflags.keep_startup_file startup_obj
(fun () -> make_startup_file ppf units_tolink);
Misc.try_finally

View File

@ -91,7 +91,7 @@ let make_package_object ppf members targetobj targetname coercion =
| PM_intf -> None
| PM_impl _ -> Some(Ident.create_persistent m.pm_name))
members in
Asmgen.compile_implementation ~sourcefile:"pack"
Asmgen.compile_implementation ~source_provenance:(Timings.Pack targetname)
(chop_extension_if_any objtemp) ppf
(Translmod.transl_store_package
components (Ident.create_persistent targetname) coercion);

View File

@ -59,12 +59,12 @@ let (++) x f = f x
let (+++) (x, y) f = (x, f y)
let implementation ppf sourcefile outputprefix =
let source_provenance = Timings.File sourcefile in
Compmisc.init_path true;
let modulename = module_of_filename ppf sourcefile outputprefix in
Env.set_unit_name modulename;
let env = Compmisc.initial_env() in
Compilenv.reset ~source_provenance:(Timings.File sourcefile)
?packname:!Clflags.for_package modulename;
Compilenv.reset ~source_provenance ?packname:!Clflags.for_package modulename;
let cmxfile = outputprefix ^ ".cmx" in
let objfile = outputprefix ^ ext_obj in
let comp ast =
@ -86,7 +86,7 @@ let implementation ppf sourcefile outputprefix =
(fun (size, lambda) ->
(size, Simplif.simplify_lambda lambda)
+++ print_if ppf Clflags.dump_lambda Printlambda.lambda
++ Asmgen.compile_implementation ~sourcefile outputprefix ppf;
++ Asmgen.compile_implementation ~source_provenance outputprefix ppf;
Compilenv.save_unit_info cmxfile)
end;
Warnings.check_fatal ();

View File

@ -25,10 +25,10 @@ type compiler_pass =
| Typing of file
| Transl of file
| Generate of file
| Assemble of file
| Clambda of file
| Cmm of file
| Compile_phrases of file
| Assemble of source_provenance
| Clambda of source_provenance
| Cmm of source_provenance
| Compile_phrases of source_provenance
| Selection of source_provenance
| Comballoc of source_provenance
| CSE of source_provenance
@ -108,10 +108,10 @@ let pass_name = function
| Typing file -> Printf.sprintf "typing(%s)" file
| Transl file -> Printf.sprintf "transl(%s)" file
| Generate file -> Printf.sprintf "generate(%s)" file
| Assemble file -> Printf.sprintf "assemble(%s)" file
| Clambda file -> Printf.sprintf "clambda(%s)" file
| Cmm file -> Printf.sprintf "cmm(%s)" file
| Compile_phrases file -> Printf.sprintf "compile_phrases(%s)" file
| Assemble k -> Printf.sprintf "assemble(%s)" (kind_name k)
| Clambda k -> Printf.sprintf "clambda(%s)" (kind_name k)
| Cmm k -> Printf.sprintf "cmm(%s)" (kind_name k)
| Compile_phrases k -> Printf.sprintf "compile_phrases(%s)" (kind_name k)
| Selection k -> Printf.sprintf "selection(%s)" (kind_name k)
| Comballoc k -> Printf.sprintf "comballoc(%s)" (kind_name k)
| CSE k -> Printf.sprintf "cse(%s)" (kind_name k)

View File

@ -27,10 +27,10 @@ type compiler_pass =
| Typing of file
| Transl of file
| Generate of file
| Assemble of file
| Clambda of file
| Cmm of file
| Compile_phrases of file
| Assemble of source_provenance
| Clambda of source_provenance
| Cmm of source_provenance
| Compile_phrases of source_provenance
| Selection of source_provenance
| Comballoc of source_provenance
| CSE of source_provenance