Skip to content

Commit 958e2be

Browse files
committed
feat(runtest): dune runtest for (tests)
Signed-off-by: Ali Caglayan <[email protected]>
1 parent 123354c commit 958e2be

File tree

7 files changed

+308
-19
lines changed

7 files changed

+308
-19
lines changed

bin/build.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -101,6 +101,7 @@ let poll_handling_rpc_build_requests ~(common : Common.t) ~config =
101101
| Runtest test_paths ->
102102
Runtest_common.make_request
103103
~contexts:setup.contexts
104+
~scontexts:setup.scontexts
104105
~to_cwd:root.to_cwd
105106
~test_paths
106107
in

bin/import.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -39,6 +39,7 @@ include struct
3939
module Library = Library
4040
module Melange = Melange
4141
module Executables = Executables
42+
module Dir_contents = Dir_contents
4243
end
4344

4445
include struct

bin/runtest.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -44,6 +44,7 @@ let runtest_term =
4444
Build.run_build_command ~common ~config ~request:(fun setup ->
4545
Runtest_common.make_request
4646
~contexts:setup.contexts
47+
~scontexts:setup.scontexts
4748
~to_cwd:(Common.root common).to_cwd
4849
~test_paths)
4950
| Error lock_held_by ->

bin/runtest_common.ml

Lines changed: 93 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -4,11 +4,20 @@ module Test_kind = struct
44
type t =
55
| Runtest of Path.t
66
| Cram of Path.t * Source.Cram_test.t
7+
| Test_executable of
8+
{ dir : Path.t
9+
; exe_name : string
10+
}
711

812
let alias ~contexts = function
913
| Cram (dir, cram) ->
1014
let name = Dune_engine.Alias.Name.of_string (Source.Cram_test.name cram) in
1115
Alias.in_dir ~name ~recursive:false ~contexts dir
16+
| Test_executable { dir; exe_name } ->
17+
(* CR-someday Alizter: get the proper alias, also check js_of_ocaml
18+
runtst aliases? *)
19+
let name = Dune_engine.Alias.Name.of_string ("runtest-" ^ exe_name) in
20+
Alias.in_dir ~name ~recursive:false ~contexts dir
1221
| Runtest dir ->
1322
Alias.in_dir ~name:Dune_rules.Alias.runtest ~recursive:true ~contexts dir
1423
;;
@@ -34,13 +43,53 @@ let find_cram_test cram_tests path =
3443
| Error (Dune_rules.Cram_rules.Missing_run_t _) | Ok _ -> None)
3544
;;
3645

