Skip to content

Commit

Permalink
Actions summary: print as part of the question
Browse files Browse the repository at this point in the history
  • Loading branch information
AltGr committed Feb 8, 2022
1 parent bd9971b commit 6edfcd3
Show file tree
Hide file tree
Showing 17 changed files with 47 additions and 114 deletions.
1 change: 1 addition & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,7 @@ users)
* Add cli 2.2 handling [#4853 @rjbou]
* --no-depexts is the default in CLI 2.0 mode [#4908 @dra27]
* [BUG] Fix behaviour on closed stdout/stderr [#4901 @altgr - fix #4216]
* Refresh the actions list output, now sorted by action/package rather than dependency [#5045 @kit-ty-kate @AltGr - fix #5041]

## Plugins
*
Expand Down
25 changes: 8 additions & 17 deletions src/client/opamSolution.ml
Original file line number Diff line number Diff line change
Expand Up @@ -962,18 +962,13 @@ let simulate_new_state state t =
the packages in the user request *)
let confirmation ?ask requested solution =
OpamCoreConfig.answer_is_yes () ||
match ask with
| Some false -> true
| Some true -> OpamConsole.confirm "Do you want to continue?"
| None ->
let open PackageActionGraph in
let solution_packages =
fold_vertex (fun v acc ->
OpamPackage.Name.Set.add (OpamPackage.name (action_contents v)) acc)
solution
OpamPackage.Name.Set.empty in
OpamPackage.Name.Set.equal requested solution_packages
|| OpamConsole.confirm "Do you want to continue?"
ask = Some false ||
let solution_packages =
OpamPackage.names_of_packages (OpamSolver.all_packages solution)
in
ask <> Some true && OpamPackage.Name.Set.equal requested solution_packages ||
let stats = OpamSolver.stats solution in
OpamConsole.confirm "\nProceed with %s?" (OpamSolver.string_of_stats stats)

let run_hook_job t name ?(local=[]) ?(allow_stdout=false) w =
let shell_env = OpamEnv.get_full ~set_opamroot:true ~set_opamswitch:true ~force_path:true t in
Expand Down Expand Up @@ -1158,7 +1153,6 @@ let apply ?ask t ~requested ?add_roots ?(assume_built=false)
t, Nothing_to_do
else (
(* Otherwise, compute the actions to perform *)
let stats = OpamSolver.stats solution in
let show_solution = ask <> Some false in
let action_graph = OpamSolver.get_atomic_action_graph solution in
let new_state = simulate_new_state t action_graph in
Expand Down Expand Up @@ -1194,12 +1188,9 @@ let apply ?ask t ~requested ?add_roots ?(assume_built=false)
~requested ~reinstall:(Lazy.force t.reinstall)
~available:(Lazy.force t.available_packages)
solution;
let total_actions = sum stats in
if total_actions >= 2 then
OpamConsole.msg "===== %s =====\n" (OpamSolver.string_of_stats stats);
);
if not OpamClientConfig.(!r.show) &&
(download_only || confirmation ?ask requested action_graph)
(download_only || confirmation ?ask requested solution)
then (
let t =
install_depexts t @@ OpamPackage.Set.inter
Expand Down
9 changes: 9 additions & 0 deletions src/solver/opamActionGraph.ml
Original file line number Diff line number Diff line change
Expand Up @@ -31,6 +31,15 @@ let name_of_action = function
| `Build _ -> "build"
| `Fetch _ -> "fetch"

let noun_of_action = function
| `Remove _ -> "removal", "removals"
| `Install _ -> "installation", "installations"
| `Change (`Up,_,_) -> "upgrade", "upgrades"
| `Change (`Down,_,_) -> "downgrade", "downgrades"
| `Reinstall _ -> "recompilation", "recompilations"
| `Build _ -> "build", "builds"
| `Fetch _ -> "fetch", "fetches"

let symbol_of_action =
let open OpamConsole in
function
Expand Down
4 changes: 4 additions & 0 deletions src/solver/opamActionGraph.mli
Original file line number Diff line number Diff line change
Expand Up @@ -69,3 +69,7 @@ val name_of_action: 'a action -> string

(** Colorise string according to the action *)
val action_color: 'a action -> string -> string

(** Returns a noun corresponding to the action name, singular and plural
forms *)
val noun_of_action: 'a action -> string * string
54 changes: 25 additions & 29 deletions src/solver/opamSolver.ml
Original file line number Diff line number Diff line change
Expand Up @@ -685,35 +685,31 @@ let stats sol =

let string_of_stats stats =
let utf = (OpamConsole.utf8 ()) in
let stats = [
stats.s_install;
stats.s_reinstall;
stats.s_upgrade;
stats.s_downgrade;
stats.s_remove;
let titles_stats = [
`Remove (), stats.s_remove;
`Change (`Down,(),()), stats.s_downgrade;
`Reinstall (), stats.s_reinstall;
`Change (`Up,(),()), stats.s_upgrade;
`Install (), stats.s_install;
] in
let titles =
List.map
(fun a ->
let s = OpamActionGraph.action_strings a in
if utf then OpamActionGraph.action_color a s else s)
[`Install ();
`Reinstall ();
`Change (`Up,(),());
`Change (`Down,(),());
`Remove ()]
in
let msgs = List.filter (fun (a,_) -> a <> 0) (List.combine stats titles) in
if utf then
OpamStd.List.concat_map " "
(fun (n,t) -> Printf.sprintf "%s %s" t (string_of_int n))
msgs
else
OpamStd.List.concat_map " | "
(fun (n,t) ->
Printf.sprintf "%s to %s"
(OpamConsole.colorise `yellow (string_of_int n)) t)
msgs
let titles_stats = List.filter (fun (_, n) -> n <> 0) titles_stats in
let msgs =
let open OpamActionGraph in
List.map (fun (a, n) ->
let noun =
let sing, plur = noun_of_action a in
if n = 1 then sing else plur
in
String.concat " "
(if utf
then [ action_color a (symbol_of_action a);
OpamConsole.colorise `bold (string_of_int n);
noun ]
else [ OpamConsole.colorise `bold (string_of_int n);
action_color a noun ]))
titles_stats
in
OpamStd.Format.pretty_list msgs

