Skip to content

Commit

Permalink
Merge pull request #5613 from kit-ty-kate/opam-tree-pkg-dir
Browse files Browse the repository at this point in the history
opam tree: Allow packages with a specific version, directories or local opam files, as input
  • Loading branch information
kit-ty-kate authored Aug 24, 2023
2 parents 6fa193a + 54f0e9b commit 8a23fc0
Show file tree
Hide file tree
Showing 5 changed files with 181 additions and 29 deletions.
5 changes: 5 additions & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -41,6 +41,10 @@ users)

## Update / Upgrade

## Tree
* Allow packages with a specific version, directories or local opam files, as input [#5613 @kit-ty-kate]
* Add handling of `--recurse` and `--subpath` for directory arguments [#5613 @kit-ty-kate]

## Exec

## Source
Expand Down Expand Up @@ -109,6 +113,7 @@ users)

# API updates
## opam-client
* `OpamTreeCommand.run`: now takes an `atom` instead of `name` [#5613 @kit-ty-kate]

## opam-repository

Expand Down
16 changes: 11 additions & 5 deletions src/client/opamCommands.ml
Original file line number Diff line number Diff line change
Expand Up @@ -821,28 +821,34 @@ let tree ?(why=false) cli =
switch to draw the forest"
in
let tree global_options mode filter post dev doc test dev_setup no_constraint
no_switch names () =
if names = [] && no_switch then
no_switch recurse subpath atoms_or_locals () =
if atoms_or_locals = [] && no_switch then
`Error
(true, "--no-switch can't be used without specifying a name")
(true, "--no-switch can't be used without specifying a package or a path")
else
(apply_global_options cli global_options;
OpamGlobalState.with_ `Lock_none @@ fun gt ->
OpamSwitchState.with_ `Lock_none gt @@ fun st ->
let st, atoms =
OpamAuxCommands.simulate_autopin
st ~recurse ?subpath ~quiet:true
?locked:OpamStateConfig.(!r.locked) atoms_or_locals
in
let tog = OpamListCommand.{
post; test; doc; dev; dev_setup;
recursive = false;
depopts = false;
build = true;
} in
OpamTreeCommand.run st tog ~no_constraint ~no_switch mode filter names;
OpamTreeCommand.run st tog ~no_constraint ~no_switch mode filter atoms;
`Ok ())
in
mk_command_ret ~cli (cli_from cli2_2) "tree" ~doc ~man
Term.(const tree $global_options cli $mode $filter
$post cli $dev cli $doc_flag cli $test cli $dev_setup cli
$no_cstr $no_switch
$name_list)
$recurse cli $subpath cli
$atom_or_local_list)

(* SHOW *)
let show_doc = "Display information about specific packages."
Expand Down
40 changes: 20 additions & 20 deletions src/client/opamTreeCommand.ml
Original file line number Diff line number Diff line change
Expand Up @@ -43,13 +43,6 @@ type resulting_forest =
| DepsForest of deps node forest
| RevdepsForest of revdeps node forest

let installed st names =
names |> List.fold_left (fun state n ->
(* non-installed packages should already be simulated to be installed *)
OpamSwitchState.find_installed_package_by_name st n :: state
) [] |> OpamPackage.Set.of_list


(** Forest building *)

let build_condition_map tog st =
Expand Down Expand Up @@ -143,7 +136,6 @@ let cut_leaves (mode: [ `succ | `pred]) ~names ~root st graph =
OpamPackage.Set.inter root packages, graph

let build_deps_forest st universe tog filter names =
let names = installed st names in
let OpamListCommand.{ build; post; _ } = tog in
let root, graph =
let graph =
Expand Down Expand Up @@ -191,7 +183,6 @@ let build_deps_forest st universe tog filter names =
|> snd

