Skip to content

Commit 07b1b7d

Browse files
authored
feat: Add dune describe tests command with comprehensive support (#12545)
Implement a new subcommand to list all test stanzas (unit tests, CRAM, and inline tests) with metadata including name, location, target, package, and enabled status. - Support for Tests.T, Cram_stanza.T, and Library stanzas (for inline tests). - Generate actionable targets for IDE integration: - `.exe` for unit tests. - `@dir/runtest` for CRAM. - `@dir/runtest-<lib_name>` for inline tests. - Handle multiple tests per stanza as separate entries. - Add comprehensive test suite in describe-tests.t. Fixes #12030 Signed-off-by: Rodrigue LEITAO--PEREIRA DIAS <[email protected]> Signed-off-by: Rudi Grinberg <[email protected]>
1 parent 658f0cb commit 07b1b7d

File tree

6 files changed

+479
-0
lines changed

6 files changed

+479
-0
lines changed

bin/describe/describe.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -22,6 +22,7 @@ let subcommands =
2222
; Describe_contexts.command
2323
; Describe_depexts.command
2424
; Describe_location.command
25+
; Describe_tests.command
2526
]
2627
;;
2728

bin/describe/describe_tests.ml

Lines changed: 159 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,159 @@
1+
open Import
2+
open Dune_rules
3+
4+
module Test_description = struct
5+
type t =
6+
{ name : string
7+
; source_dir : string
8+
; package : string option
9+
; enabled : bool
10+
; location : string
11+
; target : string
12+
}
13+
14+
let to_dyn { name; source_dir; package; enabled; location; target } =
15+
let open Dyn in
16+
record
17+
[ "name", string name
18+
; "source_dir", string source_dir
19+
; "package", option string package
20+
; "enabled", bool enabled
21+
; "location", string location
22+
; "target", string target
23+
]
24+
;;
25+
end
26+
27+
module Crawl = struct
28+
open Memo.O
29+
30+
(* Collect all (stanza, dir, expander) for test-related stanzas *)
31+
let collect_test_stanzas
32+
({ Import.Main.contexts = _; scontexts } : Import.Main.build_system)
33+
(context : Context.t)
34+
: (Stanza.t * Path.Build.t * Expander.t) list Memo.t
35+
=
36+
let context_name = Context.name context in
37+
let sctx = Context_name.Map.find_exn scontexts context_name in
38+
let* dune_files = Dune_load.dune_files context_name in
39+
Memo.parallel_map dune_files ~f:(fun (dune_file : Dune_file.t) ->
40+
Dune_file.stanzas dune_file
41+
>>= fun stanzas ->
42+
let dir =
43+
Path.Build.append_source (Context.build_dir context) (Dune_file.dir dune_file)
44+
in
45+
let* expander = Super_context.expander sctx ~dir in
46+
Memo.return
47+
(List.filter_map stanzas ~f:(fun stanza ->
48+
match Stanza.repr stanza with
49+
| Tests.T _ | Cram_stanza.T _ -> Some (stanza, dir, expander)
50+
| Library.T lib ->
51+
(match
52+
Sub_system_name.Map.find lib.sub_systems Inline_tests_info.Tests.name
53+
with
54+
| Some (Dune_rules.Inline_tests_info.Tests.T _) ->
55+
Some (stanza, dir, expander)
56+
| _ -> None)
57+
| _ -> None)))
58+
>>| List.concat
59+
;;
60+
61+
(* Transform a stanza into a list of Test_description.t *)
62+
let describe_stanza stanza dir expander : Test_description.t list Memo.t =
63+
match Stanza.repr stanza with
64+
| Tests.T (tests : Tests.t) ->
65+
let* enabled = Expander.eval_blang expander tests.enabled_if in
66+
let names = List.map ~f:snd (Nonempty_list.to_list tests.exes.names) in
67+
let package =
68+
Option.map tests.package ~f:(fun p ->
69+
Dune_lang.Package.name p |> Dune_lang.Package_name.to_string)
70+
in
71+
let location = Loc.to_file_colon_line tests.exes.buildable.loc in
72+
let source_dir = Path.Build.drop_build_context_exn dir |> Path.Source.to_string in
73+
let descs =
74+
List.map names ~f:(fun name ->
75+
let target = Path.Build.relative dir (name ^ ".exe") |> Path.Build.to_string in
76+
{ Test_description.name; source_dir; package; enabled; location; target })
77+
in
78+
Memo.return descs
79+
| Cram_stanza.T cram ->
80+
let* enabled = Expander.eval_blang expander cram.enabled_if in
81+
let package =
82+
Option.map cram.package ~f:(fun p ->
83+
Dune_lang.Package.name p |> Dune_lang.Package_name.to_string)
84+
in
85+
let location = Loc.to_file_colon_line cram.loc in
86+
let source_dir = Path.Build.drop_build_context_exn dir |> Path.Source.to_string in
87+
let name = "cram" in
88+
(* Use the runtest alias as target, which is the actual executable target *)
89+
let target = "@" ^ source_dir ^ "/runtest" in
90+
let description =
91+
{ Test_description.name; source_dir; package; enabled; location; target }
92+
in
93+
Memo.return [ description ]
94+
| Library.T lib ->
95+
let* enabled =
96+
let inline_tests =
97+
match Sub_system_name.Map.find lib.sub_systems Inline_tests_info.Tests.name with
98+
| Some (Dune_rules.Inline_tests_info.Tests.T t) -> t
99+
| _ -> assert false
100+
in
101+
Expander.eval_blang expander inline_tests.enabled_if
102+
in
103+
let name = Lib_name.Local.to_string (snd lib.name) in
104+
let package =
105+
Option.map (Library.package lib) ~f:(fun p ->
106+
Dune_lang.Package.name p |> Dune_lang.Package_name.to_string)
107+
in
108+
let location = Loc.to_file_colon_line lib.buildable.loc in
109+
let source_dir = Path.Build.drop_build_context_exn dir |> Path.Source.to_string in
110+
let target =
111+
"@" ^ source_dir ^ "/runtest-" ^ Lib_name.Local.to_string (snd lib.name)
112+
in
113+
let description =
114+
{ Test_description.name; source_dir; package; enabled; location; target }
115+
in
116+
Memo.return [ description ]
117+
| _ -> Memo.return []
118+
;;
119+
120+
(* Main entry: crawl and describe all test stanzas *)
121+
let tests build_system context : Test_description.t list Memo.t =
122+
let* stanzas = collect_test_stanzas build_system context in
123+
Memo.parallel_map stanzas ~f:(fun (stanza, dir, expander) ->
124+
describe_stanza stanza dir expander)
125+
>>| List.concat
126+
;;
127+
end
128+
129+
let term : unit Term.t =
130+
let+ builder = Common.Builder.term
131+
and+ context_name = Common.context_arg ~doc:"Build context to use."
132+
and+ format = Describe_format.arg in
133+
let common, config = Common.init builder in
134+
Scheduler.go_with_rpc_server ~common ~config
135+
@@ fun () ->
136+
let open Fiber.O in
137+
let* setup = Import.Main.setup () in
138+
build_exn
139+
@@ fun () ->
140+
let open Memo.O in
141+
let* setup = setup in
142+
let super_context = Import.Main.find_scontext_exn setup ~name:context_name in
143+
let context = Super_context.context super_context in
144+
let* tests_data = Crawl.tests setup context in
145+
let dyn_data =
146+
List.map tests_data ~f:Test_description.to_dyn |> fun list -> Dyn.List list
147+
in
148+
Describe_format.print_dyn format dyn_data;
149+
Memo.return ()
150+
;;
151+
152+
let command =
153+
let doc =
154+
"Print out the tests defined in the project. The output format of this command is \
155+
experimental and is subject to change without warning"
156+
in
157+
let info = Cmd.info ~doc "tests" in
158+
Cmd.v info term
159+
;;

bin/describe/describe_tests.mli

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
open Import
2+
3+
(** Dune command to describe the tests in the workspace *)
4+
val command : unit Cmd.t

doc/changes/added/12545.md

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,2 @@
1+
- Add `$ dune describe tests` to describe the tests in the workspace
2+
(@Gromototo, #12545, fixes #12030)

src/dune_rules/dune_rules.ml

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -63,7 +63,10 @@ module Pkg_dev_tool = Pkg_dev_tool
6363
module Pkg_build_progress = Pkg_build_progress
6464
module Compile_time = Compile_time
6565
module Cram_rules = Cram_rules
66+
module Cram_stanza = Cram_stanza
6667
module Instrumentation = Instrumentation
68+
module Sub_system_name = Sub_system_name
69+
module Inline_tests_info = Inline_tests_info
6770

6871
module Install_rules = struct
6972
let install_file = Install_rules.install_file

0 commit comments

Comments
 (0)