Skip to content

Commit

Permalink
feature: warn if modules is missing any mentioned modules
Browse files Browse the repository at this point in the history
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 <[email protected]>
  • Loading branch information
Alizter committed Apr 21, 2023
1 parent acbfc94 commit 29f8fe0
Show file tree
Hide file tree
Showing 5 changed files with 55 additions and 5 deletions.
5 changes: 5 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,11 @@ Unreleased
- Use `$PKG_CONFIG`, when set, to find the `pkg-config` binary (#7469, fixes
#2572, @anmonteiro)

- Modules that were declared in `(modules_without_implementation)`,
`(private_modules)` or `(virtual_modules)` but not declared in `(modules)`
will cause Dune to emit a warning which will become an error in 3.9. (#7608,
fixes #7026, @Alizter)

- Preliminary support for Coq compiled intefaces (`.vos` files) enabled via
`(mode vos)` in `coq.theory` stanzas. This can be used in combination with
`dune coq top` to obtain fast re-building of dependencies (with no checking
Expand Down
37 changes: 32 additions & 5 deletions src/dune_rules/modules_field_evaluator.ml
Original file line number Diff line number Diff line change
Expand Up @@ -60,6 +60,9 @@ type single_module_error =
| Vmodule_impl_missing_impl
| Forbidden_new_public_module
| Vmodule_impls_with_own_intf
| Undeclared_module_without_implementation
| Undeclared_private_module
| Undeclared_virtual_module

type errors =
{ errors : (single_module_error * Loc.t * Module_name.Path.t) list
Expand Down Expand Up @@ -97,14 +100,19 @@ let find_errors ~modules ~intf_only ~virtual_modules ~private_modules
in
let ( ++ ) f g loc acc = f loc (g loc acc) in
let ( !? ) = Option.is_some in
with_property private_ (add_if impl_vmodule Private_impl_of_vmodule)
with_property private_
(add_if impl_vmodule Private_impl_of_vmodule
++ add_if (not !?modules) Undeclared_private_module)
@@ with_property intf_only
(add_if has_impl Spurious_module_intf
++ add_if impl_vmodule Vmodule_impl_intf_only_exclusion)
++ add_if impl_vmodule Vmodule_impl_intf_only_exclusion
++ add_if (not !?modules) Undeclared_module_without_implementation
)
@@ with_property virtual_
(add_if has_impl Spurious_module_virtual
++ add_if !?intf_only Virt_intf_overlap
++ add_if !?private_ Private_virt_module)
++ add_if !?private_ Private_virt_module
++ add_if (not !?modules) Undeclared_virtual_module)
@@ with_property modules
(add_if
((not !?private_)
Expand Down Expand Up @@ -154,18 +162,24 @@ let check_invalid_module_listing ~stanza_loc ~modules_without_implementation
let missing_intf_only = get Missing_intf_only in
let spurious_modules_intf = get Spurious_module_intf in
let spurious_modules_virtual = get Spurious_module_virtual in
let undeclared_modules_without_implementation =
get Undeclared_module_without_implementation
in
let undeclared_private_modules = get Undeclared_private_module in
let undeclared_virtual_modules = get Undeclared_virtual_module in
let uncapitalized =
List.map ~f:(fun (_, m) -> Module_name.Path.uncapitalize m)
in
let line_list modules =
Pp.enumerate modules ~f:(fun (_, m) ->
Pp.verbatim (Module_name.Path.to_string m))
in
let print before l after =
let print ?(is_error = true) before l after =
match l with
| [] -> ()
| (loc, _) :: _ ->
User_error.raise ~loc (List.concat [ before; [ line_list l ]; after ])
User_warning.emit ~is_error ~loc
(List.concat [ before; [ line_list l ]; after ])
in
print
[ Pp.text "The following modules are implementations of virtual modules:"
Expand Down Expand Up @@ -213,6 +227,18 @@ let check_invalid_module_listing ~stanza_loc ~modules_without_implementation
(unimplemented_virt_modules |> Module_name.Path.Set.to_list
|> List.map ~f:(fun name -> (stanza_loc, name)))
[ Pp.text "You must provide an implementation for all of these modules." ];
(* Checking that (modules) incldues all declared modules *)
let print_undelared_modules field mods =
(* TODO: this is a warning for now, change to an error in 3.9 *)
print ~is_error:false
[ Pp.textf "These modules appear in the %s field:" field ]
mods
[ Pp.text "They must also appear in the modules field." ]
in
print_undelared_modules "modules_without_implementation"
undeclared_modules_without_implementation;
print_undelared_modules "private_modules" undeclared_private_modules;
print_undelared_modules "virtual_modules" undeclared_virtual_modules;
(if missing_intf_only <> [] then
match Ordered_set_lang.loc modules_without_implementation with
| None ->
Expand Down Expand Up @@ -337,4 +363,5 @@ let eval ~modules:(all_modules : Module.Source.t Module_trie.t) ~stanza_loc
eval ~modules:all_modules ~stanza_loc ~private_modules ~kind ~src_dir
settings eval0
in
(* Check that modules without implementation are a subset of the modules field *)
(eval0.modules, modules)
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,12 @@ field
> EOF

$ dune build --display short
File "dune", line 4, characters 33-34:
4 | (modules_without_implementation x)
^
Warning: These modules appear in the modules_without_implementation field:
- X
They must also appear in the module field.
ocamlc .foo.objs/byte/y.{cmi,cmo,cmt} (exit 2)
File "y.ml", line 1, characters 16-17:
1 | module type F = X
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -24,6 +24,12 @@ modules:
X is silently ignored:

$ dune build
File "dune", line 5, characters 18-19:
5 | (private_modules x))
^
Warning: These modules appear in the private_modules field:
- X
They must also appear in the module field.
File "y.ml", line 1, characters 9-14:
1 | let () = X.foo ()
^^^^^
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -26,6 +26,12 @@ Specifying a virtual module that isn't inside the (modules ..) field:
$ touch impl/x.ml

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

0 comments on commit 29f8fe0

Please sign in to comment.