@@ -60,6 +60,9 @@ type single_module_error =
60
60
| Vmodule_impl_missing_impl
61
61
| Forbidden_new_public_module
62
62
| Vmodule_impls_with_own_intf
63
+ | Undeclared_module_without_implementation
64
+ | Undeclared_private_module
65
+ | Undeclared_virtual_module
63
66
64
67
type errors =
65
68
{ errors : (single_module_error * Loc .t * Module_name.Path .t ) list
@@ -97,14 +100,19 @@ let find_errors ~modules ~intf_only ~virtual_modules ~private_modules
97
100
in
98
101
let ( ++ ) f g loc acc = f loc (g loc acc) in
99
102
let ( ! ? ) = Option. is_some in
100
- with_property private_ (add_if impl_vmodule Private_impl_of_vmodule )
103
+ with_property private_
104
+ (add_if impl_vmodule Private_impl_of_vmodule
105
+ ++ add_if (not ! ?modules) Undeclared_private_module )
101
106
@@ with_property intf_only
102
107
(add_if has_impl Spurious_module_intf
103
- ++ add_if impl_vmodule Vmodule_impl_intf_only_exclusion )
108
+ ++ add_if impl_vmodule Vmodule_impl_intf_only_exclusion
109
+ ++ add_if (not ! ?modules) Undeclared_module_without_implementation
110
+ )
104
111
@@ with_property virtual_
105
112
(add_if has_impl Spurious_module_virtual
106
113
++ add_if ! ?intf_only Virt_intf_overlap
107
- ++ add_if ! ?private_ Private_virt_module )
114
+ ++ add_if ! ?private_ Private_virt_module
115
+ ++ add_if (not ! ?modules) Undeclared_virtual_module )
108
116
@@ with_property modules
109
117
(add_if
110
118
((not ! ?private_)
@@ -154,18 +162,24 @@ let check_invalid_module_listing ~stanza_loc ~modules_without_implementation
154
162
let missing_intf_only = get Missing_intf_only in
155
163
let spurious_modules_intf = get Spurious_module_intf in
156
164
let spurious_modules_virtual = get Spurious_module_virtual in
165
+ let undeclared_modules_without_implementation =
166
+ get Undeclared_module_without_implementation
167
+ in
168
+ let undeclared_private_modules = get Undeclared_private_module in
169
+ let undeclared_virtual_modules = get Undeclared_virtual_module in
157
170
let uncapitalized =
158
171
List. map ~f: (fun (_ , m ) -> Module_name.Path. uncapitalize m)
159
172
in
160
173
let line_list modules =
161
174
Pp. enumerate modules ~f: (fun (_ , m ) ->
162
175
Pp. verbatim (Module_name.Path. to_string m))
163
176
in
164
- let print before l after =
177
+ let print ?( is_error = true ) before l after =
165
178
match l with
166
179
| [] -> ()
167
180
| (loc , _ ) :: _ ->
168
- User_error. raise ~loc (List. concat [ before; [ line_list l ]; after ])
181
+ User_warning. emit ~is_error ~loc
182
+ (List. concat [ before; [ line_list l ]; after ])
169
183
in
170
184
print
171
185
[ Pp. text " The following modules are implementations of virtual modules:"
@@ -213,6 +227,18 @@ let check_invalid_module_listing ~stanza_loc ~modules_without_implementation
213
227
(unimplemented_virt_modules |> Module_name.Path.Set. to_list
214
228
|> List. map ~f: (fun name -> (stanza_loc, name)))
215
229
[ Pp. text " You must provide an implementation for all of these modules." ];
230
+ (* Checking that (modules) incldues all declared modules *)
231
+ let print_undelared_modules field mods =
232
+ (* TODO: this is a warning for now, change to an error in 3.9 *)
233
+ print ~is_error: false
234
+ [ Pp. textf " These modules appear in the %s field:" field ]
235
+ mods
236
+ [ Pp. text " They must also appear in the modules field." ]
237
+ in
238
+ print_undelared_modules " modules_without_implementation"
239
+ undeclared_modules_without_implementation;
240
+ print_undelared_modules " private_modules" undeclared_private_modules;
241
+ print_undelared_modules " virtual_modules" undeclared_virtual_modules;
216
242
(if missing_intf_only <> [] then
217
243
match Ordered_set_lang. loc modules_without_implementation with
218
244
| None ->
@@ -337,4 +363,5 @@ let eval ~modules:(all_modules : Module.Source.t Module_trie.t) ~stanza_loc
337
363
eval ~modules: all_modules ~stanza_loc ~private_modules ~kind ~src_dir
338
364
settings eval0
339
365
in
366
+ (* Check that modules without implementation are a subset of the modules field *)
340
367
(eval0.modules, modules)
0 commit comments