Skip to content

Commit af76741

Browse files
committed
Add support for directory targets
Signed-off-by: Andrey Mokhov <[email protected]>
1 parent 5306218 commit af76741

26 files changed

+996
-274
lines changed

CHANGES.md

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -241,6 +241,9 @@ Unreleased
241241
- Allow to cancel the initial scan via Control+C (#4460, fixes #4364
242242
@jeremiedimino)
243243

244+
- Add experimental support for directory targets (#3316, #5025, Andrey Mokhov),
245+
enabled via `(using directory-targets 0.1)` in `dune-project`.
246+
244247
2.9.2 (unreleased)
245248
------------------
246249

bin/exec.ml

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -72,10 +72,12 @@ let term =
7272
let not_found () =
7373
let open Memo.Build.O in
7474
let+ hints =
75+
(* CR-someday amokhov: Currently we do not provide hints for directory
76+
targets but it would be nice to do that. *)
7577
(* Good candidates for the "./x.exe" instead of "x.exe" error are
7678
executables present in the current directory *)
7779
let+ candidates =
78-
Build_system.targets_of ~dir:(Path.build dir)
80+
Build_system.file_targets_of ~dir:(Path.build dir)
7981
>>| Path.Set.to_list
8082
>>| List.filter ~f:(fun p -> Path.extension p = ".exe")
8183
>>| List.map ~f:(fun p -> "./" ^ Path.basename p)

bin/print_rules.ml

Lines changed: 16 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -34,11 +34,16 @@ let print_rule_makefile ppf (rule : Dune_engine.Reflection.Rule.t) =
3434
; Action.for_shell rule.action
3535
]
3636
in
37+
(* Makefiles seem to allow directory targets, so we include them. *)
38+
let targets =
39+
Dune_engine.Targets.map rule.targets ~f:(fun ~files ~dirs ->
40+
Path.Build.Set.union files dirs)
41+
in
3742
Format.fprintf ppf
3843
"@[<hov 2>@{<makefile-stuff>%a:%t@}@]@,@<0>\t@{<makefile-action>%a@}@,@,"
3944
(Format.pp_print_list ~pp_sep:Format.pp_print_space (fun ppf p ->
4045
Format.pp_print_string ppf (Path.to_string p)))
41-
(Targets.to_list_map rule.targets ~file:Path.build)
46+
(List.map ~f:Path.build (Path.Build.Set.to_list targets))
4247
(fun ppf ->
4348
Path.Set.iter rule.expanded_deps ~f:(fun dep ->
4449
Format.fprintf ppf "@ %s" (Path.to_string dep)))
@@ -49,14 +54,22 @@ let print_rule_sexp ppf (rule : Dune_engine.Reflection.Rule.t) =
4954
Action.for_shell action |> Action.For_shell.encode
5055
in
5156
let paths ps = Dune_lang.Encoder.list Dpath.encode (Path.Set.to_list ps) in
57+
let file_targets, dir_targets =
58+
Dune_engine.Targets.map rule.targets ~f:(fun ~files ~dirs -> (files, dirs))
59+
in
60+
let targets =
61+
Path.Build.Set.union file_targets
62+
(Path.Build.Set.map dir_targets ~f:(fun target ->
63+
Path.Build.relative target "*"))
64+
in
5265
let sexp =
5366
Dune_lang.Encoder.record
5467
(List.concat
5568
[ [ ("deps", Dep.Set.encode rule.deps)
5669
; ( "targets"
5770
, paths
58-
(Targets.to_list_map rule.targets ~file:Fun.id
59-
|> Path.set_of_build_paths_list) )
71+
(Path.Build.Set.to_list targets |> Path.set_of_build_paths_list)
72+
)
6073
]
6174
; (match rule.context with
6275
| None -> []

doc/dune-files.rst

Lines changed: 54 additions & 48 deletions
Large diffs are not rendered by default.

otherlibs/stdune-unstable/user_error.ml

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -68,13 +68,13 @@ let has_embedded_location annots =
6868
List.exists annots ~f:(fun annot ->
6969
Annot.Has_embedded_location.check annot (fun () -> true) (fun () -> false))
7070

71-
let has_location (msg : User_message.t) annots =
72-
(not (is_loc_none msg.loc)) || has_embedded_location annots
73-
7471
let needs_stack_trace annots =
7572
List.exists annots ~f:(fun annot ->
7673
Annot.Needs_stack_trace.check annot (fun () -> true) (fun () -> false))
7774

75+
let has_location (msg : User_message.t) annots =
76+
(not (is_loc_none msg.loc)) || has_embedded_location annots
77+
7878
let () =
7979
Printexc.register_printer (function
8080
| E (t, []) -> Some (Format.asprintf "%a@?" Pp.to_fmt (User_message.pp t))

src/dune_engine/action_builder.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -185,8 +185,8 @@ module With_targets = struct
185185
| xs ->
186186
let build, targets =
187187
List.fold_left xs ~init:([], Targets.empty)
188-
~f:(fun (builds, targets) x ->
189-
(x.build :: builds, Targets.combine x.targets targets))
188+
~f:(fun (acc_build, acc_targets) x ->
189+
(x.build :: acc_build, Targets.combine acc_targets x.targets))
190190
in
191191
{ build = all (List.rev build); targets }
192192

src/dune_engine/action_exec.ml

Lines changed: 9 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -127,7 +127,15 @@ let exec_run_dynamic_client ~ectx ~eenv prog args =
127127
let to_relative path =
128128
path |> Stdune.Path.build |> Stdune.Path.reach ~from:eenv.working_dir
129129
in
130-
Targets.to_list_map ectx.targets ~file:to_relative |> String.Set.of_list
130+
let file_targets, (_dir_targets_not_allowed : Nothing.t list) =
131+
Targets.to_list_map ectx.targets ~file:to_relative
132+
~dir:(fun _dir_target ->
133+
User_error.raise ~loc:ectx.rule_loc
134+
[ Pp.text
135+
"Directory targets are not compatible with dynamic actions"
136+
])
137+
in
138+
String.Set.of_list file_targets
131139
in
132140
DAP.Run_arguments.
133141
{ prepared_dependencies = eenv.prepared_dependencies; targets }

0 commit comments

Comments
 (0)