Skip to content

Commit

Permalink
chore: make undeclared modules check an error (#7674)
Browse files Browse the repository at this point in the history
Signed-off-by: Ali Caglayan <alizter@gmail.com>
  • Loading branch information
Alizter authored Aug 7, 2023
1 parent 23c6282 commit af1531e
Show file tree
Hide file tree
Showing 10 changed files with 67 additions and 10 deletions.
2 changes: 1 addition & 1 deletion CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -208,7 +208,7 @@ changelog properly.

- 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,
will cause Dune to emit a warning which will become an error in 3.11. (#7608,
fixes #7026, @Alizter)

- Preliminary support for Coq compiled intefaces (`.vos` files) enabled via
Expand Down
3 changes: 3 additions & 0 deletions doc/changes/7674.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
- Modules that were declared in `(modules_without_implementation)`,
`(private_modules)` or `(virtual_modules)` but not declared in `(modules)`
will raise an error. (#7674, @Alizter)
4 changes: 3 additions & 1 deletion src/dune_rules/melange/melange_stanzas.ml
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,7 @@ module Emit = struct
; compile_flags : Ordered_set_lang.Unexpanded.t
; allow_overlapping_dependencies : bool
; enabled_if : Blang.t
; dune_version : Dune_lang.Syntax.Version.t
}

type Stanza.t += T of t
Expand Down Expand Up @@ -113,7 +114,7 @@ module Emit = struct
let open Enabled_if in
let allowed_vars = Any in
decode ~allowed_vars ~since:None ()
in
and+ dune_version = Dune_lang.Syntax.get_exn Stanza.syntax in
let preprocess =
let init =
let f libname = Preprocess.With_instrumentation.Ordinary libname in
Expand Down Expand Up @@ -142,6 +143,7 @@ module Emit = struct
; compile_flags
; allow_overlapping_dependencies
; enabled_if
; dune_version
})
;;

Expand Down
1 change: 1 addition & 0 deletions src/dune_rules/melange/melange_stanzas.mli
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,7 @@ module Emit : sig
; compile_flags : Ordered_set_lang.Unexpanded.t
; allow_overlapping_dependencies : bool
; enabled_if : Blang.t
; dune_version : Dune_lang.Syntax.Version.t
}

