Single entry point to print deps.

master
alainfrisch 2016-02-01 18:55:47 +01:00
parent 4aea2c1903
commit 2261e4413d
1 changed files with 39 additions and 40 deletions

View File

@ -310,42 +310,43 @@ let read_parse_and_extract parse_function extract_function def magic
end end
let print_ml_dependencies source_file extracted_deps = let print_ml_dependencies source_file extracted_deps =
if !raw_dependencies then begin let basename = Filename.chop_extension source_file in
print_raw_dependencies source_file extracted_deps let byte_targets = [ basename ^ ".cmo" ] in
end else begin let native_targets =
let basename = Filename.chop_extension source_file in if !all_dependencies
let byte_targets = [ basename ^ ".cmo" ] in then [ basename ^ ".cmx"; basename ^ ".o" ]
let native_targets = else [ basename ^ ".cmx" ] in
if !all_dependencies let init_deps = if !all_dependencies then [source_file] else [] in
then [ basename ^ ".cmx"; basename ^ ".o" ] let cmi_name = basename ^ ".cmi" in
else [ basename ^ ".cmx" ] in let init_deps, extra_targets =
let init_deps = if !all_dependencies then [source_file] else [] in if List.exists (fun ext -> Sys.file_exists (basename ^ ext))
let cmi_name = basename ^ ".cmi" in !mli_synonyms
let init_deps, extra_targets = then (cmi_name :: init_deps, cmi_name :: init_deps), []
if List.exists (fun ext -> Sys.file_exists (basename ^ ext)) else (init_deps, init_deps),
!mli_synonyms (if !all_dependencies then [cmi_name] else [])
then (cmi_name :: init_deps, cmi_name :: init_deps), [] in
else (init_deps, init_deps), let (byt_deps, native_deps) =
(if !all_dependencies then [cmi_name] else []) Depend.StringSet.fold (find_dependency ML)
in extracted_deps init_deps in
let (byt_deps, native_deps) = if not !native_only then
Depend.StringSet.fold (find_dependency ML) print_dependencies (byte_targets @ extra_targets) byt_deps;
extracted_deps init_deps in print_dependencies (native_targets @ extra_targets) native_deps
if not !native_only then
print_dependencies (byte_targets @ extra_targets) byt_deps;
print_dependencies (native_targets @ extra_targets) native_deps;
end
let print_mli_dependencies source_file extracted_deps = let print_mli_dependencies source_file extracted_deps =
let basename = Filename.chop_extension source_file in
let (byt_deps, _opt_deps) =
Depend.StringSet.fold (find_dependency MLI)
extracted_deps ([], []) in
print_dependencies [basename ^ ".cmi"] byt_deps
let print_dependencies (source_file, kind, extracted_deps) =
if !raw_dependencies then begin if !raw_dependencies then begin
print_raw_dependencies source_file extracted_deps print_raw_dependencies source_file extracted_deps
end else begin end else
let basename = Filename.chop_extension source_file in match kind with
let (byt_deps, _opt_deps) = | ML -> print_ml_dependencies source_file extracted_deps
Depend.StringSet.fold (find_dependency MLI) | MLI -> print_mli_dependencies source_file extracted_deps
extracted_deps ([], []) in
print_dependencies [basename ^ ".cmi"] byt_deps
end
let ml_file_dependencies source_file = let ml_file_dependencies source_file =
let parse_use_file_as_impl lexbuf = let parse_use_file_as_impl lexbuf =
@ -360,20 +361,18 @@ let ml_file_dependencies source_file =
read_parse_and_extract parse_use_file_as_impl Depend.add_implementation () read_parse_and_extract parse_use_file_as_impl Depend.add_implementation ()
Config.ast_impl_magic_number source_file Config.ast_impl_magic_number source_file
in in
if !sort_files then let r = (source_file, ML, extracted_deps) in
files := (source_file, ML, extracted_deps) :: !files if !sort_files then files := r :: !files
else else print_dependencies r
print_ml_dependencies source_file extracted_deps
let mli_file_dependencies source_file = let mli_file_dependencies source_file =
let (extracted_deps, ()) = let (extracted_deps, ()) =
read_parse_and_extract Parse.interface Depend.add_signature () read_parse_and_extract Parse.interface Depend.add_signature ()
Config.ast_intf_magic_number source_file Config.ast_intf_magic_number source_file
in in
if !sort_files then let r = (source_file, MLI, extracted_deps) in
files := (source_file, MLI, extracted_deps) :: !files if !sort_files then files := r :: !files
else else print_dependencies r
print_mli_dependencies source_file extracted_deps
let process_file_as process_fun def source_file = let process_file_as process_fun def source_file =
Compenv.readenv ppf (Before_compile source_file); Compenv.readenv ppf (Before_compile source_file);