Skip to content

Commit d85eae5

Browse files
committed
Include non-platform-specific solver vars in portable lockdirs
Previously all expanded solver variables were omitted from lockdirs, as some solver variables are specific to the platform being solved for. This was too strict, and meant that non-platform-specific solver variables like "with-doc" were incorrectly omitted. This change adds non-platform-specific expanded solver variables to portable lockdirs. Signed-off-by: Stephen Sherratt <[email protected]>
1 parent 2346113 commit d85eae5

File tree

7 files changed

+83
-5
lines changed

7 files changed

+83
-5
lines changed

src/dune_pkg/lock_dir.ml

Lines changed: 11 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1154,6 +1154,7 @@ let create_latest_version
11541154
~repos
11551155
~expanded_solver_variable_bindings
11561156
~solved_for_platform
1157+
~portable_lock_dir
11571158
=
11581159
let packages =
11591160
Package_name.Map.map packages ~f:(fun (pkg : Pkg.t) ->
@@ -1187,6 +1188,15 @@ let create_latest_version
11871188
let solved_for_platform_platform_specific_only =
11881189
Option.map solved_for_platform ~f:Solver_env.remove_all_except_platform_specific
11891190
in
1191+
let expanded_solver_variable_bindings =
1192+
match portable_lock_dir with
1193+
| false -> expanded_solver_variable_bindings
1194+
| true ->
1195+
(* To make a portable lockdir, only include solver variables which are
1196+
not platform-specific. *)
1197+
Solver_stats.Expanded_variable_bindings.remove_platform_specific
1198+
expanded_solver_variable_bindings
1199+
in
11901200
{ version
11911201
; dependency_hash
11921202
; packages
@@ -1238,10 +1248,7 @@ let encode_metadata
12381248
| None -> []
12391249
| Some ocaml -> [ list sexp [ string "ocaml"; Package_name.encode (snd ocaml) ] ])
12401250
@ [ list sexp (string "repositories" :: Repositories.encode repos) ]
1241-
@ (if
1242-
portable_lock_dir
1243-
|| Solver_stats.Expanded_variable_bindings.is_empty
1244-
expanded_solver_variable_bindings
1251+
@ (if Solver_stats.Expanded_variable_bindings.is_empty expanded_solver_variable_bindings
12451252
then []
12461253
else
12471254
[ list

src/dune_pkg/lock_dir.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -127,6 +127,7 @@ val create_latest_version
127127
-> expanded_solver_variable_bindings:Solver_stats.Expanded_variable_bindings.t
128128
-> solved_for_platform:Solver_env.t option
129129
(* TODO: make this non-optional when portable lockdirs becomes the default *)
130+
-> portable_lock_dir:bool
130131
-> t
131132

132133
module Metadata : Dune_sexp.Versioned_file.S with type data := unit

src/dune_pkg/opam_solver.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1838,6 +1838,7 @@ let solve_lock_dir
18381838
~repos:(Some repos)
18391839
~expanded_solver_variable_bindings
18401840
~solved_for_platform:(Some solver_env)
1841+
~portable_lock_dir
18411842
in
18421843
let+ files =
18431844
match pkgs_by_name with

src/dune_pkg/solver_stats.ml

Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -145,4 +145,15 @@ module Expanded_variable_bindings = struct
145145
]
146146
~hints))
147147
;;
148+
149+
let remove_platform_specific { variable_values; unset_variables } =
150+
let is_platform_specific variable_name =
151+
Package_variable_name.Set.mem Package_variable_name.platform_specific variable_name
152+
in
153+
{ variable_values =
154+
List.filter variable_values ~f:(fun (variable_name, _) ->
155+
not (is_platform_specific variable_name))
156+
; unset_variables = List.filter unset_variables ~f:(Fun.negate is_platform_specific)
157+
}
158+
;;
148159
end

src/dune_pkg/solver_stats.mli

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -31,4 +31,7 @@ module Expanded_variable_bindings : sig
3131
common between [t] and [solver_env] is assigned the same value, and that
3232
all the unset variables in [t] are not assigned a value in [solver_env]. *)
3333
val validate_against_solver_env : t -> Solver_env.t -> unit
34+
35+
(** Remove all mention of platform-specific variables. *)
36+
val remove_platform_specific : t -> t
3437
end
Lines changed: 51 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,51 @@
1+
Test that the with-doc variable is stored in the lockdir when it's set in
2+
dune-workspace.
3+
4+
5+
$ . ../helpers.sh
6+
$ mkrepo
7+
$ add_mock_repo_if_needed
8+
9+
$ cat > dune-workspace <<EOF
10+
> (lang dune 3.20)
11+
> (pkg enabled)
12+
> (lock_dir
13+
> (repositories mock)
14+
> (solver_env
15+
> (with-doc true)))
16+
> (repository
17+
> (name mock)
18+
> (url "$PWD/mock-opam-repository"))
19+
> EOF
20+
21+
$ cat > dune-project <<EOF
22+
> (lang dune 3.18)
23+
> (package
24+
> (name x)
25+
> (depends (foo :with-doc)))
26+
> EOF
27+
28+
$ mkpkg foo
29+
30+
$ DUNE_CONFIG__PORTABLE_LOCK_DIR=enabled dune pkg lock
31+
Solution for dune.lock
32+
33+
This solution supports the following platforms:
34+
- arch = x86_64; os = linux
35+
- arch = arm64; os = linux
36+
- arch = x86_64; os = macos
37+
- arch = arm64; os = macos
38+
39+
Dependencies on all supported platforms:
40+
- foo.0.0.1
41+
42+
The list-locked-dependencies command does some validation that there are no
43+
extraneous packages in the lockdir. It uses the solver variables stored in the
44+
lockdir when filtering dependencies which have predicates such as ":with-doc".
45+
If the with-doc variable wasn't stored in the lockdir then this command would
46+
fail as the locked dependency "foo" would appear extraneous.
47+
$ dune describe pkg list-locked-dependencies
48+
Dependencies of local packages locked in dune.lock
49+
- Immediate dependencies of local package x.dev
50+
- foo.0.0.1
51+

