-
Notifications
You must be signed in to change notification settings - Fork 416
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
feature: dune show targets and dune show aliases
Add a `dune show targets` and `dune show aliases` command for showing targets and aliases in a directory like `ls`. fix #265 Signed-off-by: Ali Caglayan <[email protected]>
- Loading branch information
Showing
14 changed files
with
342 additions
and
0 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,65 @@ | ||
open Import | ||
open Stdune | ||
|
||
let doc = "Print aliases in a given directory. Works similalry to ls." | ||
|
||
let pp_aliases ~header ~(contexts : Context.t list) path = | ||
let dir = Path.of_string path in | ||
let root = | ||
match (dir : Path.t) with | ||
| External e -> | ||
Code_error.raise "target_hint: external path" | ||
[ ("path", Path.External.to_dyn e) ] | ||
| In_source_tree d -> d | ||
| In_build_dir d -> ( | ||
match Path.Build.drop_build_context d with | ||
| Some d -> d | ||
| None -> Path.Source.root) | ||
in | ||
let open Action_builder.O in | ||
let+ alias_targets = | ||
let+ load_dir = | ||
Action_builder.List.map contexts ~f:(fun ctx -> | ||
let dir = | ||
Path.Build.append_source | ||
(Dune_engine.Context_name.build_dir (Context.name ctx)) | ||
root | ||
|> Path.build | ||
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 | ||
(if header then [ Pp.textf "%s:" (Path.to_string dir) ] else []) | ||
@ [ Pp.concat_map alias_targets ~f:Pp.text ~sep:Pp.newline ] | ||
|> Pp.concat ~sep:Pp.newline | ||
|
||
let term = | ||
let+ common = Common.term | ||
and+ paths = Arg.(value & pos_all string [ "." ] & info [] ~docv:"DIR") in | ||
let config = Common.init common in | ||
let request (setup : Dune_rules.Main.build_system) = | ||
let header = List.length paths > 1 in | ||
let open Action_builder.O in | ||
let+ paragraphs = | ||
Action_builder.List.map paths | ||
~f:(pp_aliases ~header ~contexts:setup.contexts) | ||
in | ||
paragraphs | ||
|> Pp.concat ~sep:(Pp.seq Pp.newline Pp.newline) | ||
|> List.singleton |> User_message.make |> User_message.print | ||
in | ||
Scheduler.go ~common ~config @@ fun () -> | ||
let open Fiber.O in | ||
Build_cmd.run_build_system ~common ~request >>| ignore | ||
|
||
let command = Cmd.v (Cmd.info "aliases" ~doc ~envs:Common.envs) term |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,5 @@ | ||
open Import | ||
|
||
(** The aliases command lists all the aliases available in the given directory, | ||
defaulting to the current working direcctory. *) | ||
val command : unit Cmd.t |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,70 @@ | ||
open Import | ||
open Stdune | ||
|
||
let pp_all_direct_targets ~header path = | ||
let dir = Path.of_string path in | ||
let root = | ||
match (dir : Path.t) with | ||
| External e -> | ||
Code_error.raise "target_hint: external path" | ||
[ ("path", Path.External.to_dyn e) ] | ||
| In_source_tree d -> d | ||
| In_build_dir d -> ( | ||
match Path.Build.drop_build_context d with | ||
| Some d -> d | ||
| None -> Path.Source.root) | ||
in | ||
let open Action_builder.O in | ||
let+ targets = | ||
let open Memo.O in | ||
Action_builder.of_memo | ||
(Target.all_direct_targets (Some root) >>| Path.Build.Map.to_list) | ||
in | ||
let targets = | ||
if Path.is_in_build_dir dir then | ||
List.map ~f:(fun (path, k) -> (Path.build path, k)) targets | ||
else | ||
List.map targets ~f:(fun (path, k) -> | ||
match Path.Build.extract_build_context path with | ||
| None -> (Path.build path, k) | ||
| Some (_, path) -> (Path.source path, k)) | ||
in | ||
let targets = | ||
(* Only suggest hints for the basename, otherwise it's slow when there are | ||
lots of files *) | ||
List.filter_map targets ~f:(fun (path, kind) -> | ||
if Path.equal (Path.parent_exn path) dir then | ||
(* directory targets can be distinguied by the trailing path seperator *) | ||
Some | ||
(match kind with | ||
| File -> Path.basename path | ||
| Directory -> Path.basename path ^ Filename.dir_sep) | ||
else None) | ||
in | ||
(if header then [ Pp.textf "%s:" (Path.to_string dir) ] else []) | ||
@ [ Pp.concat_map targets ~f:Pp.text ~sep:Pp.newline ] | ||
|> Pp.concat ~sep:Pp.newline | ||
|
||
let term = | ||
let+ common = Common.term | ||
and+ paths = Arg.(value & pos_all string [ "." ] & info [] ~docv:"DIR") in | ||
let config = Common.init common in | ||
let request (_ : Dune_rules.Main.build_system) = | ||
let header = List.length paths > 1 in | ||
let open Action_builder.O in | ||
let+ paragraphs = | ||
Action_builder.List.map paths ~f:(pp_all_direct_targets ~header) | ||
in | ||
paragraphs | ||
|> Pp.concat ~sep:(Pp.seq Pp.newline Pp.newline) | ||
|> List.singleton |> User_message.make |> User_message.print | ||
in | ||
Scheduler.go ~common ~config @@ fun () -> | ||
let open Fiber.O in | ||
Build_cmd.run_build_system ~common ~request >>| ignore | ||
|
||
let command = | ||
let doc = | ||
"Print available targets in a given directory. Works similalry to ls." | ||
in | ||
Cmd.v (Cmd.info "targets" ~doc ~envs:Common.envs) term |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,5 @@ | ||
open Import | ||
|
||
(** The targets command lists all the targets available in the given directory, | ||
defaulting to the current working direcctory. *) | ||
val command : unit Cmd.t |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1 @@ | ||
(lang dune 3.8) |
107 changes: 107 additions & 0 deletions
107
test/blackbox-tests/test-cases/describe/aliases.t/run.t
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,107 @@ | ||
Testing the "dune show aliases" command. This command shows the aliases in the | ||
current directory. It acts similarly to ls. It will not show aliases that appear | ||
in subdirectories although this could be changed in the future. | ||
|
||
In an empty dune project, the following aliases are available. | ||
|
||
$ dune show aliases | ||
all | ||
default | ||
fmt | ||
|
||
User defined aliases can be added to a dune file. These should be picked up by | ||
the command. | ||
|
||
$ cat > dune << EOF | ||
> (alias | ||
> (name foo)) | ||
> EOF | ||
|
||
$ dune show aliases | ||
all | ||
default | ||
fmt | ||
foo | ||
|
||
Aliases in subdirectories should not be picked up. | ||
|
||
$ mkdir subdir | ||
$ cat > subdir/dune << EOF | ||
> (alias | ||
> (name bar)) | ||
> EOF | ||
|
||
$ dune show aliases | ||
all | ||
default | ||
fmt | ||
foo | ||
|
||
But checking the subdirectory it should be available. | ||
|
||
$ dune show aliases subdir | ||
all | ||
bar | ||
default | ||
fmt | ||
|
||
Adding an OCaml library will introduce OCaml specific aliases: | ||
|
||
$ cat > dune << EOF | ||
> (library | ||
> (name foo)) | ||
> EOF | ||
|
||
$ dune show aliases | ||
all | ||
check | ||
default | ||
doc-private | ||
fmt | ||
|
||
Adding a cram test will introduce an alias with the name of the test and also | ||
introduce the runtest alias: | ||
bbb | ||
$ rm dune | ||
$ cat > mytest.t | ||
|
||
$ dune show aliases | ||
all | ||
default | ||
fmt | ||
mytest | ||
runtest | ||
|
||
We can also show aliases in multiple directories at once: | ||
|
||
$ dune show aliases . subdir | ||
.: | ||
all | ||
default | ||
fmt | ||
mytest | ||
runtest | ||
|
||
subdir: | ||
all | ||
bar | ||
default | ||
fmt | ||
|
||
Including those in the _build/ directory: | ||
|
||
$ dune build | ||
$ dune show aliases . _build/default | ||
.: | ||
all | ||
default | ||
fmt | ||
mytest | ||
runtest | ||
|
||
_build/default: | ||
all | ||
default | ||
fmt | ||
mytest | ||
runtest |
Empty file.
Empty file.
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,2 @@ | ||
(library | ||
(name simple2)) |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,10 @@ | ||
(library | ||
(name simple)) | ||
|
||
(rule | ||
(targets | ||
(dir d)) | ||
(action | ||
(progn | ||
(run mkdir d) | ||
(run cat > d/foo)))) |
2 changes: 2 additions & 0 deletions
2
test/blackbox-tests/test-cases/describe/targets.t/dune-project
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,2 @@ | ||
(lang dune 3.8) | ||
(using directory-targets 0.1) |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,69 @@ | ||
Testing the "dune show targets" command in a simple OCaml project with an | ||
additional directory target to see the behaviour there. | ||
|
||
We have two libraries with one in a subdirectory. We also have a directory | ||
target d to see how the command will behave. | ||
|
||
With no directory provided to the command, it should default to the current | ||
working directory. | ||
|
||
$ dune show targets | ||
a.ml | ||
d/ | ||
dune | ||
dune-project | ||
simple.a | ||
simple.cma | ||
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. | ||
|
||
$ dune show targets . b/ | ||
.: | ||
a.ml | ||
d/ | ||
dune | ||
dune-project | ||
simple.a | ||
simple.cma | ||
simple.cmxa | ||
simple.cmxs | ||
simple.ml-gen | ||
|
||
b: | ||
c.ml | ||
dune | ||
simple2.a | ||
simple2.cma | ||
simple2.cmxa | ||
simple2.cmxs | ||
simple2.ml-gen | ||
|
||
The command also works with files in the _build directory. | ||
|
||
$ dune show targets _build/default/ | ||
a.ml | ||
d/ | ||
dune | ||
dune-project | ||
simple.a | ||
simple.cma | ||
simple.cmxa | ||
simple.cmxs | ||
simple.ml-gen | ||
|
||
$ dune show targets _build/default/b | ||
c.ml | ||
dune | ||
simple2.a | ||
simple2.cma | ||
simple2.cmxa | ||
simple2.cmxs | ||
simple2.ml-gen | ||
We cannot see inside directory targets | ||
|
||
$ dune show targets d | ||
|