Skip to content

Commit 07abd7b

Browse files
committed
feat(runtest): dune runtest for (tests)
Signed-off-by: Ali Caglayan <[email protected]>
3 parents 513d902 + 75aeca6 + 31de016 commit 07abd7b

File tree

6 files changed

+307
-19
lines changed

6 files changed

+307
-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: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -39,6 +39,8 @@ include struct
3939
module Library = Library
4040
module Melange = Melange
4141
module Executables = Executables
42+
module Dune_load = Dune_load
43+
module Dir_contents = Dir_contents
4244
end
4345

4446
include struct

bin/runtest.ml

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

bin/runtest_common.ml

Lines changed: 87 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -4,11 +4,17 @@ 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 Path.t * string (* dir, executable name *)
78

89
let alias ~contexts = function
910
| Cram (dir, cram) ->
1011
let name = Dune_engine.Alias.Name.of_string (Source.Cram_test.name cram) in
1112
Alias.in_dir ~name ~recursive:false ~contexts dir
13+
| Test_executable (dir, exe_name) ->
14+
(* CR-someday Alizter: get the proper alias, also check js_of_ocaml
15+
runtst aliases? *)
16+
let name = Dune_engine.Alias.Name.of_string ("runtest-" ^ exe_name) in
17+
Alias.in_dir ~name ~recursive:false ~contexts dir
1218
| Runtest dir ->
1319
Alias.in_dir ~name:Dune_rules.Alias.runtest ~recursive:true ~contexts dir
1420
;;
@@ -34,13 +40,51 @@ let find_cram_test cram_tests path =
3440
| Error (Dune_rules.Cram_rules.Missing_run_t _) | Ok _ -> None)
3541
;;
3642

