Skip to content

Commit 8c542a9

Browse files
authored
Merge pull request #6644 from kit-ty-kate/no-poly-list-mem
Replace every polymorphic uses of List.mem by a version that doesn't use Repr.equal
2 parents 628d259 + c34ed71 commit 8c542a9

37 files changed

+331
-123
lines changed

master_changes.md

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -102,6 +102,7 @@ users)
102102
## Shell
103103

104104
## Internal
105+
* Replace every polymorphic uses of `List.mem` by a version that doesn't use `Repr.equal` [#6644 @kit-ty-kate]
105106

106107
## Internal: Unix
107108

@@ -170,19 +171,26 @@ users)
170171
## opam-solver
171172

172173
## opam-format
174+
* `OpamFormula.equal_relop`: was added [#6644 @kit-ty-kate]
175+
* `OpamTypesBase.{action,pkg_flag,simple_arg,arg,filter,command}_equal`: were added [#6644 @kit-ty-kate]
176+
* `OpamVariable.variable_contents_equal`: was added [#6644 @kit-ty-kate]
173177

174178
## opam-core
175179
* `OpamConsole.log`: does not keep log messages before initialization if the code is ran through a library [#6487 @kit-ty-kate]
176180
* `OpamCoreConfig.in_opam`: was added [#6487 @kit-ty-kate]
177181
* `OpamSystem.cpu_count`: now uses a C binding instead of system utilities to get the number of cores of the current machine [#6634 @kit-ty-kate]
178182
* `OpamSystem.is_reg_dir`: is now exposed, which returns `true` only if its parameter is a directory, exists and is not a symlink. It returns `false` otherwise [#6450 @kit-ty-kate]
179183
* `OpamCompat.List.fold_left_map`: was added [#6442 @kit-ty-kate]
184+
* `OpamCompat.List.equal`: was added [#6644 @kit-ty-kate]
180185
* `OpamCompat.Map.filter_map`: was added [#6442 @kit-ty-kate]
181186
* `OpamCompat.MAP`: was added [#6442 @kit-ty-kate]
187+
* `OpamCompat.Pair.equal`: was added [#6644 @kit-ty-kate]
182188
* `OpamCompat.String.{starts_with,ends_with,for_all,fold_left}`: were added [#6442 @kit-ty-kate]
183189
* `OpamHash.check_string`: was added [#6661 @kit-ty-kate]
190+
* `OpamHash.equal_kind`: was added [#6644 @kit-ty-kate]
184191
* `OpamStd.List.fold_left_map`: was moved to `OpamCompat.List.fold_left_map` [#6442 @kit-ty-kate]
185192
* `OpamStd.List.{cons,find_opt,filter_map}`: were removed. Use `Stdlib.List` instead. [#6442 @kit-ty-kate]
193+
* `OpamStd.List.mem`: was added, having as argument the equality function [#6644 @kit-ty-kate]
186194
* `OpamStd.Op.{(@@),(|>)}`: were removed. Use `Stdlib` instead. [#6442 @kit-ty-kate]
187195
* `OpamStd.Option.{map,iter,compare,equal,to_string,some}`: were removed. Use `Stdlib.Option` instead. [#6442 @kit-ty-kate]
188196
* `OpamStd.Map.filter_map`: is now the implementation from `Stdlib.Map` when using OCaml >= 4.11 [#6442 @kit-ty-kate]

src/client/opamAdminCommand.ml

Lines changed: 10 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -271,7 +271,8 @@ let cache_command cli =
271271

272272
let cache_dir_url = OpamFilename.remove_prefix_dir repo_root cache_dir in
273273
if not no_repo_update then
274-
if not (List.mem cache_dir_url (OpamFile.Repo.dl_cache repo_def)) then
274+
if not (OpamStd.List.mem String.equal
275+
cache_dir_url (OpamFile.Repo.dl_cache repo_def)) then
275276
(OpamConsole.msg "Adding %s to %s...\n"
276277
cache_dir_url (OpamFile.to_string repo_file);
277278
OpamFile.Repo.write repo_file
@@ -671,7 +672,9 @@ let add_hashes_command cli =
671672
let hashes = OpamFile.URL.checksum urlf in
672673
let hashes =
673674
if replace then
674-
List.filter (fun h -> List.mem (OpamHash.kind h) hash_types)
675+
List.filter (fun h ->
676+
OpamStd.List.mem OpamHash.equal_kind
677+
(OpamHash.kind h) hash_types)
675678
hashes
676679
else hashes
677680
in
@@ -822,10 +825,13 @@ let lint_command cli =
822825
OpamPackage.Map.fold (fun nv prefix ret ->
823826
let opam_file = OpamRepositoryPath.opam repo_root prefix nv in
824827
let w, _ = OpamFileTools.lint_file ~handle_dirname:true opam_file in
825-
if List.exists (fun (n,_,_) -> List.mem n ign) w then ret else
828+
if List.exists (fun (n,_,_) -> OpamStd.List.mem Int.equal n ign) w then
829+
ret
830+
else
826831
let w =
827832
List.filter (fun (n,_,_) ->
828-
(incl = [] || List.mem n incl) && not (List.mem n excl))
833+
(incl = [] || OpamStd.List.mem Int.equal n incl) &&
834+
not (OpamStd.List.mem Int.equal n excl))
829835
w
830836
in
831837
if w <> [] then

src/client/opamAdminRepoUpgrade.ml

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -420,7 +420,8 @@ let do_upgrade repo_root =
420420
let opam0 = OpamFile.OPAM.read opam_file in
421421
OpamFile.OPAM.print_errors ~file:opam_file opam0;
422422
let nv = OpamFile.OPAM.package opam0 in
423-
if not (List.mem nv.name ocaml_package_names) &&
423+
if not (OpamStd.List.mem OpamPackage.Name.equal
424+
nv.name ocaml_package_names) &&
424425
not (OpamPackage.Name.Set.mem nv.name all_base_packages) then
425426
let opam = OpamFileTools.add_aux_files ~files_subdir_hashes:true opam0 in
426427
let opam =

src/client/opamAuxCommands.ml

Lines changed: 5 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -287,7 +287,7 @@ let autopin_aux st ?quiet ?recurse ?subpath ?locked
287287
in
288288
match OpamStd.Option.Op.( primary_url st nv >>= OpamUrl.local_dir) with
289289
| Some d ->
290-
List.mem d pinning_dirs
290+
OpamStd.List.mem OpamFilename.Dir.equal d pinning_dirs
291291
| None -> false)
292292
st.pinned
293293
in
@@ -555,7 +555,8 @@ let check_and_revert_sandboxing root config =
555555
OpamInitDefaults.sandbox_wrappers
556556
|> List.flatten
557557
in
558-
List.filter (fun cmd -> List.mem cmd init_sdbx_cmds)
558+
List.filter (fun cmd ->
559+
OpamStd.List.mem OpamTypesBase.command_equal cmd init_sdbx_cmds)
559560
OpamFile.Wrappers.(wrap_build w @ wrap_install w @ wrap_remove w)
560561
in
561562
let env = fun v ->
@@ -596,7 +597,8 @@ let check_and_revert_sandboxing root config =
596597
if working_or_noop then config else
597598
let wrappers =
598599
let filter sdbx_cmd =
599-
List.filter (fun cmd_l -> not (List.mem cmd_l sdbx_cmd))
600+
List.filter (fun cmd_l ->
601+
not (OpamStd.List.mem OpamTypesBase.command_equal cmd_l sdbx_cmd))
600602
in
601603
List.fold_left OpamFile.Wrappers.(fun w -> function
602604
| `build sdbx_build ->

src/client/opamCLIVersion.ml

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,9 @@ type t = int * int
1212

1313
let supported_versions = [(2, 0); (2, 1); (2,2); (2,3); (2,4)]
1414

15-
let is_supported v = List.mem v supported_versions
15+
let is_supported v =
16+
OpamStd.List.mem (OpamCompat.Pair.equal Int.equal Int.equal)
17+
v supported_versions
1618

1719
let of_string s =
1820
match String.index s '.' with

src/client/opamClient.ml

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -432,8 +432,8 @@ let update
432432
let all_repos = OpamRepositoryName.Map.keys rt.repositories in
433433
if dev_only then []
434434
else if names <> [] then
435-
List.filter
436-
(fun r -> List.mem (OpamRepositoryName.to_string r) names)
435+
List.filter (fun r ->
436+
OpamStd.List.mem String.equal (OpamRepositoryName.to_string r) names)
437437
all_repos
438438
else if all then all_repos
439439
else OpamSwitchState.repos_list st
@@ -506,7 +506,8 @@ let update
506506
let remaining =
507507
let ps = packages ++ ignore_packages in
508508
List.filter (fun n -> not (
509-
List.mem (OpamRepositoryName.of_string n) repo_names ||
509+
OpamStd.List.mem OpamRepositoryName.equal
510+
(OpamRepositoryName.of_string n) repo_names ||
510511
(try OpamPackage.has_name ps (OpamPackage.Name.of_string n)
511512
with Failure _ -> false) ||
512513
(try OpamPackage.Set.mem (OpamPackage.of_string n) ps

src/client/opamCommands.ml

Lines changed: 8 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -2379,7 +2379,7 @@ let repository cli =
23792379
OpamConsole.error_and_exit `Not_found
23802380
"No switch %s found"
23812381
(OpamSwitch.to_string sw)
2382-
else if List.mem sw acc then acc
2382+
else if OpamStd.List.mem OpamSwitch.equal sw acc then acc
23832383
else acc @ [sw]
23842384
| `Current_switch | `This_switch ->
23852385
match OpamStateConfig.get_switch_opt () with
@@ -2388,7 +2388,7 @@ let repository cli =
23882388
'--set-default'?";
23892389
acc
23902390
| Some sw ->
2391-
if List.mem sw acc then acc
2391+
if OpamStd.List.mem OpamSwitch.equal sw acc then acc
23922392
else acc @ [sw])
23932393
[] scope
23942394
in
@@ -4286,7 +4286,9 @@ let clean cli =
42864286
(OpamPackage.Set.elements st.pinned)
42874287
in
42884288
List.iter (fun d ->
4289-
if not (List.mem d pinning_overlay_dirs) then rmdir d)
4289+
if not (OpamStd.List.mem OpamFilename.Dir.equal
4290+
d pinning_overlay_dirs) then
4291+
rmdir d)
42904292
(OpamFilename.dirs (OpamPath.Switch.Overlay.dir root sw));
42914293
let keep_sources_dir =
42924294
OpamPackage.Set.elements
@@ -4297,7 +4299,9 @@ let clean cli =
42974299
in
42984300
OpamFilename.dirs (OpamPath.Switch.sources_dir root sw) |>
42994301
List.iter (fun d ->
4300-
if not (List.mem d keep_sources_dir) then rmdir d))
4302+
if not (OpamStd.List.mem OpamFilename.Dir.equal
4303+
d keep_sources_dir) then
4304+
rmdir d))
43014305
switches);
43024306
if repos then
43034307
(OpamFilename.with_flock `Lock_write (OpamPath.repos_lock gt.root)

src/client/opamConfigCommand.ml

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -713,7 +713,12 @@ let switch_allowed_fields, switch_allowed_sections =
713713
in
714714
let allowed_sections =
715715
let rem_elem new_elems elems =
716-
List.filter (fun n -> not (List.mem n new_elems)) elems
716+
List.filter (fun n ->
717+
not (OpamStd.List.mem
718+
(OpamCompat.Pair.equal
719+
OpamVariable.equal OpamVariable.variable_contents_equal)
720+
n new_elems))
721+
elems
717722
in
718723
lazy (
719724
OpamFile.Switch_config.([

src/client/opamRepositoryCommand.ml

Lines changed: 55 additions & 53 deletions
Original file line numberDiff line numberDiff line change
@@ -27,7 +27,7 @@ let update_selection gt ~global ~switches update_fun =
2727
if global then
2828
(* ensure all unselected switches aren't modified by changing the default *)
2929
(List.iter (fun sw ->
30-
if not (List.mem sw switches) then
30+
if not (OpamStd.List.mem OpamSwitch.equal sw switches) then
3131
OpamSwitchState.update_repositories gt (fun r -> r) sw)
3232
(OpamFile.Config.installed_switches gt.config);
3333
let (), gt =
@@ -230,58 +230,60 @@ let update_with_auto_upgrade rt repo_names =
230230
else
231231
let rt, done_upgrade =
232232
List.fold_left (fun (rt, done_upgrade) r ->
233-
if List.mem r.repo_name failed then rt, done_upgrade else
234-
let def =
235-
OpamRepositoryName.Map.find r.repo_name rt.repos_definitions
236-
in
237-
let need_upgrade = match OpamFile.Repo.opam_version def with
238-
| None ->
239-
OpamConsole.note
240-
"Repository at %s doesn't define its version, assuming it's 1.2."
241-
(OpamUrl.to_string r.repo_url);
242-
true
243-
| Some v when
244-
OpamVersion.compare v OpamAdminRepoUpgrade.upgradeto_version < 0
245-
-> true
246-
| _ -> false
247-
in
248-
if need_upgrade then
249-
(if not done_upgrade then
250-
(OpamConsole.header_msg
251-
"Upgrading repositories from older opam format";
252-
OpamRepositoryState.Cache.remove ());
253-
OpamConsole.msg "Upgrading repository \"%s\"...\n"
254-
(OpamRepositoryName.to_string r.repo_name);
255-
let open OpamProcess.Job.Op in
256-
let repo_root = OpamRepositoryState.get_repo_root rt r in
257-
OpamAdminRepoUpgrade.do_upgrade repo_root;
258-
if OpamRepositoryConfig.(!r.repo_tarring) then
259-
OpamProcess.Job.run
260-
(OpamFilename.make_tar_gz_job
261-
(OpamRepositoryPath.tar rt.repos_global.root r.repo_name)
262-
repo_root
263-
@@| function
264-
| Some e ->
265-
Printf.ksprintf failwith
266-
"Failed to regenerate local repository archive: %s"
267-
(Printexc.to_string e)
268-
| None -> ());
269-
let def =
270-
OpamFile.Repo.safe_read (OpamRepositoryPath.repo repo_root) |>
271-
OpamFile.Repo.with_root_url r.repo_url
272-
in
273-
let opams =
274-
OpamRepositoryState.load_opams_from_dir r.repo_name repo_root
275-
in
276-
let rt = {
277-
rt with
278-
repos_definitions =
279-
OpamRepositoryName.Map.add r.repo_name def rt.repos_definitions;
280-
repo_opams =
281-
OpamRepositoryName.Map.add r.repo_name opams rt.repo_opams;
282-
} in
283-
rt, true)
284-
else rt, done_upgrade)
233+
if OpamStd.List.mem OpamRepositoryName.equal r.repo_name failed then
234+
rt, done_upgrade
235+
else
236+
let def =
237+
OpamRepositoryName.Map.find r.repo_name rt.repos_definitions
238+
in
239+
let need_upgrade = match OpamFile.Repo.opam_version def with
240+
| None ->
241+
OpamConsole.note
242+
"Repository at %s doesn't define its version, assuming it's 1.2."
243+
(OpamUrl.to_string r.repo_url);
244+
true
245+
| Some v when
246+
OpamVersion.compare v OpamAdminRepoUpgrade.upgradeto_version < 0
247+
-> true
248+
| _ -> false
249+
in
250+
if need_upgrade then
251+
(if not done_upgrade then
252+
(OpamConsole.header_msg
253+
"Upgrading repositories from older opam format";
254+
OpamRepositoryState.Cache.remove ());
255+
OpamConsole.msg "Upgrading repository \"%s\"...\n"
256+
(OpamRepositoryName.to_string r.repo_name);
257+
let open OpamProcess.Job.Op in
258+
let repo_root = OpamRepositoryState.get_repo_root rt r in
259+
OpamAdminRepoUpgrade.do_upgrade repo_root;
260+
if OpamRepositoryConfig.(!r.repo_tarring) then
261+
OpamProcess.Job.run
262+
(OpamFilename.make_tar_gz_job
263+
(OpamRepositoryPath.tar rt.repos_global.root r.repo_name)
264+
repo_root
265+
@@| function
266+
| Some e ->
267+
Printf.ksprintf failwith
268+
"Failed to regenerate local repository archive: %s"
269+
(Printexc.to_string e)
270+
| None -> ());
271+
let def =
272+
OpamFile.Repo.safe_read (OpamRepositoryPath.repo repo_root) |>
273+
OpamFile.Repo.with_root_url r.repo_url
274+
in
275+
let opams =
276+
OpamRepositoryState.load_opams_from_dir r.repo_name repo_root
277+
in
278+
let rt = {
279+
rt with
280+
repos_definitions =
281+
OpamRepositoryName.Map.add r.repo_name def rt.repos_definitions;
282+
repo_opams =
283+
OpamRepositoryName.Map.add r.repo_name opams rt.repo_opams;
284+
} in
285+
rt, true)
286+
else rt, done_upgrade)
285287
(rt, false) repos
286288
in
287289
if done_upgrade then OpamRepositoryState.Cache.save rt;

src/client/opamSolution.ml

Lines changed: 22 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -937,7 +937,10 @@ let parallel_apply t
937937
(* Cleanup build/install actions when one of them failed, it's verbose and
938938
doesn't add information *)
939939
let successful =
940-
let was_successful p = not @@ List.mem (`Install p) failed in
940+
let was_successful p =
941+
not (OpamStd.List.mem (OpamTypesBase.action_equal OpamPackage.equal)
942+
(`Install p) failed)
943+
in
941944
List.filter (function
942945
| `Fetch ps -> List.for_all was_successful ps
943946
| `Build p -> was_successful p
@@ -947,10 +950,12 @@ let parallel_apply t
947950
let remaining =
948951
List.filter (function
949952
| `Remove p | `Install p
950-
when List.mem (`Build p) failed -> false
953+
when
954+
OpamStd.List.mem (OpamTypesBase.action_equal OpamPackage.equal)
955+
(`Build p) failed -> false
951956
| `Remove p | `Install p | `Build p
952957
when List.exists (function
953-
| `Fetch ps -> List.mem p ps
958+
| `Fetch ps -> OpamStd.List.mem OpamPackage.equal p ps
954959
| _ -> false) failed
955960
-> false
956961
| `Build _ | `Change _ | `Fetch _ | `Install _
@@ -960,7 +965,10 @@ let parallel_apply t
960965
let removes_missing_source =
961966
List.filter (function
962967
| `Remove p as rem ->
963-
let is_fetch = function `Fetch ps -> List.mem p ps | _ -> false in
968+
let is_fetch = function
969+
| `Fetch ps -> OpamStd.List.mem OpamPackage.equal p ps
970+
| _ -> false
971+
in
964972
List.exists is_fetch failed
965973
&& PackageActionGraph.fold_edges (fun v v' mem ->
966974
mem || (is_fetch v && PackageAction.equal v' rem))
@@ -975,8 +983,12 @@ let parallel_apply t
975983
List.filter (function
976984
| `Fetch _ as a ->
977985
let succ = PackageActionGraph.succ action_graph a in
978-
not (List.for_all (fun a -> List.mem a removes_missing_source)
979-
succ)
986+
not (
987+
List.for_all (fun a ->
988+
OpamStd.List.mem
989+
(OpamTypesBase.action_equal OpamPackage.equal)
990+
a removes_missing_source)
991+
succ)
980992
| `Build _ | `Change _ | `Install _ | `Reinstall _
981993
| `Remove _ -> true)
982994
failed
@@ -985,7 +997,10 @@ let parallel_apply t
985997
if l = [] then PackageActionGraph.create () else
986998
let g = PackageActionGraph.copy action_graph in
987999
PackageActionGraph.iter_vertex (fun v ->
988-
if not (List.mem v l) then PackageActionGraph.remove_vertex g v)
1000+
if not (OpamStd.List.mem
1001+
(OpamTypesBase.action_equal OpamPackage.equal)
1002+
v l) then
1003+
PackageActionGraph.remove_vertex g v)
9891004
g;
9901005
g
9911006
in

0 commit comments

Comments
 (0)