Skip to content

Commit fa93c54

Browse files
authored
Merge pull request #6381 from kit-ty-kate/OpamListCommand-no-poly-cmp
Avoid polymorphic comparison functions in OpamListCommand
2 parents f1cf50f + 6604bdd commit fa93c54

File tree

4 files changed

+19
-6
lines changed

4 files changed

+19
-6
lines changed

master_changes.md

+2
Original file line numberDiff line numberDiff line change
@@ -159,6 +159,7 @@ users)
159159
* Avoid issues when using wget2 where the requested url might return an html page instead of the expected content [#6303 @kit-ty-kate]
160160
* Ensure each repositories stored in repos-config is associated with an URL [#6249 @kit-ty-kate]
161161
* Run `Gc.compact` in OpamParallel, when the main process is waiting for the children processes for the first time [#5396 @kkeundotnet]
162+
* Avoid polymorphic comparison functions in `OpamListCommand` [#6381 @kit-ty-kate]
162163

163164
## Internal: Unix
164165
* Use a C stub to call the `uname` function from the C standard library instead of calling the `uname` POSIX command [#6217 @kit-ty-kate]
@@ -250,6 +251,7 @@ users)
250251
* `OpamConsole.pause`: Ensure the function always prints a newline character at the end [#6376 @kit-ty-kate]
251252
* `OpamHash.all_kinds`: was added, which returns the list of all possible values of `OpamHash.kind` [#5960 @kit-ty-kate]
252253
* `OpamStd.List.split`: Improve performance [#6210 @kit-ty-kate]
254+
* `OpamStd.Option.equal_some`: was added, which tests equality of an option with a value [#6381 @kit-ty-kate]
253255
* `OpamStd.Sys.{get_terminal_columns,uname,getconf,guess_shell_compat}`: Harden the process calls to account for failures [#6230 @kit-ty-kate - fix #6215]
254256
* `OpamStd.Sys.getconf`: was removed, replaced by `get_long_bit` [#6217 @kit-ty-kate]
255257
* `OpamStd.Sys.get_long_bit`: was added, which returns the output of the `getconf LONG_BIT` command [#6217 @kit-ty-kate]

src/client/opamListCommand.ml

+11-6
Original file line numberDiff line numberDiff line change
@@ -348,7 +348,7 @@ let apply_selector ~base st = function
348348
base
349349
| Tag t ->
350350
OpamPackage.Set.filter (fun nv ->
351-
get_opam st nv |> List.mem t @* OpamFile.OPAM.tags)
351+
get_opam st nv |> List.exists (String.equal t) @* OpamFile.OPAM.tags)
352352
base
353353
| From_repository repos ->
354354
let rt = st.switch_repos in
@@ -358,7 +358,8 @@ let apply_selector ~base st = function
358358
let packages =
359359
OpamPackage.keys (OpamRepositoryName.Map.find r rt.repo_opams)
360360
in
361-
if List.mem r repos then OpamPackage.Set.union packages (aux rl)
361+
if List.exists (OpamRepositoryName.equal r) repos
362+
then OpamPackage.Set.union packages (aux rl)
362363
else OpamPackage.Set.diff (aux rl) packages
363364
in
364365
aux (OpamSwitchState.repos_list st)
@@ -383,12 +384,13 @@ let apply_selector ~base st = function
383384
OpamStd.String.Map.exists
384385
(fun f -> function
385386
| OpamDirTrack.Removed -> false
386-
| _ -> rel_name = f)
387+
| _ -> rel_name = (f : string))
387388
changes)
388389
(OpamFilename.files (OpamPath.Switch.install_dir root switch))
389390
in
390391
let selections =
391-
if switch = st.switch then OpamSwitchState.selections st
392+
if OpamSwitch.equal switch st.switch then
393+
OpamSwitchState.selections st
392394
else
393395
OpamSwitchState.load_selections ~lock_kind:`Lock_none
394396
st.switch_global switch
@@ -504,7 +506,7 @@ let field_of_string ~raw =
504506
try
505507
OpamStd.List.assoc String.equal s names_fields
506508
with Not_found ->
507-
match OpamStd.List.find_opt (fun x -> s = x) opam_fields with
509+
match OpamStd.List.find_opt (String.equal s) opam_fields with
508510
| Some f -> Field f
509511
| None -> OpamConsole.error_and_exit `Bad_arguments "No printer for %S" s
510512

@@ -569,7 +571,10 @@ let detail_printer ?prettify ?normalise ?(sort=false) st nv =
569571
(match OpamPinned.package_opt st nv.name with
570572
| Some nv ->
571573
let opam = get_opam st nv in
572-
if Some opam = OpamPackage.Map.find_opt nv st.repos_package_index then
574+
if
575+
OpamStd.Option.equal_some OpamFile.OPAM.equal
576+
opam (OpamPackage.Map.find_opt nv st.repos_package_index)
577+
then
573578
Printf.sprintf "pinned to version %s"
574579
(OpamPackage.Version.to_string nv.version % [`blue])
575580
else

src/core/opamStd.ml

+4
Original file line numberDiff line numberDiff line change
@@ -521,6 +521,10 @@ module Option = struct
521521
| None, None -> true
522522
| _ , _ -> false
523523

524+
let equal_some f v1 = function
525+
| None -> false
526+
| Some v2 -> f v1 v2
527+
524528
let to_string ?(none="") f = function
525529
| Some x -> f x
526530
| None -> none

src/core/opamStd.mli

+2
Original file line numberDiff line numberDiff line change
@@ -163,6 +163,8 @@ module Option: sig
163163

164164
val equal: ('a -> 'a -> bool) -> 'a option -> 'a option -> bool
165165

166+
val equal_some : ('a -> 'a -> bool) -> 'a -> 'a option -> bool
167+
166168
val to_string: ?none:string -> ('a -> string) -> 'a option -> string
167169

168170
val to_list: 'a option -> 'a list

0 commit comments

Comments
 (0)