diff --git a/CHANGES.md b/CHANGES.md index 21c06e98ba1..5e711e75822 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -91,24 +91,27 @@ - Get rid of ad-hoc rules for guessing the version. Dune now only relies on the version written in the `dune-project` file and no longer read `VERSION` or similar files (#2541, @diml) - -- In `(diff? x y)` action, require `x` to exist and register a + +- In `(diff? x y)` action, require `x` to exist and register a dependency on that file. (#2486, @aalekseyev) - On Windows, an .exe suffix is no longer added implicitly to binary names that already end in .exe. Second, when resolving binary names, .opt variants are no longer chosen automatically. (#2543, @nojb) -- Make `(diff? x y)` move the correction file (`y`) away from the build - directory to promotion staging area. - This makes corrections work with sandboxing and in general reduces build - directory pollution. (#2486, @aalekseyev, fixes #2482) +- Make `(diff? x y)` move the correction file (`y`) away from the build + directory to promotion staging area. This makes corrections work with + sandboxing and in general reduces build directory pollution. (#2486, + @aalekseyev, fixes #2482) - Fix a ppx hash collision in watch mode (#2546, fixes #2520, @diml) - Remove the optimisation of passing `-nodynlink` for executalbes when not necessary. It seems to be breaking things (see #2527, @diml) +- Fix invalid library names in `dune-package` files. Only public names should + exist in such files. (#2558, fix #2425, @rgrinberg) + 1.11.0 (23/07/2019) ------------------- diff --git a/src/dune/install_rules.ml b/src/dune/install_rules.ml index fa88c34065e..09ccad300ca 100644 --- a/src/dune/install_rules.ml +++ b/src/dune/install_rules.ml @@ -268,7 +268,7 @@ let gen_dune_package sctx pkg = let libs = Super_context.libs_of_package sctx pkg.name |> Lib.Local.Set.to_list - |> List.map ~f:(fun lib -> + |> Result.List.map ~f:(fun lib -> let dir_contents = let info = Lib.Local.info lib in let dir = Lib_info.src_dir info in @@ -289,6 +289,7 @@ let gen_dune_package sctx pkg = Lib.to_dune_lib lib ~dir:(Path.build (lib_root lib)) ~modules ~foreign_objects) + |> Result.ok_exn in Dune_package.Or_meta.Dune_package { Dune_package.version = pkg.version diff --git a/src/dune/lib.ml b/src/dune/lib.ml index 9efccf4dc08..9812a4fa9d0 100644 --- a/src/dune/lib.ml +++ b/src/dune/lib.ml @@ -148,9 +148,9 @@ module Error = struct let name = Lib_info.name private_dep in make ~loc [ Pp.textf - "Library %S is private, it cannot be a dependency of a public library." - (Lib_name.to_string name) - ; Pp.textf "You need to give %S a public name." (Lib_name.to_string name) + "Library %S is private, it cannot be a dependency of a public \ + library. You need to give %S a public name." + (Lib_name.to_string name) (Lib_name.to_string name) ] let not_virtual_lib ~loc ~impl ~not_vlib = @@ -1755,15 +1755,34 @@ let to_dune_lib ({ name; info; _ } as lib) ~modules ~foreign_objects ~dir = let synopsis = Lib_info.synopsis info in let archives = Lib_info.archives info in let plugins = Lib_info.plugins info in - let implements = Lib_info.implements info in let modes = Lib_info.modes info in let kind = Lib_info.kind info in let version = Lib_info.version info in let jsoo_runtime = Lib_info.jsoo_runtime info in let special_builtin_support = Lib_info.special_builtin_support info in - let default_implementation = Lib_info.default_implementation info in let known_implementations = Lib_info.known_implementations info in let foreign_archives = Lib_info.foreign_archives info in + let use_public_name ~lib_field ~info_field = + match (info_field, lib_field) with + | Some _, None + |None, Some _ -> + assert false + | None, None -> Ok None + | Some (loc, _), Some field -> + let open Result.O in + let+ field = field in + Some (loc, field.name) + in + let open Result.O in + let* implements = + use_public_name ~info_field:(Lib_info.implements info) + ~lib_field:(implements lib) + in + let+ default_implementation = + use_public_name + ~info_field:(Lib_info.default_implementation info) + ~lib_field:(Option.map ~f:Lazy.force lib.default_implementation) + in Dune_package.Lib.make ~obj_dir ~orig_src_dir ~name ~loc ~kind ~synopsis ~version ~archives ~plugins ~foreign_archives ~foreign_objects ~jsoo_runtime diff --git a/src/dune/lib.mli b/src/dune/lib.mli index 1cff767b1b3..46947c6c4e5 100644 --- a/src/dune/lib.mli +++ b/src/dune/lib.mli @@ -269,7 +269,7 @@ val to_dune_lib : -> modules:Modules.t -> foreign_objects:Path.t list -> dir:Path.t - -> (Syntax.Version.t * Dune_lang.t list) Dune_package.Lib.t + -> (Syntax.Version.t * Dune_lang.t list) Dune_package.Lib.t Or_exn.t module Local : sig type lib diff --git a/test/blackbox-tests/test-cases/private-public-overlap/run.t b/test/blackbox-tests/test-cases/private-public-overlap/run.t index e09babe7025..912cdd64305 100644 --- a/test/blackbox-tests/test-cases/private-public-overlap/run.t +++ b/test/blackbox-tests/test-cases/private-public-overlap/run.t @@ -6,8 +6,7 @@ public libraries may not have private dependencies 8 | (libraries privatelib) ^^^^^^^^^^ Error: Library "privatelib" is private, it cannot be a dependency of a public - library. - You need to give "privatelib" a public name. + library. You need to give "privatelib" a public name. ocamldep .publiclib.objs/publiclib.ml.d [1] @@ -33,8 +32,7 @@ Unless they introduce private runtime dependencies: 16 | (pps private_ppx)) ^^^^^^^^^^^ Error: Library "private_runtime_dep" is private, it cannot be a dependency of - a public library. - You need to give "private_runtime_dep" a public name. + a public library. You need to give "private_runtime_dep" a public name. ocamlc .private_ppx.objs/byte/private_ppx.{cmi,cmo,cmt} ocamlopt .private_ppx.objs/native/private_ppx.{cmx,o} ocamlopt private_ppx.{a,cmxa} diff --git a/test/blackbox-tests/test-cases/vlib-default-impl/dune-package/a-default/dune b/test/blackbox-tests/test-cases/vlib-default-impl/dune-package/a-default/dune new file mode 100644 index 00000000000..40724106b6b --- /dev/null +++ b/test/blackbox-tests/test-cases/vlib-default-impl/dune-package/a-default/dune @@ -0,0 +1,4 @@ +(library + (name a_default) + (public_name a.default-impl) + (implements a)) diff --git a/test/blackbox-tests/test-cases/vlib-default-impl/dune-package/a-default/x.ml b/test/blackbox-tests/test-cases/vlib-default-impl/dune-package/a-default/x.ml new file mode 100644 index 00000000000..e69de29bb2d diff --git a/test/blackbox-tests/test-cases/vlib-default-impl/dune-package/dune b/test/blackbox-tests/test-cases/vlib-default-impl/dune-package/dune index 7296346d618..0c357acc58a 100644 --- a/test/blackbox-tests/test-cases/vlib-default-impl/dune-package/dune +++ b/test/blackbox-tests/test-cases/vlib-default-impl/dune-package/dune @@ -1,7 +1,7 @@ (library (public_name a) (virtual_modules x) - (default_implementation a-default)) + (default_implementation a_default)) (rule (with-stdout-to diff --git a/test/blackbox-tests/test-cases/vlib-default-impl/run.t b/test/blackbox-tests/test-cases/vlib-default-impl/run.t index 7698b48f40d..d1236fb899a 100644 --- a/test/blackbox-tests/test-cases/vlib-default-impl/run.t +++ b/test/blackbox-tests/test-cases/vlib-default-impl/run.t @@ -41,7 +41,7 @@ Check that default implementation data is installed in the dune package file. (kind normal) (virtual) (foreign_archives (native a$ext_lib)) - (default_implementation a-default) + (default_implementation a.default-impl) (main_module_name A) (modes byte native) (modules @@ -56,6 +56,32 @@ Check that default implementation data is installed in the dune package file. (kind alias) (impl)) (wrapped true)))) + (library + (name a.default-impl) + (kind normal) + (archives + (byte default-impl/a_default.cma) + (native default-impl/a_default.cmxa)) + (plugins + (byte default-impl/a_default.cma) + (native default-impl/a_default.cmxs)) + (foreign_archives (native default-impl/a_default$ext_lib)) + (requires a) + (implements a) + (main_module_name A) + (modes byte native) + (modules + (wrapped + (main_module_name A) + (modules + ((name X) (obj_name a__X) (visibility public) (kind impl_vmodule) (impl))) + (alias_module + (name A__a_default__) + (obj_name a__a_default__) + (visibility public) + (kind alias) + (impl)) + (wrapped true)))) Test default implementation for an external library diff --git a/test/blackbox-tests/test-cases/vlib/run.t b/test/blackbox-tests/test-cases/vlib/run.t index 917493fa5ee..1fc20eba3b3 100644 --- a/test/blackbox-tests/test-cases/vlib/run.t +++ b/test/blackbox-tests/test-cases/vlib/run.t @@ -328,7 +328,7 @@ Include variants and implementation information in dune-package (plugins (byte impl/impl.cma) (native impl/impl.cmxs)) (foreign_archives (native impl/impl$ext_lib)) (requires foo.vlib) - (implements vlib) + (implements foo.vlib) (main_module_name Vlib) (modes byte native) (modules