From c3d7dfb68b13a2bd38df8b17def66905cdbbd0e9 Mon Sep 17 00:00:00 2001 From: Etienne Millon Date: Tue, 3 Apr 2018 19:40:49 +0200 Subject: [PATCH] Build transitive dependencies with ocamldep This uses two different extensions: - `.d` corresponds to the raw `ocamldep` output. - `.all-deps` corresponds to this output, merged with the dependencies of all the interfaces mentioned in the earlier. This also means that `.all-deps` files will contain output from multiple files. --- src/ocamldep.ml | 70 ++++++++++++++----- .../blackbox-tests/test-cases/github660/run.t | 5 +- test/blackbox-tests/test-cases/menhir/run.t | 2 +- 3 files changed, 56 insertions(+), 21 deletions(-) diff --git a/src/ocamldep.ml b/src/ocamldep.ml index b5f6865f081c..79aae4178813 100644 --- a/src/ocamldep.ml +++ b/src/ocamldep.ml @@ -59,7 +59,7 @@ module Dep_graphs = struct end let parse_deps ~dir ~file ~(unit : Module.t) - ~modules ~alias_module ~lib_interface_module lines = + ~modules ~alias_module ~lib_interface_module ~strict lines = let invalid () = die "ocamldep returned unexpected output for %s:\n\ %s" @@ -67,17 +67,19 @@ let parse_deps ~dir ~file ~(unit : Module.t) (String.concat ~sep:"\n" (List.map lines ~f:(sprintf "> %s"))) in - match lines with - | [] | _ :: _ :: _ -> invalid () - | [line] -> + let check line ~colon_pos = + let basename = + String.sub line ~pos:0 ~len:colon_pos + |> Filename.basename + in + if basename <> Path.basename file then invalid () + in + let parse_line line = match String.index line ':' with | None -> invalid () | Some i -> - let basename = - String.sub line ~pos:0 ~len:i - |> Filename.basename - in - if basename <> Path.basename file then invalid (); + if strict then + check line ~colon_pos:i; let deps = String.extract_blank_separated_words (String.sub line ~pos:(i + 1) ~len:(String.length line - (i + 1))) @@ -115,6 +117,8 @@ let parse_deps ~dir ~file ~(unit : Module.t) | Some m -> m :: deps in deps + in + List.concat_map lines ~f:parse_line let rules ~(ml_kind:Ml_kind.t) ~dir ~modules ?(already_used=Module.Name.Set.empty) @@ -124,17 +128,49 @@ let rules ~(ml_kind:Ml_kind.t) ~dir ~modules match Module.file ~dir unit ml_kind with | None -> Build.return [] | Some file -> - let ocamldep_output = Path.extend_basename file ~suffix:".d" in + let ocamldep_output_path file = + Path.extend_basename file ~suffix:".d" + in let context = SC.context sctx in + let all_deps_file = Path.extend_basename file ~suffix:".all-deps" in + let ocamldep_output = ocamldep_output_path file in if not (Module.Name.Set.mem already_used unit.name) then - SC.add_rule sctx - (Build.run ~context (Ok context.ocamldep) - [A "-modules"; Ml_kind.flag ml_kind; Dep file] - ~stdout_to:ocamldep_output); - Build.memoize (Path.to_string ocamldep_output) - (Build.lines_of ocamldep_output + begin + SC.add_rule sctx + ( Build.run ~context (Ok context.ocamldep) + [A "-modules"; Ml_kind.flag ml_kind; Dep file] + ~stdout_to:ocamldep_output + ); + let build_paths lines = + let dependencies = + parse_deps + ~dir ~file ~unit ~modules ~alias_module + ~lib_interface_module ~strict:true lines + in + let mli_d_path m = + Option.map + (Module.file ~dir m Ml_kind.Intf) + ~f:ocamldep_output_path + in + let paths = + [ocamldep_output] + @ List.filter_map dependencies ~f:mli_d_path + in + paths + in + SC.add_rule sctx + ( Build.lines_of ocamldep_output + >>^ build_paths + >>> Build.dyn_paths (Build.arr (fun x -> x)) + >>^ (fun paths -> + Action.with_stdout_to all_deps_file @@ Action.cat paths) + >>> Build.action_dyn ~targets:[all_deps_file] () + ) + end; + Build.memoize (Path.to_string all_deps_file) + (Build.lines_of all_deps_file >>^ parse_deps ~dir ~file ~unit ~modules ~alias_module - ~lib_interface_module)) + ~lib_interface_module ~strict:false)) in let per_module = match alias_module with diff --git a/test/blackbox-tests/test-cases/github660/run.t b/test/blackbox-tests/test-cases/github660/run.t index 6f16f429d89e..5022c54a994e 100644 --- a/test/blackbox-tests/test-cases/github660/run.t +++ b/test/blackbox-tests/test-cases/github660/run.t @@ -3,6 +3,5 @@ hello $ echo 'let x = 1' >> lib_sub.ml $ jbuilder runtest --root . --display quiet -j1 2>&1 | grep -v ocamlopt - File "_none_", line 1: - Error: Files .main.eobjs/main.cmx and .main.eobjs/lib_sub.cmx - make inconsistent assumptions over implementation Lib_sub + main alias runtest + hello diff --git a/test/blackbox-tests/test-cases/menhir/run.t b/test/blackbox-tests/test-cases/menhir/run.t index 35d348a7ab1a..8dc89d999d19 100644 --- a/test/blackbox-tests/test-cases/menhir/run.t +++ b/test/blackbox-tests/test-cases/menhir/run.t @@ -8,10 +8,10 @@ ocamldep src/test_base.ml.d menhir src/test_menhir1.{ml,mli} ocamldep src/test_menhir1.ml.d + ocamldep src/test_base.mli.d ocamldep src/test_menhir1.mli.d ocamlc src/.test.eobjs/test_menhir1.{cmi,cmti} ocamlc src/.test.eobjs/lexer1.{cmi,cmo,cmt} - ocamldep src/test_base.mli.d ocamlc src/.test.eobjs/test_base.{cmi,cmti} ocamlc src/.test.eobjs/lexer2.{cmi,cmo,cmt} ocamlc src/.test.eobjs/test.{cmi,cmo,cmt}