Skip to content
New issue

Have a question about this project? # for a free GitHub account to open an issue and contact its maintainers and the community.

By clicking “#”, you agree to our terms of service and privacy statement. We’ll occasionally send you account related emails.

Already on GitHub? # to your account

Order the actions listing by action/package #5045

Merged
merged 5 commits into from
Mar 7, 2022
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
5 changes: 5 additions & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,9 @@ users)
* --no-depexts is the default in CLI 2.0 mode [#4908 @dra27]
* [BUG] Fix behaviour on closed stdout/stderr [#4901 @altgr - fix #4216]
* Add `OPAMREPOSITORYTARRING` environment variable to enable repository tarring optimisation, it is disabled by default because it is an optimisation only on some os/configurations [#5015 @rjbou]
* Refresh the actions list output, now sorted by action/package rather than dependency [#5045 @kit-ty-kate @AltGr - fix #5041]
* Put back the actions summary as part of confirmation question [#5045 @AltGr]
* Error report display: print action name [#5045 @AltGr]

## Plugins
*
Expand Down Expand Up @@ -289,6 +292,8 @@ users)
* `OpamSolver.coinstallable_subset`: add `add_invariant` optional argument [#5024 @AltGr]
* `OpamSolver.installable`: use `installable_subset` that uses `coinstallable_subset` [#5024 @kit_ty_kate]
* `OpamSolver.explicit`: when adding fetch nodes, add shared source ones. Change of `sources_needed` argument type [#4893 @rjbou]
* `OpamActionGraph.to_aligned_strings`: add `explicit` optional argument to print action name in utf8 [#5045 @AltGr]
* `OpamSolver.print_solution`: change output format [#5045 @AltGr]
## opam-format
* `OpamStd.ABSTRACT`: add `compare` and `equal`, that added those functions to `OpamSysPkg` and `OpamVariable` [#4918 @rjbou]
* Add OpamPackage.Version.default returning the version number used when no version is given for a package [#4949 @kit-ty-kate]
Expand Down
29 changes: 9 additions & 20 deletions src/client/opamSolution.ml
Original file line number Diff line number Diff line change
Expand Up @@ -961,7 +961,7 @@ let parallel_apply t
(fun x -> x)
(List.map (String.concat " ") @@
OpamStd.Format.align_table
(PackageAction.to_aligned_strings actions)))
(PackageAction.to_aligned_strings ~explicit:true actions)))
(colorise tint
(Printf.sprintf "%s%s "
(utf8_symbol Symbols.box_drawings_light_up_and_right "+")
Expand Down Expand Up @@ -1022,20 +1022,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 ->
List.map OpamPackage.name (action_contents v)
|> OpamPackage.Name.Set.of_list
|> OpamPackage.Name.Set.union 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 @@ -1220,7 +1213,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 @@ -1256,12 +1248,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
20 changes: 15 additions & 5 deletions src/solver/opamActionGraph.ml
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,8 @@ module type ACTION = sig
include OpamParallel.VERTEX with type t = package action
val to_string: [< t ] -> string
val to_aligned_strings:
?append:(package -> string) -> [< t ] list -> string list list
?explicit:bool -> ?append:(package -> string) -> [< t ] list ->
string list list
module Set: OpamStd.SET with type elt = package action
module Map: OpamStd.MAP with type key = package action
end
Expand All @@ -31,6 +32,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 Expand Up @@ -122,17 +132,17 @@ module MakeAction (P: GenericPackage) : ACTION with type package = P.t
(action_strings a)
(P.version_to_string p)

let to_aligned_strings ?(append=(fun _ -> "")) l =
let to_aligned_strings ?(explicit=false) ?(append=(fun _ -> "")) l =
let pkg_to_string p =
[ OpamConsole.colorise `bold (P.name_to_string p);
P.version_to_string p ^ append p ]
in
List.map (fun a ->
let a = (a :> package action) in
(if OpamConsole.utf8 ()
then action_color a (symbol_of_action a)
else "-")
:: name_of_action a
then action_color a (symbol_of_action a) ^
if explicit then " " ^ name_of_action a else ""
else action_color a "- " ^ name_of_action a)
:: match a with
| `Remove p | `Install p | `Reinstall p | `Build p | `Fetch [p] ->
pkg_to_string p
Expand Down
11 changes: 10 additions & 1 deletion src/solver/opamActionGraph.mli
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,8 @@ module type ACTION = sig
include OpamParallel.VERTEX with type t = package action
val to_string: [< t ] -> string
val to_aligned_strings:
?append:(package -> string) -> [< t ] list -> string list list
?explicit:bool -> ?append:(package -> string) -> [< t ] list ->
string list list
module Set: OpamStd.SET with type elt = package action
module Map: OpamStd.MAP with type key = package action
end
Expand Down Expand Up @@ -65,5 +66,13 @@ module Make (A: ACTION) : SIG with type package = A.package
val action_strings:
?utf8:bool -> 'a action -> string

val symbol_of_action: 'a action -> string

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
98 changes: 59 additions & 39 deletions src/solver/opamSolver.ml
Original file line number Diff line number Diff line change
Expand Up @@ -711,35 +711,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 All @@ -760,7 +756,7 @@ let print_solution ~messages ~append ~requested ~reinstall ~available t =
OpamCudf.compute_root_causes t requested reinstall available
in
let actions, details =
OpamCudf.ActionGraph.Topological.fold (fun a (actions,details) ->
OpamCudf.ActionGraph.fold_vertex (fun a (actions,details) ->
let cause =
try OpamCudf.Map.find (OpamCudf.action_contents a) causes
with Not_found -> Unknown in
Expand All @@ -776,16 +772,40 @@ let print_solution ~messages ~append ~requested ~reinstall ~available t =
action :: actions, (cause, messages) :: details
) t ([],[])
in
let actions, details = List.rev actions, List.rev details in
Action.to_aligned_strings ~append actions |>
List.map2 (fun (cause, messages) line ->
" " :: line @
[if cause = "" then "" else Printf.sprintf "[%s]" cause] @
if messages = [] then []
else [String.concat "\n" messages]
) details |>
OpamStd.Format.align_table |>
OpamConsole.print_table ~sep:" " stdout
let table =
List.map2 (fun action (cause, messages) ->
" " :: action @
[if cause = "" then "" else Printf.sprintf "[%s]" cause] @
if messages = [] then []
else [String.concat "\n" messages]
)
(Action.to_aligned_strings ~append actions)
details
|> OpamStd.Format.align_table
in
let actions_table = List.combine actions table in
let actions_table =
List.sort (fun a1 a2 ->
let ct (a, _) = OpamCudf.action_contents a in
OpamPackage.compare (ct a1) (ct a2))
actions_table
in
let print_actions filter =
match List.filter (fun (a, _) -> filter a) actions_table with
| [] -> ()
| ((a,_) :: _) as acts ->
OpamConsole.formatted_msg "%s %s %s %s\n"
(OpamActionGraph.action_color a "===")
(OpamActionGraph.name_of_action a)
(OpamConsole.colorise `bold (string_of_int ((List.length acts))))
(match acts with [_] -> "package" | _ -> "packages");
OpamConsole.print_table ~sep:" " stdout (List.map snd acts)
in
print_actions (function `Remove _ -> true | _ -> false);
print_actions (function `Change (`Down,_,_) -> true | _ -> false);
print_actions (function `Reinstall _ -> true | _ -> false);
print_actions (function `Change (`Up,_,_) -> true | _ -> false);
print_actions (function `Install _ -> true | _ -> false)

let dump_universe universe oc =
let version_map = cudf_versions_map universe in
Expand Down
18 changes: 15 additions & 3 deletions tests/reftests/avoid-version.test
Original file line number Diff line number Diff line change
Expand Up @@ -7,11 +7,13 @@ flags: avoid-version
### OPAMYES=1
### opam install a --show
The following actions would be faked:
=== 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 a 1

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

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
Expand All @@ -37,20 +40,23 @@ Done.
opam-version: "2.0"
### opam upgrade a
The following actions will be faked:
=== 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 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 a 2 to 3

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

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
Expand All @@ -78,19 +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 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
Faking installation of b.2
Done.
### opam upgrade
The following actions will be faked:
- upgrade a 2 to 3
=== downgrade 1 package
- downgrade b 2 to 1 [uses a]
===== 1 to upgrade | 1 to downgrade =====
=== upgrade 1 package
- upgrade a 2 to 3

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
Faking installation of a.3
Expand All @@ -112,20 +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 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 a 3 to 2

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

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
Expand Down
Loading