@@ -5,6 +5,7 @@ module Test_kind = struct
55 | Runtest of Path .t
66 | Cram of Path .t * Source.Cram_test .t
77 | Test_executable of Path .t * string (* dir, executable name *)
8+ | Inline_tests of Path .t * string (* dir, library name *)
89
910 let alias ~contexts = function
1011 | Cram (dir , cram ) ->
@@ -15,6 +16,10 @@ module Test_kind = struct
1516 runtst aliases? *)
1617 let name = Dune_engine.Alias.Name. of_string (" runtest-" ^ exe_name) in
1718 Alias. in_dir ~name ~recursive: false ~contexts dir
19+ | Inline_tests (dir , lib_name ) ->
20+ (* CR-someday Alizter: get the proper alias where it is defined. *)
21+ let name = Dune_engine.Alias.Name. of_string (" runtest-" ^ lib_name) in
22+ Alias. in_dir ~name ~recursive: false ~contexts dir
1823 | Runtest dir ->
1924 Alias. in_dir ~name: Dune_rules.Alias. runtest ~recursive: true ~contexts dir
2025 ;;
@@ -40,7 +45,13 @@ let find_cram_test cram_tests path =
4045 | Error (Dune_rules.Cram_rules. Missing_run_t _ ) | Ok _ -> None )
4146;;
4247
43- let find_test_executable ~sctx ~dir ~ml_file =
48+ let has_inline_tests (lib : Dune_rules.Library.t ) =
49+ Dune_rules.Sub_system_name.Map. mem
50+ lib.sub_systems
51+ Dune_rules.Inline_tests_info.Tests. name
52+ ;;
53+
54+ let classify_ml_test ~sctx ~dir ~ml_file =
4455 let open Memo.O in
4556 let module_name = Filename. remove_extension ml_file in
4657 match Dune_lang.Module_name. of_string_opt module_name with
@@ -57,14 +68,17 @@ let find_test_executable ~sctx ~dir ~ml_file =
5768 ~libs: (Dune_rules.Scope. libs scope)
5869 [ module_name ]
5970 >> | (function
71+ | Some (Library lib ) when has_inline_tests lib ->
72+ let lib_name = snd lib.name |> Lib_name.Local. to_string in
73+ Ok (`Inline_tests_library lib_name)
6074 | Some (Library _ | Executables _ | Melange _ ) | None -> Error `Not_a_test
6175 | Some (Tests ({ exes; _ } as _test )) ->
6276 let exe_names = Nonempty_list. to_list exes.names |> List. map ~f: snd in
6377 if List. mem exe_names (Filename. remove_extension ml_file) ~equal: String. equal
64- then Ok (Filename. remove_extension ml_file)
78+ then Ok (`Test_executable ( Filename. remove_extension ml_file) )
6579 else (
6680 match exe_names with
67- | [ single_exe ] -> Ok single_exe
81+ | [ single_exe ] -> Ok ( `Test_executable single_exe)
6882 | [] | _ :: _ -> Error `Not_an_entry_point ))
6983;;
7084
@@ -84,7 +98,7 @@ let all_tests_of_dir ~sctx parent_dir =
8498 |> Filename.Set. to_list
8599 |> List. filter ~f: (fun f -> String. is_suffix f ~suffix: " .ml" )
86100 |> Memo.List. filter ~f: (fun ml_file ->
87- find_test_executable ~sctx ~dir: parent_dir ~ml_file >> | Result. is_ok)
101+ classify_ml_test ~sctx ~dir: parent_dir ~ml_file >> | Result. is_ok)
88102 and + dir_candidates =
89103 let * parent_source_dir = Source_tree. find_dir parent_dir in
90104 match parent_source_dir with
@@ -126,22 +140,26 @@ let disambiguate_test_name ~sctx path =
126140 | None ->
127141 (* Check for test executables *)
128142 let filename = Path.Source. basename path in
129- let * test_exe_opt =
130- find_test_executable ~sctx ~dir: parent_dir ~ml_file: filename
143+ let * test_kind_opt =
144+ classify_ml_test ~sctx ~dir: parent_dir ~ml_file: filename
131145 >> | 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
146+ | Ok (`Test_executable exe_name ) -> Some (`Test_exe exe_name)
147+ | Ok (`Inline_tests_library lib_name ) -> Some (`Inline_tests lib_name)
148+ | Error `Not_an_entry_point ->
149+ User_error. raise
150+ [ Pp. textf
151+ " %S is used by multiple test executables and cannot be run directly."
152+ filename
153+ ]
154+ | Error `Not_a_test -> None
140155 in
141- (match test_exe_opt with
142- | Some exe_name ->
156+ (match test_kind_opt with
157+ | Some (`Test_exe exe_name ) ->
143158 (* Found a test executable for this ML file *)
144159 Memo. return (Test_kind. Test_executable (Path. source parent_dir, exe_name))
160+ | Some (`Inline_tests lib_name ) ->
161+ (* Found an inline tests library for this ML file *)
162+ Memo. return (Test_kind. Inline_tests (Path. source parent_dir, lib_name))
145163 | None ->
146164 (* If we don't find it, then we assume the user intended a directory for
147165 @runtest to be used. *)
0 commit comments