Skip to content
Draft
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
1 change: 1 addition & 0 deletions src/client/opamAdminCommand.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1078,6 +1078,7 @@ let get_virtual_switch_state repo_root env =
Hashtbl.add t repo.repo_name (lazy repo_root); t
in
let rt = {
repos_config = OpamFile.Repos_config.empty;
repos_global = gt;
repos_lock = OpamSystem.lock_none;
repositories = singl repo;
Expand Down
1 change: 1 addition & 0 deletions src/client/opamArg.mli
Original file line number Diff line number Diff line change
Expand Up @@ -26,6 +26,7 @@ val cli2_1: OpamCLIVersion.t
val cli2_2: OpamCLIVersion.t
val cli2_3: OpamCLIVersion.t
val cli2_4: OpamCLIVersion.t
val cli2_5: OpamCLIVersion.t

(* [cli_from ?platform ?experimental since] validity flag since [since], and no
removal version. If [experimental] is true, it is marked as is (warning and
Expand Down
1 change: 1 addition & 0 deletions src/client/opamArgTools.ml
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,7 @@ let cli2_1 = OpamCLIVersion.of_string "2.1"
let cli2_2 = OpamCLIVersion.of_string "2.2"
let cli2_3 = OpamCLIVersion.of_string "2.3"
let cli2_4 = OpamCLIVersion.of_string "2.4"
let cli2_5 = OpamCLIVersion.of_string "2.5"

type subplatform = [ `windows | `unix ]
type platform = [ `all | subplatform ]
Expand Down
1 change: 1 addition & 0 deletions src/client/opamArgTools.mli
Original file line number Diff line number Diff line change
Expand Up @@ -30,6 +30,7 @@ val cli2_1: OpamCLIVersion.t
val cli2_2: OpamCLIVersion.t
val cli2_3: OpamCLIVersion.t
val cli2_4: OpamCLIVersion.t
val cli2_5: OpamCLIVersion.t

val mk_flag:
cli:OpamCLIVersion.Sourced.t -> validity -> section:string -> string list ->
Expand Down
2 changes: 1 addition & 1 deletion src/client/opamCLIVersion.ml
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@

type t = int * int

let supported_versions = [(2, 0); (2, 1); (2,2); (2,3); (2,4)]
let supported_versions = [(2, 0); (2, 1); (2,2); (2,3); (2,4); (2,5)]

let is_supported v =
OpamStd.List.mem (OpamCompat.Pair.equal Int.equal Int.equal)
Expand Down
18 changes: 13 additions & 5 deletions src/client/opamClient.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1849,9 +1849,15 @@ let init
OpamStd.Sys.exit_because `Aborted);
try
(* Create the content of ~/.opam/config *)
let repos = match repo with
| Some r -> [r.repo_name, (r.repo_url, r.repo_trust)]
| None -> OpamFile.InitConfig.repositories init_config
let repos =
match repo with
| Some r ->
[r.repo_name,
OpamFile.Repo_config.create ?trust:r.repo_trust r.repo_url]
| None ->
List.map (fun (n,(u,t)) ->
n, OpamFile.Repo_config.create ?trust:t u)
( OpamFile.InitConfig.repositories init_config)
in
let config =
update_with_init_config
Expand All @@ -1862,7 +1868,7 @@ let init
let config, mechanism, system_packages, msys2_check_root =
if Sys.win32 then
determine_windows_configuration ?cygwin_setup ?git_location
~bypass_checks ~interactive config
~bypass_checks ~interactive config
else
config, None, [], None
in
Expand Down Expand Up @@ -1899,7 +1905,9 @@ let init
else config
in
OpamFile.Config.write config_f config;
let repos_config = OpamRepositoryName.Map.of_list repos in
let repos_config =
OpamFile.Repos_config.create (OpamRepositoryName.Map.of_list repos)
in
OpamFile.Repos_config.write (OpamPath.repos_config root)
repos_config;

Expand Down
79 changes: 60 additions & 19 deletions src/client/opamCommands.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1136,19 +1136,23 @@ module Var_Option_Common = struct
let global cli =
mk_flag ~cli (cli_from cli2_1) ["global"] "Act on global configuration"

let var_option global global_options cmd var =
let var_option global repos repo global_options cmd var =
let switch_set = (fst global_options).opt_switch <> None in
if global && switch_set then
`Error (true, "--global and --switch sw option can't be used together")
else
let scope =
if global then `Global
else if switch_set then `Switch
else match var with
| None -> `All
| Some f -> match cmd with
| `var -> `All_var
| `option -> OpamConfigCommand.get_scope f
if global then `Global else
if repos then `Repos else
match repo with
| Some repo -> `Repo repo
| None ->
if switch_set then `Switch
else match var with
| None -> `All
| Some f -> match cmd with
| `var -> `All_var
| `option -> OpamConfigCommand.get_scope f
in
let apply =
match var with
Expand Down Expand Up @@ -1179,7 +1183,7 @@ module Var_Option_Common = struct
| `value_eq _ ->
`Error (true, "variable setting needs a scope, \
use '--global' or '--switch <switch>'"))
| (`Global | `Switch) as scope ->
| (`Global | `Switch | `Repo _ | `Repos) as scope ->
match cmd, apply with
| _ , `empty ->
(match scope with
Expand All @@ -1194,7 +1198,10 @@ module Var_Option_Common = struct
(match cmd with
| `var -> OpamConfigCommand.vars_list_global gt
| `option -> OpamConfigCommand.options_list_global gt);
`Ok ())
`Ok ()
| `Repo _ | `Repos ->
(* TODO RJBOU: update *)
OpamConsole.error_and_exit `Internal_error "repo list var not implemented")
| _, `value_wo_eq v ->
(match scope with
| `Switch ->
Expand All @@ -1208,8 +1215,12 @@ module Var_Option_Common = struct
(match cmd with
| `var -> OpamConfigCommand.var_show_global gt v
| `option -> OpamConfigCommand.option_show_global gt v);
`Ok ())
| `var, `value_eq (_,#OpamConfigCommand.append_op) ->
`Ok ()
| `Repo _ | `Repos ->
(* TODO RJBOU: update *)
OpamConsole.error_and_exit `Internal_error "repo show var not implemented")
| `var, `value_eq (_,#OpamConfigCommand.append_op)
when scope = `Switch || scope = `Global ->
`Error (true, "var: append operation are not permitted")
| _, `value_eq (v,u) ->
match scope with
Expand All @@ -1232,6 +1243,15 @@ module Var_Option_Common = struct
| `option -> OpamConfigCommand.set_opt_global gt v u
in
`Ok ()
| `Repo repo ->
OpamGlobalState.with_ `Lock_write @@ fun gt ->
let _rt = OpamConfigCommand.set_var_repo gt repo v u in
`Ok ()
| `Repos ->
OpamGlobalState.with_ `Lock_write @@ fun gt ->
let _rt = OpamConfigCommand.set_opt_repo gt v u in
`Ok ()


end

Expand Down Expand Up @@ -1262,11 +1282,21 @@ let var cli =
"List all variables defined for the given package"
Arg.(some package_name) None
in
let print_var global_options package varvalue global () =
let repo cli =
mk_opt ~cli (cli_from cli2_5) ~section:Manpage.s_options
["repository"] "REPOSITORY_NAME"
"Act on repository configuration"
Arg.(some repository_name) None
in
let print_var global_options package varvalue global repo () =
apply_global_options cli global_options;
match varvalue, package with
| _, None ->
var_option global global_options `var varvalue
(match global, repo with
| true, Some _ ->
`Error (true, "--repo and global can't be specified together")
| _, _ ->
var_option global false repo global_options `var varvalue)
| None, Some pkg ->
OpamGlobalState.with_ `Lock_none @@ fun gt ->
OpamSwitchState.with_ `Lock_none gt @@ fun st ->
Expand All @@ -1278,7 +1308,7 @@ let var cli =
in
mk_command_ret ~cli cli_original "var" ~doc ~man
Term.(const print_var
$global_options cli $package $varvalue $global cli)
$global_options cli $package $varvalue $global cli $repo cli)

(* OPTION *)
let option_doc = "Global and switch configuration options settings"
Expand All @@ -1304,13 +1334,21 @@ let option cli =
in
Arg.(value & pos 0 (some string) None & info ~docv ~doc [])
in
let option global_options fieldvalue global () =
let repo cli =
mk_flag ~cli (cli_from cli2_5) ~section:Manpage.s_options
["repositories"]
"Act on repository configuration"
in
let option global_options fieldvalue global repo () =
apply_global_options cli global_options;
var_option global global_options `option fieldvalue
if global && repo then
`Error (true, "--repo and global can't be specified together")
else
var_option global repo None global_options `option fieldvalue
in
mk_command_ret ~cli (cli_from cli2_1) "option" ~doc ~man
Term.(const option
$global_options cli $fieldvalue $global cli)
$global_options cli $fieldvalue $global cli $repo cli)

module Common_config_flags = struct
let sexp cli =
Expand Down Expand Up @@ -2547,6 +2585,7 @@ let repository cli =
OpamGlobalState.with_ `Lock_none @@ fun gt ->
let repos =
OpamStateConfig.Repos.safe_read ~lock_kind:`Lock_read gt
|> OpamFile.Repos_config.repos
in
let not_found =
List.filter (fun r -> not (OpamRepositoryName.Map.mem r repos)) names
Expand Down Expand Up @@ -4308,6 +4347,7 @@ let clean cli =
@@ fun _lock ->
let repos_config =
OpamStateConfig.Repos.safe_read ~lock_kind:`Lock_write gt
|> OpamFile.Repos_config.repos
in
let all_repos =
OpamRepositoryName.Map.keys repos_config |>
Expand Down Expand Up @@ -4346,7 +4386,8 @@ let clean cli =
OpamConsole.msg "Updating %s\n"
(OpamFile.to_string (OpamPath.repos_config root));
if not dry_run then
OpamFile.Repos_config.write (OpamPath.repos_config root) repos_config);
OpamFile.Repos_config.write (OpamPath.repos_config root)
(OpamFile.Repos_config.create repos_config));
if repo_cache then
(OpamConsole.msg "Clearing repository cache\n";
if not dry_run then OpamRepositoryState.Cache.remove ());
Expand Down
Loading
Loading