Skip to content

Commit

Permalink
Require packages to be mentioned in some way
Browse files Browse the repository at this point in the history
Tighten the warning slightly - bar:installed no longer counts as a guard
because "bar" is not referred to in any way in depends/depopts.
  • Loading branch information
dra27 committed May 20, 2024
1 parent b1802c8 commit d4f9110
Show file tree
Hide file tree
Showing 4 changed files with 56 additions and 19 deletions.
11 changes: 6 additions & 5 deletions src/format/opamFormula.ml
Original file line number Diff line number Diff line change
Expand Up @@ -379,12 +379,13 @@ let verifies f nv =
check_version_formula cstr (OpamPackage.version nv))
name_formula

let all_names f =
fold_left (fun acc (name, _) ->
OpamPackage.Name.Set.add name acc)
OpamPackage.Name.Set.empty f

let packages pkgset f =
let names =
fold_left (fun acc (name, _) ->
OpamPackage.Name.Set.add name acc)
OpamPackage.Name.Set.empty f
in
let names = all_names f in
(* dnf allows us to transform the formula into a union of intervals, where
ignoring atoms for different package names works. *)
let dnf = dnf_of_formula f in
Expand Down
3 changes: 3 additions & 0 deletions src/format/opamFormula.mli
Original file line number Diff line number Diff line change
Expand Up @@ -161,6 +161,9 @@ val verifies: t -> OpamPackage.t -> bool
(** Checks if a given set of (installed) packages satisfies a formula *)
val satisfies_depends: OpamPackage.Set.t -> t -> bool

(** Returns the set of names referred to in a formula *)
val all_names: (OpamPackage.Name.t * 'a) formula -> OpamPackage.Name.Set.t

(** Returns the subset of packages possibly matching the formula (i.e. including
all disjunction cases) *)
val packages: OpamPackage.Set.t -> t -> OpamPackage.Set.t
Expand Down
59 changes: 46 additions & 13 deletions src/state/opamFileTools.ml
Original file line number Diff line number Diff line change
Expand Up @@ -158,31 +158,46 @@ let filter_guarded variables guarded_packages =
List.filter is_unguarded variables

let unguarded_packages_from_filter guarded_packages = function
| None -> [], guarded_packages
| 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
guarded_packages, filter_guarded filter_variables guarded_packages

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

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

let unguarded_commands_variables commands =
List.fold_left (fun acc c -> unguarded_command_variables c @ acc) [] commands
let f (guarded_packages, acc) c =
let guarded_packages, unguarded_variables =
unguarded_command_variables guarded_packages c
in
guarded_packages, (unguarded_variables @ acc)
in
List.fold_left f (OpamPackage.Name.Set.empty, []) commands

(* Returns all variables from all commands (or on given [command]) and all filters *)
let all_variables ?exclude_post ?command t =
Expand All @@ -199,7 +214,11 @@ let all_variables ?exclude_post ?command t =
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) @
let guarded_packages, unguarded_commands_variables =
unguarded_commands_variables (all_commands t)
in
guarded_packages,
unguarded_commands_variables @
List.fold_left (fun acc f -> OpamFilter.variables f @ acc)
[] (all_filters ?exclude_post t)

Expand Down Expand Up @@ -529,7 +548,16 @@ let t_lint ?check_extra_files ?(check_upstream=false) ?(all=false) t =
~detail:alpha_flags
(alpha_flags <> []));
*)
(let undep_pkgs =
(let all_mentioned_packages =
OpamPackage.Name.Set.union
(OpamFormula.all_names t.depends)
(OpamFormula.all_names t.depopts)
in
let undep_pkgs =
let guarded_packages, all_unguarded_variables =
all_unguarded_variables ~exclude_post:true t
in
let first_lot =
List.fold_left
(fun acc v ->
match OpamVariable.Full.package v with
Expand All @@ -540,7 +568,12 @@ let t_lint ?check_extra_files ?(check_upstream=false) ?(all=false) t =
->
OpamPackage.Name.Set.add n acc
| _ -> acc)
OpamPackage.Name.Set.empty (all_unguarded_variables ~exclude_post:true t)
OpamPackage.Name.Set.empty all_unguarded_variables
in
let second_lot =
OpamPackage.Name.Set.diff guarded_packages all_mentioned_packages
in
OpamPackage.Name.Set.union first_lot second_lot
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 @@ -423,7 +423,7 @@ 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: "baz"
warning 41: Some packages are mentioned in package scripts or features, but there is no dependency or depopt toward them: "bar", "baz"
### : E42: The 'dev-repo:' field doesn't use version control. You should use URLs of the form "git://", "git+https://", "hg+https://"...
### <lint.opam>
opam-version: "2.0"
Expand Down

0 comments on commit d4f9110

Please sign in to comment.