Skip to content

Commit

Permalink
warning cli: tweak single-letter warning deprecation (#10312)
Browse files Browse the repository at this point in the history
cli: tweak warning cli deprecation

With this commit using -w a+... and -w A+... does not trigger any deprecation message:
The deprecation message only occurs when several unsigned letters are used in sequence.
  • Loading branch information
Octachron committed Apr 15, 2021
1 parent b720b58 commit 2c85ab7
Show file tree
Hide file tree
Showing 3 changed files with 70 additions and 12 deletions.
4 changes: 3 additions & 1 deletion Changes
Original file line number Diff line number Diff line change
Expand Up @@ -225,10 +225,12 @@ Working version
- #8877: Call the linker when ocamlopt is invoked with .o and .a files only.
(Greta Yorsh, review by Leo White)

- #10207: deprecate single uppercase or lowercase letter in warning
- #10207, #10312: deprecate consecutive letters in warning
specifications.
The form `-w aBcD` was equivalent to `-w -a+b-c+d`.
It is now deprecated to improve the coexistence with warning mnemonics.
However, using isolated single letter is not deprecated to allow the form
`-w "A-32..50-45"`.
(Florian Angeletti, review by Damien Doligez and Gabriel Scherer)

- #10232: Warning for unused record fields.
Expand Down
38 changes: 38 additions & 0 deletions testsuite/tests/warnings/deprecated_warning_specs.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,38 @@
(* TEST
* expect
*)

(** Deprecated sequences of unsigned letters *)

[@@@warning "fragile-math"]
[%%expect {|
Line 3, characters 0-27:
3 | [@@@warning "fragile-math"]
^^^^^^^^^^^^^^^^^^^^^^^^^^^
Alert ocaml_deprecated_cli: Setting a warning with a sequence of lowercase or uppercase letters,
like 'ath', is deprecated.
Use the equivalent signed form: -f-r-a-g-i-l-e-m-a-t-h.
Hint: Enabling or disabling a warning by its mnemonic name requires a + or - prefix.
Hint: Did you make a spelling mistake when using a mnemonic name?
|}]

[@@@warning "ab-cdg+efh"]
[%%expect {|
Line 1, characters 0-25:
1 | [@@@warning "ab-cdg+efh"]
^^^^^^^^^^^^^^^^^^^^^^^^^
Alert ocaml_deprecated_cli: Setting a warning with a sequence of lowercase or uppercase letters,
like 'fh', is deprecated.
Use the equivalent signed form: -a-b-c-d-g+e-f-h.
Hint: Enabling or disabling a warning by its mnemonic name requires a + or - prefix.
|}]


(** -w "a+10..." and -w "A-10..." are still supported *)
[@@@warning "a+1..20+50"]
[%%expect {|
|}]

[@@@warning "A-3..14-56"]
[%%expect {|
|}]
40 changes: 29 additions & 11 deletions utils/warnings.ml
Original file line number Diff line number Diff line change
Expand Up @@ -515,8 +515,7 @@ type token =
| Num of int * int * modifier

let letter_alert tokens =
let deprecated = function Letter (c,None) -> Some c | _ -> None in
let print_char ppf c =
let print_warning_char ppf c =
let lowercase = Char.lowercase_ascii c = c in
Format.fprintf ppf "%c%c"
(if lowercase then '-' else '+') c
Expand All @@ -532,15 +531,35 @@ let letter_alert tokens =
else
Format.fprintf ppf "%a%d..%d" print_modifier m a b
| Letter(l,Some m) -> Format.fprintf ppf "%a%c" print_modifier m l
| Letter(l,None) -> print_char ppf l
| Letter(l,None) -> print_warning_char ppf l
in
match List.find_map deprecated tokens with
| None -> None
| Some example ->
let consecutive_letters =
(* we are tracking sequences of 2 or more consecutive unsigned letters
in warning strings, for instance in '-w "not-principa"'. *)
let commit_chunk l = function
| [] | [ _ ] -> l
| _ :: _ :: _ as chunk -> List.rev chunk :: l
in
let group_consecutive_letters (l,current) = function
| Letter (x, None) -> (l, x::current)
| _ -> (commit_chunk l current, [])
in
let l, on_going =
List.fold_left group_consecutive_letters ([],[]) tokens
in
commit_chunk l on_going
in
match consecutive_letters with
| [] -> None
| example :: _ ->
let pos = { Lexing.dummy_pos with pos_fname = "_none_" } in
let nowhere = { loc_start=pos; loc_end=pos; loc_ghost=true } in
let spelling_hint ppf =
if List.length (List.filter_map deprecated tokens) >= 5 then
let max_seq_len =
List.fold_left (fun l x -> max l (List.length x))
0 consecutive_letters
in
if max_seq_len >= 5 then
Format.fprintf ppf
"@ @[Hint: Did you make a spelling mistake \
when using a mnemonic name?@]"
Expand All @@ -549,14 +568,13 @@ let letter_alert tokens =
in
let message =
Format.asprintf
"@[<v>@[Setting a warning with single lowercase \
or uppercase letters, like '%c' or '%c',@ is deprecated.@]@ \
"@[<v>@[Setting a warning with a sequence of lowercase \
or uppercase letters,@ like '%a',@ is deprecated.@]@ \
@[Use the equivalent signed form:@ %t.@]@ \
@[Hint: Enabling or disabling a warning by its mnemonic name \
requires a + or - prefix.@]\
%t@?@]"
(Char.lowercase_ascii example)
(Char.uppercase_ascii example)
Format.(pp_print_list ~pp_sep:(fun _ -> ignore) pp_print_char) example
(fun ppf -> List.iter (print_token ppf) tokens)
spelling_hint
in
Expand Down

0 comments on commit 2c85ab7

Please sign in to comment.