Skip to content

Commit

Permalink
fix(pkg): add location hash mismatch error (#11007)
Browse files Browse the repository at this point in the history
We use the lcok directory as the location rather than pointing at the
hash, as the user shouldn't really touch the hash.

Signed-off-by: Rudi Grinberg <me@rgrinberg.com>
  • Loading branch information
rgrinberg authored Oct 11, 2024
1 parent b39ad6d commit 1becc6e
Show file tree
Hide file tree
Showing 6 changed files with 15 additions and 10 deletions.
5 changes: 2 additions & 3 deletions src/dune_pkg/package_universe.ml
Original file line number Diff line number Diff line change
Expand Up @@ -143,9 +143,8 @@ let up_to_date local_packages ~dependency_hash:saved_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
| Some _, Some _ -> `Invalid
| Some _, None -> `Invalid
;;

let validate_dependency_hash local_packages ~saved_dependency_hash =
Expand Down
2 changes: 1 addition & 1 deletion src/dune_pkg/package_universe.mli
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@ val create
val up_to_date
: Local_package.t Package_name.Map.t
-> dependency_hash:Local_package.Dependency_hash.t option
-> [ `Valid | `Invalid of Local_package.Dependency_hash.t option ]
-> [ `Valid | `Invalid ]

(** Returns the dependencies of the specified package within the package
universe *)
Expand Down
6 changes: 4 additions & 2 deletions src/dune_rules/gen_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -663,7 +663,7 @@ let raise_on_lock_dir_out_of_sync =
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* path, lock_dir = Lock_dir.get_with_path ctx >>| User_error.ok_exn in
let+ local_packages =
Dune_load.packages ()
>>| Dune_lang.Package.Name.Map.map ~f:Dune_pkg.Local_package.of_package
Expand All @@ -674,9 +674,11 @@ let raise_on_lock_dir_out_of_sync =
~dependency_hash:(Option.map ~f:snd lock_dir.dependency_hash)
with
| `Valid -> ()
| `Invalid _ ->
| `Invalid ->
let loc = Loc.in_file (Path.source (Path.Source.relative path "lock.dune")) in
let hints = Pp.[ text "run dune pkg lock" ] in
User_error.raise
~loc
~hints
[ Pp.text "The lock dir is not sync with your dune-project" ]
else Memo.return ())
Expand Down
10 changes: 6 additions & 4 deletions src/dune_rules/lock_dir.ml
Original file line number Diff line number Diff line change
Expand Up @@ -128,9 +128,10 @@ let get_workspace_lock_dir ctx =
Workspace.find_lock_dir workspace path
;;

let get ctx =
let* result = get_path ctx >>| Option.value_exn >>= Load.load in
match result with
let get_with_path ctx =
let* path = get_path ctx >>| Option.value_exn in
Load.load path
>>= function
| Error e -> Memo.return (Error e)
| Ok lock_dir ->
let+ workspace_lock_dir = get_workspace_lock_dir ctx in
Expand All @@ -140,9 +141,10 @@ let get ctx =
Solver_stats.Expanded_variable_bindings.validate_against_solver_env
lock_dir.expanded_solver_variable_bindings
(workspace_lock_dir.solver_env |> Option.value ~default:Solver_env.empty));
Ok lock_dir
Ok (path, lock_dir)
;;

let get ctx = get_with_path ctx >>| Result.map ~f:snd
let get_exn ctx = get ctx >>| User_error.ok_exn

let of_dev_tool dev_tool =
Expand Down
1 change: 1 addition & 0 deletions src/dune_rules/lock_dir.mli
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@ module Pkg = Dune_pkg.Lock_dir.Pkg

type t := Dune_pkg.Lock_dir.t

val get_with_path : Context_name.t -> (Path.Source.t * t, User_message.t) result Memo.t
val get : Context_name.t -> (t, User_message.t) result Memo.t
val get_exn : Context_name.t -> t Memo.t
val of_dev_tool : Dune_pkg.Dev_tool.t -> t Memo.t
Expand Down
1 change: 1 addition & 0 deletions test/blackbox-tests/test-cases/pkg/lock-out-of-sync.t
Original file line number Diff line number Diff line change
Expand Up @@ -41,6 +41,7 @@ We add the bar dependency to the test package

It fails as we have not regenerated the lock:
$ dune build
File "dune.lock/lock.dune", line 1, characters 0-0:
Error: The lock dir is not sync with your dune-project
Hint: run dune pkg lock
[1]
Expand Down

0 comments on commit 1becc6e

Please sign in to comment.