Skip to content

Commit

Permalink
feat: support libraries with the same name in multiple contexts (#10307)
Browse files Browse the repository at this point in the history
* feat: support libraries with the same name in multiple contexts


Signed-off-by: Javier Chávarri <[email protected]>
Signed-off-by: Antonio Nuno Monteiro <[email protected]>
Signed-off-by: Rudi Grinberg <[email protected]>
Co-authored-by: Javier Chávarri <[email protected]>
Co-authored-by: Rudi Grinberg <[email protected]>
  • Loading branch information
3 people authored Apr 1, 2024
1 parent 4ebcce3 commit 73c224d
Show file tree
Hide file tree
Showing 33 changed files with 781 additions and 265 deletions.
3 changes: 2 additions & 1 deletion bin/describe/describe_workspace.ml
Original file line number Diff line number Diff line change
Expand Up @@ -451,7 +451,8 @@ module Crawl = struct
let* modules_, obj_dir_ =
Dir_contents.get sctx ~dir:(Path.as_in_build_dir_exn src_dir)
>>= Dir_contents.ocaml
>>| Ml_sources.modules_and_obj_dir ~for_:(Library name)
>>| Ml_sources.modules_and_obj_dir
~for_:(Library (Lib_info.lib_id info |> Lib_id.to_local_exn))
in
let* pp_map =
let+ version =
Expand Down
4 changes: 4 additions & 0 deletions doc/changes/10307.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
- allow libraries with the same `(name ..)` in projects as long as they don't
conflict during resolution (via `enabled_if`). (#10307, @anmonteiro,
@jchavarri)

4 changes: 2 additions & 2 deletions src/dune_rules/dir_contents.ml
Original file line number Diff line number Diff line change
Expand Up @@ -456,8 +456,8 @@ let modules_of_local_lib sctx lib =
let dir = Lib_info.src_dir info in
get sctx ~dir
in
let name = Lib_info.name info in
ocaml t >>| Ml_sources.modules ~for_:(Library name)
ocaml t
>>| Ml_sources.modules ~for_:(Library (Lib_info.lib_id info |> Lib_id.to_local_exn))
;;

let modules_of_lib sctx lib =
Expand Down
2 changes: 2 additions & 0 deletions src/dune_rules/dune_package.ml
Original file line number Diff line number Diff line change
Expand Up @@ -231,6 +231,7 @@ module Lib = struct
let entry_modules = Modules.entry_modules modules |> List.map ~f:Module.name in
let info : Path.t Lib_info.t =
let src_dir = Obj_dir.dir obj_dir in
let lib_id = Lib_id.External (loc, name) in
let enabled = Memo.return Lib_info.Enabled_status.Normal in
let status =
match Lib_name.analyze name with
Expand All @@ -255,6 +256,7 @@ module Lib = struct
~path_kind:External
~loc
~name
~lib_id
~kind
~status
~src_dir
Expand Down
1 change: 1 addition & 0 deletions src/dune_rules/dune_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -24,6 +24,7 @@ module Expander = Expander
module Lib = Lib
module Lib_flags = Lib_flags
module Lib_info = Lib_info
module Lib_id = Lib_id
module Modules = Modules
module Module_compilation = Module_compilation
module Exe_rules = Exe_rules
Expand Down
5 changes: 4 additions & 1 deletion src/dune_rules/findlib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -206,10 +206,13 @@ let to_dune_library (t : Findlib.Package.t) ~dir_contents ~ext_lib ~external_loc
| Error e -> Error e))))
in
let modules = Lib_info.Source.External None in
let name = t.name in
let lib_id = Lib_id.External (loc, name) in
Lib_info.create
~loc
~path_kind:External
~name:t.name
~name
~lib_id
~kind
~status
~src_dir
Expand Down
6 changes: 5 additions & 1 deletion src/dune_rules/gen_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -111,7 +111,11 @@ end = struct
let+ () = Toplevel.Stanza.setup ~sctx ~dir ~toplevel in
empty_none
| Library.T lib ->
let* enabled_if = Lib.DB.available (Scope.libs scope) (Library.best_name lib) in
let* enabled_if =
Lib.DB.available_by_lib_id
(Scope.libs scope)
(Local (Library.to_lib_id ~src_dir lib))
in
if_available_buildable
~loc:lib.buildable.loc
(fun () -> Lib_rules.rules lib ~sctx ~dir ~scope ~dir_contents ~expander)
Expand Down
23 changes: 19 additions & 4 deletions src/dune_rules/install_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -88,7 +88,10 @@ end = struct
let lib_files ~dir_contents ~dir ~lib_config lib =
let+ modules =
let+ ml_sources = Dir_contents.ocaml dir_contents in
Some (Ml_sources.modules ml_sources ~for_:(Library (Lib_info.name lib)))
Some
(Ml_sources.modules
ml_sources
~for_:(Library (Lib_info.lib_id lib |> Lib_id.to_local_exn)))
and+ foreign_archives =
match Lib_info.virtual_ lib with
| None -> Memo.return (Mode.Map.Multi.to_flat_list @@ Lib_info.foreign_archives lib)
Expand Down Expand Up @@ -181,7 +184,9 @@ end = struct
let lib_name = Library.best_name lib in
let* installable_modules =
let+ modules =
Dir_contents.ocaml dir_contents >>| Ml_sources.modules ~for_:(Library lib_name)
Dir_contents.ocaml dir_contents
>>| Ml_sources.modules
~for_:(Library (Lib_info.lib_id info |> Lib_id.to_local_exn))
and+ impl = Virtual_rules.impl sctx ~lib ~scope in
Vimpl.impl_modules impl modules |> Modules.split_by_lib
in
Expand Down Expand Up @@ -338,7 +343,15 @@ end = struct
if enabled_if
then
if lib.optional
then Lib.DB.available (Scope.libs scope) (Library.best_name lib)
then (
let src_dir =
Expander.dir expander
|> Path.build
|> Path.drop_optional_build_context_src_exn
in
Lib.DB.available_by_lib_id
(Scope.libs scope)
(Local (Library.to_lib_id ~src_dir lib)))
else Memo.return true
else Memo.return false
| Documentation.T _ -> Memo.return true
Expand Down Expand Up @@ -652,7 +665,9 @@ end = struct
|> Foreign.Sources.object_files ~dir ~ext_obj
|> List.map ~f:Path.build
and* modules =
Dir_contents.ocaml dir_contents >>| Ml_sources.modules ~for_:(Library name)
Dir_contents.ocaml dir_contents
>>| Ml_sources.modules
~for_:(Library (Lib_info.lib_id info |> Lib_id.to_local_exn))
and* melange_runtime_deps = file_deps (Lib_info.melange_runtime_deps info)
and* public_headers = file_deps (Lib_info.public_headers info) in
let+ dune_lib =
Expand Down
Loading

0 comments on commit 73c224d

Please sign in to comment.