37-
let all_tests_of_dir parent_dir =
43+
let find_test_executable ~sctx ~dir ~ml_file =
44+
let open Memo.O in
45+
let module_name = Filename.remove_extension ml_file in
46+
match Dune_lang.Module_name.of_string_opt module_name with
47+
| None -> Memo.return (Error `Not_a_test)
48+
| Some module_name ->
49+
let build_dir =
50+
Path.Build.append_source (Super_context.context sctx |> Context.build_dir) dir
51+
in
52+
let* dir_contents = Dir_contents.get sctx ~dir:build_dir in
53+
let* ml_sources = Dir_contents.ocaml dir_contents
54+
and* scope = Dir_contents.dir dir_contents |> Dune_rules.Scope.DB.find_by_dir in
55+
Dune_rules.Ml_sources.find_origin
56+
ml_sources
57+
~libs:(Dune_rules.Scope.libs scope)
58+
[ module_name ]
59+
>>| (function
60+
| Some (Library _ | Executables _ | Melange _) | None -> Error `Not_a_test
61+
| Some (Tests ({ exes; _ } as _test)) ->
62+
let exe_names = Nonempty_list.to_list exes.names |> List.map ~f:snd in
63+
if List.mem exe_names (Filename.remove_extension ml_file) ~equal:String.equal
64+
then Ok (Filename.remove_extension ml_file)
65+
else (
66+
match exe_names with
67+
| [ single_exe ] -> Ok single_exe
68+
| [] | _ :: _ -> Error `Not_an_entry_point))
69+
;;
70+
71+
let all_tests_of_dir ~sctx parent_dir =
3872
let open Memo.O in
3973
let+ cram_candidates =
4074
cram_tests_of_dir parent_dir
4175
>>| List.filter_map ~f:(fun res ->
4276
Result.to_option res
4377
|> Option.map ~f:(fun test -> Source.Cram_test.path test |> Path.Source.to_string))
78+
and+ test_executable_candidates =
79+
Source_tree.find_dir parent_dir
80+
>>= function
81+
| None -> Memo.return []
82+
| Some source_dir ->
83+
Source_tree.Dir.filenames source_dir
84+
|> Filename.Set.to_list
85+
|> List.filter ~f:(fun f -> String.is_suffix f ~suffix:".ml")
86+
|> Memo.List.filter ~f:(fun ml_file ->
87+
find_test_executable ~sctx ~dir:parent_dir ~ml_file >>| Result.is_ok)
4488
and+ dir_candidates =
4589
let* parent_source_dir = Source_tree.find_dir parent_dir in
4690
match parent_source_dir with
@@ -53,23 +97,23 @@ let all_tests_of_dir parent_dir =
5397
>>| Source_tree.Dir.path
5498
>>| Path.Source.to_string)
5599
in
56-
List.concat [ cram_candidates; dir_candidates ]
100+
List.concat [ cram_candidates; test_executable_candidates; dir_candidates ]
57101
|> String.Set.of_list
58102
|> String.Set.to_list
59103
;;
60104

61-
let explain_unsuccessful_search path ~parent_dir =
105+
let explain_unsuccessful_search ~sctx path ~parent_dir =
62106
let open Memo.O in
63-
let+ candidates = all_tests_of_dir parent_dir in
107+
let+ candidates = all_tests_of_dir ~sctx parent_dir in
64108
User_error.raise
65109
~hints:(User_message.did_you_mean (Path.Source.to_string path) ~candidates)
66110
[ Pp.textf "%S does not match any known test." (Path.Source.to_string path) ]
67111
;;
68112

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
113+
(* [disambiguate_test_name path] is a function that takes in a directory [path]
114+
and classifies it as either a cram test, test executable, or a directory to
71115
run tests in. *)
72-
let disambiguate_test_name path =
116+
let disambiguate_test_name ~sctx path =
73117
match Path.Source.parent path with
74118
| None -> Memo.return @@ Test_kind.Runtest (Path.source Path.Source.root)
75119
| Some parent_dir ->
@@ -80,27 +124,51 @@ let disambiguate_test_name path =
80124
(* If we find the cram test, then we request that is run. *)
81125
Memo.return (Test_kind.Cram (Path.source parent_dir, test))
82126
| 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))
127+
(* Check for test executables *)
128+
let filename = Path.Source.basename path in
129+
let* test_exe_opt =
130+
find_test_executable ~sctx ~dir:parent_dir ~ml_file:filename
131+
>>| function
132+
| Ok exe_name -> Some exe_name
133+
| Error `Not_an_entry_point ->
134+
User_error.raise
135+
[ Pp.textf
136+
"%S is used by multiple test executables and cannot be run directly."
137+
filename
138+
]
139+
| Error `Not_a_test -> None
140+
in
141+
(match test_exe_opt with
142+
| Some exe_name ->
143+
(* Found a test executable for this ML file *)
144+
Memo.return (Test_kind.Test_executable (Path.source parent_dir, exe_name))
145+
| None ->
146+
(* If we don't find it, then we assume the user intended a directory for
147+
@runtest to be used. *)
148+
Source_tree.find_dir path
149+
>>= (function
150+
(* We need to make sure that this directory or file exists. *)
151+
| Some _ -> Memo.return (Test_kind.Runtest (Path.source path))
152+
| None -> explain_unsuccessful_search ~sctx path ~parent_dir)))
90153
;;
91154

92-
let make_request ~contexts ~to_cwd ~test_paths =
155+
let make_request ~contexts ~scontexts ~to_cwd ~test_paths =
93156
List.map test_paths ~f:(fun dir ->
94157
let dir = Path.of_string dir |> Path.Expert.try_localize_external in
95-
let contexts, src_dir =
158+
let sctx, contexts, src_dir =
96159
match (Util.check_path contexts dir : Util.checked) with
97-
| In_build_dir (context, dir) -> [ context ], dir
160+
| In_build_dir (context, dir) ->
161+
( Dune_engine.Context_name.Map.find_exn scontexts (Context.name context)
162+
, [ context ]
163+
, dir )
98164
| In_source_dir dir ->
99165
(* We need to adjust the path here to make up for the current working directory. *)
100166
let dir =
101167
Path.Source.L.relative Path.Source.root (to_cwd @ Path.Source.explode dir)
102168
in
103-
contexts, dir
169+
( Dune_engine.Context_name.Map.find_exn scontexts Context_name.default
170+
, contexts
171+
, dir )
104172
| In_private_context _ | In_install_dir _ ->
105173
User_error.raise
106174
[ Pp.textf "This path is internal to dune: %s" (Path.to_string_maybe_quoted dir)
@@ -113,7 +181,7 @@ let make_request ~contexts ~to_cwd ~test_paths =
113181
]
114182
in
115183
let open Action_builder.O in
116-
Action_builder.of_memo (disambiguate_test_name src_dir)
184+
Action_builder.of_memo (disambiguate_test_name ~sctx src_dir)
117185
>>| Test_kind.alias ~contexts
118186
>>= Alias.request)
119187
|> 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

0 commit comments

Comments
 (0)