Skip to content

Commit

Permalink
Turn a bunch of compatibility warnings into errors (#2442)
Browse files Browse the repository at this point in the history
Turn a bunch of compatibility warnings into errors
  • Loading branch information
rgrinberg authored Jul 24, 2019
2 parents c596a53 + 7ca3a54 commit 58a8587
Show file tree
Hide file tree
Showing 14 changed files with 56 additions and 105 deletions.
14 changes: 13 additions & 1 deletion CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,19 @@
- Enable `(explicit_js_mode)` by default. (#1941, @nojb)

- Stop symlinking object files to main directory for stanzas defined `jbuild`
files (#2440, @rgrinerg)
files (#2440, @rgrinberg)

- Library names are now validated in a strict fashion. Previously, invalid names
would be allowed for unwrapped libraries (#2442, @rgrinberg)

- mli only modules must now be explicitly declared. This was previously a
warning that is now an error. (#2442, @rgrinberg)

- Modules filtered out from the module list via the Ordered Set Language must
now be actual modules. (#2442, @rgrinberg)

- Actions which introduce targets where new targets are forbidden (e.g.
preprocessing) are now an error instead of a warning. (#2442, @rgrinberg)

1.11.0 (23/07/2019)
-------------------
Expand Down
6 changes: 2 additions & 4 deletions src/c_sources.ml
Original file line number Diff line number Diff line change
Expand Up @@ -44,13 +44,11 @@ let load_sources ~dune_version ~dir ~files =
| Unrecognized -> acc
| Not_allowed_until version ->
let loc = Loc.in_dir (Path.build dir) in
(* DUNE2: make this an error *)
User_warning.emit ~loc
User_error.raise ~loc
[ Pp.textf "Source file %s with extension %s is not allowed \
before version %s"
fn (Filename.extension fn) (Syntax.Version.to_string version)
];
acc
]
| Recognized (obj, kind) ->
let path = Path.Build.relative dir fn in
C.Kind.Dict.update acc kind ~f:(fun v ->
Expand Down
6 changes: 2 additions & 4 deletions src/dir_contents.ml
Original file line number Diff line number Diff line change
Expand Up @@ -368,8 +368,7 @@ end = struct
List.sort ~compare
(b.Buildable.loc :: List.map rest ~f:(fun b -> b.Buildable.loc))
in
(* DUNE2: make this an error *)
User_warning.emit ~loc:(Loc.drop_position b.loc)
User_error.raise ~loc:(Loc.drop_position b.loc)
[ Pp.textf "Module %S is used in several stanzas:"
(Module.Name.to_string name)
; Pp.enumerate locs ~f:(fun loc ->
Expand All @@ -381,8 +380,7 @@ end = struct
file. Note that each module cannot appear in more \
than one \"modules\" field - it must belong to a \
single library or executable."
];
b)
])
in
{ Dir_modules. libraries; executables; rev_map }

Expand Down
11 changes: 3 additions & 8 deletions src/dune_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -972,10 +972,6 @@ module Library = struct
module Wrapped = struct
include Wrapped

let value = function
| Inherited.From _ -> None
| This s -> Some (to_bool s)

let default = Simple true

let make ~wrapped ~implements ~special_builtin_support : t Inherited.t =
Expand Down Expand Up @@ -1097,13 +1093,12 @@ module Library = struct
let open Syntax.Version.Infix in
match name, public with
| Some (loc, res), _ ->
let wrapped = Wrapped.value wrapped in
(loc, Lib_name.Local.validate (loc, res) ~wrapped)
(loc, Lib_name.Local.validate (loc, res))
| None, Some { name = (loc, name) ; _ } ->
if dune_version >= (1, 1) then
match Lib_name.to_local name with
| Ok m -> (loc, m)
| Warn _ | Invalid ->
| Error ()->
User_error.raise ~loc
[ Pp.textf "Invalid library name."
; Pp.text
Expand Down Expand Up @@ -2107,7 +2102,7 @@ module Coq = struct
in
let name =
let (loc, res) = name in
(loc, Lib_name.Local.validate (loc, res) ~wrapped:None)
(loc, Lib_name.Local.validate (loc, res))
in
{ name
; public
Expand Down
41 changes: 12 additions & 29 deletions src/lib_name.ml
Original file line number Diff line number Diff line change
Expand Up @@ -6,42 +6,39 @@ let decode = Dune_lang.Decoder.string
module Local = struct
type t = string

type result =
| Ok of t
| Warn of t
| Invalid

let valid_char = function
| 'A'..'Z' | 'a'..'z' | '_' | '0'..'9' -> true
| _ -> false

let of_string (name : string) =
match name with
| "" -> Invalid
| "" -> Error ()
| (s : string) ->
if s.[0] = '.' then
Invalid
Error ()
else
let len = String.length s in
let rec loop warn i =
if i = len - 1 then
if warn then Warn s else Ok s
if warn then
Error ()
else
Ok s
else
let c = String.unsafe_get s i in
if valid_char c then
loop warn (i + 1)
else if c = '.' then
loop true (i + 1)
else
Invalid
Error ()
in
loop false 0

let of_string_exn s =
match of_string s with
| Ok s -> s
| Warn _
| Invalid ->
| Error () ->
Code_error.raise "Lib_name.Local.of_string_exn got invalid name"
[ "name", String s ]

Expand All @@ -57,24 +54,10 @@ module Local = struct
Pp.text "library names must be non-empty and composed only of the \
following characters: 'A'..'Z', 'a'..'z', '_' or '0'..'9'"

let wrapped_warning ~loc ~is_error =
User_warning.emit ~loc ~hints:[valid_format_doc] ~is_error
[ Pp.text "Invalid library name."
; Pp.text "This is temporary allowed for libraries with (wrapped false)."
; Pp.text "It will not be supported in the future. Please choose \
a valid name field."
]

let validate (loc, res) ~wrapped =
match res, wrapped with
| Ok s, _ -> s
| Warn _, None
| Warn _, Some true -> wrapped_warning ~loc ~is_error:true; assert false
| Warn s, Some false ->
(* DUNE2: turn this into an error *)
wrapped_warning ~loc ~is_error:false;
s
| Invalid, _ ->
let validate (loc, res) =
match res with
| Ok s -> s
| Error () ->
User_error.raise ~loc ~hints:[valid_format_doc]
[ Pp.text "Invalid library name." ]

Expand Down
13 changes: 4 additions & 9 deletions src/lib_name.mli
Original file line number Diff line number Diff line change
Expand Up @@ -10,18 +10,13 @@ include Dune_lang.Conv with type t := t
module Local : sig
type t

type result =
| Ok of t
| Warn of t
| Invalid

val encode : t Dune_lang.Encoder.t
val decode_loc : (Loc.t * result) Dune_lang.Decoder.t
val validate : (Loc.t * result) -> wrapped:bool option -> t
val decode_loc : (Loc.t * (t, unit) Result.t) Dune_lang.Decoder.t
val validate : (Loc.t * (t, unit) Result.t) -> t

val of_string_exn : string -> t

val of_string : string -> result
val of_string : string -> (t, unit) Result.t

val to_string : t -> string

Expand All @@ -42,7 +37,7 @@ val pp_quoted : t Fmt.t

val of_local : (Loc.t * Local.t) -> t

val to_local : t -> Local.result
val to_local : t -> (Local.t, unit) Result.t

val split : t -> Package.Name.t * string list

Expand Down
9 changes: 3 additions & 6 deletions src/modules_field_evaluator.ml
Original file line number Diff line number Diff line change
Expand Up @@ -228,8 +228,7 @@ let check_invalid_module_listing ~(buildable : Buildable.t) ~intf_only
if missing_intf_only <> [] then begin
match Ordered_set_lang.loc buildable.modules_without_implementation with
| None ->
(* DUNE2: turn this into an error *)
User_warning.emit ~loc:buildable.loc
User_error.raise ~loc:buildable.loc
[ Pp.text "Some modules don't have an implementation."
; Pp.textf
"You need to add the following field to this stanza:\
Expand All @@ -248,8 +247,7 @@ let check_invalid_module_listing ~(buildable : Buildable.t) ~intf_only
Dune_lang.to_string ~syntax:Dune (List (tag :: modules)))
]
| Some loc ->
(* DUNE2: turn this into an error *)
User_warning.emit ~loc
User_error.raise ~loc
[ Pp.text "The following modules must be listed here as they don't \
have an implementation:"
; (line_list missing_intf_only)
Expand Down Expand Up @@ -303,8 +301,7 @@ let eval ~modules:(all_modules : Module.Source.t Module.Name.Map.t)
eval ~standard:Module.Name.Map.empty private_modules
in
Module.Name.Map.iteri !fake_modules ~f:(fun m loc ->
(* DUNE2: make this an error *)
User_warning.emit ~loc
User_error.raise ~loc
[ Pp.textf "Module %s is excluded but it doesn't exist."
(Module.Name.to_string m)
]
Expand Down
7 changes: 2 additions & 5 deletions src/super_context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -695,11 +695,8 @@ module Action = struct
| [] -> ()
| x :: _ ->
let loc = String_with_vars.loc x in
(* DUNE2: make this an error *)
User_warning.emit ~loc
[ Pp.textf "%s must not have targets, this target will be ignored."
(String.capitalize context)
; Pp.textf "This will become an error in the future."
User_error.raise ~loc
[ Pp.textf "%s must not have targets." (String.capitalize context)
]
end;
let t, forms =
Expand Down
3 changes: 2 additions & 1 deletion test/blackbox-tests/test-cases/exclude-missing-module/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -2,4 +2,5 @@
File "dune", line 3, characters 22-26:
3 | (modules :standard \ fake))
^^^^
Warning: Module Fake is excluded but it doesn't exist.
Error: Module Fake is excluded but it doesn't exist.
[1]
8 changes: 1 addition & 7 deletions test/blackbox-tests/test-cases/github1811/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -4,11 +4,5 @@ Check that %{targets} is forbidden in preprocessing actions
File "dune", line 3, characters 37-47:
3 | (preprocess (action (with-stdout-to %{targets} (run cat %{input-file})))))
^^^^^^^^^^
Warning: Preprocessing actions must not have targets, this target will be
ignored.
This will become an error in the future.
File "dune", line 3, characters 39-47:
3 | (preprocess (action (with-stdout-to %{targets} (run cat %{input-file})))))
^^^^^^^^
Error: You cannot use %{targets} in preprocessing actions.
Error: Preprocessing actions must not have targets.
[1]
10 changes: 4 additions & 6 deletions test/blackbox-tests/test-cases/intf-only/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -26,25 +26,23 @@ Errors:
File "dune", line 1, characters 0-21:
1 | (library
2 | (name foo))
Warning: Some modules don't have an implementation.
Error: Some modules don't have an implementation.
You need to add the following field to this stanza:

(modules_without_implementation x y)

This will become an error in the future.
ocamlc .foo.objs/byte/foo.{cmi,cmo,cmt}
ocamlc foo.cma
[1]
$ dune build --display short --root b foo.cma
Entering directory 'b'
File "dune", line 3, characters 33-34:
3 | (modules_without_implementation x))
^
Warning: The following modules must be listed here as they don't have an
Error: The following modules must be listed here as they don't have an
implementation:
- Y
This will become an error in the future.
ocamlc .foo.objs/byte/foo.{cmi,cmo,cmt}
ocamlc foo.cma
[1]
$ dune build --display short --root c foo.cma
Entering directory 'c'
File "dune", line 3, characters 33-34:
Expand Down
6 changes: 2 additions & 4 deletions test/blackbox-tests/test-cases/name-field-validation/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -2,9 +2,7 @@
File "dune", line 3, characters 7-14:
3 | (name foo.bar)
^^^^^^^
Warning: Invalid library name.
This is temporary allowed for libraries with (wrapped false).
It will not be supported in the future. Please choose a valid name field.
Error: Invalid library name.
Hint: library names must be non-empty and composed only of the following
characters: 'A'..'Z', 'a'..'z', '_' or '0'..'9'
foo
[1]
23 changes: 4 additions & 19 deletions test/blackbox-tests/test-cases/ocamldep-multi-stanzas/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -9,26 +9,14 @@
instead.
Note: You can use "dune upgrade" to convert your project to dune.
File "jbuild", line 1, characters 0-0:
Warning: Module "Lib" is used in several stanzas:
Error: Module "Lib" is used in several stanzas:
- jbuild:2
- jbuild:6
To remove this warning, you must specify an explicit "modules" field in every
library, executable, and executables stanzas in this jbuild file. Note that
each module cannot appear in more than one "modules" field - it must belong
to a single library or executable.
Entering directory 'jbuild'
ocamldep .lib.objs/lib.ml.d
ocamlc .lib.objs/byte/lib.{cmi,cmo,cmt}
ocamlopt .lib.objs/native/lib.{cmx,o}
ocamlopt lib.{a,cmxa}
ocamldep .test.eobjs/lib.ml.d
ocamldep .test.eobjs/test.ml.d
ocamlc .test.eobjs/byte/lib.{cmi,cmo,cmt}
ocamlc .test.eobjs/byte/test.{cmi,cmo,cmt}
ocamlopt .test.eobjs/native/lib.{cmx,o}
ocamlopt .test.eobjs/native/test.{cmx,o}
ocamlopt test.exe
foo bar
[1]

$ dune build src/a.cma --debug-dep --display short --root jbuild
Entering directory 'jbuild'
Expand All @@ -41,17 +29,14 @@
instead.
Note: You can use "dune upgrade" to convert your project to dune.
File "src/jbuild", line 1, characters 0-0:
Warning: Module "X" is used in several stanzas:
Error: Module "X" is used in several stanzas:
- src/jbuild:1
- src/jbuild:2
To remove this warning, you must specify an explicit "modules" field in every
library, executable, and executables stanzas in this jbuild file. Note that
each module cannot appear in more than one "modules" field - it must belong
to a single library or executable.
ocamlc src/.a.objs/byte/a.{cmi,cmo,cmt}
ocamldep src/.a.objs/x.ml.d
ocamlc src/.a.objs/byte/a__X.{cmi,cmo,cmt}
ocamlc src/a.cma
[1]

$ dune exec ./test.exe --debug-dep --display short --root dune
Entering directory 'dune'
Expand Down
4 changes: 2 additions & 2 deletions test/blackbox-tests/test-cases/vlib/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -60,7 +60,7 @@ virtual libraries may not implement their virtual modules
1 | (library
2 | (name foo)
3 | (private_modules m))
Warning: Some modules don't have an implementation.
Error: Some modules don't have an implementation.
You need to add the following field to this stanza:
(modules_without_implementation m)
Expand Down Expand Up @@ -111,7 +111,7 @@ virtual libraries may not implement their virtual modules
File "dune", line 1, characters 0-21:
1 | (library
2 | (name foo))
Warning: Some modules don't have an implementation.
Error: Some modules don't have an implementation.
You need to add the following field to this stanza:
(modules_without_implementation m)
Expand Down

0 comments on commit 58a8587

Please sign in to comment.