Skip to content

Commit

Permalink
Merge pull request #4816 from diskuv/feature-eval-on-pwsh
Browse files Browse the repository at this point in the history
Environments for PowerShell and Windows command line
  • Loading branch information
dra27 authored Jul 26, 2022
2 parents 5a54247 + 49a7450 commit 188ce75
Show file tree
Hide file tree
Showing 16 changed files with 282 additions and 56 deletions.
3 changes: 3 additions & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -343,6 +343,9 @@ users)

## Shell
* fish: fix deprecated redirection syntax `^` [#4736 @vzaliva]
* dash: recognize dash as a POSIX shell for opam env [#4816 @jonahbeckford]
* pwsh,powershell: use $env: for opam env [#4816 @jonahbeckford]
* command prompt: use SET for opam env [#4816 @jonahbeckford]

## Doc
* Standardise `macOS` use [#4782 @kit-ty-kate]
Expand Down
15 changes: 9 additions & 6 deletions src/client/opamArg.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1034,12 +1034,15 @@ let print_short_flag cli validity =

let shell_opt cli validity =
let enum = [
"bash",SH_bash;
"sh",SH_sh;
"csh",SH_csh;
"zsh",SH_zsh;
"fish",SH_fish;
] |> List.map (fun (s,v) -> cli_original, s, v)
None,"bash",SH_bash;
None,"sh",SH_sh;
None,"csh",SH_csh;
None,"zsh",SH_zsh;
None,"fish",SH_fish;
Some cli2_2,"pwsh",SH_pwsh;
Some cli2_2,"cmd",SH_win_cmd;
Some cli2_2,"powershell",SH_win_powershell
] |> List.map (fun (c,s,v) -> OpamStd.Option.map_default cli_from cli_original c, s, v)
in
mk_enum_opt ~cli validity ["shell"] "SHELL" enum
(Printf.sprintf
Expand Down
14 changes: 12 additions & 2 deletions src/client/opamCommands.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1224,7 +1224,10 @@ let config cli =
| Some sw ->
`Ok (OpamConfigCommand.env gt sw
~set_opamroot ~set_opamswitch
~csh:(shell=SH_csh) ~sexp ~fish:(shell=SH_fish) ~inplace_path))
~csh:(shell=SH_csh) ~sexp ~fish:(shell=SH_fish)
~pwsh:(shell=SH_pwsh || shell=SH_win_powershell)
~cmd:(shell=SH_win_cmd)
~inplace_path))
| Some `revert_env, [] ->
OpamGlobalState.with_ `Lock_none @@ fun gt ->
(match OpamStateConfig.get_switch_opt () with
Expand All @@ -1233,6 +1236,8 @@ let config cli =
`Ok (OpamConfigCommand.ensure_env gt sw;
OpamConfigCommand.print_eval_env
~csh:(shell=SH_csh) ~sexp ~fish:(shell=SH_fish)
~pwsh:(shell=SH_pwsh || shell=SH_win_powershell)
~cmd:(shell=SH_win_cmd)
(OpamEnv.add [] [])))
| Some `list, [] ->
OpamGlobalState.with_ `Lock_none @@ fun gt ->
Expand Down Expand Up @@ -1529,10 +1534,15 @@ let env cli =
| Some sw ->
OpamConfigCommand.env gt sw
~set_opamroot ~set_opamswitch
~csh:(shell=SH_csh) ~sexp ~fish:(shell=SH_fish) ~inplace_path);
~csh:(shell=SH_csh) ~sexp ~fish:(shell=SH_fish)
~pwsh:(shell=SH_pwsh || shell=SH_win_powershell)
~cmd:(shell=SH_win_cmd)
~inplace_path);
| true ->
OpamConfigCommand.print_eval_env
~csh:(shell=SH_csh) ~sexp ~fish:(shell=SH_fish)
~pwsh:(shell=SH_pwsh || shell=SH_win_powershell)
~cmd:(shell=SH_win_cmd)
(OpamEnv.add [] [])
in
let open Common_config_flags in
Expand Down
42 changes: 39 additions & 3 deletions src/client/opamConfigCommand.ml
Original file line number Diff line number Diff line change
Expand Up @@ -93,6 +93,38 @@ let rec print_csh_env = function
k (OpamStd.Env.escape_single_quotes v'));
print_csh_env r

let rec print_pwsh_env = function
| [] -> ()
| (k, v, comment) :: r ->
if OpamConsole.verbose () then
OpamStd.Option.iter (OpamConsole.msg ": %s;\n") comment;
if not (List.exists (fun (k1, _, _) -> k = k1) r) || OpamConsole.verbose ()
then
OpamConsole.msg "$env:%s = '%s'\n"
k (OpamStd.Env.escape_powershell v);
print_pwsh_env r

let print_cmd_env env =
let rec aux = function
| [] -> ()
| (k, v, comment) :: r ->
if OpamConsole.verbose () then
OpamStd.Option.iter (OpamConsole.msg ": %s;\n") comment;
if not (List.exists (fun (k1, _, _) -> k = k1) r) || OpamConsole.verbose ()
then begin
let is_special = function
| '(' | ')' | '!' | '^' | '%' | '"' | '<' | '>' | '|' -> true
| _ -> false
in
if OpamCompat.String.(exists is_special v || exists is_special k) then
OpamConsole.msg "SET \"%s=%s\"\n" k v
else
OpamConsole.msg "SET %s=%s\n" k v
end;
aux r
in
aux env

let print_sexp_env env =
let rec aux = function
| [] -> ()
Expand Down Expand Up @@ -145,13 +177,17 @@ let rec print_fish_env env =
k (OpamStd.Env.escape_single_quotes ~using_backslashes:true v));
print_fish_env r

let print_eval_env ~csh ~sexp ~fish env =
let print_eval_env ~csh ~sexp ~fish ~pwsh ~cmd env =
if sexp then
print_sexp_env env
else if csh then
print_csh_env env
else if fish then
print_fish_env env
else if pwsh then
print_pwsh_env env
else if cmd then
print_cmd_env env
else
print_env env

Expand All @@ -175,7 +211,7 @@ let ensure_env_aux ?(set_opamroot=false) ?(set_opamswitch=false) ?(force_path=tr
let ensure_env gt switch = ignore (ensure_env_aux gt switch)

let env gt switch ?(set_opamroot=false) ?(set_opamswitch=false)
~csh ~sexp ~fish ~inplace_path =
~csh ~sexp ~fish ~pwsh ~cmd ~inplace_path =
log "config-env";
let opamroot_not_current =
let current = gt.root in
Expand Down Expand Up @@ -220,7 +256,7 @@ let env gt switch ?(set_opamroot=false) ?(set_opamswitch=false)
~set_opamroot ~set_opamswitch ~force_path
gt.root switch
in
print_eval_env ~csh ~sexp ~fish env
print_eval_env ~csh ~sexp ~fish ~pwsh ~cmd env
[@@ocaml.warning "-16"]

let subst gt fs =
Expand Down
6 changes: 3 additions & 3 deletions src/client/opamConfigCommand.mli
Original file line number Diff line number Diff line change
Expand Up @@ -23,16 +23,16 @@ open OpamStateTypes
val env:
'a global_state -> switch ->
?set_opamroot:bool -> ?set_opamswitch:bool ->
csh:bool -> sexp:bool -> fish:bool -> inplace_path:bool ->
unit
csh:bool -> sexp:bool -> fish:bool -> pwsh:bool -> cmd:bool ->
inplace_path:bool -> unit

(** Ensures that the environment file exists in the given switch, regenerating
it, if necessary. *)
val ensure_env: 'a global_state -> switch -> unit

(** Like [env] but allows one to specify the precise env to print rather than
compute it from a switch state *)
val print_eval_env: csh:bool -> sexp:bool -> fish:bool -> env -> unit
val print_eval_env: csh:bool -> sexp:bool -> fish:bool -> pwsh:bool -> cmd:bool -> env -> unit

(** Display the content of all available packages variables *)
val list: 'a switch_state -> name list -> unit
Expand Down
17 changes: 16 additions & 1 deletion src/core/opamCompat.ml
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,22 @@
(* *)
(**************************************************************************)

module String = String
module String =
#if OCAML_VERSION >= (4, 13, 0)
String
#else
struct
include String

let exists p s =
let n = length s in
let rec loop i =
if i = n then false
else if p (unsafe_get s i) then true
else loop (succ i) in
loop 0
end
#endif

module Char = Char

Expand Down
12 changes: 11 additions & 1 deletion src/core/opamCompat.mli
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,17 @@
(* *)
(**************************************************************************)

module String = String
module String
#if OCAML_VERSION >= (4, 13, 0)
= String
#else
: sig
include module type of struct include String end

val exists: (char -> bool) -> string -> bool
end
#endif


module Char = Char

Expand Down
Loading

0 comments on commit 188ce75

Please sign in to comment.