Skip to content

Commit fb43b79

Browse files
committed
Experimental portable lockdirs
Adds a feature flag for enabling portable lockdirs. This is a proof of concept implementation of portable lockdirs where the entire solver runs for each of a set of platforms (combinations of architecture, OS, and in some cases the OS distribution) which most people are expected to use. This can easily be extended in the future to add more platforms or to allow projects to specify more platforms. To make lockdirs portable, the build/install commands and dependencies of each package are transformed into match statements, where the appropriate value for each platform is enumerated. At solve-time, the solver runs once for each platform, populating these fields. At build-time, the command/dependencies appropriate for the current platform are used. When the feature flag is not enabled dune's behaviour is unchanged. Signed-off-by: Stephen Sherratt <stephen@sherra.tt>
1 parent fc3996b commit fb43b79

28 files changed

+998
-181
lines changed

bin/describe/describe_depexts.ml

+9-2
Original file line numberDiff line numberDiff line change
@@ -22,13 +22,20 @@ let enumerate_lock_dirs_by_path workspace ~lock_dirs =
2222
let print_depexts ~lock_dirs_arg =
2323
let open Fiber.O in
2424
let open Lock_dir in
25-
let+ workspace = Memo.run (Workspace.workspace ()) in
25+
let+ workspace = Memo.run (Workspace.workspace ())
26+
and+ solver_env =
27+
Dune_pkg.Sys_poll.make ~path:(Env_path.path Stdune.Env.initial)
28+
|> Dune_pkg.Sys_poll.solver_env_from_current_system
29+
in
2630
let depexts =
2731
enumerate_lock_dirs_by_path workspace ~lock_dirs:lock_dirs_arg
2832
|> List.concat_map ~f:(fun lock_dir ->
2933
lock_dir.packages
3034
|> Package_name.Map.values
31-
|> List.concat_map ~f:(fun (pkg : Lock_dir.Pkg.t) -> pkg.depexts))
35+
|> List.concat_map ~f:(fun (pkg : Lock_dir.Pkg.t) ->
36+
match Lock_dir.Conditional_choice.find pkg.depexts solver_env with
37+
| Some depexts -> depexts
38+
| None -> []))
3239
in
3340
Console.print [ Pp.concat_map ~sep:Pp.newline ~f:Pp.verbatim depexts ]
3441
;;

bin/lock_dev_tool.ml

+1
Original file line numberDiff line numberDiff line change
@@ -82,6 +82,7 @@ let solve ~dev_tool ~local_packages =
8282
~version_preference:None
8383
~lock_dirs:[ lock_dir ]
8484
~print_perf_stats:false
85+
~portable_lock_dir:false
8586
;;
8687

8788
let compiler_package_name = Package_name.of_string "ocaml"

bin/pkg/lock.ml

+91-8
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
open Dune_config
12
open Import
23
open Pkg_common
34
module Package_version = Dune_pkg.Package_version
@@ -66,11 +67,75 @@ let resolve_project_pins project_pins =
6667
Pin_stanza.resolve project_pins ~scan_project
6768
;;
6869

