Skip to content

Commit

Permalink
opam lint: Allow to mark a set of warnings as errors
Browse files Browse the repository at this point in the history
  • Loading branch information
kit-ty-kate committed Sep 4, 2023
1 parent cfa447c commit c7e4168
Show file tree
Hide file tree
Showing 3 changed files with 34 additions and 19 deletions.
22 changes: 16 additions & 6 deletions src/client/opamArg.ml
Original file line number Diff line number Diff line change
Expand Up @@ -890,13 +890,13 @@ let variable_bindings =

let warn_selector =
let parse str =
let sep = Re.(compile (set "+-")) in
let sep = Re.(compile (set "+-@")) in
let sel = Re.(compile @@
seq [bos; group (rep1 digit);
opt @@ seq [str ".."; group (rep1 digit)];
eos]) in
let rec seq i j =
if i = j then [i]
if Int.equal i j then [i]
else if i < j then i :: seq (i+1) j
else j :: seq (j+1) i
in
Expand All @@ -908,8 +908,13 @@ let warn_selector =
try seq i (int_of_string (Re.Group.get g 2))
with Not_found -> [i]
in
let enabled = Re.Group.get d 0 = "+" in
let acc = List.fold_left (fun acc n -> (n, enabled) :: acc) acc nums in
let state = match Re.Group.get d 0 with
| "+" -> `Enable
| "-" -> `Disable
| "@" -> `EnableError
| _ -> assert false
in
let acc = List.fold_left (fun acc n -> (n, state) :: acc) acc nums in
aux acc r
| [] -> acc
| _ -> raise Not_found
Expand All @@ -920,8 +925,13 @@ let warn_selector =
in
let print ppf warns =
pr_str ppf @@
OpamStd.List.concat_map "" (fun (num,enable) ->
Printf.sprintf "%c%d" (if enable then '+' else '-') num)
OpamStd.List.concat_map "" (fun (num,state) ->
let state = match state with
| `Enable -> '+'
| `Disable -> '-'
| `EnableError -> '@'
in
Printf.sprintf "%c%d" state num)
warns
in
parse, print
Expand Down
4 changes: 2 additions & 2 deletions src/client/opamArg.mli
Original file line number Diff line number Diff line change
Expand Up @@ -281,8 +281,8 @@ val dep_formula: formula Arg.conv
(** [var=value,...] argument *)
val variable_bindings: (OpamVariable.t * string) list Arg.conv

(** Warnings string ["+3..10-4"] *)
val warn_selector: (int * bool) list Arg.conv
(** Warnings string ["+3..10-4@12"] *)
val warn_selector: (int * [`Enable | `Disable | `EnableError]) list Arg.conv

val opamlist_columns: OpamListCommand.output_format list Arg.conv

Expand Down
27 changes: 16 additions & 11 deletions src/client/opamCommands.ml
Original file line number Diff line number Diff line change
Expand Up @@ -3780,8 +3780,9 @@ let lint cli =
let warnings =
mk_opt ~cli cli_original ["warnings";"W"] "WARNS"
"Select the warnings to show or hide. $(i,WARNS) should be a \
concatenation of $(b,+N), $(b,-N), $(b,+N..M), $(b,-N..M) to \
respectively enable or disable warning or error number $(b,N) or \
concatenation of $(b,+N), $(b,-N), $(b,@N), $(b,+N..M), \
$(b,-N..M), $(b,@N..M) to respectively enable, disable or \
enable-as-error warning or error number $(b,N) or \
all warnings with numbers between $(b,N) and $(b,M) inclusive.\n\
All warnings are enabled by default, unless $(i,WARNS) starts with \
$(b,+), which disables all but the selected ones."
Expand Down Expand Up @@ -3866,6 +3867,10 @@ let lint cli =
| None -> None
| Some _ -> Some []
in
let default_warn = match warnings_sel with
| (_, (`Enable | `EnableError)) :: _ -> `Disable
| (_, `Disable) :: _ | [] -> `Enable
in
let err,json =
List.fold_left (fun (err,json) opam_f ->
try
Expand All @@ -3886,20 +3891,20 @@ let lint cli =
None
in
let enabled =
let default = match warnings_sel with
| (_,true) :: _ -> false
| _ -> true
in
let map =
List.fold_left
(fun acc (wn, enable) -> OpamStd.IntMap.add wn enable acc)
(fun acc (wn, state) -> OpamStd.IntMap.add wn state acc)
OpamStd.IntMap.empty warnings_sel
in
fun w -> try OpamStd.IntMap.find w map with Not_found -> default
fun w -> try OpamStd.IntMap.find w map with Not_found -> default_warn
in
let warnings = List.filter (fun (n, _, _) -> enabled n) warnings in
let failed =
List.exists (function _,`Error,_ -> true | _ -> false) warnings
let warnings, failed =
List.fold_left (fun (warnings, failed) ((n, state, _) as warn) ->
match enabled n, state with
| `Enable, `Warning -> (warnings @ [warn], failed)
| `Enable, `Error | `EnableError, _ -> (warnings @ [warn], true)
| `Disable, _ -> (warnings, failed)
) ([], false) warnings
in
if short then
(if warnings <> [] then
Expand Down

0 comments on commit c7e4168

Please sign in to comment.