test/expect-tests/dune_pkg/dune_pkg_unit_tests.ml

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -114,7 +114,8 @@ let%expect_test "encode/decode round trip test for lockdir with no deps" =
114114
~ocaml:None
115115
~repos:None
116116
~expanded_solver_variable_bindings:Expanded_variable_bindings.empty
117-
~solved_for_platform:None)
117+
~solved_for_platform:None
118+
~portable_lock_dir:false)
118119
();
119120
[%expect
120121
{|
@@ -167,6 +168,7 @@ let%expect_test "encode/decode round trip test for lockdir with simple deps" =
167168
; unset_variables = [ Package_variable_name.os_family ]
168169
}
169170
~solved_for_platform:None
171+
~portable_lock_dir:false
170172
(Package_name.Map.of_list_exn
171173
[ mk_pkg_basic ~name:"foo" ~version:(Package_version.of_string "0.1.0")
172174
; mk_pkg_basic ~name:"bar" ~version:(Package_version.of_string "0.2.0")
@@ -328,6 +330,7 @@ let%expect_test "encode/decode round trip test for lockdir with complex deps" =
328330
~repos:(Some [ opam_repo ])
329331
~expanded_solver_variable_bindings:Expanded_variable_bindings.empty
330332
~solved_for_platform:None
333+
~portable_lock_dir:false
331334
(Package_name.Map.of_list_exn [ pkg_a; pkg_b; pkg_c ])
332335
in
333336
lock_dir_encode_decode_round_trip_test ~lock_dir_path:"complex_lock_dir" ~lock_dir ();
@@ -475,6 +478,7 @@ let%expect_test "encode/decode round trip test with locked repo revision" =
475478
~repos:(Some [ opam_repo ])
476479
~expanded_solver_variable_bindings:Expanded_variable_bindings.empty
477480
~solved_for_platform:None
481+
~portable_lock_dir:false
478482
(Package_name.Map.of_list_exn [ pkg_a; pkg_b; pkg_c ])
479483
in
480484
lock_dir_encode_decode_round_trip_test

0 commit comments

Comments
 (0)