70+
let solve_multiple_envs
71+
base_solver_env
72+
version_preference
73+
repos
74+
~pins
75+
~local_packages
76+
~constraints
77+
=
78+
let open Fiber.O in
79+
let solve_for_env env =
80+
Dune_pkg.Opam_solver.solve_lock_dir
81+
env
82+
version_preference
83+
repos
84+
~pins
85+
~local_packages
86+
~constraints
87+
in
88+
let portable_solver_env =
89+
(* TODO: make sure nothing system-specific sneaks into the environment here *)
90+
Dune_pkg.Solver_env.unset_multi
91+
base_solver_env
92+
Dune_lang.Package_variable_name.platform_specific
93+
in
94+
let+ results =
95+
Fiber.parallel_map Dune_pkg.Solver_env.popular_platform_envs ~f:(fun platform_env ->
96+
let solver_env = Dune_pkg.Solver_env.extend portable_solver_env platform_env in
97+
solve_for_env solver_env)
98+
in
99+
let results, errors =
100+
List.partition_map results ~f:(function
101+
| Ok result -> Left result
102+
| Error (`Diagnostic_message message) -> Right message)
103+
in
104+
match results with
105+
| [] -> Error errors
106+
| x :: xs ->
107+
Ok (List.fold_left xs ~init:x ~f:Dune_pkg.Opam_solver.Solver_result.merge, errors)
108+
;;
109+
110+
let solve_single_env
111+
solver_env
112+
version_preference
113+
repos
114+
~pins
115+
~local_packages
116+
~constraints
117+
=
118+
let open Fiber.O in
119+
let+ result =
120+
Dune_pkg.Opam_solver.solve_lock_dir
121+
solver_env
122+
version_preference
123+
repos
124+
~pins
125+
~local_packages
126+
~constraints
127+
in
128+
match result with
129+
| Ok result -> Ok (result, [])
130+
| Error (`Diagnostic_message message) -> Error [ message ]
131+
;;
132+
69133
let solve_lock_dir
70134
workspace
71135
~local_packages
72136
~project_pins
73137
~print_perf_stats
138+
~portable_lock_dir
74139
version_preference
75140
solver_env_from_current_system
76141
lock_dir_path
@@ -109,7 +174,8 @@ let solve_lock_dir
109174
let* pins = resolve_project_pins project_pins in
110175
let time_solve_start = Unix.gettimeofday () in
111176
progress_state := Some Progress_indicator.Per_lockdir.State.Solving;
112-
Dune_pkg.Opam_solver.solve_lock_dir
177+
let solve = if portable_lock_dir then solve_multiple_envs else solve_single_env in
178+
solve
113179
solver_env
114180
(Pkg_common.Version_preference.choose
115181
~from_arg:version_preference
@@ -121,8 +187,11 @@ let solve_lock_dir
121187
(Package_name.Map.map local_packages ~f:Dune_pkg.Local_package.for_solver)
122188
~constraints:(constraints_of_workspace workspace ~lock_dir_path)
123189
>>= function
124-
| Error (`Diagnostic_message message) -> Fiber.return (Error (lock_dir_path, message))
125-
| Ok { lock_dir; files; pinned_packages; num_expanded_packages } ->
190+
| Error messages -> Fiber.return (Error (lock_dir_path, messages))
191+
| Ok ({ lock_dir; files; pinned_packages; num_expanded_packages }, _errors) ->
192+
(* TODO: Users might want to know if no solution was found on certain
193+
platforms. Give the option to print the solver errors, even if a
194+
solution was found on some platforms. *)
126195
let time_end = Unix.gettimeofday () in
127196
let maybe_perf_stats =
128197
if print_perf_stats
@@ -149,7 +218,13 @@ let solve_lock_dir
149218
in
150219
progress_state := None;
151220
let+ lock_dir = Lock_dir.compute_missing_checksums ~pinned_packages lock_dir in
152-
Ok (Lock_dir.Write_disk.prepare ~lock_dir_path ~files lock_dir, summary_message)
221+
Ok
222+
( Lock_dir.Write_disk.prepare
223+
~portable:portable_lock_dir
224+
~lock_dir_path
225+
~files
226+
lock_dir
227+
, summary_message )
153228
;;
154229

155230
let solve
@@ -160,6 +235,7 @@ let solve
160235
~version_preference
161236
~lock_dirs
162237
~print_perf_stats
238+
~portable_lock_dir
163239
=
164240
let open Fiber.O in
165241
(* a list of thunks that will perform all the file IO side
@@ -182,6 +258,7 @@ let solve
182258
~local_packages
183259
~project_pins
184260
~print_perf_stats
261+
~portable_lock_dir
185262
version_preference
186263
solver_env_from_current_system
187264
lockdir_path
@@ -196,9 +273,9 @@ let solve
196273
| Error errors ->
197274
User_error.raise
198275
([ Pp.text "Unable to solve dependencies for the following lock directories:" ]
199-
@ List.concat_map errors ~f:(fun (path, message) ->
276+
@ List.concat_map errors ~f:(fun (path, messages) ->
200277
[ Pp.textf "Lock directory %s:" (Path.Source.to_string_maybe_quoted path)
201-
; Pp.hovbox message
278+
; Pp.hovbox (Pp.concat ~sep:Pp.newline messages)
202279
]))
203280
| Ok write_disks_with_summaries ->
204281
let write_disk_list, summary_messages = List.split write_disks_with_summaries in
@@ -214,7 +291,7 @@ let project_pins =
214291
Pin_stanza.DB.combine_exn acc (Dune_project.pins project))
215292
;;
216293

217-
let lock ~version_preference ~lock_dirs_arg ~print_perf_stats =
294+
let lock ~version_preference ~lock_dirs_arg ~print_perf_stats ~portable_lock_dir =
218295
let open Fiber.O in
219296
let* solver_env_from_current_system =
220297
Dune_pkg.Sys_poll.make ~path:(Env_path.path Stdune.Env.initial)
@@ -240,6 +317,7 @@ let lock ~version_preference ~lock_dirs_arg ~print_perf_stats =
240317
~version_preference
241318
~lock_dirs
242319
~print_perf_stats
320+
~portable_lock_dir
243321
;;
244322

245323
let term =
@@ -250,7 +328,12 @@ let term =
250328
let builder = Common.Builder.forbid_builds builder in
251329
let common, config = Common.init builder in
252330
Scheduler.go ~common ~config (fun () ->
253-
lock ~version_preference ~lock_dirs_arg ~print_perf_stats)
331+
let portable_lock_dir =
332+
match Config.get Dune_rules.Compile_time.portable_lock_dir with
333+
| `Enabled -> true
334+
| `Disabled -> false
335+
in
336+
lock ~version_preference ~lock_dirs_arg ~print_perf_stats ~portable_lock_dir)
254337
;;
255338

256339
let info =

bin/pkg/lock.mli

+1
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,7 @@ val solve
88
-> version_preference:Dune_pkg.Version_preference.t option
99
-> lock_dirs:Path.Source.t list
1010
-> print_perf_stats:bool
11+
-> portable_lock_dir:bool
1112
-> unit Fiber.t
1213

1314
(** Command to create lock directory *)

boot/configure.ml

+9-1
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,11 @@ let out =
1818
;;
1919

2020
let default_toggles : (string * [ `Disabled | `Enabled ]) list =
21-
[ "toolchains", `Enabled; "pkg_build_progress", `Disabled; "lock_dev_tool", `Disabled ]
21+
[ "toolchains", `Enabled
22+
; "pkg_build_progress", `Disabled
23+
; "lock_dev_tool", `Disabled
24+
; "portable_lock_dir", `Disabled
25+
]
2226
;;
2327

2428
let toggles = ref default_toggles
@@ -101,6 +105,10 @@ let () =
101105
, " Enable ocamlformat dev-tool, allows 'dune fmt' to build ocamlformat and use \
102106
it, independently from the project depenedencies .\n\
103107
\ This flag is experimental and shouldn't be relied on by packagers." )
108+
; ( "--portable-lock-dir"
109+
, toggle "portable_lock_dir"
110+
, "Generate portable lock dirs. If this feature is disabled then lock dirs will be \
111+
specialized to the machine where they are generated." )
104112
]
105113
in
106114
let anon s = bad "Don't know what to do with %s" s in

src/dune_lang/package_variable_name.ml

+4
Original file line numberDiff line numberDiff line change
@@ -53,6 +53,10 @@ let post = of_string "post"
5353
let one_of t xs = List.mem xs ~equal t
5454
let dev = of_string "dev"
5555

56+
let platform_specific =
57+
Set.of_list [ arch; os; os_version; os_distribution; os_family; sys_ocaml_version ]
58+
;;
59+
5660
module Project = struct
5761
let encode name = Dune_sexp.Encoder.string (":" ^ to_string name)
5862

src/dune_lang/package_variable_name.mli

+4
Original file line numberDiff line numberDiff line change
@@ -32,6 +32,10 @@ val build : t
3232
val dev : t
3333
val one_of : t -> t list -> bool
3434

35+
(** The set of variable names whose values are expected to differ depending on
36+
the current platform. *)
37+
val platform_specific : Set.t
38+
3539
module Project : sig
3640
val encode : t Dune_sexp.Encoder.t
3741
val decode : t Dune_sexp.Decoder.t

src/dune_pkg/file_entry.ml

+21
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,28 @@ type source =
44
| Path of Path.t
55
| Content of string
66

7+
let source_equal a b =
8+
match a, b with
9+
| Path a, Path b -> Path.equal a b
10+
| Content a, Content b -> String.equal a b
11+
| Path _, Content _ | Content _, Path _ -> false
12+
;;
13+
14+
let source_to_dyn = function
15+
| Path path -> Dyn.variant "Path" [ Path.to_dyn path ]
16+
| Content content -> Dyn.variant "Content" [ Dyn.string content ]
17+
;;
18+
719
type t =
820
{ original : source
921
; local_file : Path.Local.t
1022
}
23+
24+
let equal { original; local_file } t =
25+
source_equal original t.original && Path.Local.equal local_file t.local_file
26+
;;
27+
28+
let to_dyn { original; local_file } =
29+
Dyn.record
30+
[ "original", source_to_dyn original; "local_file", Path.Local.to_dyn local_file ]
31+
;;

src/dune_pkg/file_entry.mli

+3
Original file line numberDiff line numberDiff line change
@@ -8,3 +8,6 @@ type t =
88
{ original : source
99
; local_file : Path.Local.t
1010
}
11+
12+
val equal : t -> t -> bool
13+
val to_dyn : t -> Dyn.t

0 commit comments

Comments
 (0)