Skip to content

Commit

Permalink
Use OpamEnv.eval_string in --help output
Browse files Browse the repository at this point in the history
Use $SHELL to customise the display of --help output when eval $(opam
config env) is referred to. --shell is ignored (for reasons of code
simplicity).
  • Loading branch information
dra27 committed Apr 2, 2018
1 parent 2b9a6bb commit b4b3fca
Show file tree
Hide file tree
Showing 5 changed files with 82 additions and 64 deletions.
48 changes: 29 additions & 19 deletions src/client/opamCommands.ml
Original file line number Diff line number Diff line change
Expand Up @@ -659,18 +659,23 @@ end
let config_doc = "Display configuration options for packages."
let config =
let doc = config_doc in
let shell_help = OpamStd.Sys.guess_shell_compat () in
let commands = [
"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.(eval_string shell_help Manpage "config env" |> Manpage.escape);
"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.(eval_string shell_help Manpage "config revert-env" |> Manpage.escape)
OpamEnv.(eval_string shell_help Manpage "config env" |> Manpage.escape);
"setup", `setup, [],
"Configure global and user parameters for opam. Use $(b, opam config \
setup) to display more options. Use $(b,--list) to display the current \
Expand Down Expand Up @@ -1026,14 +1031,17 @@ let exec =
let env_doc = "Prints appropriate shell variable assignments to stdout"
let env =
let doc = env_doc in
let shell_help = OpamStd.Sys.guess_shell_compat () in
let man = [
`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.(eval_string shell_help Manpage "env" |> Manpage.escape));
`P "This is a shortcut, and equivalent to $(b,opam config env).";
] in
let revert =
Expand Down Expand Up @@ -1830,6 +1838,7 @@ let switch =
"install", `install, ["SWITCH"],
"Deprecated alias for 'create'."
] in
let shell_help = OpamStd.Sys.guess_shell_compat () in
let man = [
`S "DESCRIPTION";
`P "This command is used to manage \"switches\", which are independent \
Expand All @@ -1850,10 +1859,11 @@ let switch =
package definitions are found locally, the user is automatically \
prompted to install them after the switch is created unless \
$(b,--no-install) is specified.");
`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 $(b,%s)."
OpamEnv.(eval_string shell_help ~set_opamswitch:true ManSwitch "SWITCH"));
] @ mk_subdoc ~defaults:["","list";"SWITCH","set"] commands
@ [`S "OPTIONS"]
@ [`S OpamArg.build_option_section]
Expand Down
4 changes: 2 additions & 2 deletions src/client/opamSwitchCommand.ml
Original file line number Diff line number Diff line change
Expand Up @@ -122,14 +122,14 @@ let list ~shell gt ~print_short =
OpamConsole.warning
"The environment is not in sync with the current switch.\n\
You should run: %s"
(OpamEnv.eval_string shell gt (Some switch))
OpamEnv.(eval_string shell Root gt switch)
| Some switch, `Default ->
if not (OpamEnv.is_up_to_date_switch gt.root switch) then
(OpamConsole.msg "\n";
OpamConsole.warning
"The environment is not in sync with the current switch.\n\
You should run: %s"
(OpamEnv.eval_string shell gt (Some switch)))
OpamEnv.(eval_string shell Root gt switch))
| _ -> ()

let clear_switch ?(keep_debug=false) gt switch =
Expand Down
86 changes: 45 additions & 41 deletions src/state/opamEnv.ml
Original file line number Diff line number Diff line change
Expand Up @@ -323,43 +323,54 @@ let is_up_to_date st =
is_up_to_date_raw
(updates ~set_opamroot:false ~set_opamswitch:false ~force_path:false st)

let eval_string shell gt ?(set_opamswitch=false) switch =
let root =
let opamroot_cur = OpamFilename.Dir.to_string gt.root in
let opamroot_env =
OpamStd.Option.Op.(
OpamStd.Env.getopt "OPAMROOT" +!
OpamFilename.Dir.to_string OpamStateConfig.(default.root_dir)
) in
if opamroot_cur <> opamroot_env then
Printf.sprintf " --root=%s" opamroot_cur
else
"" in
let switch =
match switch with
| None -> ""
| Some 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) ++
(OpamFile.Config.switch gt.config >>| OpamSwitch.to_string)
)
in
if Some sw_cur <> sw_env then Printf.sprintf " --switch=%s" sw_cur
else ""
in
let eval_string_t shell cmd set_opamswitch root switch =
let root = if root = "" then "" else " --root=" ^ root in
let switch = if switch = "" then "" else " --switch=" ^ switch in
let setswitch = if set_opamswitch then " --set-switch" else "" in
match shell with
| `fish ->
Printf.sprintf "eval (opam env%s%s%s)" root switch setswitch
Printf.sprintf "eval (opam %s%s%s%s)" cmd root switch setswitch
| `csh ->
Printf.sprintf "eval `opam env%s%s%s`" root switch setswitch
Printf.sprintf "eval `opam %s%s%s%s`" cmd root switch setswitch
| _ ->
Printf.sprintf "eval $(opam env%s%s%s)" root switch setswitch

