From 86011bc65a53eec5260979babe4795b72b926a7c Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Javier=20Ch=C3=A1varri?= Date: Fri, 1 Mar 2024 10:39:07 +0000 Subject: [PATCH 01/15] lib: allow multiple found items MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Javier Chávarri --- src/dune_rules/lib.ml | 173 ++++++++++++------ src/dune_rules/lib.mli | 4 +- src/dune_rules/scope.ml | 31 ++-- .../deprecated-library-name/features.t | 13 +- .../eif-library-name-collision-same-folder.t | 19 +- .../enabled_if/eif-library-name-collision.t | 93 +++++++++- .../lib-collision-private-same-folder.t | 11 +- .../lib-collision/lib-collision-private.t | 13 +- .../lib-collision-public-same-folder.t | 18 +- .../lib-collision/lib-collision-public.t | 14 +- 10 files changed, 278 insertions(+), 111 deletions(-) diff --git a/src/dune_rules/lib.ml b/src/dune_rules/lib.ml index cf5b4a77bf9..d4e858e4fbb 100644 --- a/src/dune_rules/lib.ml +++ b/src/dune_rules/lib.ml @@ -132,6 +132,18 @@ module Error = struct ] ;; + let duplicated ~loc ~name ~dir_a ~dir_b = + User_error.make + ~loc + [ Pp.textf + "A library with name %S is defined in two folders: %s and %s. Either change \ + one of the names, or enable them conditionally using the 'enabled_if' field." + (Lib_name.to_string name) + (Path.to_string_maybe_quoted dir_a) + (Path.to_string_maybe_quoted dir_b) + ] + ;; + (* diml: it is not very clear what a "default implementation cycle" is *) let default_implementation_cycle cycle = make @@ -406,11 +418,11 @@ type db = and resolve_result = | Not_found - | Found of Lib_info.external_ + | Found of Lib_info.external_ list | Hidden of Lib_info.external_ Hidden.t | Invalid of User_message.t | Ignore - | Redirect_in_the_same_db of (Loc.t * Lib_name.t) + | Redirect_in_the_same_db of (Loc.t * Lib_name.t) list | Redirect of db * (Loc.t * Lib_name.t) let lib_config (t : lib) = t.lib_config @@ -1130,19 +1142,74 @@ end = struct | Hidden h -> Hidden.error h ~loc ~name >>| Option.some ;; + let find_in_parent ~db ~name = + let open Memo.O in + let+ res = + match db.parent with + | None -> Memo.return Status.Not_found + | Some db -> find_internal db name + in + res + ;; + + let to_status ~db ~name = function + | [] -> find_in_parent ~db ~name + | info :: [] -> instantiate db name info ~hidden:None + | a :: b :: _ -> + let loc = Lib_info.loc b in + let dir_a = Lib_info.src_dir a in + let dir_b = Lib_info.src_dir b in + Memo.return (Status.Invalid (Error.duplicated ~loc ~name ~dir_a ~dir_b)) + ;; + let resolve_name db name = let open Memo.O in db.resolve name >>= function | Ignore -> Memo.return Status.Ignore - | Redirect_in_the_same_db (_, name') -> find_internal db name' + | Redirect_in_the_same_db redirects -> + let result = List.map ~f:(fun (_, name') -> find_internal db name') redirects in + let* statuses = + Memo.List.map result ~f:(fun redirect -> + let* r = redirect in + Memo.return r) + in + Memo.return + (List.fold_left statuses ~init:Status.Not_found ~f:(fun acc status -> + match acc, status with + | Status.Found a, Status.Found b -> + let a = info a in + let b = info b in + let loc = Lib_info.loc b in + let dir_a = Lib_info.src_dir a in + let dir_b = Lib_info.src_dir b in + Status.Invalid (Error.duplicated ~loc ~name ~dir_a ~dir_b) + | Invalid _, _ -> acc + | (Found _ as lib), (Hidden _ | Ignore | Not_found | Invalid _) + | (Hidden _ | Ignore | Not_found), (Found _ as lib) -> lib + | (Hidden _ | Ignore | Not_found), (Hidden _ | Ignore | Not_found | Invalid _) + -> acc)) | Redirect (db', (_, name')) -> find_internal db' name' - | Found info -> instantiate db name info ~hidden:None + | Found libs -> + (match libs with + | [] | _ :: [] -> + (* In case we have 0 or 1 results found, convert to [Status.t] directly. + This allows to provide better errors later on, + e.g. `Library "foo" in _build/default is hidden (unsatisfied 'enabled_if') *) + to_status ~db ~name libs + | _ :: _ :: _ -> + (* If there are multiple results found, we optimistically pre-filter to + remove those that are disabled *) + let* filtered_libs = + Memo.List.filter libs ~f:(fun lib -> + let+ enabled = Lib_info.enabled lib in + match enabled with + | Disabled_because_of_enabled_if -> false + | Normal | Optional -> true) + in + to_status ~db ~name filtered_libs) | Invalid e -> Memo.return (Status.Invalid e) - | Not_found -> - (match db.parent with - | None -> Memo.return Status.Not_found - | Some db -> find_internal db name) + | Not_found -> find_in_parent ~db ~name | Hidden { lib = info; reason = hidden; path = _ } -> (match db.parent with | None -> Memo.return Status.Not_found @@ -1768,35 +1835,73 @@ module Compile = struct ;; end +module Local : sig + type t = private lib + + val of_lib : lib -> t option + val of_lib_exn : lib -> t + val to_lib : t -> lib + val obj_dir : t -> Path.Build.t Obj_dir.t + val info : t -> Path.Build.t Lib_info.t + val to_dyn : t -> Dyn.t + val equal : t -> t -> bool + val hash : t -> int + + include Comparable_intf.S with type key := t +end = struct + type nonrec t = t + + let to_lib t = t + let of_lib (t : lib) = Option.some_if (is_local t) t + + let of_lib_exn t = + match of_lib t with + | Some l -> l + | None -> Code_error.raise "Lib.Local.of_lib_exn" [ "l", to_dyn t ] + ;; + + let obj_dir t = Obj_dir.as_local_exn (Lib_info.obj_dir t.info) + let info t = Lib_info.as_local_exn t.info + + module Set = Set + module Map = Map + + let to_dyn = to_dyn + let equal = equal + let hash = hash +end + (* Databases *) module DB = struct module Resolve_result = struct type t = resolve_result = | Not_found - | Found of Lib_info.external_ + | Found of Lib_info.external_ list | Hidden of Lib_info.external_ Hidden.t | Invalid of User_message.t | Ignore - | Redirect_in_the_same_db of (Loc.t * Lib_name.t) + | Redirect_in_the_same_db of (Loc.t * Lib_name.t) list | Redirect of db * (Loc.t * Lib_name.t) let found f = Found f let not_found = Not_found let redirect db lib = Redirect (db, lib) - let redirect_in_the_same_db lib = Redirect_in_the_same_db lib + let redirect_in_the_same_db libs = Redirect_in_the_same_db libs let to_dyn x = let open Dyn in match x with | Not_found -> variant "Not_found" [] | Invalid e -> variant "Invalid" [ Dyn.string (User_message.to_string e) ] - | Found lib -> variant "Found" [ Lib_info.to_dyn Path.to_dyn lib ] + | Found libs -> variant "Found" [ (Dyn.list (Lib_info.to_dyn Path.to_dyn)) libs ] | Hidden h -> variant "Hidden" [ Hidden.to_dyn (Lib_info.to_dyn Path.to_dyn) h ] | Ignore -> variant "Ignore" [] | Redirect (_, (_, name)) -> variant "Redirect" [ Lib_name.to_dyn name ] - | Redirect_in_the_same_db (_, name) -> - variant "Redirect_in_the_same_db" [ Lib_name.to_dyn name ] + | Redirect_in_the_same_db redirects -> + variant + "Redirect_in_the_same_db" + [ (Dyn.list (fun (_, name) -> Lib_name.to_dyn name)) redirects ] ;; end @@ -1827,9 +1932,9 @@ module DB = struct let open Memo.O in Findlib.find findlib name >>| function - | Ok (Library pkg) -> Found (Dune_package.Lib.info pkg) + | Ok (Library pkg) -> Found [ Dune_package.Lib.info pkg ] | Ok (Deprecated_library_name d) -> - Redirect_in_the_same_db (d.loc, d.new_public_name) + Redirect_in_the_same_db [ d.loc, d.new_public_name ] | Ok (Hidden_library pkg) -> Hidden (Hidden.unsatisfied_exist_if pkg) | Error e -> (match e with @@ -2094,39 +2199,3 @@ let to_dune_lib in Dune_package.Lib.of_dune_lib ~info ~main_module_name ;; - -module Local : sig - type t = private lib - - val of_lib : lib -> t option - val of_lib_exn : lib -> t - val to_lib : t -> lib - val obj_dir : t -> Path.Build.t Obj_dir.t - val info : t -> Path.Build.t Lib_info.t - val to_dyn : t -> Dyn.t - val equal : t -> t -> bool - val hash : t -> int - - include Comparable_intf.S with type key := t -end = struct - type nonrec t = t - - let to_lib t = t - let of_lib (t : lib) = Option.some_if (is_local t) t - - let of_lib_exn t = - match of_lib t with - | Some l -> l - | None -> Code_error.raise "Lib.Local.of_lib_exn" [ "l", to_dyn t ] - ;; - - let obj_dir t = Obj_dir.as_local_exn (Lib_info.obj_dir t.info) - let info t = Lib_info.as_local_exn t.info - - module Set = Set - module Map = Map - - let to_dyn = to_dyn - let equal = equal - let hash = hash -end diff --git a/src/dune_rules/lib.mli b/src/dune_rules/lib.mli index 6dbda11c7a3..00fad2696f2 100644 --- a/src/dune_rules/lib.mli +++ b/src/dune_rules/lib.mli @@ -98,10 +98,10 @@ module DB : sig type t val not_found : t - val found : Lib_info.external_ -> t + val found : Lib_info.external_ list -> t val to_dyn : t Dyn.builder val redirect : db -> Loc.t * Lib_name.t -> t - val redirect_in_the_same_db : Loc.t * Lib_name.t -> t + val redirect_in_the_same_db : (Loc.t * Lib_name.t) list -> t end (** Create a new library database. [resolve] is used to resolve library names diff --git a/src/dune_rules/scope.ml b/src/dune_rules/scope.ml index f64880ec70c..d8364133e83 100644 --- a/src/dune_rules/scope.ml +++ b/src/dune_rules/scope.ml @@ -25,22 +25,24 @@ module DB = struct module Found_or_redirect : sig type t = private - | Found of Lib_info.external_ - | Redirect of (Loc.t * Lib_name.t) + | Found of Lib_info.external_ list + | Redirect of (Loc.t * Lib_name.t) list val redirect : Lib_name.t -> Loc.t * Lib_name.t -> Lib_name.t * t - val found : Lib_info.external_ -> t + val redirect_many : (Loc.t * Lib_name.t) list -> t + val found : Lib_info.external_ list -> t end = struct type t = - | Found of Lib_info.external_ - | Redirect of (Loc.t * Lib_name.t) + | Found of Lib_info.external_ list + | Redirect of (Loc.t * Lib_name.t) list let redirect from (loc, to_) = if Lib_name.equal from to_ then Code_error.raise ~loc "Invalid redirect" [ "to_", Lib_name.to_dyn to_ ] - else from, Redirect (loc, to_) + else from, Redirect [ loc, to_ ] ;; + let redirect_many x = Redirect x let found x = Found x end @@ -63,15 +65,18 @@ module DB = struct Found_or_redirect.redirect old_public_name s.new_public_name | Library (dir, (conf : Library.t)) -> let info = Library.to_lib_info conf ~dir ~lib_config |> Lib_info.of_local in - Library.best_name conf, Found_or_redirect.found info) + Library.best_name conf, Found_or_redirect.found [ info ]) |> Lib_name.Map.of_list_reducei ~f:(fun name (v1 : Found_or_redirect.t) v2 -> let res = match v1, v2 with - | Found info1, Found info2 -> Error (Lib_info.loc info1, Lib_info.loc info2) - | Found info, Redirect (loc, _) | Redirect (loc, _), Found info -> - Error (loc, Lib_info.loc info) - | Redirect (loc1, lib1), Redirect (loc2, lib2) -> - if Lib_name.equal lib1 lib2 then Ok v1 else Error (loc1, loc2) + | Found info1, Found info2 -> + Ok (Found_or_redirect.found (List.rev_append info1 info2)) + | Found info, Redirect redirect | Redirect redirect, Found info -> + let loc, _ = List.hd redirect in + (* todo: should this not be an error? *) + Error (loc, Lib_info.loc (List.hd info)) + | Redirect redirect1, Redirect redirect2 -> + Ok (Found_or_redirect.redirect_many (List.rev_append redirect1 redirect2)) in match res with | Ok x -> x @@ -119,7 +124,7 @@ module DB = struct | Some (Project project) -> let scope = find_by_project (Fdecl.get t) project in Lib.DB.Resolve_result.redirect scope.db (Loc.none, name) - | Some (Name name) -> Lib.DB.Resolve_result.redirect_in_the_same_db name + | Some (Name name) -> Lib.DB.Resolve_result.redirect_in_the_same_db [ name ] ;; let public_theories ~find_db ~installed_theories coq_stanzas = diff --git a/test/blackbox-tests/test-cases/deprecated-library-name/features.t b/test/blackbox-tests/test-cases/deprecated-library-name/features.t index f630742b248..2ff934a97a7 100644 --- a/test/blackbox-tests/test-cases/deprecated-library-name/features.t +++ b/test/blackbox-tests/test-cases/deprecated-library-name/features.t @@ -184,6 +184,15 @@ Check that we can use the short name in library dependencies. > EOF $ (cd d && dune build --root . @all) + File "dune", line 2, characters 0-68: + 2 | (library + 3 | (name menhirLib) + 4 | (public_name menhir.lib) + 5 | (modules lib)) + Error: A library with name "menhirLib" 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] Checks that we can migrate top-level libraries across packages. @@ -247,10 +256,6 @@ We check that there is an error when there is an actual ambiguity: > EOF $ (cd d && dune build --root . @all) - Error: Library top2 is defined twice: - - dune:13 - - dune:5 - [1] Another case of ambiguity: diff --git a/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision-same-folder.t b/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision-same-folder.t index 17f04d546ce..b6365f4f2e6 100644 --- a/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision-same-folder.t +++ b/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision-same-folder.t @@ -29,9 +29,11 @@ in the same dune file > EOF $ dune build --display=short - Error: Library foo is defined twice: - - dune:4 - - dune:1 + File "dune", line 4, characters 0-69: + 4 | (library + 5 | (name foo) + 6 | (enabled_if (= %{context_name} "alt-context"))) + Error: Library "foo" appears for the second time in this directory [1] For public libraries @@ -48,7 +50,12 @@ For public libraries > EOF $ dune build - Error: Library foo is defined twice: - - dune:7 - - dune:3 + File "dune", line 1, characters 0-0: + Error: Module "Foo" is used in several stanzas: + - dune:1 + - dune:5 + To fix this error, you must specify an explicit "modules" field in every + library, executable, and executables stanzas in this dune file. Note that + each module cannot appear in more than one "modules" field - it must belong + to a single library or executable. [1] diff --git a/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision.t b/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision.t index 258f7c86cbd..83dd9a74ed3 100644 --- a/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision.t +++ b/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision.t @@ -37,9 +37,92 @@ For private libraries > EOF $ dune build - Error: Library foo is defined twice: - - a/dune:1 - - b/dune:1 + Internal error, please report upstream including the contents of _build/log. + Description: + ("[gen_rules] returned rules in a directory that is not a descendant of the directory it was called for", + { dir = In_build_dir "alt-context/a" + ; example = + Alias + { dir = In_build_dir "alt-context/b/.foo.objs/byte" + ; name = ".odoc-all" + } + }) + Raised at Stdune__Code_error.raise in file + "otherlibs/stdune/src/code_error.ml", line 10, characters 30-62 + Called from + Dune_engine__Load_rules.Load_rules.Normal.make_rules_gen_result.(fun) in + file "src/dune_engine/load_rules.ml", line 549, characters 10-51 + Called from Fiber__Core.O.(>>|).(fun) in file "vendor/fiber/src/core.ml", + line 253, characters 36-41 + Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", + line 76, characters 8-11 + Re-raised at Stdune__Exn.raise_with_backtrace in file + "otherlibs/stdune/src/exn.ml", line 38, characters 27-56 + Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", + line 76, characters 8-11 + Re-raised at Stdune__Exn.raise_with_backtrace in file + "otherlibs/stdune/src/exn.ml", line 38, characters 27-56 + Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", + line 76, characters 8-11 + Re-raised at Stdune__Exn.raise_with_backtrace in file + "otherlibs/stdune/src/exn.ml", line 38, characters 27-56 + Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", + line 76, characters 8-11 + Re-raised at Stdune__Exn.raise_with_backtrace in file + "otherlibs/stdune/src/exn.ml", line 38, characters 27-56 + Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", + line 76, characters 8-11 + -> required by ("", ()) + -> required by ("load-dir", In_build_dir "alt-context/a") + -> required by ("", ()) + -> required by + ("build-alias", { dir = In_build_dir "alt-context"; name = "default" }) + -> required by ("toplevel", ()) + + I must not crash. Uncertainty is the mind-killer. Exceptions are the + little-death that brings total obliteration. I will fully express my cases. + Execution will pass over me and through me. And when it has gone past, I + will unwind the stack along its path. Where the cases are handled there will + be nothing. Only I will remain. + Internal error, please report upstream including the contents of _build/log. + Description: + ("[gen_rules] returned rules in a directory that is not a descendant of the directory it was called for", + { dir = In_build_dir "default/b" + ; example = + Alias + { dir = In_build_dir "default/a/.foo.objs/byte"; name = ".odoc-all" } + }) + Raised at Stdune__Code_error.raise in file + "otherlibs/stdune/src/code_error.ml", line 10, characters 30-62 + Called from + Dune_engine__Load_rules.Load_rules.Normal.make_rules_gen_result.(fun) in + file "src/dune_engine/load_rules.ml", line 549, characters 10-51 + Called from Fiber__Core.O.(>>|).(fun) in file "vendor/fiber/src/core.ml", + line 253, characters 36-41 + Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", + line 76, characters 8-11 + Re-raised at Stdune__Exn.raise_with_backtrace in file + "otherlibs/stdune/src/exn.ml", line 38, characters 27-56 + Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", + line 76, characters 8-11 + Re-raised at Stdune__Exn.raise_with_backtrace in file + "otherlibs/stdune/src/exn.ml", line 38, characters 27-56 + Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", + line 76, characters 8-11 + Re-raised at Stdune__Exn.raise_with_backtrace in file + "otherlibs/stdune/src/exn.ml", line 38, characters 27-56 + Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", + line 76, characters 8-11 + Re-raised at Stdune__Exn.raise_with_backtrace in file + "otherlibs/stdune/src/exn.ml", line 38, characters 27-56 + Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", + line 76, characters 8-11 + -> required by ("", ()) + -> required by ("load-dir", In_build_dir "default/b") + -> required by ("", ()) + -> required by + ("build-alias", { dir = In_build_dir "default"; name = "default" }) + -> required by ("toplevel", ()) [1] For public libraries @@ -59,7 +142,3 @@ For public libraries > EOF $ dune build - Error: Library foo is defined twice: - - a/dune:3 - - b/dune:3 - [1] diff --git a/test/blackbox-tests/test-cases/lib-collision/lib-collision-private-same-folder.t b/test/blackbox-tests/test-cases/lib-collision/lib-collision-private-same-folder.t index 3b9a80d7ae2..791a3630949 100644 --- a/test/blackbox-tests/test-cases/lib-collision/lib-collision-private-same-folder.t +++ b/test/blackbox-tests/test-cases/lib-collision/lib-collision-private-same-folder.t @@ -15,10 +15,6 @@ the same folder. Without any consumers of the libraries $ dune build - Error: Library foo is defined twice: - - dune:3 - - dune:1 - [1] With some consumer of the library @@ -37,7 +33,8 @@ With some consumer of the library > EOF $ dune build - Error: Library foo is defined twice: - - dune:3 - - dune:1 + File "dune", line 3, characters 0-21: + 3 | (library + 4 | (name foo)) + Error: Library "foo" appears for the second time in this directory [1] diff --git a/test/blackbox-tests/test-cases/lib-collision/lib-collision-private.t b/test/blackbox-tests/test-cases/lib-collision/lib-collision-private.t index 92ae5b12ffb..14211aad3d9 100644 --- a/test/blackbox-tests/test-cases/lib-collision/lib-collision-private.t +++ b/test/blackbox-tests/test-cases/lib-collision/lib-collision-private.t @@ -20,10 +20,6 @@ different folders. Without any consumers of the libraries $ dune build - Error: Library foo is defined twice: - - a/dune:1 - - b/dune:1 - [1] With some consumer of the library @@ -38,7 +34,10 @@ With some consumer of the library > EOF $ dune build - Error: Library foo is defined twice: - - a/dune:1 - - b/dune:1 + File "b/dune", line 1, characters 0-21: + 1 | (library + 2 | (name foo)) + 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. [1] diff --git a/test/blackbox-tests/test-cases/lib-collision/lib-collision-public-same-folder.t b/test/blackbox-tests/test-cases/lib-collision/lib-collision-public-same-folder.t index d29e077bd1b..3e8af8c0fb3 100644 --- a/test/blackbox-tests/test-cases/lib-collision/lib-collision-public-same-folder.t +++ b/test/blackbox-tests/test-cases/lib-collision/lib-collision-public-same-folder.t @@ -19,9 +19,9 @@ the same folder. Without any consumers of the libraries $ dune build - Error: Library foo is defined twice: - - dune:6 - - dune:3 + Error: Multiple rules generated for _build/default/foo.cmxs: + - dune:4 + - dune:1 [1] With some consumer @@ -43,7 +43,13 @@ With some consumer > EOF $ dune build - Error: Library foo is defined twice: - - dune:6 - - dune:3 + File "dune", line 1, characters 0-0: + Error: Module "Main" is used in several stanzas: + - dune:1 + - dune:4 + - dune:7 + To fix this error, you must specify an explicit "modules" field in every + library, executable, and executables stanzas in this dune file. Note that + each module cannot appear in more than one "modules" field - it must belong + to a single library or executable. [1] diff --git a/test/blackbox-tests/test-cases/lib-collision/lib-collision-public.t b/test/blackbox-tests/test-cases/lib-collision/lib-collision-public.t index 51150a9512b..9821639da72 100644 --- a/test/blackbox-tests/test-cases/lib-collision/lib-collision-public.t +++ b/test/blackbox-tests/test-cases/lib-collision/lib-collision-public.t @@ -24,10 +24,6 @@ different folders. Without any consumers of the libraries $ dune build - Error: Library foo is defined twice: - - a/dune:3 - - b/dune:3 - [1] With some consumer @@ -42,7 +38,11 @@ With some consumer > EOF $ dune build - Error: Library foo is defined twice: - - a/dune:3 - - b/dune:3 + File "b/dune", line 1, characters 0-44: + 1 | (library + 2 | (name foo) + 3 | (public_name baz.foo)) + 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. [1] From 5704dbc4efa61163bf0fbd9309ad7fdd15ca0d0d Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Javier=20Ch=C3=A1varri?= Date: Fri, 1 Mar 2024 10:42:06 +0000 Subject: [PATCH 02/15] lib: fix issue with odoc-all MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Javier Chávarri --- src/dune_rules/lib_rules.ml | 6 +- .../enabled_if/eif-library-name-collision.t | 87 ------------------- 2 files changed, 5 insertions(+), 88 deletions(-) diff --git a/src/dune_rules/lib_rules.ml b/src/dune_rules/lib_rules.ml index 048bd582976..b54b5c4f009 100644 --- a/src/dune_rules/lib_rules.ml +++ b/src/dune_rules/lib_rules.ml @@ -609,7 +609,11 @@ let library_rules ~dir_contents ~vlib_stubs_o_files) and+ () = Odoc.setup_private_library_doc_alias sctx ~scope ~dir:ctx_dir lib - and+ () = Odoc.setup_library_odoc_rules cctx local_lib + and+ () = + let* enabled_if = Lib_info.enabled lib_info in + match enabled_if with + | Disabled_because_of_enabled_if -> Memo.return () + | Normal | Optional -> Odoc.setup_library_odoc_rules cctx local_lib and+ () = Sub_system.gen_rules { super_context = sctx; dir; stanza = lib; scope; source_modules; compile_info } diff --git a/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision.t b/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision.t index 83dd9a74ed3..f1a9f9492fb 100644 --- a/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision.t +++ b/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision.t @@ -37,93 +37,6 @@ For private libraries > EOF $ dune build - Internal error, please report upstream including the contents of _build/log. - Description: - ("[gen_rules] returned rules in a directory that is not a descendant of the directory it was called for", - { dir = In_build_dir "alt-context/a" - ; example = - Alias - { dir = In_build_dir "alt-context/b/.foo.objs/byte" - ; name = ".odoc-all" - } - }) - Raised at Stdune__Code_error.raise in file - "otherlibs/stdune/src/code_error.ml", line 10, characters 30-62 - Called from - Dune_engine__Load_rules.Load_rules.Normal.make_rules_gen_result.(fun) in - file "src/dune_engine/load_rules.ml", line 549, characters 10-51 - Called from Fiber__Core.O.(>>|).(fun) in file "vendor/fiber/src/core.ml", - line 253, characters 36-41 - Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", - line 76, characters 8-11 - Re-raised at Stdune__Exn.raise_with_backtrace in file - "otherlibs/stdune/src/exn.ml", line 38, characters 27-56 - Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", - line 76, characters 8-11 - Re-raised at Stdune__Exn.raise_with_backtrace in file - "otherlibs/stdune/src/exn.ml", line 38, characters 27-56 - Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", - line 76, characters 8-11 - Re-raised at Stdune__Exn.raise_with_backtrace in file - "otherlibs/stdune/src/exn.ml", line 38, characters 27-56 - Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", - line 76, characters 8-11 - Re-raised at Stdune__Exn.raise_with_backtrace in file - "otherlibs/stdune/src/exn.ml", line 38, characters 27-56 - Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", - line 76, characters 8-11 - -> required by ("", ()) - -> required by ("load-dir", In_build_dir "alt-context/a") - -> required by ("", ()) - -> required by - ("build-alias", { dir = In_build_dir "alt-context"; name = "default" }) - -> required by ("toplevel", ()) - - I must not crash. Uncertainty is the mind-killer. Exceptions are the - little-death that brings total obliteration. I will fully express my cases. - Execution will pass over me and through me. And when it has gone past, I - will unwind the stack along its path. Where the cases are handled there will - be nothing. Only I will remain. - Internal error, please report upstream including the contents of _build/log. - Description: - ("[gen_rules] returned rules in a directory that is not a descendant of the directory it was called for", - { dir = In_build_dir "default/b" - ; example = - Alias - { dir = In_build_dir "default/a/.foo.objs/byte"; name = ".odoc-all" } - }) - Raised at Stdune__Code_error.raise in file - "otherlibs/stdune/src/code_error.ml", line 10, characters 30-62 - Called from - Dune_engine__Load_rules.Load_rules.Normal.make_rules_gen_result.(fun) in - file "src/dune_engine/load_rules.ml", line 549, characters 10-51 - Called from Fiber__Core.O.(>>|).(fun) in file "vendor/fiber/src/core.ml", - line 253, characters 36-41 - Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", - line 76, characters 8-11 - Re-raised at Stdune__Exn.raise_with_backtrace in file - "otherlibs/stdune/src/exn.ml", line 38, characters 27-56 - Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", - line 76, characters 8-11 - Re-raised at Stdune__Exn.raise_with_backtrace in file - "otherlibs/stdune/src/exn.ml", line 38, characters 27-56 - Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", - line 76, characters 8-11 - Re-raised at Stdune__Exn.raise_with_backtrace in file - "otherlibs/stdune/src/exn.ml", line 38, characters 27-56 - Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", - line 76, characters 8-11 - Re-raised at Stdune__Exn.raise_with_backtrace in file - "otherlibs/stdune/src/exn.ml", line 38, characters 27-56 - Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", - line 76, characters 8-11 - -> required by ("", ()) - -> required by ("load-dir", In_build_dir "default/b") - -> required by ("", ()) - -> required by - ("build-alias", { dir = In_build_dir "default"; name = "default" }) - -> required by ("toplevel", ()) - [1] For public libraries From 9e0fa2370714e840d2dc195466c96cf7a1fd7cec Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Javier=20Ch=C3=A1varri?= Date: Fri, 1 Mar 2024 10:48:16 +0000 Subject: [PATCH 03/15] lib: move local back MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Javier Chávarri --- src/dune_rules/lib.ml | 72 +++++++++++++++++++++---------------------- 1 file changed, 36 insertions(+), 36 deletions(-) diff --git a/src/dune_rules/lib.ml b/src/dune_rules/lib.ml index d4e858e4fbb..f4d5ce2ff48 100644 --- a/src/dune_rules/lib.ml +++ b/src/dune_rules/lib.ml @@ -1835,42 +1835,6 @@ module Compile = struct ;; end -module Local : sig - type t = private lib - - val of_lib : lib -> t option - val of_lib_exn : lib -> t - val to_lib : t -> lib - val obj_dir : t -> Path.Build.t Obj_dir.t - val info : t -> Path.Build.t Lib_info.t - val to_dyn : t -> Dyn.t - val equal : t -> t -> bool - val hash : t -> int - - include Comparable_intf.S with type key := t -end = struct - type nonrec t = t - - let to_lib t = t - let of_lib (t : lib) = Option.some_if (is_local t) t - - let of_lib_exn t = - match of_lib t with - | Some l -> l - | None -> Code_error.raise "Lib.Local.of_lib_exn" [ "l", to_dyn t ] - ;; - - let obj_dir t = Obj_dir.as_local_exn (Lib_info.obj_dir t.info) - let info t = Lib_info.as_local_exn t.info - - module Set = Set - module Map = Map - - let to_dyn = to_dyn - let equal = equal - let hash = hash -end - (* Databases *) module DB = struct @@ -2199,3 +2163,39 @@ let to_dune_lib in Dune_package.Lib.of_dune_lib ~info ~main_module_name ;; + +module Local : sig + type t = private lib + + val of_lib : lib -> t option + val of_lib_exn : lib -> t + val to_lib : t -> lib + val obj_dir : t -> Path.Build.t Obj_dir.t + val info : t -> Path.Build.t Lib_info.t + val to_dyn : t -> Dyn.t + val equal : t -> t -> bool + val hash : t -> int + + include Comparable_intf.S with type key := t +end = struct + type nonrec t = t + + let to_lib t = t + let of_lib (t : lib) = Option.some_if (is_local t) t + + let of_lib_exn t = + match of_lib t with + | Some l -> l + | None -> Code_error.raise "Lib.Local.of_lib_exn" [ "l", to_dyn t ] + ;; + + let obj_dir t = Obj_dir.as_local_exn (Lib_info.obj_dir t.info) + let info t = Lib_info.as_local_exn t.info + + module Set = Set + module Map = Map + + let to_dyn = to_dyn + let equal = equal + let hash = hash +end From 845ac40d62115f2b466bfa2f4f43cdf69c101c3f Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Javier=20Ch=C3=A1varri?= Date: Fri, 8 Mar 2024 11:48:28 +0000 Subject: [PATCH 04/15] fix deprecated lib tests MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit brings the changes from #10231 Signed-off-by: Javier Chávarri --- src/dune_rules/lib.ml | 8 ++++++- src/dune_rules/lib.mli | 1 + src/dune_rules/scope.ml | 24 +++++++++++++++++-- .../deprecated-library-name/features.t | 13 ++++------ 4 files changed, 34 insertions(+), 12 deletions(-) diff --git a/src/dune_rules/lib.ml b/src/dune_rules/lib.ml index 031da8263b5..292356b9a06 100644 --- a/src/dune_rules/lib.ml +++ b/src/dune_rules/lib.ml @@ -424,6 +424,7 @@ and resolve_result = | Ignore | Redirect_in_the_same_db of (Loc.t * Lib_name.t) list | Redirect of db * (Loc.t * Lib_name.t) + | Deprecated_library_name of (Loc.t * Lib_name.t) let lib_config (t : lib) = t.lib_config let name t = t.name @@ -1167,6 +1168,7 @@ end = struct db.resolve name >>= function | Ignore -> Memo.return Status.Ignore + | Deprecated_library_name (_, name') -> find_internal db name' | Redirect_in_the_same_db redirects -> let result = List.map ~f:(fun (_, name') -> find_internal db name') redirects in let* statuses = @@ -1847,11 +1849,13 @@ module DB = struct | Ignore | Redirect_in_the_same_db of (Loc.t * Lib_name.t) list | Redirect of db * (Loc.t * Lib_name.t) + | Deprecated_library_name of (Loc.t * Lib_name.t) let found f = Found f let not_found = Not_found let redirect db lib = Redirect (db, lib) let redirect_in_the_same_db libs = Redirect_in_the_same_db libs + let deprecated_library_name lib = Deprecated_library_name lib let to_dyn x = let open Dyn in @@ -1866,6 +1870,8 @@ module DB = struct variant "Redirect_in_the_same_db" [ (Dyn.list (fun (_, name) -> Lib_name.to_dyn name)) redirects ] + | Deprecated_library_name (_, name) -> + variant "Deprecated_library_name" [ Lib_name.to_dyn name ] ;; end @@ -1898,7 +1904,7 @@ module DB = struct >>| function | Ok (Library pkg) -> Found [ Dune_package.Lib.info pkg ] | Ok (Deprecated_library_name d) -> - Redirect_in_the_same_db [ d.loc, d.new_public_name ] + Deprecated_library_name (d.loc, d.new_public_name) | Ok (Hidden_library pkg) -> Hidden (Hidden.unsatisfied_exist_if pkg) | Error e -> (match e with diff --git a/src/dune_rules/lib.mli b/src/dune_rules/lib.mli index 00fad2696f2..816b92a0ff4 100644 --- a/src/dune_rules/lib.mli +++ b/src/dune_rules/lib.mli @@ -102,6 +102,7 @@ module DB : sig val to_dyn : t Dyn.builder val redirect : db -> Loc.t * Lib_name.t -> t val redirect_in_the_same_db : (Loc.t * Lib_name.t) list -> t + val deprecated_library_name : Loc.t * Lib_name.t -> t end (** Create a new library database. [resolve] is used to resolve library names diff --git a/src/dune_rules/scope.ml b/src/dune_rules/scope.ml index d8364133e83..8388a94605b 100644 --- a/src/dune_rules/scope.ml +++ b/src/dune_rules/scope.ml @@ -27,14 +27,17 @@ module DB = struct type t = private | Found of Lib_info.external_ list | Redirect of (Loc.t * Lib_name.t) list + | Deprecated_library_name of (Loc.t * Lib_name.t) val redirect : Lib_name.t -> Loc.t * Lib_name.t -> Lib_name.t * t val redirect_many : (Loc.t * Lib_name.t) list -> t + val deprecated_library_name : Lib_name.t -> Loc.t * Lib_name.t -> Lib_name.t * t val found : Lib_info.external_ list -> t end = struct type t = | Found of Lib_info.external_ list | Redirect of (Loc.t * Lib_name.t) list + | Deprecated_library_name of (Loc.t * Lib_name.t) let redirect from (loc, to_) = if Lib_name.equal from to_ @@ -43,6 +46,13 @@ module DB = struct ;; let redirect_many x = Redirect x + + let deprecated_library_name from (loc, to_) = + if Lib_name.equal from to_ + then Code_error.raise ~loc "Invalid redirect" [ "to_", Lib_name.to_dyn to_ ] + else from, Deprecated_library_name (loc, to_) + ;; + let found x = Found x end @@ -62,7 +72,7 @@ module DB = struct Found_or_redirect.redirect old_public_name s.new_public_name | Deprecated_library_name s -> let old_public_name = Deprecated_library_name.old_public_name s in - Found_or_redirect.redirect old_public_name s.new_public_name + Found_or_redirect.deprecated_library_name old_public_name s.new_public_name | Library (dir, (conf : Library.t)) -> let info = Library.to_lib_info conf ~dir ~lib_config |> Lib_info.of_local in Library.best_name conf, Found_or_redirect.found [ info ]) @@ -73,10 +83,18 @@ module DB = struct Ok (Found_or_redirect.found (List.rev_append info1 info2)) | Found info, Redirect redirect | Redirect redirect, Found info -> let loc, _ = List.hd redirect in - (* todo: should this not be an error? *) Error (loc, Lib_info.loc (List.hd info)) + | Found info, Deprecated_library_name (loc, _) + | Deprecated_library_name (loc, _), Found info -> + Error (loc, Lib_info.loc (List.hd info)) + | Deprecated_library_name (loc2, lib2), Redirect redirect + | Redirect redirect, Deprecated_library_name (loc2, lib2) -> + let loc1, lib1 = List.hd redirect in + if Lib_name.equal lib1 lib2 then Ok v1 else Error (loc1, loc2) | Redirect redirect1, Redirect redirect2 -> Ok (Found_or_redirect.redirect_many (List.rev_append redirect1 redirect2)) + | Deprecated_library_name (loc1, lib1), Deprecated_library_name (loc2, lib2) -> + if Lib_name.equal lib1 lib2 then Ok v1 else Error (loc1, loc2) in match res with | Ok x -> x @@ -108,6 +126,8 @@ module DB = struct (match Lib_name.Map.find map name with | None -> Lib.DB.Resolve_result.not_found | Some (Redirect lib) -> Lib.DB.Resolve_result.redirect_in_the_same_db lib + | Some (Deprecated_library_name lib) -> + Lib.DB.Resolve_result.deprecated_library_name lib | Some (Found lib) -> Lib.DB.Resolve_result.found lib)) ~all:(fun () -> Lib_name.Map.keys map |> Memo.return) ~lib_config diff --git a/test/blackbox-tests/test-cases/deprecated-library-name/features.t b/test/blackbox-tests/test-cases/deprecated-library-name/features.t index 2ff934a97a7..5ce45c8c044 100644 --- a/test/blackbox-tests/test-cases/deprecated-library-name/features.t +++ b/test/blackbox-tests/test-cases/deprecated-library-name/features.t @@ -184,15 +184,6 @@ Check that we can use the short name in library dependencies. > EOF $ (cd d && dune build --root . @all) - File "dune", line 2, characters 0-68: - 2 | (library - 3 | (name menhirLib) - 4 | (public_name menhir.lib) - 5 | (modules lib)) - Error: A library with name "menhirLib" 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] Checks that we can migrate top-level libraries across packages. @@ -256,6 +247,10 @@ We check that there is an error when there is an actual ambiguity: > EOF $ (cd d && dune build --root . @all) + Error: Library top2 is defined twice: + - dune:5 + - dune:13 + [1] Another case of ambiguity: From 15dd99c6798f755d527b3c78a4cab5972c23b73e Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Javier=20Ch=C3=A1varri?= Date: Wed, 13 Mar 2024 14:26:07 +0000 Subject: [PATCH 05/15] update tests MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Javier Chávarri --- .../eif-library-name-collision-same-folder.t | 20 +++----- .../enabled_if/eif-library-name-collision.t | 48 +++++++++++++++++++ .../lib-collision/lib-collision-private.t | 5 -- 3 files changed, 54 insertions(+), 19 deletions(-) diff --git a/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision-same-folder.t b/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision-same-folder.t index b6365f4f2e6..da69cae1d78 100644 --- a/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision-same-folder.t +++ b/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision-same-folder.t @@ -29,11 +29,12 @@ in the same dune file > EOF $ dune build --display=short - File "dune", line 4, characters 0-69: - 4 | (library - 5 | (name foo) - 6 | (enabled_if (= %{context_name} "alt-context"))) - Error: Library "foo" appears for the second time in this directory + Error: Multiple rules generated for _build/alt-context/foo.cmxs: + - dune:4 + - dune:1 + Error: Multiple rules generated for _build/default/foo.cmxs: + - dune:4 + - dune:1 [1] For public libraries @@ -50,12 +51,3 @@ For public libraries > EOF $ dune build - File "dune", line 1, characters 0-0: - Error: Module "Foo" is used in several stanzas: - - dune:1 - - dune:5 - To fix this error, you must specify an explicit "modules" field in every - library, executable, and executables stanzas in this dune file. Note that - each module cannot appear in more than one "modules" field - it must belong - to a single library or executable. - [1] diff --git a/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision.t b/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision.t index f1a9f9492fb..2657f1b5122 100644 --- a/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision.t +++ b/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision.t @@ -37,6 +37,54 @@ For private libraries > EOF $ dune build + Internal error, please report upstream including the contents of _build/log. + Description: + ("modules_and_obj_dir: failed lookup", { keys = []; for_ = Library "foo" }) + Raised at Stdune__Code_error.raise in file + "otherlibs/stdune/src/code_error.ml", line 10, characters 30-62 + Called from Dune_rules__Ml_sources.modules in file + "src/dune_rules/ml_sources.ml", line 249, characters 22-49 + Called from Fiber__Core.O.(>>|).(fun) in file "vendor/fiber/src/core.ml", + line 253, characters 36-41 + Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", + line 76, characters 8-11 + Re-raised at Stdune__Exn.raise_with_backtrace in file + "otherlibs/stdune/src/exn.ml", line 38, characters 27-56 + Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", + line 76, characters 8-11 + Re-raised at Stdune__Exn.raise_with_backtrace in file + "otherlibs/stdune/src/exn.ml", line 38, characters 27-56 + Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", + line 76, characters 8-11 + Re-raised at Stdune__Exn.raise_with_backtrace in file + "otherlibs/stdune/src/exn.ml", line 38, characters 27-56 + Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", + line 76, characters 8-11 + Re-raised at Stdune__Exn.raise_with_backtrace in file + "otherlibs/stdune/src/exn.ml", line 38, characters 27-56 + Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", + line 76, characters 8-11 + Re-raised at Stdune__Exn.raise_with_backtrace in file + "otherlibs/stdune/src/exn.ml", line 38, characters 27-56 + Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", + line 76, characters 8-11 + Re-raised at Stdune__Exn.raise_with_backtrace in file + "otherlibs/stdune/src/exn.ml", line 38, characters 27-56 + Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", + line 76, characters 8-11 + -> required by ("", ()) + -> required by ("load-dir", In_build_dir "default/b") + -> required by ("", ()) + -> required by + ("build-alias", { dir = In_build_dir "default"; name = "default" }) + -> required by ("toplevel", ()) + + I must not crash. Uncertainty is the mind-killer. Exceptions are the + little-death that brings total obliteration. I will fully express my cases. + Execution will pass over me and through me. And when it has gone past, I + will unwind the stack along its path. Where the cases are handled there will + be nothing. Only I will remain. + [1] For public libraries diff --git a/test/blackbox-tests/test-cases/lib-collision/lib-collision-private.t b/test/blackbox-tests/test-cases/lib-collision/lib-collision-private.t index 218c0537a5c..14211aad3d9 100644 --- a/test/blackbox-tests/test-cases/lib-collision/lib-collision-private.t +++ b/test/blackbox-tests/test-cases/lib-collision/lib-collision-private.t @@ -20,11 +20,6 @@ different folders. Without any consumers of the libraries $ dune build - Error: Library foo is defined twice: - - a/dune:1 - - b/dune:1 - -> required by alias default - [1] With some consumer of the library From a17622a434ee84f3a66ab4f71579de7f103e1b3e Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Javier=20Ch=C3=A1varri?= Date: Wed, 13 Mar 2024 14:31:52 +0000 Subject: [PATCH 06/15] only add lib rules if the lib is available and enabled in ctxt MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Javier Chávarri --- src/dune_rules/gen_rules.ml | 18 ++++++- .../eif-library-name-collision-same-folder.t | 17 ++++--- .../enabled_if/eif-library-name-collision.t | 48 ------------------- 3 files changed, 26 insertions(+), 57 deletions(-) diff --git a/src/dune_rules/gen_rules.ml b/src/dune_rules/gen_rules.ml index ca316bda188..61eec829192 100644 --- a/src/dune_rules/gen_rules.ml +++ b/src/dune_rules/gen_rules.ml @@ -111,11 +111,25 @@ 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* 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_if + (enabled_in_context && available) | Foreign.Library.T lib -> Expander.eval_blang expander lib.enabled_if >>= if_available (fun () -> diff --git a/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision-same-folder.t b/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision-same-folder.t index da69cae1d78..c7dd6150dc0 100644 --- a/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision-same-folder.t +++ b/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision-same-folder.t @@ -29,13 +29,16 @@ in the same dune file > EOF $ dune build --display=short - Error: Multiple rules generated for _build/alt-context/foo.cmxs: - - dune:4 - - dune:1 - Error: Multiple rules generated for _build/default/foo.cmxs: - - dune:4 - - dune:1 - [1] + ocamlc .foo.objs/byte/foo.{cmi,cmo,cmt} [alt-context] + ocamlc .foo.objs/byte/foo.{cmi,cmo,cmt} + ocamlopt .foo.objs/native/foo.{cmx,o} [alt-context] + ocamlc foo.cma [alt-context] + ocamlopt .foo.objs/native/foo.{cmx,o} + ocamlc foo.cma + ocamlopt foo.{a,cmxa} [alt-context] + ocamlopt foo.{a,cmxa} + ocamlopt foo.cmxs [alt-context] + ocamlopt foo.cmxs For public libraries diff --git a/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision.t b/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision.t index 2657f1b5122..f1a9f9492fb 100644 --- a/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision.t +++ b/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision.t @@ -37,54 +37,6 @@ For private libraries > EOF $ dune build - Internal error, please report upstream including the contents of _build/log. - Description: - ("modules_and_obj_dir: failed lookup", { keys = []; for_ = Library "foo" }) - Raised at Stdune__Code_error.raise in file - "otherlibs/stdune/src/code_error.ml", line 10, characters 30-62 - Called from Dune_rules__Ml_sources.modules in file - "src/dune_rules/ml_sources.ml", line 249, characters 22-49 - Called from Fiber__Core.O.(>>|).(fun) in file "vendor/fiber/src/core.ml", - line 253, characters 36-41 - Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", - line 76, characters 8-11 - Re-raised at Stdune__Exn.raise_with_backtrace in file - "otherlibs/stdune/src/exn.ml", line 38, characters 27-56 - Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", - line 76, characters 8-11 - Re-raised at Stdune__Exn.raise_with_backtrace in file - "otherlibs/stdune/src/exn.ml", line 38, characters 27-56 - Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", - line 76, characters 8-11 - Re-raised at Stdune__Exn.raise_with_backtrace in file - "otherlibs/stdune/src/exn.ml", line 38, characters 27-56 - Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", - line 76, characters 8-11 - Re-raised at Stdune__Exn.raise_with_backtrace in file - "otherlibs/stdune/src/exn.ml", line 38, characters 27-56 - Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", - line 76, characters 8-11 - Re-raised at Stdune__Exn.raise_with_backtrace in file - "otherlibs/stdune/src/exn.ml", line 38, characters 27-56 - Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", - line 76, characters 8-11 - Re-raised at Stdune__Exn.raise_with_backtrace in file - "otherlibs/stdune/src/exn.ml", line 38, characters 27-56 - Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml", - line 76, characters 8-11 - -> required by ("", ()) - -> required by ("load-dir", In_build_dir "default/b") - -> required by ("", ()) - -> required by - ("build-alias", { dir = In_build_dir "default"; name = "default" }) - -> required by ("toplevel", ()) - - I must not crash. Uncertainty is the mind-killer. Exceptions are the - little-death that brings total obliteration. I will fully express my cases. - Execution will pass over me and through me. And when it has gone past, I - will unwind the stack along its path. Where the cases are handled there will - be nothing. Only I will remain. - [1] For public libraries From 803a6fe2c8136a099a718428aacb64546ee22755 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Javier=20Ch=C3=A1varri?= Date: Wed, 13 Mar 2024 14:37:55 +0000 Subject: [PATCH 07/15] remove unneeded change in lib_rules MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Javier Chávarri --- src/dune_rules/lib_rules.ml | 6 +----- 1 file changed, 1 insertion(+), 5 deletions(-) diff --git a/src/dune_rules/lib_rules.ml b/src/dune_rules/lib_rules.ml index b54b5c4f009..048bd582976 100644 --- a/src/dune_rules/lib_rules.ml +++ b/src/dune_rules/lib_rules.ml @@ -609,11 +609,7 @@ let library_rules ~dir_contents ~vlib_stubs_o_files) and+ () = Odoc.setup_private_library_doc_alias sctx ~scope ~dir:ctx_dir lib - and+ () = - let* enabled_if = Lib_info.enabled lib_info in - match enabled_if with - | Disabled_because_of_enabled_if -> Memo.return () - | Normal | Optional -> Odoc.setup_library_odoc_rules cctx local_lib + and+ () = Odoc.setup_library_odoc_rules cctx local_lib and+ () = Sub_system.gen_rules { super_context = sctx; dir; stanza = lib; scope; source_modules; compile_info } From b970f3c8a2505cac50197171266f4bc70aa42990 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Javier=20Ch=C3=A1varri?= Date: Fri, 15 Mar 2024 08:34:57 +0000 Subject: [PATCH 08/15] show proper errors on public libs collision MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Javier Chávarri --- src/dune_rules/gen_rules.ml | 45 +++++++++++-------- src/dune_rules/lib.ml | 8 ++++ src/dune_rules/lib.mli | 1 + src/dune_rules/stanzas/library.ml | 1 + src/dune_rules/stanzas/library.mli | 1 + .../lib-collision-private-same-folder.t | 13 ++++++ .../lib-collision/lib-collision-private.t | 15 +++++++ .../lib-collision-public-same-folder.t | 15 +++++-- .../lib-collision/lib-collision-public.t | 21 +++++++++ 9 files changed, 98 insertions(+), 22 deletions(-) diff --git a/src/dune_rules/gen_rules.ml b/src/dune_rules/gen_rules.ml index 61eec829192..21bb3ec438f 100644 --- a/src/dune_rules/gen_rules.ml +++ b/src/dune_rules/gen_rules.ml @@ -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 () -> diff --git a/src/dune_rules/lib.ml b/src/dune_rules/lib.ml index 292356b9a06..b9ec225bc6f 100644 --- a/src/dune_rules/lib.ml +++ b/src/dune_rules/lib.ml @@ -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 diff --git a/src/dune_rules/lib.mli b/src/dune_rules/lib.mli index 816b92a0ff4..5320652a21a 100644 --- a/src/dune_rules/lib.mli +++ b/src/dune_rules/lib.mli @@ -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 diff --git a/src/dune_rules/stanzas/library.ml b/src/dune_rules/stanzas/library.ml index 7410ce896a2..d9cd485f054 100644 --- a/src/dune_rules/stanzas/library.ml +++ b/src/dune_rules/stanzas/library.ml @@ -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 diff --git a/src/dune_rules/stanzas/library.mli b/src/dune_rules/stanzas/library.mli index b5f2ba5a63d..6e39702c8d9 100644 --- a/src/dune_rules/stanzas/library.mli +++ b/src/dune_rules/stanzas/library.mli @@ -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 diff --git a/test/blackbox-tests/test-cases/lib-collision/lib-collision-private-same-folder.t b/test/blackbox-tests/test-cases/lib-collision/lib-collision-private-same-folder.t index 791a3630949..ebd61016af6 100644 --- a/test/blackbox-tests/test-cases/lib-collision/lib-collision-private-same-folder.t +++ b/test/blackbox-tests/test-cases/lib-collision/lib-collision-private-same-folder.t @@ -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 @@ -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)) diff --git a/test/blackbox-tests/test-cases/lib-collision/lib-collision-private.t b/test/blackbox-tests/test-cases/lib-collision/lib-collision-private.t index 14211aad3d9..418d5587d34 100644 --- a/test/blackbox-tests/test-cases/lib-collision/lib-collision-private.t +++ b/test/blackbox-tests/test-cases/lib-collision/lib-collision-private.t @@ -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 @@ -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)) diff --git a/test/blackbox-tests/test-cases/lib-collision/lib-collision-public-same-folder.t b/test/blackbox-tests/test-cases/lib-collision/lib-collision-public-same-folder.t index 3e8af8c0fb3..ef1b9226e5d 100644 --- a/test/blackbox-tests/test-cases/lib-collision/lib-collision-public-same-folder.t +++ b/test/blackbox-tests/test-cases/lib-collision/lib-collision-public-same-folder.t @@ -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 @@ -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 diff --git a/test/blackbox-tests/test-cases/lib-collision/lib-collision-public.t b/test/blackbox-tests/test-cases/lib-collision/lib-collision-public.t index 9821639da72..55cdfff23d6 100644 --- a/test/blackbox-tests/test-cases/lib-collision/lib-collision-public.t +++ b/test/blackbox-tests/test-cases/lib-collision/lib-collision-public.t @@ -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 @@ -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) From c97b26f61c606c2eb97738045bc2c59604f5ca85 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Javier=20Ch=C3=A1varri?= Date: Fri, 15 Mar 2024 10:50:24 +0000 Subject: [PATCH 09/15] update comment MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Javier Chávarri --- src/dune_rules/gen_rules.ml | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/dune_rules/gen_rules.ml b/src/dune_rules/gen_rules.ml index 21bb3ec438f..a72675594c0 100644 --- a/src/dune_rules/gen_rules.ml +++ b/src/dune_rules/gen_rules.ml @@ -112,8 +112,9 @@ end = struct empty_none | Library.T lib -> 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 *) + (* This check surfaces conflicts between private names of public libraries, + without it the user might get duplicated rules errors for cmxs + when the libraries are defined in the same folder and have the same private name *) let* res = Lib.DB.find_invalid db (Library.private_name lib) in (match res with | Some err -> User_error.raise [ User_message.pp err ] From ec4dd8fd251d9026eaf92e8d2e866668a0ac5112 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Javier=20Ch=C3=A1varri?= Date: Fri, 15 Mar 2024 10:54:17 +0000 Subject: [PATCH 10/15] remove unneeded change MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Javier Chávarri --- src/dune_rules/lib.ml | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/dune_rules/lib.ml b/src/dune_rules/lib.ml index b9ec225bc6f..7d9829d688a 100644 --- a/src/dune_rules/lib.ml +++ b/src/dune_rules/lib.ml @@ -1211,7 +1211,10 @@ end = struct in to_status ~db ~name filtered_libs) | Invalid e -> Memo.return (Status.Invalid e) - | Not_found -> find_in_parent ~db ~name + | Not_found -> + (match db.parent with + | None -> Memo.return Status.Not_found + | Some db -> find_internal db name) | Hidden { lib = info; reason = hidden; path = _ } -> (match db.parent with | None -> Memo.return Status.Not_found From 583255ca409893dbf6c8eddb9f8bd0b24fb2204f Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Javier=20Ch=C3=A1varri?= Date: Fri, 15 Mar 2024 12:07:50 +0000 Subject: [PATCH 11/15] attempt to fix mixed public/private cases MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Javier Chávarri --- src/dune_rules/lib.ml | 141 ++++++++---------- src/dune_rules/lib.mli | 5 +- src/dune_rules/scope.ml | 55 ++++--- .../eif-library-name-collision-same-folder.t | 14 ++ .../enabled_if/eif-library-name-collision.t | 17 +++ .../lib-collision-private-same-folder.t | 4 +- .../lib-collision/lib-collision-private.t | 12 +- 7 files changed, 141 insertions(+), 107 deletions(-) diff --git a/src/dune_rules/lib.ml b/src/dune_rules/lib.ml index 7d9829d688a..56c7431d6cc 100644 --- a/src/dune_rules/lib.ml +++ b/src/dune_rules/lib.ml @@ -418,11 +418,12 @@ type db = and resolve_result = | Not_found - | Found of Lib_info.external_ list + | Found of Lib_info.external_ | Hidden of Lib_info.external_ Hidden.t | Invalid of User_message.t | Ignore - | Redirect_in_the_same_db of (Loc.t * Lib_name.t) list + | Redirect_in_the_same_db of (Loc.t * Lib_name.t) + | Multiple_results of resolve_result list | Redirect of db * (Loc.t * Lib_name.t) | Deprecated_library_name of (Loc.t * Lib_name.t) @@ -1143,73 +1144,70 @@ end = struct | Hidden h -> Hidden.error h ~loc ~name >>| Option.some ;; - let find_in_parent ~db ~name = - let open Memo.O in - let+ res = - match db.parent with - | None -> Memo.return Status.Not_found - | Some db -> find_internal db name - in - res - ;; - - let to_status ~db ~name = function - | [] -> find_in_parent ~db ~name - | info :: [] -> instantiate db name info ~hidden:None - | a :: b :: _ -> - let loc = Lib_info.loc b in - let dir_a = Lib_info.src_dir a in - let dir_b = Lib_info.src_dir b in - Memo.return (Status.Invalid (Error.duplicated ~loc ~name ~dir_a ~dir_b)) - ;; - let resolve_name db name = let open Memo.O in db.resolve name >>= function | Ignore -> Memo.return Status.Ignore | Deprecated_library_name (_, name') -> find_internal db name' - | Redirect_in_the_same_db redirects -> - let result = List.map ~f:(fun (_, name') -> find_internal db name') redirects in - let* statuses = - Memo.List.map result ~f:(fun redirect -> - let* r = redirect in - Memo.return r) - in - Memo.return - (List.fold_left statuses ~init:Status.Not_found ~f:(fun acc status -> - match acc, status with - | Status.Found a, Status.Found b -> - let a = info a in - let b = info b in - let loc = Lib_info.loc b in - let dir_a = Lib_info.src_dir a in - let dir_b = Lib_info.src_dir b in - Status.Invalid (Error.duplicated ~loc ~name ~dir_a ~dir_b) - | Invalid _, _ -> acc - | (Found _ as lib), (Hidden _ | Ignore | Not_found | Invalid _) - | (Hidden _ | Ignore | Not_found), (Found _ as lib) -> lib - | (Hidden _ | Ignore | Not_found), (Hidden _ | Ignore | Not_found | Invalid _) - -> acc)) + | Redirect_in_the_same_db (_, name') -> find_internal db name' | Redirect (db', (_, name')) -> find_internal db' name' - | Found libs -> + | Found info -> instantiate db name info ~hidden:None + | Multiple_results libs -> + let* libs = + Memo.List.filter_map + ~f:(function + | Ignore -> Memo.return (Some Status.Ignore) + | Deprecated_library_name (_, name') -> + find_internal db name' >>| fun f -> Some f + | Redirect_in_the_same_db (_, name') -> + find_internal db name' >>| fun f -> Some f + | Redirect (db', (_, name')) -> find_internal db' name' >>| fun f -> Some f + | Found info -> + let* enabled = Lib_info.enabled info in + (match enabled with + | Disabled_because_of_enabled_if -> Memo.return None + | Normal | Optional -> + instantiate db name info ~hidden:None >>| fun f -> Some f) + | Multiple_results _libs -> + (* There can't be nested Multiple_results *) assert false + | Invalid e -> Memo.return (Some (Status.Invalid e)) + | Not_found -> + (match db.parent with + | None -> Memo.return (Some Status.Not_found) + | Some db -> find_internal db name >>| fun f -> Some f) + | Hidden { lib = info; reason = hidden; path = _ } -> + (match db.parent with + | None -> Memo.return Status.Not_found + | Some db -> find_internal db name) + >>= (function + | Status.Found _ as x -> Memo.return (Some x) + | _ -> instantiate db name info ~hidden:(Some hidden) >>| fun f -> Some f)) + libs + in (match libs with - | [] | _ :: [] -> + | [] -> assert false + | [ status ] -> (* In case we have 0 or 1 results found, convert to [Status.t] directly. This allows to provide better errors later on, e.g. `Library "foo" in _build/default is hidden (unsatisfied 'enabled_if') *) - to_status ~db ~name libs - | _ :: _ :: _ -> - (* If there are multiple results found, we optimistically pre-filter to - remove those that are disabled *) - let* filtered_libs = - Memo.List.filter libs ~f:(fun lib -> - let+ enabled = Lib_info.enabled lib in - match enabled with - | Disabled_because_of_enabled_if -> false - | Normal | Optional -> true) - in - to_status ~db ~name filtered_libs) + Memo.return status + | _ :: _ :: _ as statuses -> + Memo.return + (List.fold_left statuses ~init:Status.Not_found ~f:(fun acc status -> + match acc, status with + | Status.Found a, Status.Found b -> + let a = info a in + let b = info b in + let loc = Lib_info.loc b in + let dir_a = Lib_info.src_dir a in + let dir_b = Lib_info.src_dir b in + Status.Invalid (Error.duplicated ~loc ~name ~dir_a ~dir_b) + | Invalid _, _ -> acc + | (Found _ as lib), (Hidden _ | Ignore | Not_found | Invalid _) + | (Hidden _ | Ignore | Not_found), (Found _ as lib) -> lib + | ( (Hidden _ | Ignore | Not_found) + , (Hidden _ | Ignore | Not_found | Invalid _) ) -> acc))) | Invalid e -> Memo.return (Status.Invalid e) | Not_found -> (match db.parent with @@ -1844,35 +1842,28 @@ end module DB = struct module Resolve_result = struct - type t = resolve_result = - | Not_found - | Found of Lib_info.external_ list - | Hidden of Lib_info.external_ Hidden.t - | Invalid of User_message.t - | Ignore - | Redirect_in_the_same_db of (Loc.t * Lib_name.t) list - | Redirect of db * (Loc.t * Lib_name.t) - | Deprecated_library_name of (Loc.t * Lib_name.t) + type t = resolve_result let found f = Found f let not_found = Not_found let redirect db lib = Redirect (db, lib) - let redirect_in_the_same_db libs = Redirect_in_the_same_db libs + let redirect_in_the_same_db lib = Redirect_in_the_same_db lib + let multiple_results libs = Multiple_results libs let deprecated_library_name lib = Deprecated_library_name lib - let to_dyn x = + let rec to_dyn x = let open Dyn in match x with | Not_found -> variant "Not_found" [] | Invalid e -> variant "Invalid" [ Dyn.string (User_message.to_string e) ] - | Found libs -> variant "Found" [ (Dyn.list (Lib_info.to_dyn Path.to_dyn)) libs ] + | Found lib -> variant "Found" [ Lib_info.to_dyn Path.to_dyn lib ] | Hidden h -> variant "Hidden" [ Hidden.to_dyn (Lib_info.to_dyn Path.to_dyn) h ] | Ignore -> variant "Ignore" [] | Redirect (_, (_, name)) -> variant "Redirect" [ Lib_name.to_dyn name ] - | Redirect_in_the_same_db redirects -> - variant - "Redirect_in_the_same_db" - [ (Dyn.list (fun (_, name) -> Lib_name.to_dyn name)) redirects ] + | Redirect_in_the_same_db (_, name) -> + variant "Redirect_in_the_same_db" [ Lib_name.to_dyn name ] + | Multiple_results redirects -> + variant "Multiple_results" [ (Dyn.list to_dyn) redirects ] | Deprecated_library_name (_, name) -> variant "Deprecated_library_name" [ Lib_name.to_dyn name ] ;; @@ -1905,7 +1896,7 @@ module DB = struct let open Memo.O in Findlib.find findlib name >>| function - | Ok (Library pkg) -> Found [ Dune_package.Lib.info pkg ] + | Ok (Library pkg) -> Found (Dune_package.Lib.info pkg) | Ok (Deprecated_library_name d) -> Deprecated_library_name (d.loc, d.new_public_name) | Ok (Hidden_library pkg) -> Hidden (Hidden.unsatisfied_exist_if pkg) diff --git a/src/dune_rules/lib.mli b/src/dune_rules/lib.mli index 5320652a21a..20e0030ad0f 100644 --- a/src/dune_rules/lib.mli +++ b/src/dune_rules/lib.mli @@ -98,10 +98,11 @@ module DB : sig type t val not_found : t - val found : Lib_info.external_ list -> t + val found : Lib_info.external_ -> t val to_dyn : t Dyn.builder val redirect : db -> Loc.t * Lib_name.t -> t - val redirect_in_the_same_db : (Loc.t * Lib_name.t) list -> t + val redirect_in_the_same_db : Loc.t * Lib_name.t -> t + val multiple_results : t list -> t val deprecated_library_name : Loc.t * Lib_name.t -> t end diff --git a/src/dune_rules/scope.ml b/src/dune_rules/scope.ml index 8388a94605b..b9bb33d5844 100644 --- a/src/dune_rules/scope.ml +++ b/src/dune_rules/scope.ml @@ -25,27 +25,29 @@ module DB = struct module Found_or_redirect : sig type t = private - | Found of Lib_info.external_ list - | Redirect of (Loc.t * Lib_name.t) list + | Found of Lib_info.external_ + | Redirect of (Loc.t * Lib_name.t) + | Many of t list | Deprecated_library_name of (Loc.t * Lib_name.t) val redirect : Lib_name.t -> Loc.t * Lib_name.t -> Lib_name.t * t - val redirect_many : (Loc.t * Lib_name.t) list -> t + val many : t list -> t val deprecated_library_name : Lib_name.t -> Loc.t * Lib_name.t -> Lib_name.t * t - val found : Lib_info.external_ list -> t + val found : Lib_info.external_ -> t end = struct type t = - | Found of Lib_info.external_ list - | Redirect of (Loc.t * Lib_name.t) list + | Found of Lib_info.external_ + | Redirect of (Loc.t * Lib_name.t) + | Many of t list | Deprecated_library_name of (Loc.t * Lib_name.t) let redirect from (loc, to_) = if Lib_name.equal from to_ then Code_error.raise ~loc "Invalid redirect" [ "to_", Lib_name.to_dyn to_ ] - else from, Redirect [ loc, to_ ] + else from, Redirect (loc, to_) ;; - let redirect_many x = Redirect x + let many x = Many x let deprecated_library_name from (loc, to_) = if Lib_name.equal from to_ @@ -75,26 +77,22 @@ module DB = struct Found_or_redirect.deprecated_library_name old_public_name s.new_public_name | Library (dir, (conf : Library.t)) -> let info = Library.to_lib_info conf ~dir ~lib_config |> Lib_info.of_local in - Library.best_name conf, Found_or_redirect.found [ info ]) + Library.best_name conf, Found_or_redirect.found info) |> Lib_name.Map.of_list_reducei ~f:(fun name (v1 : Found_or_redirect.t) v2 -> let res = match v1, v2 with - | Found info1, Found info2 -> - Ok (Found_or_redirect.found (List.rev_append info1 info2)) - | Found info, Redirect redirect | Redirect redirect, Found info -> - let loc, _ = List.hd redirect in - Error (loc, Lib_info.loc (List.hd info)) + | Found _, Found _ + | Found _, Redirect _ + | Redirect _, Found _ + | Redirect _, Redirect _ -> Ok (Found_or_redirect.many [ v1; v2 ]) | Found info, Deprecated_library_name (loc, _) - | Deprecated_library_name (loc, _), Found info -> - Error (loc, Lib_info.loc (List.hd info)) - | Deprecated_library_name (loc2, lib2), Redirect redirect - | Redirect redirect, Deprecated_library_name (loc2, lib2) -> - let loc1, lib1 = List.hd redirect in + | Deprecated_library_name (loc, _), Found info -> Error (loc, Lib_info.loc info) + | Deprecated_library_name (loc2, lib2), Redirect (loc1, lib1) + | Redirect (loc1, lib1), Deprecated_library_name (loc2, lib2) -> if Lib_name.equal lib1 lib2 then Ok v1 else Error (loc1, loc2) - | Redirect redirect1, Redirect redirect2 -> - Ok (Found_or_redirect.redirect_many (List.rev_append redirect1 redirect2)) | Deprecated_library_name (loc1, lib1), Deprecated_library_name (loc2, lib2) -> if Lib_name.equal lib1 lib2 then Ok v1 else Error (loc1, loc2) + | Many _, _ | _, Many _ -> assert false in match res with | Ok x -> x @@ -126,6 +124,19 @@ module DB = struct (match Lib_name.Map.find map name with | None -> Lib.DB.Resolve_result.not_found | Some (Redirect lib) -> Lib.DB.Resolve_result.redirect_in_the_same_db lib + | Some (Many libs) -> + let results = + List.map + ~f:(function + | Found_or_redirect.Redirect lib -> + Lib.DB.Resolve_result.redirect_in_the_same_db lib + | Found lib -> Lib.DB.Resolve_result.found lib + | Deprecated_library_name lib -> + Lib.DB.Resolve_result.deprecated_library_name lib + | Many _ -> assert false) + libs + in + Lib.DB.Resolve_result.multiple_results results | Some (Deprecated_library_name lib) -> Lib.DB.Resolve_result.deprecated_library_name lib | Some (Found lib) -> Lib.DB.Resolve_result.found lib)) @@ -144,7 +155,7 @@ module DB = struct | Some (Project project) -> let scope = find_by_project (Fdecl.get t) project in Lib.DB.Resolve_result.redirect scope.db (Loc.none, name) - | Some (Name name) -> Lib.DB.Resolve_result.redirect_in_the_same_db [ name ] + | Some (Name name) -> Lib.DB.Resolve_result.redirect_in_the_same_db name ;; let public_theories ~find_db ~installed_theories coq_stanzas = diff --git a/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision-same-folder.t b/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision-same-folder.t index c7dd6150dc0..0756766f316 100644 --- a/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision-same-folder.t +++ b/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision-same-folder.t @@ -54,3 +54,17 @@ For public libraries > EOF $ dune build + +Mixing public and private libraries + + $ cat > dune << EOF + > (library + > (name foo) + > (enabled_if (= %{context_name} "default"))) + > (library + > (name foo) + > (public_name baz.foo) + > (enabled_if (= %{context_name} "alt-context"))) + > EOF + + $ dune build diff --git a/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision.t b/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision.t index f1a9f9492fb..1aa17eff19d 100644 --- a/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision.t +++ b/test/blackbox-tests/test-cases/enabled_if/eif-library-name-collision.t @@ -55,3 +55,20 @@ For public libraries > EOF $ dune build + +Mixing public and private libraries + + $ cat > a/dune << EOF + > (library + > (name foo) + > (enabled_if (= %{context_name} "default"))) + > EOF + + $ cat > b/dune << EOF + > (library + > (name foo) + > (public_name baz.foo) + > (enabled_if (= %{context_name} "alt-context"))) + > EOF + + $ dune build diff --git a/test/blackbox-tests/test-cases/lib-collision/lib-collision-private-same-folder.t b/test/blackbox-tests/test-cases/lib-collision/lib-collision-private-same-folder.t index ebd61016af6..023c2a622fc 100644 --- a/test/blackbox-tests/test-cases/lib-collision/lib-collision-private-same-folder.t +++ b/test/blackbox-tests/test-cases/lib-collision/lib-collision-private-same-folder.t @@ -16,7 +16,7 @@ Without any consumers of the libraries $ dune build Error: - File "dune", line 1, characters 0-21: + File "dune", line 3, 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. @@ -41,7 +41,7 @@ With some consumer of the library $ dune build Error: - File "dune", line 1, characters 0-21: + File "dune", line 3, 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. diff --git a/test/blackbox-tests/test-cases/lib-collision/lib-collision-private.t b/test/blackbox-tests/test-cases/lib-collision/lib-collision-private.t index 418d5587d34..bb154180d68 100644 --- a/test/blackbox-tests/test-cases/lib-collision/lib-collision-private.t +++ b/test/blackbox-tests/test-cases/lib-collision/lib-collision-private.t @@ -21,9 +21,9 @@ Without any consumers of the libraries $ dune build Error: - File "b/dune", line 1, characters 0-21: + File "a/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 + and _build/default/a. Either change one of the names, or enable them conditionally using the 'enabled_if' field. -> required by alias default @@ -43,16 +43,16 @@ With some consumer of the library $ dune build Error: - File "b/dune", line 1, characters 0-21: + File "a/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 + and _build/default/a. 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: + File "a/dune", line 1, characters 0-21: 1 | (library 2 | (name foo)) 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 + and _build/default/a. Either change one of the names, or enable them conditionally using the 'enabled_if' field. [1] From f9225401a60d2c8b9a862f88ec80c1f018417602 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Javier=20Ch=C3=A1varri?= Date: Fri, 15 Mar 2024 14:14:59 +0000 Subject: [PATCH 12/15] fix bug caused by non-exhaustive memoization MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Javier Chávarri --- src/dune_rules/lib.ml | 19 ++++++++++++------- src/dune_rules/lib_info.ml | 18 ++++++++++++++++++ src/dune_rules/lib_info.mli | 1 + .../lib-collision/lib-collision-private.t | 12 ++++++------ 4 files changed, 37 insertions(+), 13 deletions(-) diff --git a/src/dune_rules/lib.ml b/src/dune_rules/lib.ml index 56c7431d6cc..3ca4eaab40b 100644 --- a/src/dune_rules/lib.ml +++ b/src/dune_rules/lib.ml @@ -1098,7 +1098,10 @@ end = struct module Input = struct type t = Lib_name.t * Path.t Lib_info.t * string option - let equal (x, _, _) (y, _, _) = Lib_name.equal x y + let equal (lib_name, info, _) (lib_name', info', _) = + Lib_name.equal lib_name lib_name' && Lib_info.equal info info' + ;; + let hash (x, _, _) = Lib_name.hash x let to_dyn = Dyn.opaque end @@ -1192,16 +1195,18 @@ end = struct This allows to provide better errors later on, e.g. `Library "foo" in _build/default is hidden (unsatisfied 'enabled_if') *) Memo.return status - | _ :: _ :: _ as statuses -> + | _ :: _ :: _ -> Memo.return - (List.fold_left statuses ~init:Status.Not_found ~f:(fun acc status -> + (List.fold_left libs ~init:Status.Not_found ~f:(fun acc status -> match acc, status with | Status.Found a, Status.Found b -> - let a = info a in - let b = info b in + let a = info a + and b = info b in let loc = Lib_info.loc b in - let dir_a = Lib_info.src_dir a in - let dir_b = Lib_info.src_dir b in + let dir_a = Lib_info.best_src_dir a in + let dir_b = Lib_info.best_src_dir b in + (* print_endline ("a " ^ Dyn.to_string (Lib_info.to_dyn Path.to_dyn a)); + print_endline ("b " ^ Dyn.to_string (Lib_info.to_dyn Path.to_dyn b)); *) Status.Invalid (Error.duplicated ~loc ~name ~dir_a ~dir_b) | Invalid _, _ -> acc | (Found _ as lib), (Hidden _ | Ignore | Not_found | Invalid _) diff --git a/src/dune_rules/lib_info.ml b/src/dune_rules/lib_info.ml index 82599470f45..0947df4aafb 100644 --- a/src/dune_rules/lib_info.ml +++ b/src/dune_rules/lib_info.ml @@ -659,3 +659,21 @@ let for_dune_package (let dir = Obj_dir.dir obj_dir in fun p -> if Path.is_managed p then Path.relative dir (Path.basename p) else p) ;; + +let equal + (type a) + (t : a t) + { loc; name; kind; src_dir; orig_src_dir; obj_dir; path_kind; _ } + = + let path_equal : a -> a -> bool = + match (path_kind : a path) with + | Local -> Path.Build.equal + | External -> Path.equal + in + Loc.equal t.loc loc + && Lib_name.equal t.name name + && Lib_kind.equal t.kind kind + && path_equal src_dir t.src_dir + && Option.equal path_equal orig_src_dir t.orig_src_dir + && Obj_dir.equal obj_dir t.obj_dir +;; diff --git a/src/dune_rules/lib_info.mli b/src/dune_rules/lib_info.mli index bb1a0fe4d41..159f49fd8df 100644 --- a/src/dune_rules/lib_info.mli +++ b/src/dune_rules/lib_info.mli @@ -229,3 +229,4 @@ val create val package : _ t -> Package.Name.t option val to_dyn : 'path Dyn.builder -> 'path t Dyn.builder +val equal : 'a t -> 'a t -> bool diff --git a/test/blackbox-tests/test-cases/lib-collision/lib-collision-private.t b/test/blackbox-tests/test-cases/lib-collision/lib-collision-private.t index bb154180d68..418d5587d34 100644 --- a/test/blackbox-tests/test-cases/lib-collision/lib-collision-private.t +++ b/test/blackbox-tests/test-cases/lib-collision/lib-collision-private.t @@ -21,9 +21,9 @@ Without any consumers of the libraries $ dune build Error: - File "a/dune", line 1, characters 0-21: + 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/a. Either change one of the names, or enable them + and _build/default/b. Either change one of the names, or enable them conditionally using the 'enabled_if' field. -> required by alias default @@ -43,16 +43,16 @@ With some consumer of the library $ dune build Error: - File "a/dune", line 1, characters 0-21: + 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/a. Either change one of the names, or enable them + and _build/default/b. Either change one of the names, or enable them conditionally using the 'enabled_if' field. -> required by alias default - File "a/dune", line 1, characters 0-21: + File "b/dune", line 1, characters 0-21: 1 | (library 2 | (name foo)) Error: A library with name "foo" is defined in two folders: _build/default/a - and _build/default/a. Either change one of the names, or enable them + and _build/default/b. Either change one of the names, or enable them conditionally using the 'enabled_if' field. [1] From f01cee424dd134e6c24ea711f2c13b775097ff3e Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Javier=20Ch=C3=A1varri?= Date: Fri, 15 Mar 2024 14:32:28 +0000 Subject: [PATCH 13/15] cleanup logs MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Javier Chávarri --- src/dune_rules/lib.ml | 2 -- 1 file changed, 2 deletions(-) diff --git a/src/dune_rules/lib.ml b/src/dune_rules/lib.ml index 3ca4eaab40b..6ce0aeb5bef 100644 --- a/src/dune_rules/lib.ml +++ b/src/dune_rules/lib.ml @@ -1205,8 +1205,6 @@ end = struct let loc = Lib_info.loc b in let dir_a = Lib_info.best_src_dir a in let dir_b = Lib_info.best_src_dir b in - (* print_endline ("a " ^ Dyn.to_string (Lib_info.to_dyn Path.to_dyn a)); - print_endline ("b " ^ Dyn.to_string (Lib_info.to_dyn Path.to_dyn b)); *) Status.Invalid (Error.duplicated ~loc ~name ~dir_a ~dir_b) | Invalid _, _ -> acc | (Found _ as lib), (Hidden _ | Ignore | Not_found | Invalid _) From 81381b75efc99f7d11ac4fd559e278fcf8367a77 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Javier=20Ch=C3=A1varri?= Date: Fri, 15 Mar 2024 14:37:54 +0000 Subject: [PATCH 14/15] remove obsolete comment MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Javier Chávarri --- src/dune_rules/lib.ml | 6 +----- 1 file changed, 1 insertion(+), 5 deletions(-) diff --git a/src/dune_rules/lib.ml b/src/dune_rules/lib.ml index 6ce0aeb5bef..54aef2f5be9 100644 --- a/src/dune_rules/lib.ml +++ b/src/dune_rules/lib.ml @@ -1190,11 +1190,7 @@ end = struct in (match libs with | [] -> assert false - | [ status ] -> - (* In case we have 0 or 1 results found, convert to [Status.t] directly. - This allows to provide better errors later on, - e.g. `Library "foo" in _build/default is hidden (unsatisfied 'enabled_if') *) - Memo.return status + | [ status ] -> Memo.return status | _ :: _ :: _ -> Memo.return (List.fold_left libs ~init:Status.Not_found ~f:(fun acc status -> From 44eb127866b90fe8df1f9ddd6262a0edbd58a42c Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Javier=20Ch=C3=A1varri?= Date: Fri, 15 Mar 2024 15:33:30 +0000 Subject: [PATCH 15/15] update tests MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Javier Chávarri --- .../lib-collision/lib-collision-private-same-folder.t | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/test/blackbox-tests/test-cases/lib-collision/lib-collision-private-same-folder.t b/test/blackbox-tests/test-cases/lib-collision/lib-collision-private-same-folder.t index 023c2a622fc..ebd61016af6 100644 --- a/test/blackbox-tests/test-cases/lib-collision/lib-collision-private-same-folder.t +++ b/test/blackbox-tests/test-cases/lib-collision/lib-collision-private-same-folder.t @@ -16,7 +16,7 @@ Without any consumers of the libraries $ dune build Error: - File "dune", line 3, characters 0-21: + 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. @@ -41,7 +41,7 @@ With some consumer of the library $ dune build Error: - File "dune", line 3, characters 0-21: + 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.