Skip to content

Commit

Permalink
show proper errors on public libs collision
Browse files Browse the repository at this point in the history
Signed-off-by: Javier Chávarri <javier.chavarri@gmail.com>
  • Loading branch information
jchavarri committed Mar 15, 2024
1 parent 803a6fe commit b970f3c
Show file tree
Hide file tree
Showing 9 changed files with 98 additions and 22 deletions.
45 changes: 26 additions & 19 deletions src/dune_rules/gen_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -111,25 +111,32 @@ end = struct
let+ () = Toplevel.Stanza.setup ~sctx ~dir ~toplevel in
empty_none
| Library.T lib ->
let* lib_info =
let* ocaml =
let ctx = Super_context.context sctx in
Context.ocaml ctx
in
let lib_config = ocaml.lib_config in
Memo.return (Library.to_lib_info lib ~dir ~lib_config)
in
let* enabled_in_context =
let* enabled = Lib_info.enabled lib_info in
match enabled with
| Disabled_because_of_enabled_if -> Memo.return false
| Normal | Optional -> Memo.return true
in
let* available = Lib.DB.available (Scope.libs scope) (Library.best_name lib) in
if_available_buildable
~loc:lib.buildable.loc
(fun () -> Lib_rules.rules lib ~sctx ~dir ~scope ~dir_contents ~expander)
(enabled_in_context && available)
let db = Scope.libs scope in
(* This check reveals conflicts between the private names of public libraries,
otherwise the user will see duplicated rules for their cmxs *)
let* res = Lib.DB.find_invalid db (Library.private_name lib) in
(match res with
| Some err -> User_error.raise [ User_message.pp err ]
| None ->
let* lib_info =
let* ocaml =
let ctx = Super_context.context sctx in
Context.ocaml ctx
in
let lib_config = ocaml.lib_config in
Memo.return (Library.to_lib_info lib ~dir ~lib_config)
in
let* enabled_in_context =
let* enabled = Lib_info.enabled lib_info in
match enabled with
| Disabled_because_of_enabled_if -> Memo.return false
| Normal | Optional -> Memo.return true
in
let* available = Lib.DB.available (Scope.libs scope) (Library.best_name lib) in
if_available_buildable
~loc:lib.buildable.loc
(fun () -> Lib_rules.rules lib ~sctx ~dir ~scope ~dir_contents ~expander)
(enabled_in_context && available))
| Foreign.Library.T lib ->
Expander.eval_blang expander lib.enabled_if
>>= if_available (fun () ->
Expand Down
8 changes: 8 additions & 0 deletions src/dune_rules/lib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1941,6 +1941,14 @@ module DB = struct
| Ignore | Not_found | Invalid _ | Hidden _ -> None
;;

let find_invalid t name =
let open Memo.O in
Resolve_names.find_internal t name
>>| function
| Invalid err -> Some err
| Found _ | Ignore | Not_found | Hidden _ -> None
;;

let find_even_when_hidden t name =
let open Memo.O in
Resolve_names.find_internal t name
Expand Down
1 change: 1 addition & 0 deletions src/dune_rules/lib.mli
Original file line number Diff line number Diff line change
Expand Up @@ -122,6 +122,7 @@ module DB : sig
-> t

val find : t -> Lib_name.t -> lib option Memo.t
val find_invalid : t -> Lib_name.t -> User_message.t option Memo.t
val find_even_when_hidden : t -> Lib_name.t -> lib option Memo.t
val available : t -> Lib_name.t -> bool Memo.t

Expand Down
1 change: 1 addition & 0 deletions src/dune_rules/stanzas/library.ml
Original file line number Diff line number Diff line change
Expand Up @@ -366,6 +366,7 @@ let best_name t =
| Public p -> snd p.name
;;

let private_name t = Lib_name.of_local t.name
let is_virtual t = Option.is_some t.virtual_modules
let is_impl t = Option.is_some t.implements

Expand Down
1 change: 1 addition & 0 deletions src/dune_rules/stanzas/library.mli
Original file line number Diff line number Diff line change
Expand Up @@ -72,6 +72,7 @@ val foreign_lib_files
val archive : t -> dir:Path.Build.t -> ext:string -> Path.Build.t

val best_name : t -> Lib_name.t
val private_name : t -> Lib_name.t
val is_virtual : t -> bool
val is_impl : t -> bool
val obj_dir : dir:Path.Build.t -> t -> Path.Build.t Obj_dir.t
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,13 @@ the same folder.
Without any consumers of the libraries
$ dune build
Error:
File "dune", line 1, characters 0-21:
Error: A library with name "foo" is defined in two folders: _build/default
and _build/default. Either change one of the names, or enable them
conditionally using the 'enabled_if' field.
[1]
With some consumer of the library
Expand All @@ -33,6 +40,12 @@ With some consumer of the library
> EOF
$ dune build
Error:
File "dune", line 1, characters 0-21:
Error: A library with name "foo" is defined in two folders: _build/default
and _build/default. Either change one of the names, or enable them
conditionally using the 'enabled_if' field.
File "dune", line 3, characters 0-21:
3 | (library
4 | (name foo))
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,14 @@ different folders.
Without any consumers of the libraries
$ dune build
Error:
File "b/dune", line 1, characters 0-21:
Error: A library with name "foo" is defined in two folders: _build/default/a
and _build/default/b. Either change one of the names, or enable them
conditionally using the 'enabled_if' field.
-> required by alias default
[1]
With some consumer of the library
Expand All @@ -34,6 +42,13 @@ With some consumer of the library
> EOF
$ dune build
Error:
File "b/dune", line 1, characters 0-21:
Error: A library with name "foo" is defined in two folders: _build/default/a
and _build/default/b. Either change one of the names, or enable them
conditionally using the 'enabled_if' field.
-> required by alias default
File "b/dune", line 1, characters 0-21:
1 | (library
2 | (name foo))
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -19,9 +19,12 @@ the same folder.
Without any consumers of the libraries
$ dune build
Error: Multiple rules generated for _build/default/foo.cmxs:
- dune:4
- dune:1
Error:
File "dune", line 1, characters 0-44:
Error: A library with name "foo" is defined in two folders: _build/default
and _build/default. Either change one of the names, or enable them
conditionally using the 'enabled_if' field.
[1]
With some consumer
Expand All @@ -43,6 +46,12 @@ With some consumer
> EOF
$ dune build
Error:
File "dune", line 1, characters 0-44:
Error: A library with name "foo" is defined in two folders: _build/default
and _build/default. Either change one of the names, or enable them
conditionally using the 'enabled_if' field.
File "dune", line 1, characters 0-0:
Error: Module "Main" is used in several stanzas:
- dune:1
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -24,6 +24,17 @@ different folders.
Without any consumers of the libraries
$ dune build
Error:
File "b/dune", line 1, characters 0-44:
Error: A library with name "foo" is defined in two folders: _build/default/a
and _build/default/b. Either change one of the names, or enable them
conditionally using the 'enabled_if' field.
-> required by _build/install/default/lib/bar/foo/foo.a
-> required by _build/default/bar.install
-> required by alias all
-> required by alias default
[1]
With some consumer
Expand All @@ -38,6 +49,16 @@ With some consumer
> EOF
$ dune build
Error:
File "b/dune", line 1, characters 0-44:
Error: A library with name "foo" is defined in two folders: _build/default/a
and _build/default/b. Either change one of the names, or enable them
conditionally using the 'enabled_if' field.
-> required by _build/install/default/lib/bar/foo/foo.a
-> required by _build/default/bar.install
-> required by alias all
-> required by alias default
File "b/dune", line 1, characters 0-44:
1 | (library
2 | (name foo)
Expand Down

0 comments on commit b970f3c

Please sign in to comment.