Skip to content

Commit

Permalink
Use a map based on library's rather than names for vlib status
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <rudi.grinberg@gmail.com>
  • Loading branch information
rgrinberg committed Mar 25, 2019
1 parent 50439bc commit bebc548
Showing 1 changed file with 18 additions and 16 deletions.
34 changes: 18 additions & 16 deletions src/lib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -704,27 +704,29 @@ let rec find_implementation_for db lib ~variants =
(* Update the variant status map according to `lib` which is being added to the
closure. *)
let handle_vlibs lib virtual_status =
match lib.info.virtual_, lib.info.implements with
match lib.info.virtual_, lib.implements with
| Some _, Some _ -> assert false
| None, None -> ()
| None, None -> Ok ()
| Some _, None ->
(* Virtual library: add it in the map if it doesn't exist yet. *)
begin match Lib_name.Map.find !virtual_status lib.name with
begin match Map.find !virtual_status lib with
| None ->
virtual_status :=
Lib_name.Map.add !virtual_status lib.name Vlib_status.No_implementation;
Map.add !virtual_status lib Vlib_status.No_implementation;
| Some _ -> ()
end
| None, Some (_, implements) ->
end;
Ok ()
| None, Some implements ->
(* Implementation: find the corresponding virtual library *)
let+ implements = implements in
let impl =
match Lib_name.Map.find !virtual_status implements with
match Map.find !virtual_status implements with
| Some No_implementation
| None -> Vlib_status.Implemented_by lib
| Some (Implemented_by x) -> Too_many_impl [lib; x]
| Some (Too_many_impl lst) -> Too_many_impl (lib :: lst)
in
virtual_status := Lib_name.Map.add !virtual_status implements impl
virtual_status := Map.add !virtual_status implements impl

let rec instantiate db name (info : Lib_info.t) ~stack ~hidden =
let id, stack =
Expand Down Expand Up @@ -1085,11 +1087,11 @@ and closure_with_overlap_checks db ts ~stack:orig_stack ~linking ~variants =
resolve_dep (Option.value_exn db) name
~allow_private_deps:true ~loc ~stack:Dep_stack.empty
in
let visited = ref Lib_name.Map.empty in
let virtual_status = ref Lib_name.Map.empty in
let visited = ref Map.empty in
let virtual_status = ref Map.empty in
let res = ref [] in
let rec loop t ~stack =
match Lib_name.Map.find !visited t.name with
match Map.find !visited t with
| Some (t', stack') ->
if t = t' then
Ok ()
Expand All @@ -1100,7 +1102,7 @@ and closure_with_overlap_checks db ts ~stack:orig_stack ~linking ~variants =
; lib2 = (t.info, req_by stack )
}))
| None ->
visited := Lib_name.Map.add !visited t.name (t, stack);
visited := Map.add !visited t (t, stack);
let* () =
match db with
| None -> Ok ()
Expand All @@ -1121,7 +1123,7 @@ and closure_with_overlap_checks db ts ~stack:orig_stack ~linking ~variants =
in
let* new_stack = Dep_stack.push stack (to_id t) in
let* deps = t.requires in
handle_vlibs t virtual_status;
handle_vlibs t virtual_status >>= fun () ->
let+ () = Result.List.iter deps ~f:(loop ~stack:new_stack) in
res := (t, stack) :: !res
in
Expand All @@ -1133,14 +1135,14 @@ and closure_with_overlap_checks db ts ~stack:orig_stack ~linking ~variants =
else begin
(* Virtual libraries: find implementations according to variants. *)
let* (lst, with_default_impl) =
Lib_name.Map.foldi !virtual_status ~init:(Ok ([], []))
~f:(fun name status acc ->
Map.foldi !virtual_status ~init:(Ok ([], []))
~f:(fun lib status acc ->
match status with
| Implemented_by _
| Too_many_impl _ -> acc
| No_implementation ->
let* (lst, def) = acc in
let (lib, _) = Lib_name.Map.find_exn !visited name in
let (lib, _) = Map.find_exn !visited lib in
let* impl =
find_implementation_for (Option.value_exn db) lib ~variants in
match impl, lib.default_implementation with
Expand Down

0 comments on commit bebc548

Please sign in to comment.