Skip to content

Commit 4a3e11c

Browse files
committed
feat(runtest): dune runtest for (tests)
Signed-off-by: Ali Caglayan <[email protected]>
1 parent ab8ddf4 commit 4a3e11c

File tree

9 files changed

+328
-26
lines changed

9 files changed

+328
-26
lines changed

bin/build.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -100,7 +100,7 @@ let poll_handling_rpc_build_requests ~(common : Common.t) ~config =
100100
Target.interpret_targets (Common.root common) config setup targets
101101
| Runtest test_paths ->
102102
Runtest_common.make_request
103-
~contexts:setup.contexts
103+
~scontexts:setup.scontexts
104104
~to_cwd:root.to_cwd
105105
~test_paths
106106
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 & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -43,7 +43,7 @@ let runtest_term =
4343
| Ok () ->
4444
Build.run_build_command ~common ~config ~request:(fun setup ->
4545
Runtest_common.make_request
46-
~contexts:setup.contexts
46+
~scontexts:setup.scontexts
4747
~to_cwd:(Common.root common).to_cwd
4848
~test_paths)
4949
| Error lock_held_by ->

bin/runtest_common.ml

Lines changed: 98 additions & 23 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,44 +43,92 @@ 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+
(** [find_test_executable ~sctx ~dir ~ml_file] looks up whether [ml_file] is part
47+
of a (tests) stanza in [dir] and returns:
48+
- [Ok exe_name] if the file is a test entry point, or if the file belongs to
49+
a tests stanza with a single entry point (in which case that entry point is
50+
returned)
51+
- [Error `Not_an_entry_point] if the file belongs to a tests stanza with
52+
multiple entry points but is not itself an entry point
53+
- [Error `Not_a_test] if the file is not part of any tests stanza *)
54+
let find_test_executable ~sctx ~dir ~ml_file =
55+
let open Memo.O in
56+
let ml_file_no_ext = Filename.remove_extension ml_file in
57+
match Dune_lang.Module_name.of_string_opt ml_file_no_ext with
58+
| None -> Memo.return (Error `Not_a_test)
59+
| Some module_name ->
60+
let* dir_contents =
61+
let dir =
62+
Path.Build.append_source (Super_context.context sctx |> Context.build_dir) dir
63+
in
64+
Dir_contents.get sctx ~dir
65+
in
66+
let* ml_sources = Dir_contents.ocaml dir_contents
67+
and* scope = Dir_contents.dir dir_contents |> Dune_rules.Scope.DB.find_by_dir in
68+
Dune_rules.Ml_sources.find_origin
69+
ml_sources
70+
~libs:(Dune_rules.Scope.libs scope)
71+
[ module_name ]
72+
>>| (function
73+
| Some (Library _ | Executables _ | Melange _) | None -> Error `Not_a_test
74+
| Some (Tests { exes; _ }) ->
75+
let exe_names = Nonempty_list.to_list exes.names |> List.map ~f:snd in
76+
if List.mem exe_names ml_file_no_ext ~equal:String.equal
77+
then Ok ml_file_no_ext
78+
else (
79+
match exe_names with
80+
| [ single_exe ] -> Ok single_exe
81+
| _ -> Error `Not_an_entry_point))
82+
;;
83+
84+
let all_tests_of_dir ~sctx parent_dir =
3885
let open Memo.O in
3986
let+ cram_candidates =
4087
cram_tests_of_dir parent_dir
4188
>>| List.filter_map ~f:(fun res ->
4289
Result.to_option res
4390
|> Option.map ~f:(fun test -> Source.Cram_test.path test |> Path.Source.to_string))
91+
and+ test_executables_candidates =
92+
let dir =
93+
Path.Build.append_source
94+
(Super_context.context sctx |> Context.build_dir)
95+
parent_dir
96+
in
97+
Dir_contents.get sctx ~dir
98+
>>= Dir_contents.ocaml
99+
>>| Dune_rules.Ml_sources.test_entry_points
100+
>>| List.map ~f:(fun name -> name ^ ".ml")
44101
and+ dir_candidates =
45-
let* parent_source_dir = Source_tree.find_dir parent_dir in
46-
match parent_source_dir with
102+
Source_tree.find_dir parent_dir
103+
>>= function
47104
| None -> Memo.return []
48105
| Some parent_source_dir ->
49-
let dirs = Source_tree.Dir.sub_dirs parent_source_dir in
50-
String.Map.to_list dirs
106+
Source_tree.Dir.sub_dirs parent_source_dir
107+
|> String.Map.to_list
51108
|> Memo.List.map ~f:(fun (_candidate, candidate_path) ->
52109
Source_tree.Dir.sub_dir_as_t candidate_path
53110
>>| Source_tree.Dir.path
54111
>>| Path.Source.to_string)
55112
in
56-
List.concat [ cram_candidates; dir_candidates ]
113+
List.concat [ cram_candidates; test_executables_candidates; dir_candidates ]
57114
|> String.Set.of_list
58115
|> String.Set.to_list
59116
;;
60117

61-
let explain_unsuccessful_search path ~parent_dir =
118+
let explain_unsuccessful_search ~sctx path ~parent_dir =
62119
let open Memo.O in
63-
let+ candidates = all_tests_of_dir parent_dir in
120+
let+ candidates = all_tests_of_dir ~sctx parent_dir in
64121
User_error.raise
65122
~hints:(User_message.did_you_mean (Path.Source.to_string path) ~candidates)
66123
[ Pp.textf "%S does not match any known test." (Path.Source.to_string path) ]
67124
;;
68125

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
126+
(* [disambiguate_test_name path] is a function that takes in a directory [path]
127+
and classifies it as either a cram test, test executable, or a directory to
71128
run tests in. *)
72-
let disambiguate_test_name path =
129+
let disambiguate_test_name ~sctx path =
73130
match Path.Source.parent path with
74-
| None -> Memo.return @@ Test_kind.Runtest (Path.source Path.Source.root)
131+
| None -> Memo.return (Test_kind.Runtest (Path.source Path.Source.root))
75132
| Some parent_dir ->
76133
let open Memo.O in
77134
let* cram_tests = cram_tests_of_dir parent_dir in
@@ -80,27 +137,45 @@ let disambiguate_test_name path =
80137
(* If we find the cram test, then we request that is run. *)
81138
Memo.return (Test_kind.Cram (Path.source parent_dir, test))
82139
| 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
140+
(* Check for test executables *)
141+
let filename = Path.Source.basename path in
142+
find_test_executable ~sctx ~dir:parent_dir ~ml_file:filename
86143
>>= (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))
144+
| Ok exe_name ->
145+
Memo.return
146+
(Test_kind.Test_executable { dir = Path.source parent_dir; exe_name })
147+
| Error `Not_an_entry_point ->
148+
User_error.raise
149+
[ Pp.textf
150+
"%S is used by multiple test executables and cannot be run directly."
151+
filename
152+
]
153+
| Error `Not_a_test ->
154+
(* If we don't find it, then we assume the user intended a directory for
155+
@runtest to be used. *)
156+
Source_tree.find_dir path
157+
>>= (function
158+
(* We need to make sure that this directory or file exists. *)
159+
| Some _ -> Memo.return (Test_kind.Runtest (Path.source path))
160+
| None -> explain_unsuccessful_search ~sctx path ~parent_dir)))
90161
;;
91162

92-
let make_request ~contexts ~to_cwd ~test_paths =
163+
let make_request ~scontexts ~to_cwd ~test_paths =
164+
let contexts =
165+
Context_name.Map.to_list_map scontexts ~f:(fun _ -> Super_context.context)
166+
in
93167
List.map test_paths ~f:(fun dir ->
94168
let dir = Path.of_string dir |> Path.Expert.try_localize_external in
95-
let contexts, src_dir =
169+
let sctx, contexts, src_dir =
96170
match (Util.check_path contexts dir : Util.checked) with
97-
| In_build_dir (context, dir) -> [ context ], dir
171+
| In_build_dir (context, dir) ->
172+
Context_name.Map.find_exn scontexts (Context.name context), [ context ], dir
98173
| In_source_dir dir ->
99174
(* We need to adjust the path here to make up for the current working directory. *)
100175
let dir =
101176
Path.Source.L.relative Path.Source.root (to_cwd @ Path.Source.explode dir)
102177
in
103-
contexts, dir
178+
Context_name.Map.find_exn scontexts Context_name.default, contexts, dir
104179
| In_private_context _ | In_install_dir _ ->
105180
User_error.raise
106181
[ Pp.textf "This path is internal to dune: %s" (Path.to_string_maybe_quoted dir)
@@ -113,7 +188,7 @@ let make_request ~contexts ~to_cwd ~test_paths =
113188
]
114189
in
115190
let open Action_builder.O in
116-
Action_builder.of_memo (disambiguate_test_name src_dir)
191+
Action_builder.of_memo (disambiguate_test_name ~sctx src_dir)
117192
>>| Test_kind.alias ~contexts
118193
>>= Alias.request)
119194
|> Action_builder.all_unit

bin/runtest_common.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
open Import
22

33
val make_request
4-
: contexts:Context.t list
4+
: scontexts:Super_context.t Context_name.Map.t
55
-> to_cwd:string list
66
-> test_paths:string list
77
-> 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)

src/dune_rules/ml_sources.ml

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -282,6 +282,18 @@ let find_origin (t : t) ~libs path =
282282
| origins -> raise_module_conflict_error origins ~module_path:path)
283283
;;
284284

285+
let test_entry_points t =
286+
String.Map.fold
287+
t.modules.executables
288+
~init:[]
289+
~f:(fun (origin, _modules, _obj_dir) acc ->
290+
match origin with
291+
| Origin.Tests tests ->
292+
let names = Nonempty_list.to_list tests.exes.names |> List.map ~f:snd in
293+
names @ acc
294+
| Origin.Library _ | Origin.Executables _ | Origin.Melange _ -> acc)
295+
;;
296+
285297
let modules_and_obj_dir t ~libs ~for_ =
286298
match
287299
match for_ with

src/dune_rules/ml_sources.mli

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -39,6 +39,9 @@ val modules : t -> libs:Lib.DB.t -> for_:for_ -> Modules.t Memo.t
3939
(** Find out the origin of the stanza for a given module *)
4040
val find_origin : t -> libs:Lib.DB.t -> Module_name.Path.t -> Origin.t option Memo.t
4141

42+
(** Returns the entry point names for all Tests stanzas in this directory *)
43+
val test_entry_points : t -> string list
44+
4245
val empty : t
4346

4447
(** This [lookup_vlib] argument is required for constructing the collection of modules for

0 commit comments

Comments
 (0)