Skip to content

Commit

Permalink
Refactor eval_string further into shell_eval_invocation and opam_env_…
Browse files Browse the repository at this point in the history
…invocation
  • Loading branch information
freevoid committed Nov 13, 2020
1 parent ee14631 commit 8340e6e
Showing 1 changed file with 28 additions and 16 deletions.
44 changes: 28 additions & 16 deletions src/state/opamEnv.ml
Original file line number Diff line number Diff line change
Expand Up @@ -334,17 +334,31 @@ let is_up_to_date ?skip st =
is_up_to_date_raw ?skip
(updates ~set_opamroot:false ~set_opamswitch:false ~force_path:false st)

(** The "simple" version of [eval_string] in the sense that it doesn't support
figuring out `opam env` arguments and requires passing any extra arguments
via [suffix]. *)
let eval_string_simple ?(suffix="") shell =
(** Returns shell-appropriate statement to evaluate [cmd]. *)
let shell_eval_invocation shell cmd =
match shell with
| SH_fish ->
Printf.sprintf "eval (opam env%s)" suffix
Printf.sprintf "eval (%s)" cmd
| SH_csh ->
Printf.sprintf "eval `opam env%s`" suffix
Printf.sprintf "eval `%s`" cmd
| _ ->
Printf.sprintf "eval $(opam env%s)" suffix
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 =
match root with
| None -> ""
| Some r -> Printf.sprintf " --root=%s" r
in
let switch =
match switch with
| None -> ""
| Some s -> Printf.sprintf " --switch=%s" s
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 =
Expand All @@ -355,12 +369,13 @@ 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 -> ""
| None -> None
| Some sw ->
let sw_cur = OpamSwitch.to_string sw in
let sw_env =
Expand All @@ -371,13 +386,10 @@ let eval_string gt ?(set_opamswitch=false) switch =
(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
let setswitch = if set_opamswitch then " --set-switch" else "" in
let shell = OpamStd.Sys.guess_shell_compat () in
let suffix = root ^ switch ^ setswitch in
eval_string_simple ~suffix shell
shell_eval_invocation shell (opam_env_invocation ?root ?switch ~set_opamswitch ())


(* -- Shell and init scripts handling -- *)
Expand Down Expand Up @@ -706,7 +718,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_string_simple shell);
(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

0 comments on commit 8340e6e

Please sign in to comment.