Skip to content

Commit

Permalink
fix: correctly generate .install files (#7547)
Browse files Browse the repository at this point in the history
Previously, the contents of the .install file would depend on whether
the .opam install file would be present in the source.

This check is wrong whenever we generate the .opam file ourselves. This
commit checks if we are generating the .opam file.

Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg authored Apr 13, 2023
1 parent aaf675d commit e64f198
Show file tree
Hide file tree
Showing 9 changed files with 40 additions and 27 deletions.
4 changes: 4 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -101,6 +101,10 @@ Unreleased
- Allow `(package ...)` in any position within `(rule ...)` stanza (#7445,
@Leonidas-from-XIV)

- Always include `opam` files in the generated `.install` file. Previously, it
would not be included whenever `(generate_opam_files true)` was set and the
`.install` file wasn't yet generated. (#7547, @rgrinberg)

3.7.1 (2023-04-04)
------------------

Expand Down
24 changes: 16 additions & 8 deletions src/dune_rules/dune_project.ml
Original file line number Diff line number Diff line change
Expand Up @@ -730,7 +730,7 @@ let forbid_opam_files_relative_to_project opam_file_location packages =
]

let parse_packages (name : Name.t option) ~info ~dir ~version packages
opam_file_location opam_packages =
opam_file_location ~generate_opam_files opam_packages =
let open Memo.O in
let+ packages =
forbid_opam_files_relative_to_project opam_file_location opam_packages;
Expand Down Expand Up @@ -799,18 +799,26 @@ let parse_packages (name : Name.t option) ~info ~dir ~version packages
| Ok packages -> (
Memo.return
@@
let generated_opam_file =
if generate_opam_files then fun p ->
{ p with Package.has_opam_file = Generated }
else Fun.id
in
match opam_file_location with
| `Inside_opam_directory ->
Package.Name.Map.map packages ~f:(fun p ->
let dir = Path.Source.relative dir "opam" in
Package.set_inside_opam_dir p ~dir)
let p = Package.set_inside_opam_dir p ~dir in
generated_opam_file p)
| `Relative_to_project ->
Package.Name.Map.merge packages opam_packages
~f:(fun _name dune opam ->
match (dune, opam) with
| _, None -> dune
| None, None -> assert false
| Some p, None -> Some (generated_opam_file p)
| Some p, Some _ ->
Some { p with Package.has_opam_file = Exists true }
let p = { p with Package.has_opam_file = Exists true } in
Some (generated_opam_file p)
| None, Some (loc, _) ->
User_error.raise ~loc
[ Pp.text
Expand Down Expand Up @@ -907,10 +915,13 @@ let parse ~dir ~(lang : Lang.Instance.t) ~file =
Option.value opam_file_location
~default:(opam_file_location_default ~lang)
in
let generate_opam_files =
Option.value ~default:false generate_opam_files
in
let open Memo.O in
let+ packages =
parse_packages name ~info ~dir ~version packages opam_file_location
opam_packages
~generate_opam_files opam_packages
in
let name =
match name with
Expand Down Expand Up @@ -945,9 +956,6 @@ let parse ~dir ~(lang : Lang.Instance.t) ~file =
let explicit_js_mode =
Option.value explicit_js_mode ~default:(explicit_js_mode_default ~lang)
in
let generate_opam_files =
Option.value ~default:false generate_opam_files
in
let use_standard_c_and_cxx_flags =
match use_standard_c_and_cxx_flags with
| None -> use_standard_c_and_cxx_flags_default ~lang
Expand Down
20 changes: 9 additions & 11 deletions src/dune_rules/install_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -10,16 +10,14 @@ let install_file ~(package : Package.Name.t) ~findlib_toolchain =

module Package_paths = struct
let opam_file (ctx : Context.t) (pkg : Package.t) =
match pkg.has_opam_file with
| Exists false -> Memo.return None
| Exists true ->
Memo.return
@@ Some (Path.Build.append_source ctx.build_dir (Package.opam_file pkg))
| Look_inside_opam_dir -> (
let opam_file = Package.opam_file pkg in
Source_tree.file_exists opam_file >>| function
| true -> Some (Path.Build.append_source ctx.build_dir opam_file)
| false -> None)
let opam_file = Package.opam_file pkg in
let exists =
match pkg.has_opam_file with
| Exists b -> b
| Generated -> true
in
if exists then Some (Path.Build.append_source ctx.build_dir opam_file)
else None

let meta_file (ctx : Context.t) pkg =
Path.Build.append_source ctx.build_dir (Package.meta_file pkg)
Expand Down Expand Up @@ -419,7 +417,7 @@ end = struct
let+ init =
Package.Name.Map_traversals.parallel_map packages
~f:(fun _name (pkg : Package.t) ->
let* opam_file = Package_paths.opam_file ctx pkg in
let opam_file = Package_paths.opam_file ctx pkg in
let init =
let file section local_file dst =
Install.Entry.make section local_file ~kind:`File ~dst
Expand Down
9 changes: 3 additions & 6 deletions src/dune_rules/package.ml
Original file line number Diff line number Diff line change
Expand Up @@ -549,7 +549,7 @@ end

type opam_file =
| Exists of bool
| Look_inside_opam_dir
| Generated

type t =
{ id : Id.t
Expand Down Expand Up @@ -579,10 +579,7 @@ let name t = t.id.name
let dir t = t.id.dir

let set_inside_opam_dir t ~dir =
{ t with
has_opam_file = Look_inside_opam_dir
; opam_file = Path.Source.relative dir (Name.opam_fn t.id.name)
}
{ t with opam_file = Path.Source.relative dir (Name.opam_fn t.id.name) }

let encode (name : Name.t)
{ id = _
Expand Down Expand Up @@ -687,7 +684,7 @@ let dyn_of_opam_file =
let open Dyn in
function
| Exists b -> variant "Exists" [ bool b ]
| Look_inside_opam_dir -> variant "Look_inside_opam_dir" []
| Generated -> variant "Generated" []

let to_dyn
{ id
Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/package.mli
Original file line number Diff line number Diff line change
Expand Up @@ -142,7 +142,7 @@ end

type opam_file =
| Exists of bool
| Look_inside_opam_dir
| Generated

type t =
{ id : Id.t
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@ source tree if (generate_opam_files true) is enabled.

$ dune build foo.install
$ grep opam _build/default/foo.install
[1]
"_build/install/default/lib/foo/opam"

$ dune build @check
$ dune build foo.install
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -153,13 +153,15 @@ This is not allowed in toplevels, so it fails.
$ dune install --prefix _install --display short
Installing _install/lib/top-plugin1/META
Installing _install/lib/top-plugin1/dune-package
Installing _install/lib/top-plugin1/opam
Installing _install/lib/top-plugin1/plugin1_impl/plugin1_impl.cma
Installing _install/lib/top-plugin1/plugin1_impl/plugin1_impl.cmi
Installing _install/lib/top-plugin1/plugin1_impl/plugin1_impl.cmt
Installing _install/lib/top-plugin1/plugin1_impl/plugin1_impl.ml
Installing _install/lib/top_with_plugins/top_plugins/plugin1/META
Installing _install/lib/top-plugin2/META
Installing _install/lib/top-plugin2/dune-package
Installing _install/lib/top-plugin2/opam
Installing _install/lib/top-plugin2/plugin2_impl/plugin2_impl.cma
Installing _install/lib/top-plugin2/plugin2_impl/plugin2_impl.cmi
Installing _install/lib/top-plugin2/plugin2_impl/plugin2_impl.cmt
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -154,13 +154,15 @@ This is not allowed in toplevels, so it fails.
$ dune install --prefix _install --display short
Installing _install/lib/top-plugin1/META
Installing _install/lib/top-plugin1/dune-package
Installing _install/lib/top-plugin1/opam
Installing _install/lib/top-plugin1/plugin1_impl/plugin1_impl.cma
Installing _install/lib/top-plugin1/plugin1_impl/plugin1_impl.cmi
Installing _install/lib/top-plugin1/plugin1_impl/plugin1_impl.cmt
Installing _install/lib/top-plugin1/plugin1_impl/plugin1_impl.ml
Installing _install/lib/top_with_plugins/top_plugins/plugin1/META
Installing _install/lib/top-plugin2/META
Installing _install/lib/top-plugin2/dune-package
Installing _install/lib/top-plugin2/opam
Installing _install/lib/top-plugin2/plugin2_impl/plugin2_impl.cma
Installing _install/lib/top-plugin2/plugin2_impl/plugin2_impl.cmi
Installing _install/lib/top-plugin2/plugin2_impl/plugin2_impl.cmt
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -151,13 +151,15 @@ Testsuite for (toplevel that loads plugins).
$ dune install --prefix _install --display short
Installing _install/lib/top-plugin1/META
Installing _install/lib/top-plugin1/dune-package
Installing _install/lib/top-plugin1/opam
Installing _install/lib/top-plugin1/plugin1_impl/plugin1_impl.cma
Installing _install/lib/top-plugin1/plugin1_impl/plugin1_impl.cmi
Installing _install/lib/top-plugin1/plugin1_impl/plugin1_impl.cmt
Installing _install/lib/top-plugin1/plugin1_impl/plugin1_impl.ml
Installing _install/lib/top_with_plugins/top_plugins/plugin1/META
Installing _install/lib/top-plugin2/META
Installing _install/lib/top-plugin2/dune-package
Installing _install/lib/top-plugin2/opam
Installing _install/lib/top-plugin2/plugin2_impl/plugin2_impl.cma
Installing _install/lib/top-plugin2/plugin2_impl/plugin2_impl.cmi
Installing _install/lib/top-plugin2/plugin2_impl/plugin2_impl.cmt
Expand Down

0 comments on commit e64f198

Please sign in to comment.