@@ -119,6 +119,91 @@ let map_all_filters f t =
119
119
with_deprecated_build_test (map_commands t.deprecated_build_test) |>
120
120
with_deprecated_build_doc (map_commands t.deprecated_build_doc)
121
121
122
+ (* unguarded_commands_variables is an alternative implementation of
123
+ OpamFilter.commands_variables which excludes package variables which are
124
+ guarded by an unambiguous {package:installed} filter. That is, at each level,
125
+ if assuming !package:installed reduces the filter to false, then the uses of
126
+ package:variable are not returned. This allows expressions like:
127
+ ["--with-foo=%{foo:share}%" {foo:installed}] or even
128
+ ["--with-foo"] {foo:installed & foo:bar != "baz"} not to trigger warning 41
129
+ if the package is not explicitly depended on. *)
130
+
131
+ let unguarded_commands_variables commands =
132
+ let is_installed_variable filter guarded_packages v =
133
+ match OpamVariable.Full. package v with
134
+ | None -> guarded_packages
135
+ | (Some name ) as package ->
136
+ let is_installed var =
137
+ String. equal " installed"
138
+ (OpamVariable. to_string (OpamVariable.Full. variable var))
139
+ in
140
+ let env var =
141
+ if Option. equal OpamPackage.Name. equal
142
+ (OpamVariable.Full. package var) package &&
143
+ is_installed var then
144
+ Some (B false )
145
+ else
146
+ None
147
+ in
148
+ if is_installed v &&
149
+ OpamFilter. partial_eval env filter = FBool false then
150
+ OpamPackage.Name.Set. add name guarded_packages
151
+ else
152
+ guarded_packages
153
+ in
154
+ let filter_guarded variables guarded_packages =
155
+ let is_unguarded v =
156
+ match OpamVariable.Full. package v with
157
+ | Some package ->
158
+ not (OpamPackage.Name.Set. mem package guarded_packages)
159
+ | None -> true
160
+ in
161
+ List. filter is_unguarded variables
162
+ in
163
+ let unguarded_packages_from_filter guarded_packages = function
164
+ | None -> guarded_packages, []
165
+ | Some f ->
166
+ let filter_variables = OpamFilter. variables f in
167
+ let guarded_packages =
168
+ List. fold_left (is_installed_variable f)
169
+ guarded_packages filter_variables
170
+ in
171
+ guarded_packages, filter_guarded filter_variables guarded_packages
172
+ in
173
+ let unguarded_argument_variables guarded_packages (argument , filter ) =
174
+ let guarded_packages, filter_variables =
175
+ unguarded_packages_from_filter guarded_packages filter
176
+ in
177
+ let variables_from_arguments =
178
+ filter_guarded (OpamFilter. simple_arg_variables argument) guarded_packages
179
+ in
180
+ guarded_packages, variables_from_arguments @ filter_variables
181
+ in
182
+ let unguarded_command_variables guarded_packages (command , filter ) =
183
+ let filter_guarded_packages, filter_variables =
184
+ unguarded_packages_from_filter OpamPackage.Name.Set. empty filter
185
+ in
186
+ let add_argument (guarded_packages , acc ) argument =
187
+ let guarded_packages, unguarded_variables =
188
+ unguarded_argument_variables guarded_packages argument
189
+ in
190
+ guarded_packages, unguarded_variables @ acc
191
+ in
192
+ let command_guarded_packages, unguarded_variables =
193
+ List. fold_left add_argument (filter_guarded_packages, filter_variables)
194
+ command
195
+ in
196
+ OpamPackage.Name.Set. union guarded_packages command_guarded_packages,
197
+ unguarded_variables
198
+ in
199
+ let f (guarded_packages , acc ) c =
200
+ let guarded_packages, unguarded_variables =
201
+ unguarded_command_variables guarded_packages c
202
+ in
203
+ guarded_packages, (unguarded_variables @ acc)
204
+ in
205
+ List. fold_left f (OpamPackage.Name.Set. empty, [] ) commands
206
+
122
207
(* Returns all variables from all commands (or on given [command]) and all filters *)
123
208
let all_variables ?exclude_post ?command t =
124
209
let commands =
@@ -130,6 +215,18 @@ let all_variables ?exclude_post ?command t =
130
215
List. fold_left (fun acc f -> OpamFilter. variables f @ acc)
131
216
[] (all_filters ?exclude_post t)
132
217
218
+ (* As all_variables, but any commands or arguments which are fully guarded by
219
+ package:installed are excluded; used for Warning 41 so that
220
+ ["%{foo:share}%" {foo:installed}] doesn't trigger a warning on foo *)
221
+ let all_unguarded_variables ?exclude_post t =
222
+ let guarded_packages, unguarded_commands_variables =
223
+ unguarded_commands_variables (all_commands t)
224
+ in
225
+ guarded_packages,
226
+ unguarded_commands_variables @
227
+ List. fold_left (fun acc f -> OpamFilter. variables f @ acc)
228
+ [] (all_filters ?exclude_post t)
229
+
133
230
let map_all_variables f t =
134
231
let map_fld (x , flt ) = x, OpamFilter. map_variables f flt in
135
232
let map_optfld = function
@@ -456,18 +553,32 @@ let t_lint ?check_extra_files ?(check_upstream=false) ?(all=false) t =
456
553
~detail:alpha_flags
457
554
(alpha_flags <> []));
458
555
*)
459
- (let undep_pkgs =
460
- List. fold_left
461
- (fun acc v ->
462
- match OpamVariable.Full. package v with
463
- | Some n when
464
- t.OpamFile.OPAM. name <> Some n &&
465
- not (OpamPackage.Name.Set. mem n all_depends) &&
466
- OpamVariable. (Full. variable v <> of_string " installed" )
467
- ->
468
- OpamPackage.Name.Set. add n acc
469
- | _ -> acc)
470
- OpamPackage.Name.Set. empty (all_variables ~exclude_post: true t)
556
+ (let all_mentioned_packages =
557
+ OpamPackage.Name.Set. union
558
+ (OpamFormula. all_names t.depends)
559
+ (OpamFormula. all_names t.depopts)
560
+ in
561
+ let undep_pkgs =
562
+ let guarded_packages, all_unguarded_variables =
563
+ all_unguarded_variables ~exclude_post: true t
564
+ in
565
+ let first_lot =
566
+ List. fold_left
567
+ (fun acc v ->
568
+ match OpamVariable.Full. package v with
569
+ | Some n when
570
+ t.OpamFile.OPAM. name <> Some n &&
571
+ not (OpamPackage.Name.Set. mem n all_depends) &&
572
+ OpamVariable. (Full. variable v <> of_string " installed" )
573
+ ->
574
+ OpamPackage.Name.Set. add n acc
575
+ | _ -> acc)
576
+ OpamPackage.Name.Set. empty all_unguarded_variables
577
+ in
578
+ let second_lot =
579
+ OpamPackage.Name.Set. diff guarded_packages all_mentioned_packages
580
+ in
581
+ OpamPackage.Name.Set. union first_lot second_lot
471
582
in
472
583
cond 41 `Warning
473
584
" Some packages are mentioned in package scripts or features, but \
0 commit comments