Skip to content

Commit

Permalink
feat: dune build asks for relocking (#10851)
Browse files Browse the repository at this point in the history
* feat: ask to re run dune pkg lock on change

Signed-off-by: Etienne Marais <[email protected]>
  • Loading branch information
maiste authored Sep 16, 2024
1 parent 0a4a468 commit faff7ff
Show file tree
Hide file tree
Showing 4 changed files with 110 additions and 1 deletion.
21 changes: 21 additions & 0 deletions src/dune_pkg/package_universe.ml
Original file line number Diff line number Diff line change
Expand Up @@ -127,6 +127,27 @@ let check_for_unnecessary_packges_in_lock_dir
])
;;

let up_to_date local_packages (lock_dir : Lock_dir.t) =
let local_packages =
Package_name.Map.values local_packages |> List.map ~f:Local_package.for_solver
in
let non_local_dependencies =
Local_package.For_solver.list_non_local_dependency_set local_packages
in
let dependency_hash = Local_package.Dependency_set.hash non_local_dependencies in
match lock_dir.dependency_hash, dependency_hash with
| None, None -> `Valid
| Some (_, lock_dir_dependency_hash), Some non_local_dependencies_hash
when Local_package.Dependency_hash.equal
lock_dir_dependency_hash
non_local_dependencies_hash -> `Valid
| None, Some _ ->
`Valid (* This case happens when the user writes themselves their lock.dune. *)
| Some _, Some non_local_dependencies_hash ->
`Invalid (Some non_local_dependencies_hash)
| Some _, None -> `Invalid None
;;

let validate_dependency_hash { local_packages; lock_dir; _ } =
let local_packages =
Package_name.Map.values local_packages |> List.map ~f:Local_package.for_solver
Expand Down
8 changes: 8 additions & 0 deletions src/dune_pkg/package_universe.mli
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,14 @@ val create
-> Lock_dir.t
-> (t, User_message.t) result

(** Verifies if the dependencies described in the project file are still
synchronize with the dependencies selected in the lock directroy. If it is
not the case, it returns the hash of the new dependency set. *)
val up_to_date
: Local_package.t Package_name.Map.t
-> Lock_dir.t
-> [ `Valid | `Invalid of Local_package.Dependency_hash.t option ]

(** Returns the dependencies of the specified package within the package
universe *)
val opam_package_dependencies_of_package
Expand Down
28 changes: 27 additions & 1 deletion src/dune_rules/gen_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -656,6 +656,30 @@ let private_context ~dir components _ctx =
Gen_rules.make ~build_dir_only_sub_dirs (Memo.return Rules.empty)
;;

let raise_on_lock_dir_out_of_sync =
Per_context.create_by_name ~name:"check-lock-dir" (fun ctx ->
Memo.lazy_ (fun () ->
let open Memo.O in
let* lock_dir_available = Lock_dir.lock_dir_active ctx in
if lock_dir_available
then
let* lock_dir = Lock_dir.get_exn ctx in
let+ local_packages =
Dune_load.packages ()
>>| Dune_lang.Package.Name.Map.map ~f:Dune_pkg.Local_package.of_package
in
match Dune_pkg.Package_universe.up_to_date local_packages lock_dir with
| `Valid -> ()
| `Invalid _ ->
let hints = Pp.[ text "run dune pkg lock" ] in
User_error.raise
~hints
[ Pp.text "The lock dir is not sync with your dune-project" ]
else Memo.return ())
|> Memo.Lazy.force)
|> Staged.unstage
;;

let gen_rules ctx ~dir components =
if Context_name.equal ctx Install.Context.install_context.name
then (
Expand Down Expand Up @@ -684,5 +708,7 @@ let gen_rules ctx ~dir components =
then private_context ~dir components ctx
else if Context_name.equal ctx Fetch_rules.context.name
then Fetch_rules.gen_rules ~dir ~components
else gen_rules ctx (Super_context.find_exn ctx) ~dir components
else
let* () = raise_on_lock_dir_out_of_sync ctx in
gen_rules ctx (Super_context.find_exn ctx) ~dir components
;;
54 changes: 54 additions & 0 deletions test/blackbox-tests/test-cases/pkg/lock-out-of-sync.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,54 @@
Trying to build a package after updating the dependencies in dune-project but
without running `dune pkg lock` must raise an error in the context of Dune
Package Managemenet.

$ . ./helpers.sh

Create a fake project and lock it:

$ mkrepo
$ mkpkg foo <<EOF
> build: [ "echo" "foo" ]
> EOF
$ mkpkg bar <<EOF
> build: [ "echo" "bar" ]
> EOF

$ cat > dune-project <<EOF
> (lang dune 3.16)
> (package
> (name test)
> (allow_empty)
> (depends foo))
> EOF
$ add_mock_repo_if_needed
$ dune pkg lock
Solution for dune.lock:
- foo.0.0.1

As the lock file is syncronised with `dune-pkg`, the build succeeds:
$ dune build
foo

We add the bar dependency to the test package
$ cat > dune-project <<EOF
> (lang dune 3.16)
> (package
> (name test)
> (allow_empty)
> (depends foo bar))
> EOF

It fails as we have not regenerated the lock:
$ dune build
Error: The lock dir is not sync with your dune-project
Hint: run dune pkg lock
[1]

We fix it and the build succeeds again:
$ dune pkg lock
Solution for dune.lock:
- bar.0.0.1
- foo.0.0.1
$ dune build
bar

0 comments on commit faff7ff

Please sign in to comment.