@@ -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,53 @@ 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 * dir_contents =
50+ let dir =
51+ Path.Build. append_source (Super_context. context sctx |> Context. build_dir) dir
52+ in
53+ Dir_contents. get sctx ~dir
54+ in
55+ let * ml_sources = Dir_contents. ocaml dir_contents
56+ and * scope = Dir_contents. dir dir_contents |> Dune_rules.Scope.DB. find_by_dir in
57+ Dune_rules.Ml_sources. find_origin
58+ ml_sources
59+ ~libs: (Dune_rules.Scope. libs scope)
60+ [ module_name ]
61+ >> | (function
62+ | Some (Library _ | Executables _ | Melange _ ) | None -> Error `Not_a_test
63+ | Some (Tests ({ exes; _ } as _test )) ->
64+ let exe_names = Nonempty_list. to_list exes.names |> List. map ~f: snd in
65+ if List. mem exe_names (Filename. remove_extension ml_file) ~equal: String. equal
66+ then Ok (Filename. remove_extension ml_file)
67+ else (
68+ match exe_names with
69+ | [ single_exe ] -> Ok single_exe
70+ | [] | _ :: _ -> Error `Not_an_entry_point ))
71+ ;;
72+
73+ let all_tests_of_dir ~sctx parent_dir =
3874 let open Memo.O in
3975 let + cram_candidates =
4076 cram_tests_of_dir parent_dir
4177 >> | List. filter_map ~f: (fun res ->
4278 Result. to_option res
4379 |> Option. map ~f: (fun test -> Source.Cram_test. path test |> Path.Source. to_string))
80+ and + test_executable_candidates =
81+ Source_tree. find_dir parent_dir
82+ >> = function
83+ | None -> Memo. return []
84+ | Some source_dir ->
85+ Source_tree.Dir. filenames source_dir
86+ |> Filename.Set. to_list
87+ |> List. filter ~f: (fun f -> String. is_suffix f ~suffix: " .ml" )
88+ |> Memo.List. filter ~f: (fun ml_file ->
89+ find_test_executable ~sctx ~dir: parent_dir ~ml_file >> | Result. is_ok)
4490 and + dir_candidates =
4591 let * parent_source_dir = Source_tree. find_dir parent_dir in
4692 match parent_source_dir with
@@ -53,23 +99,23 @@ let all_tests_of_dir parent_dir =
5399 >> | Source_tree.Dir. path
54100 >> | Path.Source. to_string)
55101 in
56- List. concat [ cram_candidates; dir_candidates ]
102+ List. concat [ cram_candidates; test_executable_candidates; dir_candidates ]
57103 |> String.Set. of_list
58104 |> String.Set. to_list
59105;;
60106
61- let explain_unsuccessful_search path ~parent_dir =
107+ let explain_unsuccessful_search ~ sctx path ~parent_dir =
62108 let open Memo.O in
63- let + candidates = all_tests_of_dir parent_dir in
109+ let + candidates = all_tests_of_dir ~sctx parent_dir in
64110 User_error. raise
65111 ~hints: (User_message. did_you_mean (Path.Source. to_string path) ~candidates )
66112 [ Pp. textf " %S does not match any known test." (Path.Source. to_string path) ]
67113;;
68114
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
115+ (* [disambiguate_test_name path] is a function that takes in a directory [path]
116+ and classifies it as either a cram test, test executable, or a directory to
71117 run tests in. *)
72- let disambiguate_test_name path =
118+ let disambiguate_test_name ~ sctx path =
73119 match Path.Source. parent path with
74120 | None -> Memo. return @@ Test_kind. Runtest (Path. source Path.Source. root)
75121 | Some parent_dir ->
@@ -80,27 +126,51 @@ let disambiguate_test_name path =
80126 (* If we find the cram test, then we request that is run. *)
81127 Memo. return (Test_kind. Cram (Path. source parent_dir, test))
82128 | 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 ))
129+ (* Check for test executables *)
130+ let filename = Path.Source. basename path in
131+ let * test_exe_opt =
132+ find_test_executable ~sctx ~dir: parent_dir ~ml_file: filename
133+ >> | function
134+ | Ok exe_name -> Some exe_name
135+ | Error `Not_an_entry_point ->
136+ User_error. raise
137+ [ Pp. textf
138+ " %S is used by multiple test executables and cannot be run directly."
139+ filename
140+ ]
141+ | Error `Not_a_test -> None
142+ in
143+ (match test_exe_opt with
144+ | Some exe_name ->
145+ (* Found a test executable for this ML file *)
146+ Memo. return (Test_kind. Test_executable (Path. source parent_dir, exe_name))
147+ | None ->
148+ (* If we don't find it, then we assume the user intended a directory for
149+ @runtest to be used. *)
150+ Source_tree. find_dir path
151+ >> = (function
152+ (* We need to make sure that this directory or file exists. *)
153+ | Some _ -> Memo. return (Test_kind. Runtest (Path. source path))
154+ | None -> explain_unsuccessful_search ~sctx path ~parent_dir )))
90155;;
91156
92- let make_request ~contexts ~to_cwd ~test_paths =
157+ let make_request ~contexts ~scontexts ~ to_cwd ~test_paths =
93158 List. map test_paths ~f: (fun dir ->
94159 let dir = Path. of_string dir |> Path.Expert. try_localize_external in
95- let contexts, src_dir =
160+ let sctx, contexts, src_dir =
96161 match (Util. check_path contexts dir : Util.checked ) with
97- | In_build_dir (context , dir ) -> [ context ], dir
162+ | In_build_dir (context , dir ) ->
163+ ( Dune_engine.Context_name.Map. find_exn scontexts (Context. name context)
164+ , [ context ]
165+ , dir )
98166 | In_source_dir dir ->
99167 (* We need to adjust the path here to make up for the current working directory. *)
100168 let dir =
101169 Path.Source.L. relative Path.Source. root (to_cwd @ Path.Source. explode dir)
102170 in
103- contexts, dir
171+ ( Dune_engine.Context_name.Map. find_exn scontexts Context_name. default
172+ , contexts
173+ , dir )
104174 | In_private_context _ | In_install_dir _ ->
105175 User_error. raise
106176 [ Pp. textf " This path is internal to dune: %s" (Path. to_string_maybe_quoted dir)
@@ -113,7 +183,7 @@ let make_request ~contexts ~to_cwd ~test_paths =
113183 ]
114184 in
115185 let open Action_builder.O in
116- Action_builder. of_memo (disambiguate_test_name src_dir)
186+ Action_builder. of_memo (disambiguate_test_name ~sctx src_dir)
117187 >> | Test_kind. alias ~contexts
118188 >> = Alias. request)
119189 |> Action_builder. all_unit
0 commit comments