Skip to content

Commit 87e920e

Browse files
committed
feature: warn if modules is missing any mentioned modules
We warn the user if modules_without_implementation, private_modules or virtual_modules contains any modules not in the modules field. Fixes #7026 This will be made into an error in 3.9. Signed-off-by: Ali Caglayan <alizter@gmail.com>
1 parent e591278 commit 87e920e

File tree

5 files changed

+55
-5
lines changed

5 files changed

+55
-5
lines changed

CHANGES.md

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -20,6 +20,11 @@ Unreleased
2020
- Use `$PKG_CONFIG`, when set, to find the `pkg-config` binary (#7469, fixes
2121
#2572, @anmonteiro)
2222

23+
- Modules that were declared in `(modules_without_implementation)`,
24+
`(private_modules)` or `(virtual_modules` but not declared in `(modules)` will
25+
cause Dune to emit a warning which will become an error in 3.9. (#7608, fixes
26+
#7026, @Alizter)
27+
2328
- Preliminary support for Coq compiled intefaces (`.vos` files) enabled via
2429
`(mode vos)` in `coq.theory` stanzas. This can be used in combination with
2530
`dune coq top` to obtain fast re-building of dependencies (with no checking

src/dune_rules/modules_field_evaluator.ml

Lines changed: 32 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -60,6 +60,9 @@ type single_module_error =
6060
| Vmodule_impl_missing_impl
6161
| Forbidden_new_public_module
6262
| Vmodule_impls_with_own_intf
63+
| Undeclared_module_without_implementation
64+
| Undeclared_private_module
65+
| Undeclared_virtual_module
6366

6467
type errors =
6568
{ 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
97100
in
98101
let ( ++ ) f g loc acc = f loc (g loc acc) in
99102
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)
101106
@@ with_property intf_only
102107
(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+
)
104111
@@ with_property virtual_
105112
(add_if has_impl Spurious_module_virtual
106113
++ 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)
108116
@@ with_property modules
109117
(add_if
110118
((not !?private_)
@@ -154,18 +162,24 @@ let check_invalid_module_listing ~stanza_loc ~modules_without_implementation
154162
let missing_intf_only = get Missing_intf_only in
155163
let spurious_modules_intf = get Spurious_module_intf in
156164
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
157170
let uncapitalized =
158171
List.map ~f:(fun (_, m) -> Module_name.Path.uncapitalize m)
159172
in
160173
let line_list modules =
161174
Pp.enumerate modules ~f:(fun (_, m) ->
162175
Pp.verbatim (Module_name.Path.to_string m))
163176
in
164-
let print before l after =
177+
let print ?(is_error = true) before l after =
165178
match l with
166179
| [] -> ()
167180
| (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 ])
169183
in
170184
print
171185
[ Pp.text "The following modules are implementations of virtual modules:"
@@ -213,6 +227,18 @@ let check_invalid_module_listing ~stanza_loc ~modules_without_implementation
213227
(unimplemented_virt_modules |> Module_name.Path.Set.to_list
214228
|> List.map ~f:(fun name -> (stanza_loc, name)))
215229
[ 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;
216242
(if missing_intf_only <> [] then
217243
match Ordered_set_lang.loc modules_without_implementation with
218244
| None ->
@@ -337,4 +363,5 @@ let eval ~modules:(all_modules : Module.Source.t Module_trie.t) ~stanza_loc
337363
eval ~modules:all_modules ~stanza_loc ~private_modules ~kind ~src_dir
338364
settings eval0
339365
in
366+
(* Check that modules without implementation are a subset of the modules field *)
340367
(eval0.modules, modules)

test/blackbox-tests/test-cases/intf-only/excluded-by-modules-field.t

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -19,6 +19,12 @@ field
1919
> EOF
2020

2121
$ dune build --display short
22+
File "dune", line 4, characters 33-34:
23+
4 | (modules_without_implementation x)
24+
^
25+
Warning: These modules appear in the modules_without_implementation field:
26+
- X
27+
They must also appear in the module field.
2228
ocamlc .foo.objs/byte/y.{cmi,cmo,cmt} (exit 2)
2329
File "y.ml", line 1, characters 16-17:
2430
1 | module type F = X

test/blackbox-tests/test-cases/private-modules/private-module-excluded-by-modules-field.t

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -24,6 +24,12 @@ modules:
2424
X is silently ignored:
2525

2626
$ dune build
27+
File "dune", line 5, characters 18-19:
28+
5 | (private_modules x))
29+
^
30+
Warning: These modules appear in the private_modules field:
31+
- X
32+
They must also appear in the module field.
2733
File "y.ml", line 1, characters 9-14:
2834
1 | let () = X.foo ()
2935
^^^^^

test/blackbox-tests/test-cases/virtual-libraries/virtual-modules-excluded-by-modules-field.t

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -26,6 +26,12 @@ Specifying a virtual module that isn't inside the (modules ..) field:
2626
$ touch impl/x.ml
2727

2828
$ dune build --display short
29+
File "dune", line 4, characters 18-19:
30+
4 | (virtual_modules x)
31+
^
32+
Warning: These modules appear in the virtual_modules field:
33+
- X
34+
They must also appear in the module field.
2935
ocamldep impl/.impl.objs/x.impl.d
3036
ocamlc .foo.objs/byte/y.{cmi,cmo,cmt} (exit 2)
3137
File "y.ml", line 1, characters 16-17:

0 commit comments

Comments
 (0)