type Stanza.t += T of t
Expand Down
5 changes: 5 additions & 0 deletions src/dune_rules/ml_sources.ml
Original file line number Diff line number Diff line change
Expand Up @@ -297,6 +297,7 @@ let make_lib_modules
~(lib : Library.t)
~modules
~include_subdirs:(loc_include_subdirs, (include_subdirs : Dune_file.Include_subdirs.t))
~version
=
let open Resolve.Memo.O in
let* kind, main_module_name, wrapped =
Expand Down Expand Up @@ -354,6 +355,7 @@ let make_lib_modules
(Option.value ~default:Ordered_set_lang.standard lib.private_modules)
~src_dir:dir
modules_settings
~version
in
let () =
match lib.stdlib, include_subdirs with
Expand Down Expand Up @@ -424,6 +426,7 @@ let modules_of_stanzas dune_file ~dir ~scope ~lookup_vlib ~modules ~include_subd
~modules
~lib
~include_subdirs
~version:lib.dune_version
>>= Resolve.read_memo
in
let obj_dir = Library.obj_dir lib ~dir in
Expand All @@ -440,6 +443,7 @@ let modules_of_stanzas dune_file ~dir ~scope ~lookup_vlib ~modules ~include_subd
~src_dir:dir
~kind:Modules_field_evaluator.Exe_or_normal_lib
~private_modules:Ordered_set_lang.standard
~version:exes.dune_version
modules_settings
in
let modules =
Expand All @@ -457,6 +461,7 @@ let modules_of_stanzas dune_file ~dir ~scope ~lookup_vlib ~modules ~include_subd
~modules
~stanza_loc:mel.loc
~kind:Modules_field_evaluator.Exe_or_normal_lib
~version:mel.dune_version
~private_modules:Ordered_set_lang.standard
~src_dir:dir
mel.modules
Expand Down
10 changes: 7 additions & 3 deletions src/dune_rules/modules_field_evaluator.ml
Original file line number Diff line number Diff line change
Expand Up @@ -153,6 +153,7 @@ let check_invalid_module_listing
~existing_virtual_modules
~allow_new_public_modules
~is_vendored
~version
=
let { errors; unimplemented_virt_modules } =
find_errors
Expand Down Expand Up @@ -240,12 +241,11 @@ let check_invalid_module_listing
[ Pp.text "You must provide an implementation for all of these modules." ];
(* Checking that (modules) includes all declared modules *)
let print_undelared_modules field mods =
(* TODO: this is a warning for now, change to an error in 3.9. *)
(* If we are in a vendored stanza we do nothing. *)
if not is_vendored
then
print
~is_error:false
~is_error:(version >= (3, 11))
[ Pp.textf "These modules appear in the %s field:" field ]
mods
[ Pp.text "They must also appear in the modules field." ]
Expand Down Expand Up @@ -320,6 +320,7 @@ let eval
~kind
~src_dir
~is_vendored
~version
{ Stanza_common.Modules_settings.modules = _
; root_module
; modules_without_implementation
Expand Down Expand Up @@ -360,7 +361,8 @@ let eval
~private_modules
~existing_virtual_modules
~allow_new_public_modules
~is_vendored;
~is_vendored
~version;
let all_modules =
Module_trie.mapi modules ~f:(fun _path (_, m) ->
let name = [ Module.Source.name m ] in
Expand Down Expand Up @@ -394,6 +396,7 @@ let eval
~private_modules
~kind
~src_dir
~version
(settings : Stanza_common.Modules_settings.t)
=
let eval0 =
Expand All @@ -418,6 +421,7 @@ let eval
~is_vendored
settings
eval0
~version
in
eval0.modules, modules
;;
1 change: 1 addition & 0 deletions src/dune_rules/modules_field_evaluator.mli
Original file line number Diff line number Diff line change
Expand Up @@ -25,5 +25,6 @@ val eval
-> private_modules:Ordered_set_lang.t
-> kind:kind
-> src_dir:Path.Build.t
-> version:Dune_lang.Syntax.Version.t
-> Stanza_common.Modules_settings.t
-> ((Loc.t * Module.Source.t) Module_trie.t * Module.t Module_trie.t) Memo.t
Original file line number Diff line number Diff line change
Expand Up @@ -22,20 +22,34 @@ field

X is warned about:

$ dune build --display short
$ dune build
File "src/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 modules field.
ocamlc src/.foo.objs/byte/y.{cmi,cmo,cmt} (exit 2)
File "src/y.ml", line 1, characters 16-17:
1 | module type F = X
^
Error: Unbound module type X
[1]

In 3.11 onwards this warning becomes an error

$ cat > dune-project << EOF
> (lang dune 3.11)
> EOF

$ dune build
File "src/dune", line 4, characters 33-34:
4 | (modules_without_implementation x)
^
Error: These modules appear in the modules_without_implementation field:
- X
They must also appear in the modules field.
[1]

This should be ignored if we are in vendored_dirs

$ cat > dune << EOF
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -37,6 +37,21 @@ X is warned about:
Error: Unbound module X
[1]

In 3.11 onwards this warning becomes an error

$ cat > dune-project << EOF
> (lang dune 3.11)
> EOF

$ dune build
File "src/dune", line 5, characters 18-19:
5 | (private_modules x))
^
Error: These modules appear in the private_modules field:
- X
They must also appear in the modules field.
[1]

This warning should be ignored if we are in vendored_dirs

$ cat > dune << EOF
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -29,15 +29,13 @@ Specifying a virtual module that isn't inside the (modules ..) field:

X is warned about:

$ dune build --display short
$ dune build
File "src/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 modules field.
ocamldep src/impl/.impl.objs/x.impl.d
ocamlc src/.foo.objs/byte/y.{cmi,cmo,cmt} (exit 2)
File "src/y.ml", line 1, characters 16-17:
1 | module type F = X
^
Expand All @@ -49,6 +47,20 @@ X is warned about:
Error: No rule found for src/.foo.objs/y.impl.all-deps
[1]

In 3.11 onwards this warning becomes an error

$ cat > dune-project << EOF
> (lang dune 3.11)
> EOF

$ dune build ./bar.exe
File "src/dune", line 4, characters 18-19:
4 | (virtual_modules x)
^
Error: These modules appear in the virtual_modules field:
- X
They must also appear in the modules field.
[1]

This should be ignored if we are in vendored_dirs

Expand Down

0 comments on commit af1531e

Please sign in to comment.