Skip to content

Commit

Permalink
Merge pull request #4427 from freevoid/eval_cmd_on_init
Browse files Browse the repository at this point in the history
Print shell-appropriate eval command on `opam init`
  • Loading branch information
dra27 committed Dec 21, 2020
2 parents d6cc0fd + b44030e commit a56a38e
Show file tree
Hide file tree
Showing 4 changed files with 76 additions and 37 deletions.
1 change: 1 addition & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,7 @@ New option/command/subcommand are prefixed with ◈.
## Init
* Fix sandbox check with not yet set opam environment variables [#4370 @rjbou - fix #4368]
* Sandboxing check: use configured temp dir and cleanup afterwards [#4467 @AltGr]
* Print shell-appropriate eval command on `opam init` [#4427 @freevoid]

## Config Upgrade
*
Expand Down
54 changes: 35 additions & 19 deletions src/client/opamCommands.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1097,19 +1097,25 @@ end
(* CONFIG *)
let config_doc = "Display configuration options for packages."
let config cli =
let shell = OpamStd.Sys.guess_shell_compat () in
let doc = config_doc in
let commands = [
cli_original, "env", `env, [],
"Returns the bindings for the environment variables set in the current \
switch, e.g. PATH, in a format intended to be evaluated by a shell. With \
$(i,-v), add comments documenting the reason or package of origin for \
each binding. This is most usefully used as $(b,eval \\$(opam config \
env\\)) to have further shell commands be evaluated in the proper opam \
context. Can also be accessed through $(b,opam env).";
Printf.sprintf
"Returns the bindings for the environment variables set in the \
current switch, e.g. PATH, in a format intended to be evaluated by \
a shell. With $(i,-v), add comments documenting the reason or \
package of origin for each binding. This is most usefully used as \
$(b,%s) to have further shell commands be evaluated in the proper \
opam context. Can also be accessed through $(b,opam env)."
OpamEnv.(shell_eval_invocation shell "opam config env" |> Manpage.escape);
cli_original, "revert-env", `revert_env, [],
"Reverts environment changes made by opam, e.g. $(b,eval \\$(opam config \
revert-env)) undoes what $(b,eval \\$(opam config env\\)) did, as much as \
possible.";
Printf.sprintf
"Reverts environment changes made by opam, e.g. $(b,%s) undoes what \
$(b,%s) did, as much as possible."
OpamEnv.(shell_eval_invocation shell "opam config revert-env"
|> Manpage.escape)
OpamEnv.(shell_eval_invocation shell "opam config env" |> Manpage.escape);
cli_original, "list", `list, ["[PACKAGE]..."],
"Without argument, prints a documented list of all available variables. \
With $(i,PACKAGE), lists all the variables available for these packages. \
Expand Down Expand Up @@ -1416,15 +1422,20 @@ let exec cli =
(* ENV *)
let env_doc = "Prints appropriate shell variable assignments to stdout"
let env cli =
let shell = OpamStd.Sys.guess_shell_compat () in
let doc = env_doc in
let man = [
`S Manpage.s_description;
`P "Returns the bindings for the environment variables set in the current \
switch, e.g. PATH, in a format intended to be evaluated by a shell. \
With $(i,-v), add comments documenting the reason or package of origin \
for each binding. This is most usefully used as $(b,eval \\$(opam \
env\\)) to have further shell commands be evaluated in the proper opam \
context.";
`P (Printf.sprintf
"Returns the bindings for the environment variables set in the current \
switch, e.g. PATH, in a format intended to be evaluated by a shell. \
With $(i,-v), add comments documenting the reason or package of origin \
for each binding. This is most usefully used as $(b,%s) \
to have further shell commands be evaluated in the proper opam \
context."
OpamEnv.(
shell_eval_invocation shell (opam_env_invocation ())
|> Manpage.escape));
`P "This is a shortcut, and equivalent to $(b,opam config env).";
] in
let revert =
Expand Down Expand Up @@ -2293,6 +2304,7 @@ let with_repos_rt gt repos f =

let switch_doc = "Manage multiple installation prefixes."
let switch cli =
let shell = OpamStd.Sys.guess_shell_compat () in
let doc = switch_doc in
let commands = [
cli_original, "create", `install, ["SWITCH"; "[COMPILER]"],
Expand Down Expand Up @@ -2365,10 +2377,14 @@ let switch cli =
prompted to install them after the switch is created unless \
$(b,--no-install) is specified."
OpamArg.dir_sep OpamSwitch.external_dirname);
`P "$(b,opam switch set) sets the default switch globally, but it is also \
possible to select a switch in a given shell session, using the \
environment. For that, use $(i,eval \\$(opam env \
--switch=SWITCH --set-switch\\)).";
`P (Printf.sprintf
"$(b,opam switch set) sets the default switch globally, but it is also \
possible to select a switch in a given shell session, using the \
environment. For that, use $(i,%s)."
OpamEnv.(
shell_eval_invocation shell
(opam_env_invocation ~switch:"SWITCH" ~set_opamswitch:true ())
|> Manpage.escape));
] @ mk_subdoc ~cli ~defaults:["","list";"SWITCH","set"] commands
@ [
`S Manpage.s_examples;
Expand Down
49 changes: 31 additions & 18 deletions src/state/opamEnv.ml
Original file line number Diff line number Diff line change
Expand Up @@ -335,6 +335,24 @@ let is_up_to_date ?skip st =
is_up_to_date_raw ?skip
(updates ~set_opamroot:false ~set_opamswitch:false ~force_path:false st)

(** Returns shell-appropriate statement to evaluate [cmd]. *)
let shell_eval_invocation shell cmd =
match shell with
| SH_fish ->
Printf.sprintf "eval (%s)" cmd
| SH_csh ->
Printf.sprintf "eval `%s`" cmd
| _ ->
Printf.sprintf "eval $(%s)" cmd

(** Returns "opam env" invocation string together with optional root and switch
overrides *)
let opam_env_invocation ?root ?switch ?(set_opamswitch=false) () =
let root = OpamStd.Option.map_default (Printf.sprintf " --root=%s") "" root in
let switch = OpamStd.Option.map_default (Printf.sprintf " --switch=%s") "" switch in
let setswitch = if set_opamswitch then " --set-switch" else "" in
Printf.sprintf "opam env%s%s%s" root switch setswitch

let eval_string gt ?(set_opamswitch=false) switch =
let root =
let opamroot_cur = OpamFilename.Dir.to_string gt.root in
Expand All @@ -344,34 +362,29 @@ let eval_string gt ?(set_opamswitch=false) switch =
OpamFilename.Dir.to_string OpamStateConfig.(default.root_dir)
) in
if opamroot_cur <> opamroot_env then
Printf.sprintf " --root=%s" opamroot_cur
Some opamroot_cur
else
"" in
None
in
let switch =
match switch with
| None -> ""
| Some sw ->
(* Returns the switch only if it is different from the one determined by the
environment *)
let f sw =
let sw_cur = OpamSwitch.to_string sw in
let sw_env =
OpamStd.Option.Op.(
OpamStd.Env.getopt "OPAMSWITCH" ++
(OpamStateConfig.get_current_switch_from_cwd gt.root >>|
OpamSwitch.to_string) ++
OpamSwitch.to_string) ++
(OpamFile.Config.switch gt.config >>| OpamSwitch.to_string)
)
in
if Some sw_cur <> sw_env then Printf.sprintf " --switch=%s" sw_cur
else ""
if Some sw_cur <> sw_env then Some sw_cur else None
in
OpamStd.Option.replace f switch
in
let setswitch = if set_opamswitch then " --set-switch" else "" in
match OpamStd.Sys.guess_shell_compat () with
| SH_fish ->
Printf.sprintf "eval (opam env%s%s%s)" root switch setswitch
| SH_csh ->
Printf.sprintf "eval `opam env%s%s%s`" root switch setswitch
| _ ->
Printf.sprintf "eval $(opam env%s%s%s)" root switch setswitch

let shell = OpamStd.Sys.guess_shell_compat () in
shell_eval_invocation shell (opam_env_invocation ?root ?switch ~set_opamswitch ())


(* -- Shell and init scripts handling -- *)
Expand Down Expand Up @@ -700,7 +713,7 @@ let setup
(OpamConsole.colorise `bold @@ string_of_shell shell)
(OpamConsole.colorise `cyan @@ OpamFilename.prettify dot_profile)
(OpamConsole.colorise `bold @@ source root shell (init_file shell))
(OpamConsole.colorise `bold @@ "eval $(opam env)");
(OpamConsole.colorise `bold @@ shell_eval_invocation shell (opam_env_invocation ()));
if OpamCoreConfig.(!r.answer = Some true) then begin
OpamConsole.warning "Shell not updated in non-interactive mode: use --shell-setup";
None
Expand Down
9 changes: 9 additions & 0 deletions src/state/opamEnv.mli
Original file line number Diff line number Diff line change
Expand Up @@ -70,6 +70,15 @@ val is_up_to_date_switch: dirname -> switch -> bool
its set of installed packages *)
val compute_updates: ?force_path:bool -> 'a switch_state -> env_update list

(** Returns shell-appropriate statement to evaluate [cmd]. *)
val shell_eval_invocation:
OpamTypes.shell -> string -> string

(** Returns "opam env" invocation string together with optional root and switch
overrides *)
val opam_env_invocation:
?root:string -> ?switch:string -> ?set_opamswitch:bool -> unit -> string

(** The shell command to run by the user to set his OPAM environment, adapted to
the current shell (as returned by [eval `opam config env`]) *)
val eval_string:
Expand Down

0 comments on commit a56a38e

Please sign in to comment.