Skip to content

Commit

Permalink
feature: add --aliases option to dune targets
Browse files Browse the repository at this point in the history
Signed-off-by: Ali Caglayan <[email protected]>
  • Loading branch information
Alizter committed May 22, 2023
1 parent 52fcac2 commit c82105a
Show file tree
Hide file tree
Showing 2 changed files with 62 additions and 6 deletions.
44 changes: 39 additions & 5 deletions bin/targets_cmd.ml
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ open Stdune

let doc = "Print available targets in a given directory. Works similalry to ls."

let pp_all_direct_targets path =
let pp_all_direct_targets ~(contexts : Context.t list) ~show_aliases path =
let dir = Path.of_string path in
let root =
match (dir : Path.t) with
Expand All @@ -17,7 +17,7 @@ let pp_all_direct_targets path =
| None -> Path.Source.root)
in
let open Action_builder.O in
let+ targets =
let* targets =
let open Memo.O in
Action_builder.of_memo
(Target.all_direct_targets (Some root) >>| Path.Build.Map.to_list)
Expand All @@ -43,18 +43,52 @@ let pp_all_direct_targets path =
| Directory -> Path.basename path ^ Filename.dir_sep)
else None)
in
let+ alias_targets =
let+ load_dir =
Action_builder.all
@@ List.map contexts ~f:(fun ctx ->
let dir =
Path.build
@@ Path.Build.append_source
(Dune_engine.Context_name.build_dir (Context.name ctx))
root
in
Action_builder.of_memo @@ Load_rules.load_dir ~dir)
in
List.fold_left load_dir ~init:Dune_engine.Alias.Name.Map.empty
~f:(fun acc x ->
match (x : Load_rules.Loaded.t) with
| Build build ->
Dune_engine.Alias.Name.Map.union
~f:(fun _ a _ -> Some a)
acc build.aliases
| _ -> acc)
|> Dune_engine.Alias.Name.Map.to_list_map ~f:(fun name _ ->
Dune_engine.Alias.Name.to_string name)
in
[ Pp.textf "%s:" (Path.to_string dir)
; Pp.concat_map targets ~f:Pp.text ~sep:Pp.newline
; (if show_aliases then
Pp.concat_map alias_targets
~f:(fun alias -> Pp.text ("@" ^ alias))
~sep:Pp.newline
else Pp.nop)
]
|> Pp.concat ~sep:Pp.newline

let term =
let+ common = Common.term
and+ paths = Arg.(value & pos_all string [ "." ] & info [] ~docv:"DIR") in
and+ paths = Arg.(value & pos_all string [ "." ] & info [] ~docv:"DIR")
and+ show_aliases =
Arg.(value & flag & info [ "aliases" ] ~doc:"Show aliases")
in
let config = Common.init common in
let request _setup =
let request (setup : Dune_rules.Main.build_system) =
let open Action_builder.O in
let+ paragraphs = Action_builder.List.map paths ~f:pp_all_direct_targets in
let+ paragraphs =
Action_builder.List.map paths
~f:(pp_all_direct_targets ~contexts:setup.contexts ~show_aliases)
in
paragraphs
|> Pp.concat ~sep:(Pp.seq Pp.newline Pp.newline)
|> List.singleton |> User_message.make |> User_message.print
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,7 @@ working directory.
simple.cmxa
simple.cmxs
simple.ml-gen


Multiple directories can be provided to the command. Also subdirectories may be
used, and only the targets available in that directory will be displayed.
Expand All @@ -34,6 +35,7 @@ used, and only the targets available in that directory will be displayed.
simple.cmxs
simple.ml-gen


b:
c.ml
dune
Expand All @@ -42,6 +44,7 @@ used, and only the targets available in that directory will be displayed.
simple2.cmxa
simple2.cmxs
simple2.ml-gen


The command also works with files in the _build directory.

Expand All @@ -56,6 +59,7 @@ The command also works with files in the _build directory.
simple.cmxa
simple.cmxs
simple.ml-gen


$ dune targets _build/default/b
_build/default/b:
Expand All @@ -66,10 +70,28 @@ The command also works with files in the _build directory.
simple2.cmxa
simple2.cmxs
simple2.ml-gen

We cannot see inside directory targets

$ dune targets d
d:


Testing the --aliases command too:

$ dune targets --aliases
.:
a.ml
d/
dune
dune-project
simple.a
simple.cma
simple.cmxa
simple.cmxs
simple.ml-gen
@all
@check
@default
@doc-private
@fmt

0 comments on commit c82105a

Please sign in to comment.