let build_revdeps_forest st universe tog filter names =
let names = installed st names in
let OpamListCommand.{ build; post; _ } = tog in
let root, graph =
let graph =
Expand Down Expand Up @@ -406,15 +397,13 @@ let simulate_new_state tog st universe install names =
(OpamSwitchState.unavailable_reason st) cs);
OpamStd.Sys.exit_because `No_solution

let dry_install tog st universe missing =
let install = missing |> List.map (fun name -> name, None) in
let dry_install tog st universe install =
simulate_new_state tog st universe install
(OpamPackage.Name.Set.of_list missing)
(OpamPackage.Name.Set.of_list (List.map fst install))

let raw_state tog st names =
let raw_state tog st install =
let OpamListCommand.{doc; test; dev_setup; _} = tog in
let install = List.map (fun name -> name, None) names in
let names = OpamPackage.Name.Set.of_list names in
let names = OpamPackage.Name.Set.of_list (List.map fst install) in
let requested =
OpamPackage.packages_of_names
(Lazy.force st.available_packages)
Expand All @@ -430,9 +419,17 @@ let raw_state tog st names =
in
simulate_new_state tog st universe install names

let run st tog ?no_constraint ?(no_switch=false) mode filter names =
let run st tog ?no_constraint ?(no_switch=false) mode filter atoms =
let open OpamPackage.Set.Op in
let select, missing =
List.partition (OpamSwitchState.is_name_installed st) names
List.fold_left (fun (select, missing) atom ->
let installed =
OpamPackage.Set.filter (OpamFormula.check atom) st.installed
in
if OpamPackage.Set.is_empty installed then
(select, atom :: missing)
else (installed ++ select, missing))
(OpamPackage.Set.empty, []) atoms
in
let st, universe =
let universe = get_universe tog st in
Expand All @@ -450,16 +447,19 @@ let run st tog ?no_constraint ?(no_switch=false) mode filter names =
OpamConsole.warning "Not installed package%s %s, skipping"
(match missing with | [_] -> "" | _ -> "s")
(OpamStd.Format.pretty_list
(List.map OpamPackage.Name.to_string missing));
if select = [] && names <> [] then
(List.map OpamFormula.string_of_atom missing));
if OpamPackage.Set.is_empty select && atoms <> [] then
OpamConsole.error_and_exit `Not_found "No package to display"
else
st, universe
in
if OpamPackage.Set.is_empty st.installed then
OpamConsole.error_and_exit `Not_found "No package is installed"
else
let forest = build st universe tog mode filter names in
let simulated = OpamFormula.packages_of_atoms st.installed missing in
let forest =
build st universe tog mode filter (select ++ simulated)
in
print ?no_constraint forest;
if OpamClientConfig.(!r.json_out) <> None then
(if not no_switch then
Expand Down
3 changes: 1 addition & 2 deletions src/client/opamTreeCommand.mli
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,6 @@

(** Functions handling the "opam tree" subcommand *)

open OpamTypes
open OpamStateTypes

(** Speficy the type of the forest to build *)
Expand All @@ -37,4 +36,4 @@ val run :
?no_constraint:bool ->
(* do no keep switch consistency *)
?no_switch:bool ->
mode -> tree_filter -> name list -> unit
mode -> tree_filter -> OpamTypes.atom list -> unit
146 changes: 144 additions & 2 deletions tests/reftests/tree.test
Original file line number Diff line number Diff line change
Expand Up @@ -282,8 +282,8 @@ e.1
[ERROR] No package to display
# Return code 5 #
### opam tree --no-switch | '…' -> '...' | '`' -> "'"
opam: --no-switch can't be used without specifying a name
Usage: opam tree [OPTION]... [PACKAGES]...
opam: --no-switch can't be used without specifying a package or a path
Usage: opam tree [--recursive] [--subpath=PATH] [OPTION]... [PACKAGES]...
Try 'opam tree --help' or 'opam --help' for more information.
# Return code 2 #
### opam tree f h --no-switch
Expand Down Expand Up @@ -388,3 +388,145 @@ Done.
You can temporarily relax the switch invariant with `--update-invariant'

# Return code 20 #
### <pkg:i.1>
opam-version: "2.0"
depends: "a"
### <pkg:i.2>
opam-version: "2.0"
depends: "b"
### opam switch create extended-inputs --empty
### opam tree i
The following actions are simulated:
=== install 3 packages
- install a 1 [required by b]
- install b 1 [required by i]
- install i 2

i.2
'-- b.1
'-- a.1
### opam tree i.1
The following actions are simulated:
=== install 2 packages
- install a 1 [required by i]
- install i 1

i.1
'-- a.1
### opam tree i.2
The following actions are simulated:
=== install 3 packages
- install a 1 [required by b]
- install b 1 [required by i]
- install i 2

i.2
'-- b.1
'-- a.1
### opam install i.2
The following actions will be performed:
=== install 3 packages
- install a 1 [required by b]
- install b 1 [required by i]
- install i 2

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
-> installed a.1
-> installed b.1
-> installed i.2
Done.
### opam tree i.1
The following actions are simulated:
=== downgrade 1 package
- downgrade i 2 to 1

i.1
'-- a.1
### <local-pkg.opam>
opam-version: "2.0"
depends: ["local-pkg-core" "b"]
### <local-pkg-core.opam>
opam-version: "2.0"
depends: "a"
### opam tree .
The following actions are simulated:
=== install 2 packages
- install local-pkg dev
- install local-pkg-core dev

local-pkg.dev
|-- b.1
| '-- a.1
'-- local-pkg-core.dev
'-- a.1 [*]

local-pkg-core.dev
### opam tree ./local-pkg-core.opam
The following actions are simulated:
=== install 1 package
- install local-pkg-core dev

local-pkg-core.dev
'-- a.1
### <pin:dir/installed-local.opam>
opam-version: "2.0"
depends: ["b" "installed-local-core"]
### <pin:dir/installed-local-core.opam>
opam-version: "2.0"
depends: "a"
### opam install ./dir
Package installed-local does not exist, create as a NEW package? [y/n] y
installed-local is now pinned to file://${BASEDIR}/dir (version dev)
Package installed-local-core does not exist, create as a NEW package? [y/n] y
installed-local-core is now pinned to file://${BASEDIR}/dir (version dev)
The following actions will be performed:
=== install 2 packages
- install installed-local dev (pinned)
- install installed-local-core dev (pinned)

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
-> retrieved installed-local.dev (file://${BASEDIR}/dir)
-> retrieved installed-local-core.dev (file://${BASEDIR}/dir)
-> installed installed-local-core.dev
-> installed installed-local.dev
Done.
### opam tree installed-local
installed-local.dev
|-- b.1
| '-- a.1
'-- installed-local-core.dev
'-- a.1 [*]
### opam tree ./dir
installed-local.dev
|-- b.1
| '-- a.1
'-- installed-local-core.dev
'-- a.1 [*]

installed-local-core.dev
### opam tree ./dir/installed-local-core.opam
installed-local-core.dev
'-- a.1
### : different package version :
### <pkg:a.2>
opam-version: "2.0"
### opam tree a.2
The following actions are simulated:
=== recompile 4 packages
- recompile b 1 [uses a]
- recompile i 2 [uses b]
- recompile installed-local dev (pinned) [uses b, installed-local-core]
- recompile installed-local-core dev (pinned) [uses a]
=== upgrade 1 package
- upgrade a 1 to 2

a.2
### opam list a
# Packages matching: name-match(a) & (installed | available)
# Package # Installed # Synopsis
a.1 1
a.2 1
### opam tree --rev-deps a.2
[WARNING] Not installed package a (= 2), skipping
[ERROR] No package to display
# Return code 5 #

0 comments on commit 8a23fc0

Please sign in to comment.