37-
let all_tests_of_dir parent_dir =
46+
let find_test_executable ~sctx ~dir ~ml_file =
47+
let open Memo.O in
48+
let ml_file_no_ext = Filename.remove_extension ml_file in
49+
match Dune_lang.Module_name.of_string_opt ml_file_no_ext with
50+
| None -> Memo.return (Error `Not_a_test)
51+
| Some module_name ->
52+
let* dir_contents =
53+
let dir =
54+
Path.Build.append_source (Super_context.context sctx |> Context.build_dir) dir
55+
in
56+
Dir_contents.get sctx ~dir
57+
in
58+
let* ml_sources = Dir_contents.ocaml dir_contents
59+
and* scope = Dir_contents.dir dir_contents |> Dune_rules.Scope.DB.find_by_dir in
60+
Dune_rules.Ml_sources.find_origin
61+
ml_sources
62+
~libs:(Dune_rules.Scope.libs scope)
63+
[ module_name ]
64+
>>| (function
65+
| Some (Library _ | Executables _ | Melange _) | None -> Error `Not_a_test
66+
| Some (Tests ({ exes; _ } as _test)) ->
67+
let exe_names = Nonempty_list.to_list exes.names |> List.map ~f:snd in
68+
if List.mem exe_names ml_file_no_ext ~equal:String.equal
69+
then Ok ml_file_no_ext
70+
else (
71+
match exe_names with
72+
| [ single_exe ] -> Ok single_exe
73+
| [] | _ :: _ -> Error `Not_an_entry_point))
74+
;;
75+
76+
let all_tests_of_dir ~sctx parent_dir =
3877
let open Memo.O in
3978
let+ cram_candidates =
4079
cram_tests_of_dir parent_dir
4180
>>| List.filter_map ~f:(fun res ->
4281
Result.to_option res
4382
|> Option.map ~f:(fun test -> Source.Cram_test.path test |> Path.Source.to_string))
83+
and+ test_executable_candidates =
84+
Source_tree.find_dir parent_dir
85+
>>= function
86+
| None -> Memo.return []
87+
| Some source_dir ->
88+
Source_tree.Dir.filenames source_dir
89+
|> Filename.Set.to_list
90+
|> List.filter ~f:(fun f -> String.is_suffix f ~suffix:".ml")
91+
|> Memo.List.filter ~f:(fun ml_file ->
92+
find_test_executable ~sctx ~dir:parent_dir ~ml_file >>| Result.is_ok)
4493
and+ dir_candidates =
4594
let* parent_source_dir = Source_tree.find_dir parent_dir in
4695
match parent_source_dir with
@@ -53,23 +102,23 @@ let all_tests_of_dir parent_dir =
53102
>>| Source_tree.Dir.path
54103
>>| Path.Source.to_string)
55104
in
56-
List.concat [ cram_candidates; dir_candidates ]
105+
List.concat [ cram_candidates; test_executable_candidates; dir_candidates ]
57106
|> String.Set.of_list
58107
|> String.Set.to_list
59108
;;
60109

61-
let explain_unsuccessful_search path ~parent_dir =
110+
let explain_unsuccessful_search ~sctx path ~parent_dir =
62111
let open Memo.O in
63-
let+ candidates = all_tests_of_dir parent_dir in
112+
let+ candidates = all_tests_of_dir ~sctx parent_dir in
64113
User_error.raise
65114
~hints:(User_message.did_you_mean (Path.Source.to_string path) ~candidates)
66115
[ Pp.textf "%S does not match any known test." (Path.Source.to_string path) ]
67116
;;
68117

69-
(* [disambiguate_test_name path] is a function that takes in a
70-
directory [path] and classifies it as either a cram test or a directory to
118+
(* [disambiguate_test_name path] is a function that takes in a directory [path]
119+
and classifies it as either a cram test, test executable, or a directory to
71120
run tests in. *)
72-
let disambiguate_test_name path =
121+
let disambiguate_test_name ~sctx path =
73122
match Path.Source.parent path with
74123
| None -> Memo.return @@ Test_kind.Runtest (Path.source Path.Source.root)
75124
| Some parent_dir ->
@@ -80,27 +129,52 @@ let disambiguate_test_name path =
80129
(* If we find the cram test, then we request that is run. *)
81130
Memo.return (Test_kind.Cram (Path.source parent_dir, test))
82131
| None ->
83-
(* If we don't find it, then we assume the user intended a directory for
84-
@runtest to be used. *)
85-
Source_tree.find_dir path
86-
>>= (function
87-
(* We need to make sure that this directory or file exists. *)
88-
| Some _ -> Memo.return (Test_kind.Runtest (Path.source path))
89-
| None -> explain_unsuccessful_search path ~parent_dir))
132+
(* Check for test executables *)
133+
let filename = Path.Source.basename path in
134+
let* test_exe_opt =
135+
find_test_executable ~sctx ~dir:parent_dir ~ml_file:filename
136+
>>| function
137+
| Ok exe_name -> Some exe_name
138+
| Error `Not_an_entry_point ->
139+
User_error.raise
140+
[ Pp.textf
141+
"%S is used by multiple test executables and cannot be run directly."
142+
filename
143+
]
144+
| Error `Not_a_test -> None
145+
in
146+
(match test_exe_opt with
147+
| Some exe_name ->
148+
(* Found a test executable for this ML file *)
149+
Memo.return
150+
(Test_kind.Test_executable { dir = Path.source parent_dir; exe_name })
151+
| None ->
152+
(* If we don't find it, then we assume the user intended a directory for
153+
@runtest to be used. *)
154+
Source_tree.find_dir path
155+
>>= (function
156+
(* We need to make sure that this directory or file exists. *)
157+
| Some _ -> Memo.return (Test_kind.Runtest (Path.source path))
158+
| None -> explain_unsuccessful_search ~sctx path ~parent_dir)))
90159
;;
91160

92-
let make_request ~contexts ~to_cwd ~test_paths =
161+
let make_request ~contexts ~scontexts ~to_cwd ~test_paths =
93162
List.map test_paths ~f:(fun dir ->
94163
let dir = Path.of_string dir |> Path.Expert.try_localize_external in
95-
let contexts, src_dir =
164+
let sctx, contexts, src_dir =
96165
match (Util.check_path contexts dir : Util.checked) with
97-
| In_build_dir (context, dir) -> [ context ], dir
166+
| In_build_dir (context, dir) ->
167+
( Dune_engine.Context_name.Map.find_exn scontexts (Context.name context)
168+
, [ context ]
169+
, dir )
98170
| In_source_dir dir ->
99171
(* We need to adjust the path here to make up for the current working directory. *)
100172
let dir =
101173
Path.Source.L.relative Path.Source.root (to_cwd @ Path.Source.explode dir)
102174
in
103-
contexts, dir
175+
( Dune_engine.Context_name.Map.find_exn scontexts Context_name.default
176+
, contexts
177+
, dir )
104178
| In_private_context _ | In_install_dir _ ->
105179
User_error.raise
106180
[ Pp.textf "This path is internal to dune: %s" (Path.to_string_maybe_quoted dir)
@@ -113,7 +187,7 @@ let make_request ~contexts ~to_cwd ~test_paths =
113187
]
114188
in
115189
let open Action_builder.O in
116-
Action_builder.of_memo (disambiguate_test_name src_dir)
190+
Action_builder.of_memo (disambiguate_test_name ~sctx src_dir)
117191
>>| Test_kind.alias ~contexts
118192
>>= Alias.request)
119193
|> Action_builder.all_unit

bin/runtest_common.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@ open Import
22

33
val make_request
44
: contexts:Context.t list
5+
-> scontexts:Super_context.t Context_name.Map.t
56
-> to_cwd:string list
67
-> test_paths:string list
78
-> unit Action_builder.t

doc/changes/added/12785.md

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
- `dune runtest` can now run individual test executables from `(tests)` stanzas
2+
by providing their source files as arguments. (#12785, partially addresses
3+
#870, @Alizter)

0 commit comments

Comments
 (0)