Skip to content

Commit e41d185

Browse files
Track whether the package had a dune dependency
We don't register the dependency because we will not build it but we add it to the type to know whether the package depended on Dune. Signed-off-by: Marek Kubica <marek@tarides.com>
1 parent 4313430 commit e41d185

File tree

1 file changed

+33
-29
lines changed

1 file changed

+33
-29
lines changed

src/dune_rules/pkg_rules.ml

Lines changed: 33 additions & 29 deletions
Original file line numberDiff line numberDiff line change
@@ -439,6 +439,7 @@ module Pkg = struct
439439
; build_command : Build_command.t option
440440
; install_command : Dune_lang.Action.t option
441441
; depends : t list
442+
; depends_on_dune : bool (* notes whether the package has a dependency on Dune *)
442443
; depexts : Depexts.t list
443444
; info : Pkg_info.t
444445
; paths : Path.t Paths.t
@@ -1143,33 +1144,15 @@ module Action_expander = struct
11431144

11441145
let sandbox = Sandbox_mode.Set.singleton Sandbox_mode.copy
11451146

1146-
let rec action_contains_run action =
1147-
match (action : Dune_lang.Action.t) with
1148-
| Run _ -> true
1149-
| Progn actions -> actions |> List.find ~f:action_contains_run |> Option.is_some
1150-
| When (_, action) -> action_contains_run action
1151-
| Withenv (_, action) -> action_contains_run action
1152-
| _ -> false
1153-
;;
1154-
11551147
let expand context (pkg : Pkg.t) action =
1156-
let depend_on_dune =
1157-
match action_contains_run action with
1158-
| false -> Action_builder.return ()
1159-
| true ->
1160-
Path.External.of_string Sys.executable_name
1161-
|> Path.external_
1162-
|> Action_builder.path
1163-
in
11641148
let+ action =
11651149
let expander = expander context pkg in
11661150
expand action ~expander >>| Action.chdir pkg.paths.source_dir
11671151
in
11681152
(* TODO copying is needed for build systems that aren't dune and those
11691153
with an explicit install step *)
1170-
let open Action_builder.O in
1171-
depend_on_dune
1172-
>>> (Action.Full.make ~sandbox action |> Action_builder.return)
1154+
Action.Full.make ~sandbox action
1155+
|> Action_builder.return
11731156
|> Action_builder.with_no_targets
11741157
;;
11751158

@@ -1220,6 +1203,7 @@ module DB = struct
12201203
type entry =
12211204
{ pkg : Pkg.t
12221205
; deps : dep list
1206+
; has_dune_dep : bool
12231207
; pkg_digest : Pkg_digest.t
12241208
}
12251209

@@ -1249,24 +1233,30 @@ module DB = struct
12491233
Package.Name.Table.find_or_add cache pkg.info.name ~f:(fun name ->
12501234
let seen_set = Package.Name.Set.add seen_set name in
12511235
let seen_list = pkg :: seen_list in
1252-
let deps =
1236+
let system_deps, deps =
12531237
Dune_pkg.Lock_dir.Conditional_choice.choose_for_platform pkg.depends ~platform
12541238
|> Option.value ~default:[]
1255-
|> List.filter_map
1239+
|> List.partition_map
12561240
~f:(fun { Dune_pkg.Lock_dir.Dependency.name; loc = dep_loc } ->
12571241
if Package.Name.Set.mem system_provided name
1258-
then None
1242+
then Left name
12591243
else (
12601244
let dep_pkg = Package.Name.Map.find_exn pkgs_by_name name in
12611245
let dep_entry = compute_entry dep_pkg ~seen_set ~seen_list in
1262-
Some { dep_pkg; dep_loc; dep_pkg_digest = dep_entry.pkg_digest }))
1246+
Right { dep_pkg; dep_loc; dep_pkg_digest = dep_entry.pkg_digest }))
1247+
in
1248+
let has_dune_dep =
1249+
List.mem
1250+
~equal:Dune_lang.Package_name.equal
1251+
system_deps
1252+
Dune_pkg.Dune_dep.name
12631253
in
12641254
let pkg_digest =
12651255
Pkg_digest.create
12661256
pkg
12671257
(List.map deps ~f:(fun { dep_pkg_digest; _ } -> dep_pkg_digest))
12681258
in
1269-
{ pkg; deps; pkg_digest })
1259+
{ pkg; deps; has_dune_dep; pkg_digest })
12701260
in
12711261
Package.Name.Map.map
12721262
pkgs_by_name
@@ -1289,8 +1279,8 @@ module DB = struct
12891279
dependencies are identical as a sanity check. *)
12901280
let union_check
12911281
pkg_digest
1292-
({ pkg = pkg_a; deps = deps_a; pkg_digest = _ } as entry)
1293-
{ pkg = pkg_b; deps = deps_b; pkg_digest = _ }
1282+
({ pkg = pkg_a; deps = deps_a; has_dune_dep = _; pkg_digest = _ } as entry)
1283+
{ pkg = pkg_b; deps = deps_b; has_dune_dep = _; pkg_digest = _ }
12941284
=
12951285
if not (Pkg.equal (Pkg.remove_locs pkg_a) (Pkg.remove_locs pkg_b))
12961286
then
@@ -1493,6 +1483,7 @@ end = struct
14931483
; enabled_on_platforms = _
14941484
} as pkg
14951485
; deps
1486+
; has_dune_dep
14961487
; pkg_digest = _
14971488
} ->
14981489
assert (Package.Name.equal pkg_digest.name info.name);
@@ -1607,6 +1598,7 @@ end = struct
16071598
; build_command
16081599
; install_command
16091600
; depends
1601+
; depends_on_dune = has_dune_dep
16101602
; depexts
16111603
; paths
16121604
; write_paths
@@ -2252,9 +2244,21 @@ let build_rule context_name ~source_deps (pkg : Pkg.t) =
22522244
|> Action_builder.progn
22532245
in
22542246
let deps = Dep.Set.union source_deps (Pkg.package_deps pkg) in
2247+
let depend_on_dune =
2248+
match pkg.depends_on_dune with
2249+
| false -> Action_builder.return ()
2250+
| true ->
2251+
Sys.executable_name
2252+
|> Path.External.of_string
2253+
|> Path.external_
2254+
|> Action_builder.path
2255+
in
2256+
let open Action_builder.O in
2257+
let action_builder =
2258+
Action_builder.deps deps >>> depend_on_dune |> Action_builder.with_no_targets
2259+
in
22552260
let open Action_builder.With_targets.O in
2256-
Action_builder.deps deps
2257-
|> Action_builder.with_no_targets
2261+
action_builder
22582262
(* TODO should we add env deps on these? *)
22592263
>>> add_env (Pkg.exported_env pkg) build_action
22602264
|> Action_builder.With_targets.add_directories

0 commit comments

Comments
 (0)