Printf.sprintf "eval $(opam %s%s%s%s)" cmd root switch setswitch

type _ eval_string = Root : ('a global_state -> switch -> string) eval_string
| Manpage : (string -> string) eval_string
| ManSwitch : (string -> string) eval_string

let eval_string : type s . shell -> ?set_opamswitch:bool -> s eval_string -> s = fun shell ?(set_opamswitch=false) ->
function
| Root ->
fun gt sw ->
let root =
let opamroot_cur = OpamFilename.Dir.to_string gt.root in
let opamroot_env =
OpamStd.Option.Op.(
OpamStd.Env.getopt "OPAMROOT" +!
OpamFilename.Dir.to_string OpamStateConfig.(default.root_dir)
) in
if opamroot_cur <> opamroot_env then opamroot_cur
else ""
in
let switch =
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) ++
(OpamFile.Config.switch gt.config >>| OpamSwitch.to_string)
)
in
if Some sw_cur <> sw_env then sw_cur
else ""
in
eval_string_t shell "env" set_opamswitch root switch
| Manpage ->
fun cmd -> eval_string_t shell cmd set_opamswitch "" ""
| ManSwitch ->
fun switch -> eval_string_t shell "env" set_opamswitch "" switch


(* -- Shell and init scripts handling -- *)
Expand Down Expand Up @@ -620,8 +631,7 @@ let check_and_print_env_warning shell st =
not (is_up_to_date st) then
OpamConsole.formatted_msg
"# Run %s to update the current shell environment\n"
(OpamConsole.colorise `bold (eval_string shell st.switch_global
(Some st.switch)))
(OpamConsole.colorise `bold (eval_string shell Root st.switch_global st.switch))

let setup_interactive root ~dot_profile shell =
let update dot_profile =
Expand All @@ -633,12 +643,6 @@ let setup_interactive root ~dot_profile shell =
OpamConsole.msg "\n";

OpamConsole.header_msg "Required setup - please read";
let fake_gt =
{global_lock = OpamSystem.lock_none;
root;
config = OpamFile.Config.empty;
global_variables = OpamVariable.Map.empty}
in
OpamConsole.msg
"\n\
\ In normal operation, opam only alters files within ~/.opam.\n\
Expand All @@ -658,7 +662,7 @@ let setup_interactive root ~dot_profile shell =
(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_string shell fake_gt None);
(OpamConsole.colorise `bold @@ eval_string shell Manpage "env");
match
OpamConsole.read
"Do you want opam to modify %s ? [N/y/f]\n\
Expand Down
6 changes: 5 additions & 1 deletion src/state/opamEnv.mli
Original file line number Diff line number Diff line change
Expand Up @@ -57,10 +57,14 @@ 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

type _ eval_string = Root : ('a global_state -> switch -> string) eval_string
| Manpage : (string -> string) eval_string
| ManSwitch : (string -> string) eval_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:
shell -> 'a global_state -> ?set_opamswitch:bool -> switch option -> string
shell -> ?set_opamswitch:bool -> 'a eval_string -> 'a

(** Returns the updated contents of the PATH variable for the given opam root
and switch (set [force_path] to ensure the opam path is leading) *)
Expand Down
2 changes: 1 addition & 1 deletion src/state/opamSwitchAction.ml
Original file line number Diff line number Diff line change
Expand Up @@ -128,7 +128,7 @@ let set_current_switch shell lock gt ?rt switch =
"Can not set external switch '%s' globally. To set it in the current \
shell use:\n %s"
(OpamSwitch.to_string switch)
(OpamEnv.eval_string shell gt ~set_opamswitch:true (Some switch));
OpamEnv.(eval_string shell ~set_opamswitch:true Root gt switch);
let config = OpamFile.Config.with_switch switch gt.config in
let gt = { gt with config } in
OpamGlobalState.write gt;
Expand Down

0 comments on commit b4b3fca

Please sign in to comment.