Skip to content

Commit

Permalink
Merge pull request #4903 from rjbou/var-err
Browse files Browse the repository at this point in the history
More accurate error message on not found (package) variable with `opam var`
  • Loading branch information
rjbou authored Jul 12, 2023
2 parents 9173bee + c13df74 commit eaa702a
Show file tree
Hide file tree
Showing 3 changed files with 121 additions and 48 deletions.
2 changes: 2 additions & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -37,6 +37,8 @@ users)
## Show

## Var/Option
* Handle package variable syntax in parse update regexp [#4903 @rjbou - fix #4489]
* Error with more accurate message in case of package/self variable wrongly given as argument [#4903 @rjbou - fix #4489]

## Update / Upgrade

Expand Down
124 changes: 79 additions & 45 deletions src/client/opamConfigCommand.ml
Original file line number Diff line number Diff line change
Expand Up @@ -445,7 +445,7 @@ let parse_update fv =
Re.(compile @@ seq [
group @@ seq [
wordc;
opt @@ (seq [ rep @@ alt [ wordc ; char '-' ]; wordc ])
opt @@ (seq [ rep @@ alt [ wordc ; char '-' ; char ':' ]; wordc ])
];
(opt @@ seq [
(group @@ (alt [
Expand Down Expand Up @@ -490,6 +490,10 @@ let switch_doc switch =
Printf.sprintf "switch %s"
(OpamConsole.colorise `bold (OpamSwitch.to_string switch))

let no_self_variable_error () =
OpamConsole.error_and_exit `Bad_arguments
"Self variables (`_:`) are not valid here";

module OpamParser = OpamParser.FullPos
module OpamPrinter = OpamPrinter.FullPos

Expand Down Expand Up @@ -863,12 +867,8 @@ type ('var,'config) var_confset =
(* Global or switch specification, used to print final user message *)
}

let set_var svar value conf =
let var = OpamVariable.Full.of_string svar in
let set_var var value conf =
let conf = conf (OpamVariable.Full.variable var) in
if not (OpamVariable.Full.is_global var) then
OpamConsole.error_and_exit `Bad_arguments
"Only global variables may be set using this command";
let global_vars = conf.stv_vars in
let rest = List.filter (fun v -> not (conf.stv_find v)) global_vars in
let config = conf.stv_remove_elem rest conf.stv_config in
Expand All @@ -881,40 +881,50 @@ let set_var svar value conf =
else
(conf.stv_write config;
OpamConsole.msg "Removed variable %s in %s\n"
(OpamConsole.colorise `underline svar)
(OpamConsole.colorise `underline (OpamVariable.Full.to_string var))
conf.stv_doc);
config

let set_var_global gt var value =
let config =
set_var var value @@
fun var ->
let global_vars = OpamFile.Config.global_variables gt.config in
{ stv_vars = global_vars;
stv_find = (fun (k,_,_) -> k = var);
stv_config = gt.config;
stv_varstr = (fun v ->
OpamPrinter.Normalise.value (nullify_pos @@ List (nullify_pos @@ [
nullify_pos @@ Ident (OpamVariable.to_string var);
nullify_pos @@ String v;
nullify_pos @@ String "Set through 'opam var'"
])));
stv_set_opt = (fun config value ->
let gt =
set_opt_global_t ~inner:true { gt with config }
"global-variables" value
in gt.config);
stv_remove_elem = (fun rest config ->
OpamFile.Config.with_global_variables rest config
|> OpamFile.Config.with_eval_variables
(List.filter (fun (k,_,_) -> k <> var)
(OpamFile.Config.eval_variables config)));
stv_write = (fun config -> OpamGlobalState.write { gt with config });
stv_doc = global_doc;
} in
{ gt with config }
let set_var_global gt svar value =
let var = OpamVariable.Full.of_string svar in
match OpamVariable.Full.scope var with
| Global ->
let config =
set_var var value @@
fun var ->
let global_vars = OpamFile.Config.global_variables gt.config in
{ stv_vars = global_vars;
stv_find = (fun (k,_,_) -> k = var);
stv_config = gt.config;
stv_varstr = (fun v ->
OpamPrinter.Normalise.value (nullify_pos @@ List (nullify_pos @@ [
nullify_pos @@ Ident (OpamVariable.to_string var);
nullify_pos @@ String v;
nullify_pos @@ String "Set through 'opam var'"
])));
stv_set_opt = (fun config value ->
let gt =
set_opt_global_t ~inner:true { gt with config }
"global-variables" value
in gt.config);
stv_remove_elem = (fun rest config ->
OpamFile.Config.with_global_variables rest config
|> OpamFile.Config.with_eval_variables
(List.filter (fun (k,_,_) -> k <> var)
(OpamFile.Config.eval_variables config)));
stv_write = (fun config -> OpamGlobalState.write { gt with config });
stv_doc = global_doc;
} in
{ gt with config }
| Self -> no_self_variable_error ()
| Package _ ->
OpamConsole.error_and_exit `Bad_arguments
"Package variables are read-only and \
cannot be updated using `opam var --global`"

let set_var_switch gt ?st var value =

let set_var_switch gt ?st svar value =
let var = OpamVariable.Full.of_string svar in
let var_confset switch switch_config var =
let switch_vars = switch_config.OpamFile.Switch_config.variables in
{ stv_vars = switch_vars;
Expand All @@ -937,7 +947,19 @@ let set_var_switch gt ?st var value =
} in
let switch_config =
with_switch ~display:false gt `Lock_write st @@ fun sw swc ->
set_var var value (var_confset sw swc)
match OpamVariable.Full.scope var with
| Global -> set_var var value (var_confset sw swc)
| Self -> no_self_variable_error ()
| Package n ->
OpamConsole.error_and_exit `Bad_arguments
"%sPackage variables are read-only and \
cannot be updated using `opam var --global`"
(if OpamPackage.package_of_name_opt
(OpamStateConfig.Switch.safe_read_selections
~lock_kind:`Lock_read gt sw).sel_installed n = None then
Printf.sprintf "Package %s is not installed. "
(OpamPackage.Name.to_string n)
else "")
in
OpamStd.Option.map (fun st -> { st with switch_config }) st

Expand Down Expand Up @@ -1131,15 +1153,27 @@ let option_show_switch gt ?st field =
let option_show_global gt field =
option_show OpamFile.Config.to_list (confset_global gt) field

let var_show_t resolve ?switch v =
match resolve (OpamVariable.Full.of_string v) with
let var_show_t resolve gt ?switch v =
let var = OpamVariable.Full.of_string v in
if OpamVariable.Full.scope var = OpamVariable.Full.Self then
no_self_variable_error ();
match resolve var with
| Some c ->
OpamConsole.msg "%s\n" (OpamVariable.string_of_variable_contents c)
| None ->
OpamConsole.error_and_exit `Not_found "Variable %s not found in %s" v
OpamConsole.error_and_exit `Not_found "Variable %s not found in %s%s" v
(match switch with
| None -> "global config"
| Some switch -> "switch " ^ (OpamSwitch.to_string switch))
| None -> "the global configuration"
| Some switch -> "switch " ^ (OpamSwitch.to_string switch))
(match switch, OpamVariable.Full.scope var with
| Some switch, Package n ->
if OpamPackage.package_of_name_opt
(OpamStateConfig.Switch.safe_read_selections
~lock_kind:`Lock_read gt switch).sel_installed n = None then
Printf.sprintf "; package %s is not installed in this switch"
(OpamPackage.Name.to_string n)
else ""
| _ -> "")

let is_switch_defined_var switch_config v =
OpamFile.Switch_config.variable switch_config
Expand Down Expand Up @@ -1171,7 +1205,7 @@ let var_show_switch gt ?st v =
if var_switch_raw gt v = None then
let resolve_switch st =
if is_switch_defined_var st.switch_config v then
var_show_t (OpamPackageVar.resolve st) ~switch:st.switch v
var_show_t (OpamPackageVar.resolve st) gt ~switch:st.switch v
else
OpamConsole.error_and_exit `Not_found
"Variable %s not found in switch %s"
Expand All @@ -1181,7 +1215,7 @@ let var_show_switch gt ?st v =
| Some st -> resolve_switch st
| None -> OpamSwitchState.with_ `Lock_none gt resolve_switch

let var_show_global gt f = var_show_t (OpamPackageVar.resolve_global gt) f
let var_show_global gt f = var_show_t (OpamPackageVar.resolve_global gt) gt f

let var_show gt v =
if var_switch_raw gt v = None then
Expand All @@ -1194,7 +1228,7 @@ let var_show gt v =
resolve,
if is_switch_defined_var st.switch_config v then Some st.switch else None
in
var_show_t resolve ?switch v
var_show_t resolve gt ?switch v

(* detect scope *)
let get_scope field =
Expand Down
43 changes: 40 additions & 3 deletions tests/reftests/var-option.test
Original file line number Diff line number Diff line change
Expand Up @@ -130,7 +130,7 @@ ${BASEDIR}/OPAM/var-option/bin
### opam var bin --switch var-option
${BASEDIR}/OPAM/var-option/bin
### opam var bin --global
[ERROR] Variable bin not found in global config
[ERROR] Variable bin not found in the global configuration
# Return code 5 #
### opam var bin=global-bin --global
Added '[bin "global-bin" "Set through 'opam var'"]' to field global-variables in global configuration
Expand All @@ -153,17 +153,23 @@ switch-foo
### opam var foo --global
global-foo
### opam var ocaml-base-compiler:version
[ERROR] Variable ocaml-base-compiler:version not found in switch var-option
[ERROR] Variable ocaml-base-compiler:version not found in switch var-option; package ocaml-base-compiler is not installed in this switch
# Return code 5 #
### opam var ocaml-base-compiler:version --switch var-option
[ERROR] Variable ocaml-base-compiler:version not found in switch var-option
[ERROR] Variable ocaml-base-compiler:version not found in switch var-option; package ocaml-base-compiler is not installed in this switch
# Return code 5 #
### opam var ocaml-base-compiler:version --global
[ERROR] Variable ocaml-base-compiler:version not found in the global configuration
# Return code 5 #
### opam var --package ocaml | ".*build-id.*" -> '\c' | ".*opamfile.*" -> '\c' | " *" -> " "
[ERROR] Package ocaml not found, skipping
### opam var i-got-the-variables:version
2.4.6
### opam var i-got-the-variables:version --switch var-option
2.4.6
### opam var i-got-the-variables:version --global
[ERROR] Variable i-got-the-variables:version not found in the global configuration
# Return code 5 #
### opam var --package i-got-the-variables | ".*build-id.*" -> '\c' | ".*opamfile.*" -> '\c' | " *" -> " "
i-got-the-variables:name i-got-the-variables # Name of the package
i-got-the-variables:version 2.4.6 # Version of the package
Expand All @@ -180,6 +186,37 @@ i-got-the-variables:share ${BASEDIR}/OPAM/var-option/share/i-got-the-variables #
i-got-the-variables:etc ${BASEDIR}/OPAM/var-option/etc/i-got-the-variables # Etc directory for this package
i-got-the-variables:build ${BASEDIR}/OPAM/var-option/.opam-switch/build/i-got-the-variables.2.4.6 # Directory where the package was built
i-got-the-variables:dev false # True if this is a development package
### opam var i-got-the-variables:version=1 | '…' -> '...' | '`' -> "'"
opam: variable setting needs a scope, use '--global' or '--switch <switch>'
Usage: opam var [--global] [--package=PACKAGE] [OPTION]... [VAR[=[VALUE]]]
Try 'opam var --help' or 'opam --help' for more information.
# Return code 2 #
### opam var i-got-the-variables:version=1 --switch var-option
[ERROR] Package variables are read-only and cannot be updated using `opam var --global`
# Return code 2 #
### opam var i-got-the-variables:version=1 --global
[ERROR] Package variables are read-only and cannot be updated using `opam var --global`
# Return code 2 #
### opam var _:version
[ERROR] Self variables (`_:`) are not valid here
# Return code 2 #
### opam var _:version --switch var-option
[ERROR] Self variables (`_:`) are not valid here
# Return code 2 #
### opam var _:version --global
[ERROR] Self variables (`_:`) are not valid here
# Return code 2 #
### opam var _:version=1 | '…' -> '...' | '`' -> "'"
opam: variable setting needs a scope, use '--global' or '--switch <switch>'
Usage: opam var [--global] [--package=PACKAGE] [OPTION]... [VAR[=[VALUE]]]
Try 'opam var --help' or 'opam --help' for more information.
# Return code 2 #
### opam var _:version=1 --switch var-option
[ERROR] Self variables (`_:`) are not valid here
# Return code 2 #
### opam var _:version=1 --global
[ERROR] Self variables (`_:`) are not valid here
# Return code 2 #
### opam option

<><> Global configuration <><><><><><><><><><><><><><><><><><><><><><><><><><><>
Expand Down

0 comments on commit eaa702a

Please sign in to comment.