Skip to content

Commit

Permalink
cli:yes: add --confirm-level to specify levels of automatic answer …
Browse files Browse the repository at this point in the history
…to opam questions, and `--no`

There is 3 levels, 4 states:
* unsafe-yes: yes to all questions & launch system package manager in non interactive mode
* yes: answers no to all questions, similar to `--yes`
* no: answers no to all questions, similar to `--no`
* ask (default): ask for all questions
  • Loading branch information
rjbou committed Apr 7, 2021
1 parent 625d849 commit feab70d
Show file tree
Hide file tree
Showing 12 changed files with 104 additions and 35 deletions.
53 changes: 43 additions & 10 deletions src/client/opamArg.ml
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,14 @@ let when_enum =
[ "always", `Always; "never", `Never; "auto", `Auto ]
|> List.map (fun (s,v) -> cli_original, s, v)

let confirm_enum =
[
cli_from cli2_1, "ask", `Ask;
cli_from cli2_1, "yes", `All_yes;
cli_from cli2_1, "no", `All_no;
cli_from cli2_1, "unsafe-yes", `Unsafe_yes;
]

(* Windows directory separators need to be escaped for manpages *)
let dir_sep, escape_path =
match Filename.dir_sep with
Expand All @@ -45,7 +53,8 @@ let preinit_environment_variables =
let open OpamCoreConfig.E in [
"DEBUG", (fun v -> DEBUG (env_int v)),
"see options `--debug' and `--debug-level'.";
"YES", (fun v -> YES (env_bool v)), "see option `--yes'.";
"YES", (fun v -> YES (env_answer v)),
"see option `--yes' and `--confirm-level`.";
] in
let client =
let open OpamClientConfig.E in [
Expand Down Expand Up @@ -98,7 +107,8 @@ let environment_variables =
"MERGEOUT", cli_original, (fun v -> MERGEOUT (env_bool v)),
"merge process outputs, stderr on stdout.";
"NO", cli_original, (fun v -> NO (env_bool v)),
"answer no to any question asked.";
"answer no to any question asked, \
see option `--no` and `--confirm-level`.";
"PRECISETRACKING", cli_original, (fun v -> PRECISETRACKING (env_bool v)),
"fine grain tracking of directories.";
"SAFE", cli_original, (fun v -> SAFE (env_bool v)),
Expand Down Expand Up @@ -411,7 +421,7 @@ type global_options = {
quiet : bool;
color : OpamStd.Config.when_ option;
opt_switch : string option;
yes : bool;
answer : OpamStd.Config.answer option;
strict : bool;
opt_root : dirname option;
git_version : bool;
Expand All @@ -430,7 +440,9 @@ type global_options = {

(* The --cli passed by cmdliner is ignored (it's only there for --help) *)
let create_global_options
git_version debug debug_level verbose quiet color opt_switch yes strict
git_version debug debug_level verbose quiet color opt_switch
yes confirm_level
strict
opt_root external_solver use_internal_solver
cudf_file solver_preferences best_effort safe_mode json no_auto_upgrade
working_dir ignore_pin_depends
Expand All @@ -442,9 +454,16 @@ let create_global_options
let debug_level = OpamStd.Option.Op.(
debug_level >>+ fun () -> if debug then Some 1 else None
) in
let answer =
match yes, confirm_level with
| None, None -> None
| _ , Some c -> Some c
| Some true, None -> Some `All_yes
| Some false, None -> Some `All_no
in
let verbose = List.length verbose in
let cli = OpamCLIVersion.current in
{ git_version; debug_level; verbose; quiet; color; opt_switch; yes;
{ git_version; debug_level; verbose; quiet; color; opt_switch; answer;
strict; opt_root; external_solver; use_internal_solver;
cudf_file; solver_preferences; best_effort; safe_mode; json;
no_auto_upgrade; working_dir; ignore_pin_depends; cli }
Expand Down Expand Up @@ -481,7 +500,7 @@ let apply_global_options cli o =
?color:o.color
(* ?utf8:[ `Extended | `Always | `Never | `Auto ] *)
(* ?disp_status_line:[ `Always | `Never | `Auto ] *)
?answer:(some (flag o.yes))
?answer:o.answer
?safe_mode:(flag o.safe_mode)
(* ?lock_retries:int *)
(* ?log_dir:OpamTypes.dirname *)
Expand Down Expand Up @@ -1119,9 +1138,22 @@ let global_options cli =
This is equivalent to setting $(b,\\$OPAMSWITCH) to $(i,SWITCH)."
Arg.(some string) None in
let yes =
mk_flag ~cli cli_original ~section ["y";"yes"]
"Answer yes to all yes/no questions without prompting. \
This is equivalent to setting $(b,\\$OPAMYES) to \"true\"." in
mk_vflag ~cli None [
cli_original, Some true, ["y";"yes"],
"Answer yes to all opam yes/no questions without prompting. \
This is equivalent to setting $(b,\\$OPAMYES) to \"true\".";
cli_from cli2_1, Some false, ["no"],
"Answer no to all opam yes/no questions without prompting. \
This is equivalent to setting $(b,\\$OPAMNO) to \"true\".";
]
in
let confirm_level =
mk_enum_opt ~cli (cli_from cli2_1) ~section ["confirm-level"] "LEVEL"
confirm_enum
(Printf.sprintf "Confirmation level, $(docv) must be %s. \
This is equivalent to setting $(b, \\$OPAMYES)`."
(string_of_enum confirm_enum))
in
let strict =
mk_flag ~cli cli_original ~section ["strict"]
"Fail whenever an error is found in a package definition \
Expand Down Expand Up @@ -1216,7 +1248,8 @@ let global_options cli =
equivalent to setting $(b,IGNOREPINDEPENDS=true)."
in
Term.(const create_global_options
$git_version $debug $debug_level $verbose $quiet $color $switch $yes
$git_version $debug $debug_level $verbose $quiet $color $switch
$yes $confirm_level
$strict $root $external_solver
$use_internal_solver $cudf_file $solver_preferences $best_effort
$safe_mode $json_flag $no_auto_upgrade $working_dir
Expand Down
2 changes: 1 addition & 1 deletion src/client/opamArg.mli
Original file line number Diff line number Diff line change
Expand Up @@ -143,7 +143,7 @@ type global_options = {
quiet : bool;
color : OpamStd.Config.when_ option;
opt_switch : string option;
yes : bool;
answer : OpamStd.Config.answer option;
strict : bool;
opt_root : dirname option;
git_version : bool;
Expand Down
4 changes: 2 additions & 2 deletions src/client/opamCliMain.ml
Original file line number Diff line number Diff line change
Expand Up @@ -133,8 +133,8 @@ let check_and_run_external_commands () =
else
(* No such command, check if there is a matching plugin *)
let command = plugin_prefix ^ name in
let answer = if yes then Some true else OpamCoreConfig.E.yes () in
OpamCoreConfig.init ~answer ();
let answer = if yes then Some `All_yes else OpamCoreConfig.E.yes () in
OpamCoreConfig.init ?answer ();
OpamFormatConfig.init ();
let root_dir = OpamStateConfig.opamroot () in
let has_init = OpamStateConfig.load_defaults root_dir <> None in
Expand Down
2 changes: 1 addition & 1 deletion src/client/opamClientConfig.mli
Original file line number Diff line number Diff line change
Expand Up @@ -153,7 +153,7 @@ val opam_init:
?color:OpamStd.Config.when_ ->
?utf8:OpamStd.Config.when_ext ->
?disp_status_line:OpamStd.Config.when_ ->
?answer:bool option ->
?answer:OpamStd.Config.answer ->
?safe_mode:bool ->
?keep_log_dir:bool ->
?errlog_length:int ->
Expand Down
4 changes: 2 additions & 2 deletions src/client/opamSolution.ml
Original file line number Diff line number Diff line change
Expand Up @@ -937,7 +937,7 @@ let simulate_new_state state t =
(* Ask confirmation whenever the packages to modify are not exactly
the packages in the user request *)
let confirmation ?ask requested solution =
OpamCoreConfig.(!r.answer = Some true) ||
OpamCoreConfig.is_answer_yes () ||
match ask with
| Some false -> true
| Some true -> OpamConsole.confirm "Do you want to continue?"
Expand Down Expand Up @@ -1077,7 +1077,7 @@ let install_depexts ?(force_depext=false) ?(confirm=true) t packages =
system packages altogether.\n";
OpamStd.Sys.exit_because `Aborted
in
if not OpamStd.Sys.tty_in || OpamCoreConfig.(!r.answer <> None) then
if not OpamStd.Sys.tty_in || OpamCoreConfig.(!r.answer <> `Ask) then
give_up ()
else if OpamConsole.confirm
"%s\nWhen you are done: check again and continue?"
Expand Down
7 changes: 4 additions & 3 deletions src/core/opamConsole.ml
Original file line number Diff line number Diff line change
Expand Up @@ -695,16 +695,17 @@ let header_error fmt =
) fmt



let confirm ?(default=true) fmt =
Printf.ksprintf (fun s ->
try
if OpamCoreConfig.(!r.safe_mode) then false else
let prompt () =
formatted_msg "%s [%s] " s (if default then "Y/n" else "y/N")
in
if OpamCoreConfig.(!r.answer) = Some true then
if OpamCoreConfig.is_answer_yes () then
(prompt (); msg "y\n"; true)
else if OpamCoreConfig.(!r.answer) = Some false ||
else if OpamCoreConfig.(!r.answer) = `All_no ||
OpamStd.Sys.(not tty_in)
then
(prompt (); msg "n\n"; false)
Expand Down Expand Up @@ -758,7 +759,7 @@ let confirm ?(default=true) fmt =
let read fmt =
Printf.ksprintf (fun s ->
formatted_msg "%s " s;
if OpamCoreConfig.(!r.answer = None && not !r.safe_mode) then (
if OpamCoreConfig.(!r.answer = `Ask && not !r.safe_mode) then (
try match read_line () with
| "" -> None
| s -> Some s
Expand Down
22 changes: 17 additions & 5 deletions src/core/opamCoreConfig.ml
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ module E = struct
| UTF8 of OpamStd.Config.when_ext option
| UTF8MSGS of bool option
| VERBOSE of OpamStd.Config.level option
| YES of bool option
| YES of OpamStd.Config.answer option

open OpamStd.Config.E
let color = value (function COLOR c -> c | _ -> None)
Expand All @@ -46,7 +46,7 @@ module E = struct
let utf8 = value (function UTF8 c -> c | _ -> None)
let utf8msgs = value (function UTF8MSGS b -> b | _ -> None)
let verbose = value (function VERBOSE l -> l | _ -> None)
let yes = value (function YES b -> b | _ -> None)
let yes = value (function YES a -> a | _ -> None)

end

Expand All @@ -57,7 +57,7 @@ type t = {
color: OpamStd.Config.when_;
utf8: OpamStd.Config.when_ext;
disp_status_line: OpamStd.Config.when_;
answer: bool option;
answer: OpamStd.Config.answer;
safe_mode: bool;
log_dir: string;
keep_log_dir: bool;
Expand All @@ -75,7 +75,7 @@ type 'a options_fun =
?color:OpamStd.Config.when_ ->
?utf8:OpamStd.Config.when_ext ->
?disp_status_line:OpamStd.Config.when_ ->
?answer:bool option ->
?answer:OpamStd.Config.answer ->
?safe_mode:bool ->
?log_dir:string ->
?keep_log_dir:bool ->
Expand All @@ -92,7 +92,7 @@ let default = {
color = `Auto;
utf8 = `Auto;
disp_status_line = `Auto;
answer = None;
answer = `Ask;
safe_mode = false;
log_dir =
(let user = try Unix.getlogin() with Unix.Unix_error _ -> "xxx" in
Expand Down Expand Up @@ -157,11 +157,18 @@ let initk k =
| true -> Some `Extended
| false -> None)
) in
let answer = match E.yes (), E.no () with
| Some c, _ -> Some c
| _, Some true -> Some `All_no
| None, None -> None
| _ -> Some `Ask
(*
let answer = match E.yes (), E.no () with
| Some true, _ -> Some (Some true)
| _, Some true -> Some (Some false)
| None, None -> None
| _ -> Some None
*)
in
(setk (setk (fun c -> r := c; k)) !r)
?debug_level:(E.debug ())
Expand All @@ -181,6 +188,11 @@ let initk k =

let init ?noop:_ = initk (fun () -> ())

let is_answer_yes () =
match !r.answer with
| `All_yes | `Unsafe_yes -> true
| _ -> false

#ifdef DEVELOPER
let developer = true
#else
Expand Down
10 changes: 6 additions & 4 deletions src/core/opamCoreConfig.mli
Original file line number Diff line number Diff line change
Expand Up @@ -28,10 +28,10 @@ module E : sig
| UTF8 of OpamStd.Config.when_ext option
| UTF8MSGS of bool option
| VERBOSE of OpamStd.Config.level option
| YES of bool option
| YES of OpamStd.Config.answer option
val debug: unit -> int option
val logs: unit -> string option
val yes: unit -> bool option
val yes: unit -> OpamStd.Config.answer option
end

type t = private {
Expand All @@ -51,7 +51,7 @@ type t = private {
disp_status_line: OpamStd.Config.when_;
(** Controls on-line display of parallel commands being run, using ANSI
escapes *)
answer : bool option;
answer : OpamStd.Config.answer;
(** Affects interactive questions in OpamConsole: auto-answer with the given
bool if Some *)
safe_mode : bool;
Expand Down Expand Up @@ -82,7 +82,7 @@ type 'a options_fun =
?color:OpamStd.Config.when_ ->
?utf8:OpamStd.Config.when_ext ->
?disp_status_line:OpamStd.Config.when_ ->
?answer:bool option ->
?answer:OpamStd.Config.answer ->
?safe_mode:bool ->
?log_dir:string ->
?keep_log_dir:bool ->
Expand Down Expand Up @@ -110,5 +110,7 @@ val init: ?noop:_ -> (unit -> unit) options_fun
stacking *)
val initk: 'a -> 'a options_fun

val is_answer_yes : unit -> bool

(** [true] if OPAM was compiled in developer mode *)
val developer : bool
26 changes: 21 additions & 5 deletions src/core/opamStd.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1402,6 +1402,7 @@ module Config = struct

type when_ = [ `Always | `Never | `Auto ]
type when_ext = [ `Extended | when_ ]
type answer = [ `Unsafe_yes | `All_yes | `All_no | `Ask ]

let env conv var =
try Option.map conv (Env.getopt ("OPAM"^var))
Expand All @@ -1417,11 +1418,12 @@ module Config = struct
| "1" | "yes" | "true" -> Some true
| _ -> None

let env_bool var =
env (fun s -> match bool_of_string s with
| Some s -> s
| None -> failwith "env_bool")
var
let bool s =
match bool_of_string s with
| Some s -> s
| None -> failwith "env_bool"

let env_bool var = env bool var

let env_int var = env int_of_string var

Expand Down Expand Up @@ -1479,6 +1481,20 @@ module Config = struct
| `Never -> false
| `Auto -> Lazy.force auto

let answer s =
match String.lowercase_ascii s with
| "ask" -> `Ask
| "yes" -> `All_yes
| "no" -> `All_no
| "unsafe-yes" -> `Unsafe_yes
| _ -> failwith "env_answer"

let env_answer =
env (fun s ->
try if bool s then `All_yes else `All_no
with Failure _ -> answer s)


module E = struct
type t = ..
let (r : t list ref) = ref []
Expand Down
3 changes: 3 additions & 0 deletions src/core/opamStd.mli
Original file line number Diff line number Diff line change
Expand Up @@ -542,6 +542,7 @@ module Config : sig

type when_ = [ `Always | `Never | `Auto ]
type when_ext = [ `Extended | when_ ]
type answer = [ `Unsafe_yes | `All_yes | `All_no | `Ask ]

(* Parse a envrionement variable boolean value *)
val bool_of_string: string -> bool option
Expand Down Expand Up @@ -569,6 +570,8 @@ module Config : sig

val resolve_when: auto:(bool Lazy.t) -> when_ -> bool

val env_answer: env_var -> answer option

module type Sig = sig

(** Read-only record type containing the lib's configuration options *)
Expand Down
2 changes: 1 addition & 1 deletion src/state/opamEnv.ml
Original file line number Diff line number Diff line change
Expand Up @@ -714,7 +714,7 @@ let setup
(OpamConsole.colorise `cyan @@ OpamFilename.prettify dot_profile)
(OpamConsole.colorise `bold @@ source root shell (init_file shell))
(OpamConsole.colorise `bold @@ shell_eval_invocation shell (opam_env_invocation ()));
if OpamCoreConfig.(!r.answer = Some true) then begin
if OpamCoreConfig.is_answer_yes () then begin
OpamConsole.warning "Shell not updated in non-interactive mode: use --shell-setup";
None
end else
Expand Down
4 changes: 3 additions & 1 deletion src/state/opamStateConfig.ml
Original file line number Diff line number Diff line change
Expand Up @@ -180,7 +180,9 @@ let initk k =
?no_env_notice:(E.noenvnotice ())
?locked:(E.locked () >>| function "" -> None | s -> Some s)
?no_depexts:(E.nodepexts ())
?depext_yes:(E.depextyes ())
?depext_yes:(E.depextyes () ++
if OpamCoreConfig.(!r.answer) = `Unsafe_yes then
Some true else None)

let init ?noop:_ = initk (fun () -> ())

Expand Down

0 comments on commit feab70d

Please sign in to comment.