Skip to content

Commit

Permalink
Add support for directory targets
Browse files Browse the repository at this point in the history
Signed-off-by: Andrey Mokhov <[email protected]>
  • Loading branch information
snowleopard committed Oct 25, 2021
1 parent 5306218 commit adbbc2a
Show file tree
Hide file tree
Showing 24 changed files with 939 additions and 226 deletions.
4 changes: 3 additions & 1 deletion bin/exec.ml
Original file line number Diff line number Diff line change
Expand Up @@ -72,10 +72,12 @@ let term =
let not_found () =
let open Memo.Build.O in
let+ hints =
(* CR-someday amokhov: Currently we do not provide hints for directory
targets but it would be nice to do that. *)
(* Good candidates for the "./x.exe" instead of "x.exe" error are
executables present in the current directory *)
let+ candidates =
Build_system.targets_of ~dir:(Path.build dir)
Build_system.file_targets_of ~dir:(Path.build dir)
>>| Path.Set.to_list
>>| List.filter ~f:(fun p -> Path.extension p = ".exe")
>>| List.map ~f:(fun p -> "./" ^ Path.basename p)
Expand Down
19 changes: 16 additions & 3 deletions bin/print_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -34,11 +34,16 @@ let print_rule_makefile ppf (rule : Dune_engine.Reflection.Rule.t) =
; Action.for_shell rule.action
]
in
(* Makefiles seem to allow directory targets, so we include them. *)
let targets =
Dune_engine.Targets.map rule.targets ~f:(fun ~files ~dirs ->
Path.Build.Set.union files dirs)
in
Format.fprintf ppf
"@[<hov 2>@{<makefile-stuff>%a:%t@}@]@,@<0>\t@{<makefile-action>%a@}@,@,"
(Format.pp_print_list ~pp_sep:Format.pp_print_space (fun ppf p ->
Format.pp_print_string ppf (Path.to_string p)))
(Targets.to_list_map rule.targets ~file:Path.build)
(List.map ~f:Path.build (Path.Build.Set.to_list targets))
(fun ppf ->
Path.Set.iter rule.expanded_deps ~f:(fun dep ->
Format.fprintf ppf "@ %s" (Path.to_string dep)))
Expand All @@ -49,14 +54,22 @@ let print_rule_sexp ppf (rule : Dune_engine.Reflection.Rule.t) =
Action.for_shell action |> Action.For_shell.encode
in
let paths ps = Dune_lang.Encoder.list Dpath.encode (Path.Set.to_list ps) in
let file_targets, dir_targets =
Dune_engine.Targets.map rule.targets ~f:(fun ~files ~dirs -> (files, dirs))
in
let targets =
Path.Build.Set.union file_targets
(Path.Build.Set.map dir_targets ~f:(fun target ->
Path.Build.relative target "*"))
in
let sexp =
Dune_lang.Encoder.record
(List.concat
[ [ ("deps", Dep.Set.encode rule.deps)
; ( "targets"
, paths
(Targets.to_list_map rule.targets ~file:Fun.id
|> Path.set_of_build_paths_list) )
(Path.Build.Set.to_list targets |> Path.set_of_build_paths_list)
)
]
; (match rule.context with
| None -> []
Expand Down
6 changes: 3 additions & 3 deletions otherlibs/stdune-unstable/user_error.ml
Original file line number Diff line number Diff line change
Expand Up @@ -68,13 +68,13 @@ let has_embedded_location annots =
List.exists annots ~f:(fun annot ->
Annot.Has_embedded_location.check annot (fun () -> true) (fun () -> false))

let has_location (msg : User_message.t) annots =
(not (is_loc_none msg.loc)) || has_embedded_location annots

let needs_stack_trace annots =
List.exists annots ~f:(fun annot ->
Annot.Needs_stack_trace.check annot (fun () -> true) (fun () -> false))

let has_location (msg : User_message.t) annots =
(not (is_loc_none msg.loc)) || has_embedded_location annots

let () =
Printexc.register_printer (function
| E (t, []) -> Some (Format.asprintf "%a@?" Pp.to_fmt (User_message.pp t))
Expand Down
4 changes: 2 additions & 2 deletions src/dune_engine/action_builder.ml
Original file line number Diff line number Diff line change
Expand Up @@ -185,8 +185,8 @@ module With_targets = struct
| xs ->
let build, targets =
List.fold_left xs ~init:([], Targets.empty)
~f:(fun (builds, targets) x ->
(x.build :: builds, Targets.combine x.targets targets))
~f:(fun (acc_build, acc_targets) x ->
(x.build :: acc_build, Targets.combine acc_targets x.targets))
in
{ build = all (List.rev build); targets }

Expand Down
10 changes: 9 additions & 1 deletion src/dune_engine/action_exec.ml
Original file line number Diff line number Diff line change
Expand Up @@ -127,7 +127,15 @@ let exec_run_dynamic_client ~ectx ~eenv prog args =
let to_relative path =
path |> Stdune.Path.build |> Stdune.Path.reach ~from:eenv.working_dir
in
Targets.to_list_map ectx.targets ~file:to_relative |> String.Set.of_list
let file_targets, (_dir_targets_not_allowed : Nothing.t list) =
Targets.to_list_map ectx.targets ~file:to_relative
~dir:(fun _dir_target ->
User_error.raise ~loc:ectx.rule_loc
[ Pp.text
"Directory targets are not compatible with dynamic actions"
])
in
String.Set.of_list file_targets
in
DAP.Run_arguments.
{ prepared_dependencies = eenv.prepared_dependencies; targets }
Expand Down
Loading

0 comments on commit adbbc2a

Please sign in to comment.