Skip to content

Commit

Permalink
Move find_implementations and resolve to own functions
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 7, 2019
1 parent 751fae7 commit 692c6be
Showing 1 changed file with 25 additions and 18 deletions.
43 changes: 25 additions & 18 deletions src/scope.ml
Original file line number Diff line number Diff line change
Expand Up @@ -56,6 +56,27 @@ module DB = struct
(Dune_project.Name.Map.keys t.by_name)
]

let resolve by_name_cell public_libs name : Lib.DB.Resolve_result.t =
match Lib_name.Map.find public_libs name with
| None -> Not_found
| Some project ->
let scope =
Dune_project.name project
|> Dune_project.Name.Map.find_exn !by_name_cell
in
Redirect (Some scope.db, name)

let find_implementations by_name_cell public_libs virt =
Lib_name.Map.values public_libs
|> List.map ~f:(fun project ->
let scope =
Dune_project.name project
|> Dune_project.Name.Map.find_exn !by_name_cell
in
Lib.DB.find_implementations scope.db virt)
|> List.fold_left ~init:Variant.Map.empty ~f:(fun acc impls ->
Variant.Map.union acc impls ~f:(fun _ a b -> Some (a @ b)))

let create ~projects ~context ~installed_libs ~has_native ~ext_lib ~ext_obj
internal_libs =
let projects_by_name =
Expand Down Expand Up @@ -104,26 +125,12 @@ module DB = struct
(Loc.to_file_colon_line loc1)
(Loc.to_file_colon_line loc2)
in
let resolve = resolve by_name_cell public_libs in
let find_implementations = find_implementations by_name_cell public_libs in
Lib.DB.create ()
~parent:installed_libs
~resolve:(fun name ->
match Lib_name.Map.find public_libs name with
| None -> Not_found
| Some project ->
let scope =
Dune_project.Name.Map.find_exn !by_name_cell
(Dune_project.name project) in
Redirect (Some scope.db, name))
~find_implementations:(fun virt ->
Lib_name.Map.values public_libs
|> List.map ~f:(fun project ->
let scope =
Dune_project.Name.Map.find_exn !by_name_cell
(Dune_project.name project)
in
Lib.DB.find_implementations scope.db virt)
|> List.fold_left ~init:Variant.Map.empty ~f:(fun acc impls -> Variant.Map.union acc impls ~f:(fun _ a b -> Some (a@b)))
)
~resolve
~find_implementations
~all:(fun () -> Lib_name.Map.keys public_libs)
in
let by_name =
Expand Down

0 comments on commit 692c6be

Please sign in to comment.