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 c10f902
Show file tree
Hide file tree
Showing 25 changed files with 218 additions and 285 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
30 changes: 14 additions & 16 deletions tests/reftests/avoid-version.test
Original file line number Diff line number Diff line change
Expand Up @@ -7,13 +7,13 @@ flags: avoid-version
### OPAMYES=1
### opam install a --show
The following actions would be faked:
== install 1 package: ==
== install 1 package ==
- install a 2
### <pkg:a.1>
opam-version: "2.0"
### opam install a
The following actions will be faked:
== install 1 package: ==
== install 1 package ==
- install a 1

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
Expand All @@ -30,7 +30,7 @@ Nothing to do.
opam-version: "2.0"
### opam upgrade a
The following actions will be faked:
== upgrade 1 package: ==
== upgrade 1 package ==
- upgrade a 1 to 1.1

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
Expand All @@ -40,23 +40,23 @@ Done.
opam-version: "2.0"
### opam upgrade a
The following actions will be faked:
== upgrade 1 package: ==
== upgrade 1 package ==
- upgrade a 1.1 to 3

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
Faking installation of a.3
Done.
### opam install a.2
The following actions will be faked:
== downgrade 1 package: ==
== downgrade 1 package ==
- downgrade a 3 to 2

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
Faking installation of a.2
Done.
### opam upgrade a
The following actions will be faked:
== upgrade 1 package: ==
== upgrade 1 package ==
- upgrade a 2 to 3

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
Expand All @@ -70,7 +70,7 @@ opam-version: "2.0"
depends: "a" {= "2"}
### opam install b
The following actions will be faked:
== install 1 package: ==
== install 1 package ==
- install b 1

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
Expand All @@ -85,23 +85,21 @@ However, you may "opam upgrade" these packages explicitly, which will ask permis
Nothing to do.
### opam upgrade b
The following actions will be faked:
== downgrade 1 package: ==
== downgrade 1 package ==
- downgrade a 3 to 2 [required by b]
== upgrade 1 package: ==
== upgrade 1 package ==
- upgrade b 1 to 2
===== 1 to upgrade | 1 to downgrade =====

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
Faking installation of a.2
Faking installation of b.2
Done.
### opam upgrade
The following actions will be faked:
== downgrade 1 package: ==
== downgrade 1 package ==
- downgrade b 2 to 1 [uses a]
== upgrade 1 package: ==
== upgrade 1 package ==
- upgrade a 2 to 3
===== 1 to upgrade | 1 to downgrade =====

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
Faking installation of a.3
Expand All @@ -123,23 +121,23 @@ However, you may "opam upgrade" these packages explicitly, which will ask permis
Nothing to do.
### opam upgrade b.3
The following actions will be faked:
== upgrade 1 package: ==
== upgrade 1 package ==
- upgrade b 1 to 3

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
Faking installation of b.3
Done.
### opam install a.2
The following actions will be faked:
== downgrade 1 package: ==
== downgrade 1 package ==
- downgrade a 3 to 2

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
Faking installation of a.2
Done.
### opam upgrade
The following actions will be faked:
== upgrade 1 package: ==
== upgrade 1 package ==
- upgrade a 2 to 4

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
Expand Down
14 changes: 7 additions & 7 deletions tests/reftests/clean.test
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@ install: [
### opam switch create clean --empty
### opam install things
The following actions will be performed:
== install 1 package: ==
== install 1 package ==
- install things 1

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
Expand All @@ -26,30 +26,30 @@ ${BASEDIR}/OPAM/clean/lib/things/second

### opam remove things
The following actions will be performed:
== remove 1 package: ==
== remove 1 package ==
- remove things 1

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
-> removed things.1
Done.
### opam install things
The following actions will be performed:
== install 1 package: ==
== install 1 package ==
- install things 1

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
-> installed things.1
Done.
### opam remove things --fake
The following actions will be faked:
== remove 1 package: ==
== remove 1 package ==
- remove things 1

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
Done.
### opam install things
The following actions will be performed:
== install 1 package: ==
== install 1 package ==
- install things 1

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
Expand Down Expand Up @@ -83,7 +83,7 @@ Remaining directories and files:
Remove them? [Y/n] y
### opam install things
The following actions will be performed:
== install 1 package: ==
== install 1 package ==
- install things 1

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
Expand All @@ -93,7 +93,7 @@ Done.
another content
### opam remove things --no | '\\' -> '/'
The following actions will be performed:
== remove 1 package: ==
== remove 1 package ==
- remove things 1

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
Expand Down
16 changes: 8 additions & 8 deletions tests/reftests/cli-versioning.test
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ opam: install was removed in version 2.1 of the opam CLI, but version 2.2 has be
# Return code 2 #
### opam install baz --assume-depexts --cli 2.1
The following actions would be performed:
== install 1 package: ==
== install 1 package ==
- install baz 2
### OPAMCLI=2.0 opam install baz --assume-depexts
opam: --assume-depexts was added in version 2.1 of the opam CLI, but version 2.0 has been requested, which is older.
Expand Down Expand Up @@ -55,12 +55,12 @@ opam: --update-invariant was added in version 2.1 of the opam CLI, but version 2
# Return code 2 #
### opam install baz.2 --update-invariant
The following actions would be performed:
== install 1 package: ==
== install 1 package ==
- install baz 2
### OPAMCLI=2.0 opam install baz.2 --unlock-base
[WARNING] OPAMNODEPEXTS was ignored because CLI 2.0 was requested and it was introduced in 2.1.
The following actions would be performed:
== install 1 package: ==
== install 1 package ==
- install baz 2
### opam install baz.2 --unlock-base
opam: --unlock-base was removed in version 2.1 of the opam CLI, but version 2.2 has been requested. Use --update-invariant instead or set OPAMCLI environment variable to 2.0.
Expand Down Expand Up @@ -103,31 +103,31 @@ remove: ["sh" "-c" "env | grep -qFx 'OPAMCLI=2.1'"]
The switch invariant was set to []
### opam install env-2-0
The following actions will be performed:
== install 1 package: ==
== install 1 package ==
- install env-2-0 1

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
-> installed env-2-0.1
Done.
### opam install env-2-1
The following actions will be performed:
== install 1 package: ==
== install 1 package ==
- install env-2-1 1

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
-> installed env-2-1.1
Done.
### opam remove env-2-0
The following actions will be performed:
== remove 1 package: ==
== remove 1 package ==
- remove env-2-0 1

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
-> removed env-2-0.1
Done.
### opam remove env-2-1
The following actions will be performed:
== remove 1 package: ==
== remove 1 package ==
- remove env-2-1 1

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
Expand All @@ -153,5 +153,5 @@ ${BASEDIR}/OPAM/cli-versioning/share
<><> Installing new switch packages <><><><><><><><><><><><><><><><><><><><><><>
Switch invariant: ["baz" "baz" {= "2"}]
The following actions would be performed:
== install 1 package: ==
== install 1 package ==
- install baz 2
Loading

0 comments on commit c10f902

Please # to comment.