Skip to content

Commit e22de59

Browse files
authored
Merge branch 'master' into split-desprecated-files-from-2.0-fields
2 parents 295c6c2 + 40e9530 commit e22de59

File tree

7 files changed

+39
-27
lines changed

7 files changed

+39
-27
lines changed

master_changes.md

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -32,6 +32,7 @@ users)
3232
## Remove
3333

3434
## UI
35+
* Read full lines when asking for user input when `TERM=dumb` [#6829 @arvidj - fix #6828]
3536

3637
## Switch
3738

@@ -42,6 +43,7 @@ users)
4243
## List
4344

4445
## Show
46+
* Improve performance of `opam show` by reading switch selection only once instead of once per package-version [#6818 @dra27]
4547

4648
## Var/Option
4749

@@ -157,6 +159,8 @@ users)
157159

158160
## opam-state
159161
* `OpamRepositoryState.load_opams_from_diff` track added packages to avoid removing version-equivalent packages [#6774 @arozovyk fix #6754]
162+
* `OpamGlobalState.all_installed_versions`: was added [#6818 @dra27]
163+
* `OpamGlobalState.installed_versions`: was removed [#6818 @dra27]
160164

161165
## opam-solver
162166

@@ -173,3 +177,4 @@ users)
173177
* `OpamCompat.Int.min`: was added [#6515 @kit-ty-kate]
174178
* `OpamStd.String.compare_case`: is now allocation free [#6515 @dra27]
175179
* `OpamVersionCompare.{compare,equal}`: are now allocation free [#6515 @dra27]
180+
* `OpamCompat.Map.add_to_list`: was added [#6818 @dra27]

src/client/opamListCommand.ml

Lines changed: 16 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -511,10 +511,7 @@ let field_of_string ~raw =
511511
| None -> OpamConsole.error_and_exit `Bad_arguments "No printer for %S" s
512512

513513
(* NOTE: upon changes, please update the man page section in opamCommands.ml *)
514-
let version_color st nv =
515-
let installed = (* (in any switch) *)
516-
OpamGlobalState.installed_versions st.switch_global nv.name
517-
in
514+
let version_color installed st nv =
518515
let is_available nv = (* Ignore unavailability due to pinning *)
519516
try
520517
OpamFilter.eval_to_bool ~default:false
@@ -545,7 +542,8 @@ let mini_field_printer ?(prettify=false) ?(normalise=false) =
545542
| List l -> OpamPrinter.value_list l
546543
| _ -> OpamPrinter.Normalise.value v
547544

548-
let detail_printer ?prettify ?normalise ?(sort=false) st nv =
545+
let detail_printer ?prettify ?normalise ?(sort=false) installed st nv =
546+
let version_color = version_color installed in
549547
let open OpamStd.Option.Op in
550548
let (%) s cols = OpamConsole.colorise' cols s in
551549
let root_sty =
@@ -643,12 +641,14 @@ let detail_printer ?prettify ?normalise ?(sort=false) st nv =
643641
OpamStd.Option.default "" hash_opt
644642
| Raw -> OpamFile.OPAM.write_to_string (get_opam st nv)
645643
| All_installed_versions ->
646-
OpamGlobalState.installed_versions st.switch_global nv.name |>
647-
OpamPackage.Map.mapi (fun nv switches ->
648-
Printf.sprintf "%s [%s]"
649-
(OpamPackage.version_to_string nv % version_color st nv)
650-
(String.concat " " (List.map OpamSwitch.to_string switches))) |>
651-
OpamPackage.Map.values |>
644+
let needed = nv.name in
645+
OpamPackage.Map.fold (fun nv switches acc ->
646+
if OpamPackage.Name.equal needed nv.name then
647+
(Printf.sprintf "%s [%s]"
648+
(OpamPackage.version_to_string nv % version_color st nv)
649+
(String.concat " " (List.map OpamSwitch.to_string switches)))::acc
650+
else acc) installed [] |>
651+
List.rev |>
652652
String.concat " "
653653
| Available_versions ->
654654
let available =
@@ -759,8 +759,9 @@ let display st format packages =
759759
OpamConsole.errmsg "%s\n"
760760
(OpamConsole.colorise `red "# No matches found"))
761761
else
762+
let installed = OpamGlobalState.all_installed_versions st.switch_global in
762763
List.rev_map (fun nv ->
763-
List.map (detail_printer ~prettify ~normalise st nv) format.columns)
764+
List.map (detail_printer ~prettify ~normalise installed st nv) format.columns)
764765
packages |>
765766
List.rev |>
766767
add_head |>
@@ -834,10 +835,11 @@ let info st ~fields ~raw ~where ?normalise ?(show_empty=false)
834835
Synopsis;
835836
Description;
836837
] in
838+
let installed = OpamGlobalState.all_installed_versions st.switch_global in
837839
let output_table fields nv =
838840
let tbl =
839841
List.fold_left (fun acc item ->
840-
let contents = detail_printer ?normalise ~sort st nv item in
842+
let contents = detail_printer ?normalise ~sort installed st nv item in
841843
if show_empty || contents <> "" then
842844
[ OpamConsole.colorise `blue (string_of_field ~raw item); contents ]
843845
:: acc
@@ -888,7 +890,7 @@ let info st ~fields ~raw ~where ?normalise ?(show_empty=false)
888890
| [] ->
889891
OpamConsole.header_msg "Version-specific details";
890892
output_table one_version_fields pkg
891-
| [f] -> OpamConsole.msg "%s\n" (detail_printer ?normalise ~sort st pkg f)
893+
| [f] -> OpamConsole.msg "%s\n" (detail_printer ?normalise ~sort installed st pkg f)
892894
| fields -> output_table fields pkg
893895
in
894896
List.iter (fun (name,_) ->

src/core/opamCompat.ml

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -238,6 +238,9 @@ module type MAP = sig
238238

239239
(** NOTE: OCaml >= 4.11 *)
240240
val filter_map: (key -> 'a -> 'b option) -> 'a t -> 'b t
241+
242+
(** NOTE: OCaml >= 5.1 *)
243+
val add_to_list: key -> 'a -> 'a list t -> 'a list t
241244
end
242245

243246
module Map(Ord : Stdlib.Map.OrderedType) = struct
@@ -253,6 +256,11 @@ module Map(Ord : Stdlib.Map.OrderedType) = struct
253256
| None -> map
254257
) map M.empty
255258

259+
(** NOTE: OCaml >= 5.1 *)
260+
let add_to_list x data m =
261+
let add = function None -> Some [data] | Some l -> Some (data :: l) in
262+
M.update x add m
263+
256264
include M
257265
end
258266

src/core/opamCompat.mli

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -78,6 +78,9 @@ module type MAP = sig
7878

7979
(** NOTE: OCaml >= 4.11 *)
8080
val filter_map: (key -> 'a -> 'b option) -> 'a t -> 'b t
81+
82+
(** NOTE: OCaml >= 5.1 *)
83+
val add_to_list: key -> 'a -> 'a list t -> 'a list t
8184
end
8285

8386
module Map(Ord : Stdlib.Map.OrderedType) : MAP with type key = Ord.t

src/core/opamConsole.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -716,7 +716,7 @@ let short_user_input ~prompt ?default ?on_eof f =
716716
let on_eof = OpamStd.Option.Op.(on_eof ++ default) in
717717
let prompt () = print_string prompt; flush stdout in
718718
try
719-
if OpamStd.Sys.(not tty_out || os () = Win32 || os () = Cygwin) then
719+
if OpamStd.Sys.(not tty_out || os () = Win32 || os () = Cygwin || Lazy.force dumb_term) then
720720
let rec loop () =
721721
prompt ();
722722
let input = match String.lowercase_ascii (read_line ()) with

src/state/opamGlobalState.ml

Lines changed: 3 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -167,16 +167,10 @@ let all_installed gt =
167167
OpamPackage.Set.union acc sel.sel_installed)
168168
gt OpamPackage.Set.empty
169169

170-
let installed_versions gt name =
170+
let all_installed_versions gt =
171171
fold_switches (fun switch sel acc ->
172-
let installed =
173-
OpamPackage.packages_of_name sel.sel_installed name
174-
in
175-
try
176-
let nv = OpamPackage.Set.choose installed in
177-
try OpamPackage.Map.add nv (switch::OpamPackage.Map.find nv acc) acc
178-
with Not_found -> OpamPackage.Map.add nv [switch] acc
179-
with Not_found -> acc)
172+
OpamPackage.Set.fold (fun nv acc ->
173+
OpamPackage.Map.add_to_list nv switch acc) sel.sel_installed acc)
180174
gt OpamPackage.Map.empty
181175

182176
let repos_list gt = OpamFile.Config.repositories gt.config

src/state/opamGlobalState.mli

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -37,9 +37,9 @@ val fold_switches:
3737
local switch with a configuration file pointing to the current root *)
3838
val switch_exists: 'a global_state -> switch -> bool
3939

40-
(** Returns the map of installed instances of the package name towards the list
41-
of switches they are installed in *)
42-
val installed_versions: 'a global_state -> name -> switch list package_map
40+
(** Returns the map of all installed packages to the list of switch(es) they're
41+
installed in. *)
42+
val all_installed_versions: 'a global_state -> switch list package_map
4343

4444
(** Default list of repositories to get packages from, ordered by decreasing
4545
priority. This can be overridden by switch-specific selections, and does not

0 commit comments

Comments
 (0)