Skip to content

Commit

Permalink
Relax warning 41 inside package:installed filters
Browse files Browse the repository at this point in the history
Warning 41 is never triggered for the use of package:installed. Extend
this so that the warning is not triggered for any uses of package:foo
_underneath_ package:installed, i.e.
  "%{package:foo}% {package:installed}
can no longer cause warning 41 on package.
  • Loading branch information
dra27 committed Apr 18, 2024
1 parent c76ce98 commit 14d1ce7
Show file tree
Hide file tree
Showing 4 changed files with 79 additions and 2 deletions.
1 change: 1 addition & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -48,6 +48,7 @@ users)
## Source

## Lint
* Relax warning 41 not to trigger on uses of package variables which are guarded by a package:installed filter [#5927 @dra27]

## Repository

Expand Down
3 changes: 3 additions & 0 deletions src/format/opamFilter.mli
Original file line number Diff line number Diff line change
Expand Up @@ -155,6 +155,9 @@ val commands: env -> command list -> string list list
(** Process a simpler command, without filters *)
val single_command: env -> arg list -> string list

(** Extracts the list of variables from an argument *)
val simple_arg_variables: simple_arg -> full_variable list

(** Extracts variables appearing in a list of commands *)
val commands_variables: command list -> full_variable list

Expand Down
75 changes: 74 additions & 1 deletion src/state/opamFileTools.ml
Original file line number Diff line number Diff line change
Expand Up @@ -119,6 +119,71 @@ let map_all_filters f t =
with_deprecated_build_test (map_commands t.deprecated_build_test) |>
with_deprecated_build_doc (map_commands t.deprecated_build_doc)

(* unguarded_commands_variables is an alternative implementation of
OpamFilter.commands_variables which excludes package variables which are
guarded by an unambiguous {package:installed} filter. That is, at each level,
if assuming !package:installed reduces the filter to false, then the uses of
package:variable are not returned. This allows expressions like:
["--with-foo=%{foo:share}%" {foo:installed}] or even
["--with-foo"] {foo:installed & foo:bar != "baz"} not to trigger warning 41
if the package is not explicitly depended on. *)

let is_installed_variable filter guarded_packages v =
match OpamVariable.Full.package v with
| None -> guarded_packages
| (Some name) as package ->
if OpamVariable.to_string (OpamVariable.Full.variable v) = "installed" then
let env v =
if OpamVariable.Full.package v = package &&
OpamVariable.(to_string (Full.variable v)) = "installed" then
Some (B false)
else
None
in
if OpamFilter.partial_eval env filter = FBool false then
OpamPackage.Name.Set.add name guarded_packages
else
guarded_packages
else
guarded_packages

let filter_guarded variables guarded_packages =
let is_unguarded v =
match OpamVariable.Full.package v with
| Some package ->
not (OpamPackage.Name.Set.mem package guarded_packages)
| None ->
true
in
List.filter is_unguarded variables

let unguarded_packages_from_filter guarded_packages = function
| None -> [], guarded_packages
| Some f ->
let filter_variables = OpamFilter.variables f in
let guarded_packages =
List.fold_left (is_installed_variable f) guarded_packages filter_variables
in
filter_guarded filter_variables guarded_packages, guarded_packages

let unguarded_argument_variables guarded_packages (argument, filter) =
let filter_variables, guarded_packages =
unguarded_packages_from_filter guarded_packages filter
in
(filter_guarded (OpamFilter.simple_arg_variables argument) guarded_packages) @ filter_variables

let unguarded_command_variables (command, filter) =
let filter_variables, guarded_packages =
unguarded_packages_from_filter OpamPackage.Name.Set.empty filter
in
let add_argument acc argument =
unguarded_argument_variables guarded_packages argument @ acc
in
List.fold_left add_argument filter_variables command

let unguarded_commands_variables commands =
List.fold_left (fun acc c -> unguarded_command_variables c @ acc) [] commands

(* Returns all variables from all commands (or on given [command]) and all filters *)
let all_variables ?exclude_post ?command t =
let commands =
Expand All @@ -130,6 +195,14 @@ let all_variables ?exclude_post ?command t =
List.fold_left (fun acc f -> OpamFilter.variables f @ acc)
[] (all_filters ?exclude_post t)

(* As all_variables, but any commands or arguments which are fully guarded by
package:installed are excluded; used for Warning 41 so that
["%{foo:share}%" {foo:installed}] doesn't trigger a warning on foo *)
let all_unguarded_variables ?exclude_post t =
unguarded_commands_variables (all_commands t) @
List.fold_left (fun acc f -> OpamFilter.variables f @ acc)
[] (all_filters ?exclude_post t)

let map_all_variables f t =
let map_fld (x, flt) = x, OpamFilter.map_variables f flt in
let map_optfld = function
Expand Down Expand Up @@ -467,7 +540,7 @@ let t_lint ?check_extra_files ?(check_upstream=false) ?(all=false) t =
->
OpamPackage.Name.Set.add n acc
| _ -> acc)
OpamPackage.Name.Set.empty (all_variables ~exclude_post:true t)
OpamPackage.Name.Set.empty (all_unguarded_variables ~exclude_post:true t)
in
cond 41 `Warning
"Some packages are mentioned in package scripts or features, but \
Expand Down
2 changes: 1 addition & 1 deletion tests/reftests/lint.test
Original file line number Diff line number Diff line change
Expand Up @@ -985,4 +985,4 @@ build: [
]
### opam lint ./lint.opam
${BASEDIR}/lint.opam: Warnings.
warning 41: Some packages are mentioned in package scripts or features, but there is no dependency or depopt toward them: "bar", "baz", "foo"
warning 41: Some packages are mentioned in package scripts or features, but there is no dependency or depopt toward them: "baz"

0 comments on commit 14d1ce7

Please sign in to comment.