let solution_is_empty t =
OpamCudf.ActionGraph.is_empty t
Expand Down Expand Up @@ -772,7 +768,7 @@ let print_solution ~messages ~append ~requested ~reinstall ~available t =
match List.filter (fun (a, _) -> filter a) actions_table with
| [] -> ()
| ((a,_) :: _) as acts ->
OpamConsole.formatted_msg " %s %s %s %s: %s\n"
OpamConsole.formatted_msg " %s %s %s %s %s\n"
(OpamActionGraph.action_color a "==")
(OpamActionGraph.name_of_action a)
(OpamConsole.colorise `bold (string_of_int ((List.length acts))))
Expand Down
2 changes: 0 additions & 2 deletions tests/reftests/avoid-version.test
Original file line number Diff line number Diff line change
Expand Up @@ -89,7 +89,6 @@ The following actions will be faked:
- downgrade a 3 to 2 [required by b]
== upgrade 1 package: ==
- upgrade b 1 to 2
===== 1 to upgrade | 1 to downgrade =====

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
Faking installation of a.2
Expand All @@ -101,7 +100,6 @@ The following actions will be faked:
- downgrade b 2 to 1 [uses a]
== upgrade 1 package: ==
- upgrade a 2 to 3
===== 1 to upgrade | 1 to downgrade =====

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
Faking installation of a.3
Expand Down
5 changes: 0 additions & 5 deletions tests/reftests/cudf-preprocess.test
Original file line number Diff line number Diff line change
Expand Up @@ -153,7 +153,6 @@ The following actions will be faked:
- install xenstore 2.1.1 [required by conduit-mirage]
- install xenstore_transport 1.3.0 [required by vchan]
- install zarith 1.12 [required by awa]
===== 135 to install =====

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
Faking installation of cmdliner.1.0.4
Expand Down Expand Up @@ -309,7 +308,6 @@ The following actions would be faked:
== upgrade 2 packages: ==
- upgrade checkseum 0.3.0 to 0.3.1 [required by git]
- upgrade optint 0.0.4 to 0.1.0
===== 9 to recompile | 2 to upgrade =====
### opam install optint.0.1.0
The following actions would be faked:
== recompile 9 packages: ==
Expand All @@ -325,7 +323,6 @@ The following actions would be faked:
== upgrade 2 packages: ==
- upgrade checkseum 0.3.0 to 0.3.1 [uses optint]
- upgrade optint 0.0.4 to 0.1.0
===== 9 to recompile | 2 to upgrade =====
### OPAMCUDFTRIM=0 opam install optint.0.1.0
The following actions would be faked:
== recompile 9 packages: ==
Expand All @@ -341,7 +338,6 @@ The following actions would be faked:
== upgrade 2 packages: ==
- upgrade checkseum 0.3.0 to 0.3.1 [uses optint]
- upgrade optint 0.0.4 to 0.1.0
===== 9 to recompile | 2 to upgrade =====
### OPAMCUDFTRIM=simple opam install optint.0.1.0
The following actions would be faked:
== recompile 9 packages: ==
Expand All @@ -357,4 +353,3 @@ The following actions would be faked:
== upgrade 2 packages: ==
- upgrade checkseum 0.3.0 to 0.3.1 [uses optint]
- upgrade optint 0.0.4 to 0.1.0
===== 9 to recompile | 2 to upgrade =====
1 change: 0 additions & 1 deletion tests/reftests/init.test
Original file line number Diff line number Diff line change
Expand Up @@ -87,7 +87,6 @@ The following actions will be faked:
- upgrade ocaml 4.07.0 to 4.10.0
== install 1 package: ==
- install ocaml-base-compiler 4.10.0 [required by ocaml]
===== 1 to install | 1 to recompile | 1 to upgrade | 1 to remove =====

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
Faking installation of ocaml-base-compiler.4.10.0
Expand Down
13 changes: 0 additions & 13 deletions tests/reftests/legacy-git.test
Original file line number Diff line number Diff line change
Expand Up @@ -775,7 +775,6 @@ The following actions will be performed:
== install 2 packages: ==
- install P1 1 [required by P5] I ll always bother you displaying this message
- install P5 1
===== 2 to install =====

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
-> retrieved P1.1 (git+file://${BASEDIR}/GIT/P1-1)
Expand Down Expand Up @@ -821,7 +820,6 @@ The following actions will be performed:
== remove 2 packages: ==
- remove P1 1
- remove P5 1
===== 2 to remove =====

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
-> removed P5.1
Expand All @@ -834,7 +832,6 @@ The following actions will be performed:
== install 2 packages: ==
- install P1 1 [required by P5] I ll always bother you displaying this message
- install P5 1
===== 2 to install =====

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
-> retrieved P1.1 (git+file://${BASEDIR}/GIT/P1-1)
Expand All @@ -856,7 +853,6 @@ The following actions will be performed:
- recompile P5 1 [uses P2]
== install 1 package: ==
- install P2 1
===== 1 to install | 1 to recompile =====

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
-> retrieved P2.1 (git+file://${BASEDIR}/GIT/P2)
Expand Down Expand Up @@ -888,7 +884,6 @@ The following actions will be performed:
== remove 2 packages: ==
- remove P1 1
- remove P2 1
===== 2 to remove =====

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
-> removed P2.1
Expand All @@ -902,7 +897,6 @@ The following actions will be performed:
- install P1 1 I ll always bother you displaying this message
- install P2 1
- install P5 1
===== 3 to install =====

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
-> retrieved P1.1 (git+file://${BASEDIR}/GIT/P1-1)
Expand All @@ -928,7 +922,6 @@ The following actions will be performed:
- remove P2 1
== recompile 1 package: ==
- recompile P5 1 [uses P2]
===== 1 to recompile | 1 to remove =====

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
-> retrieved P5.1 (no changes)
Expand All @@ -946,7 +939,6 @@ The following actions will be performed:
== remove 2 packages: ==
- remove P1 1
- remove P5 1 [uses P1]
===== 2 to remove =====

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
-> removed P5.1
Expand Down Expand Up @@ -1049,7 +1041,6 @@ The following actions will be performed:
- recompile P2 1 [uses P1]
- recompile P3 1~weird-version.test [uses P1]
- recompile P4 1 [uses P2, P3]
===== 4 to recompile =====

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
-> retrieved P1.1 (no changes)
Expand Down Expand Up @@ -1157,7 +1148,6 @@ The following actions will be performed:
- recompile P3 1~weird-version.test [uses P1]
== upgrade 1 package: ==
- upgrade P4 1 to 3
===== 3 to recompile | 1 to upgrade =====

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
-> retrieved P1.1 (no changes)
Expand Down Expand Up @@ -1238,7 +1228,6 @@ The following actions will be performed:
== remove 2 packages: ==
- remove P3 1~weird-version.test
- remove P4 2
===== 2 to remove =====

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
-> removed P4.2
Expand All @@ -1265,7 +1254,6 @@ The following actions will be performed:
== install 2 packages: ==
- install P1 1 I ll always bother you displaying this message
- install P2 1
===== 2 to install =====

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
-> retrieved P1.1 (git+file://${BASEDIR}/GIT/P1-1)
Expand Down Expand Up @@ -1341,7 +1329,6 @@ The following actions will be performed:
- install P2 1
- install P3 1~weird-version.test
- install P4 3
===== 5 to install =====

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
-> installed ocaml.10+a+b
Expand Down
Loading

0 comments on commit 6edfcd3

Please sign in to comment.