Skip to content

Commit

Permalink
Fix #485
Browse files Browse the repository at this point in the history
  • Loading branch information
Jeremie Dimino committed Feb 13, 2018
1 parent 473b8d1 commit 61c343b
Show file tree
Hide file tree
Showing 5 changed files with 29 additions and 29 deletions.
10 changes: 3 additions & 7 deletions src/build_interpret.ml
Original file line number Diff line number Diff line change
Expand Up @@ -88,7 +88,7 @@ let static_deps t ~all_targets =
loop (Build.repr t) { rule_deps = Pset.empty; action_deps = Pset.empty }

let lib_deps =
let rec loop : type a b. (a, b) t -> Build.lib_deps option -> Build.lib_deps option
let rec loop : type a b. (a, b) t -> Build.lib_deps -> Build.lib_deps
= fun t acc ->
match t with
| Arr _ -> acc
Expand All @@ -105,17 +105,13 @@ let lib_deps =
| Dyn_paths t -> loop t acc
| Contents _ -> acc
| Lines_of _ -> acc
| Record_lib_deps deps ->
begin match acc with
| None -> Some deps
| Some acc -> Some (Build.merge_lib_deps deps acc)
end
| Record_lib_deps deps -> Build.merge_lib_deps deps acc
| Fail _ -> acc
| If_file_exists (_, state) ->
loop (get_if_file_exists_exn state) acc
| Memo m -> loop m.t acc
in
fun t -> loop (Build.repr t) None
fun t -> loop (Build.repr t) String_map.empty

let targets =
let rec loop : type a b. (a, b) t -> Target.t list -> Target.t list = fun t acc ->
Expand Down
2 changes: 1 addition & 1 deletion src/build_interpret.mli
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,7 @@ val static_deps

val lib_deps
: (_, _) Build.t
-> Build.lib_deps option
-> Build.lib_deps

val targets
: (_, _) Build.t
Expand Down
39 changes: 19 additions & 20 deletions src/build_system.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1165,7 +1165,7 @@ module Ir_set = Set.Make(Internal_rule)

let rules_for_files t paths =
List.filter_map paths ~f:(fun path ->
if Path.is_in_build_dir path then load_dir t ~dir:path;
if Path.is_in_build_dir path then load_dir t ~dir:(Path.parent path);
match Hashtbl.find t.files path with
| None -> None
| Some (File_spec.T { rule; _ }) -> Some rule)
Expand Down Expand Up @@ -1207,29 +1207,28 @@ let all_lib_deps t ~request =
let targets = static_deps_of_request t request in
List.fold_left (rules_for_targets t targets) ~init:Pmap.empty
~f:(fun acc (rule : Internal_rule.t) ->
let lib_deps =
match Build_interpret.lib_deps rule.build with
| None -> Pmap.empty
| Some deps -> Pmap.singleton rule.dir deps in
Pmap.merge acc lib_deps ~f:(fun _ a b ->
match a, b with
| None, None -> None
| Some a, None -> Some a
| None, Some b -> Some b
| Some a, Some b -> Some (Build.merge_lib_deps a b)))
let deps = Build_interpret.lib_deps rule.build in
if String_map.is_empty deps then
acc
else
let deps =
match Pmap.find rule.dir acc with
| None -> deps
| Some deps' -> Build.merge_lib_deps deps deps'
in
Pmap.add acc ~key:rule.dir ~data:deps)

let all_lib_deps_by_context t ~request =
let targets = static_deps_of_request t request in
rules_for_targets t targets
|> List.fold_left ~init:[] ~f:(fun acc (rule : Internal_rule.t) ->
let lib_deps =
match Build_interpret.lib_deps rule.build with
| None -> Pmap.empty
| Some deps -> Pmap.singleton rule.dir deps in
Path.Map.fold lib_deps ~init:acc ~f:(fun ~key:path ~data:lib_deps acc ->
match Path.extract_build_context path with
let rules = rules_for_targets t targets in
List.fold_left rules ~init:[] ~f:(fun acc (rule : Internal_rule.t) ->
let deps = Build_interpret.lib_deps rule.build in
if String_map.is_empty deps then
acc
else
match Path.extract_build_context rule.dir with
| None -> acc
| Some (context, _) -> (context, lib_deps) :: acc))
| Some (context, _) -> (context, deps) :: acc)
|> String_map.of_alist_multi
|> String_map.map ~f:(function
| [] -> String_map.empty
Expand Down
3 changes: 2 additions & 1 deletion src/super_context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -303,7 +303,8 @@ module Libs = struct
in
let vrequires = vrequires t ~dir ~item in
add_rule t
(Build.record_lib_deps ~kind:dep_kind (List.map virtual_deps ~f:Lib_dep.direct)
(Build.record_lib_deps ~kind:dep_kind
(List.map virtual_deps ~f:Lib_dep.direct)
>>>
Build.fanout
(closure t ~scope ~dep_kind libraries)
Expand Down
4 changes: 4 additions & 0 deletions test/blackbox-tests/test-cases/findlib/run.t
Original file line number Diff line number Diff line change
@@ -1 +1,5 @@
$ $JBUILDER external-lib-deps --root . -j1 --display quiet @install
These are the external library dependencies in the default context:
- a
- b
- c

0 comments on commit 61c343b

Please sign in to comment.