Skip to content

Commit

Permalink
Eliminate the separate constructors for powershell
Browse files Browse the repository at this point in the history
Record whether the shell was detected as powershell or pwsh, although
this information isn't actually used at the moment.
  • Loading branch information
dra27 committed Jul 29, 2022
1 parent eb5be54 commit 092945f
Show file tree
Hide file tree
Showing 8 changed files with 39 additions and 36 deletions.
1 change: 1 addition & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -254,6 +254,7 @@ users)
* Make SHA computation faster by using ocaml-sha [#5042 @kit-ty-kate]
* Make OpamConfigCommand.global_allowed_fields fully lazy [#5162 @LasseBlaauwbroek]
* Overhaul Windows C stubs and update for Unicode [#5190 @dra27]
* Unify constructors for powershell hosts [#5203 @dra27]

## Internal: Windows
* Support MSYS2: treat MSYS2 and Cygwin as equivalent [#4813 @jonahbeckford]
Expand Down
4 changes: 2 additions & 2 deletions src/client/opamArg.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1039,9 +1039,9 @@ let shell_opt cli validity =
None,"csh",SH_csh;
None,"zsh",SH_zsh;
None,"fish",SH_fish;
Some cli2_2,"pwsh",SH_pwsh;
Some cli2_2,"pwsh",SH_pwsh Powershell_pwsh;
Some cli2_2,"cmd",SH_win_cmd;
Some cli2_2,"powershell",SH_win_powershell
Some cli2_2,"powershell",SH_pwsh 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
Expand Down
14 changes: 6 additions & 8 deletions src/client/opamCommands.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1216,6 +1216,7 @@ let config cli =
| Some s -> s
| None -> OpamStd.Sys.guess_shell_compat ()
in
let pwsh = match shell with SH_pwsh _ -> true | _ -> false in
match command, params with
| Some `env, [] ->
OpamGlobalState.with_ `Lock_none @@ fun gt ->
Expand All @@ -1225,8 +1226,7 @@ let config cli =
`Ok (OpamConfigCommand.env gt sw
~set_opamroot ~set_opamswitch
~csh:(shell=SH_csh) ~sexp ~fish:(shell=SH_fish)
~pwsh:(shell=SH_pwsh || shell=SH_win_powershell)
~cmd:(shell=SH_win_cmd)
~pwsh ~cmd:(shell=SH_win_cmd)
~inplace_path))
| Some `revert_env, [] ->
OpamGlobalState.with_ `Lock_none @@ fun gt ->
Expand All @@ -1236,8 +1236,7 @@ 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)
~pwsh ~cmd:(shell=SH_win_cmd)
(OpamEnv.add [] [])))
| Some `list, [] ->
OpamGlobalState.with_ `Lock_none @@ fun gt ->
Expand Down Expand Up @@ -1529,6 +1528,7 @@ let env cli =
| Some s -> s
| None -> OpamStd.Sys.guess_shell_compat ()
in
let pwsh = match shell with SH_pwsh _ -> true | _ -> false in
match revert with
| false ->
OpamGlobalState.with_ `Lock_none @@ fun gt ->
Expand All @@ -1538,14 +1538,12 @@ let env cli =
OpamConfigCommand.env gt sw
~set_opamroot ~set_opamswitch
~csh:(shell=SH_csh) ~sexp ~fish:(shell=SH_fish)
~pwsh:(shell=SH_pwsh || shell=SH_win_powershell)
~cmd:(shell=SH_win_cmd)
~pwsh ~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)
~pwsh ~cmd:(shell=SH_win_cmd)
(OpamEnv.add [] [])
in
let open Common_config_flags in
Expand Down
14 changes: 8 additions & 6 deletions src/core/opamStd.ml
Original file line number Diff line number Diff line change
Expand Up @@ -903,8 +903,9 @@ module OpamSys = struct
) in
fun () -> Lazy.force os

type shell = SH_sh | SH_bash | SH_zsh | SH_csh | SH_fish | SH_pwsh
| SH_win_cmd | SH_win_powershell
type powershell_host = Powershell_pwsh | Powershell
type shell = SH_sh | SH_bash | SH_zsh | SH_csh | SH_fish
| SH_pwsh of powershell_host | SH_win_cmd

let windows_default_shell = SH_win_cmd
let unix_default_shell = SH_sh
Expand All @@ -916,7 +917,7 @@ module OpamSys = struct
| "zsh" -> Some SH_zsh
| "bash" -> Some SH_bash
| "fish" -> Some SH_fish
| "pwsh" -> Some SH_pwsh
| "pwsh" -> Some (SH_pwsh Powershell_pwsh)
| "dash"
| "sh" -> Some SH_sh
| _ -> None
Expand Down Expand Up @@ -961,8 +962,9 @@ module OpamSys = struct

let windows_get_shell =
let categorize_process = function
| "powershell.exe" | "powershell_ise.exe" -> Some (Accept SH_win_powershell)
| "pwsh.exe" -> Some (Accept SH_pwsh)
| "powershell.exe" | "powershell_ise.exe" ->
Some (Accept (SH_pwsh Powershell))
| "pwsh.exe" -> Some (Accept (SH_pwsh Powershell_pwsh))
| "cmd.exe" -> Some (Accept SH_win_cmd)
| "env.exe" -> Some (Accept SH_sh)
| name ->
Expand Down Expand Up @@ -1064,7 +1066,7 @@ module OpamSys = struct
let cshrc = home ".cshrc" in
let tcshrc = home ".tcshrc" in
if Sys.file_exists cshrc then cshrc else tcshrc
| SH_pwsh | SH_win_powershell ->
| SH_pwsh _ ->
if Sys.win32 then win_my_powershell "Microsoft.Powershell_profile.ps1" else
List.fold_left Filename.concat (home ".config") ["powershell"; "Microsoft.Powershell_profile.ps1"]
| SH_sh -> home ".profile"
Expand Down
5 changes: 3 additions & 2 deletions src/core/opamStd.mli
Original file line number Diff line number Diff line change
Expand Up @@ -439,8 +439,9 @@ module Sys : sig
val executable_name : string -> string

(** The different families of shells we know about *)
type shell = SH_sh | SH_bash | SH_zsh | SH_csh | SH_fish | SH_pwsh
| SH_win_cmd | SH_win_powershell
type powershell_host = Powershell_pwsh | Powershell
type shell = SH_sh | SH_bash | SH_zsh | SH_csh | SH_fish
| SH_pwsh of powershell_host | SH_win_cmd

(** Guess the shell compat-mode *)
val guess_shell_compat: unit -> shell
Expand Down
5 changes: 3 additions & 2 deletions src/format/opamTypes.mli
Original file line number Diff line number Diff line change
Expand Up @@ -318,9 +318,10 @@ type universe = {
type pin_kind = [ `version | OpamUrl.backend ]

(** Shell compatibility modes *)
type powershell_host = OpamStd.Sys.powershell_host = Powershell_pwsh | Powershell
type shell = OpamStd.Sys.shell =
SH_sh | SH_bash | SH_zsh | SH_csh | SH_fish | SH_pwsh
| SH_win_cmd | SH_win_powershell
| SH_sh | SH_bash | SH_zsh | SH_csh | SH_fish | SH_pwsh of powershell_host
| SH_win_cmd

(** {2 Generic command-line definitions with filters} *)

Expand Down
4 changes: 2 additions & 2 deletions src/format/opamTypesBase.ml
Original file line number Diff line number Diff line change
Expand Up @@ -48,9 +48,9 @@ let string_of_shell = function
| SH_zsh -> "zsh"
| SH_sh -> "sh"
| SH_bash -> "bash"
| SH_pwsh -> "pwsh"
| SH_pwsh Powershell_pwsh -> "pwsh"
| SH_pwsh Powershell -> "powershell"
| SH_win_cmd -> "cmd"
| SH_win_powershell -> "powershell"

let file_null = ""
let pos_file filename =
Expand Down
28 changes: 14 additions & 14 deletions src/state/opamEnv.ml
Original file line number Diff line number Diff line change
Expand Up @@ -365,7 +365,7 @@ let is_up_to_date ?skip st =
(** Returns shell-appropriate statement to evaluate [cmd]. *)
let shell_eval_invocation shell cmd =
match shell with
| SH_win_powershell | SH_pwsh ->
| SH_pwsh _ ->
Printf.sprintf "(& %s) -split '\\r?\\n' | ForEach-Object { Invoke-Expression $_ }" cmd
| SH_fish ->
Printf.sprintf "eval (%s)" cmd
Expand Down Expand Up @@ -427,43 +427,43 @@ let shells_list = [ SH_sh; SH_zsh; SH_csh; SH_fish ]
let complete_file = function
| SH_sh | SH_bash -> Some "complete.sh"
| SH_zsh -> Some "complete.zsh"
| SH_csh | SH_fish | SH_pwsh | SH_win_cmd | SH_win_powershell -> None
| SH_csh | SH_fish | SH_pwsh _ | SH_win_cmd -> None

let env_hook_file = function
| SH_sh | SH_bash -> Some "env_hook.sh"
| SH_zsh -> Some "env_hook.zsh"
| SH_csh -> Some "env_hook.csh"
| SH_fish -> Some "env_hook.fish"
| SH_pwsh | SH_win_cmd | SH_win_powershell ->
| SH_pwsh _ | SH_win_cmd ->
(* N/A because not present in `shells_list` yet *) None

let variables_file = function
| SH_sh | SH_bash | SH_zsh -> "variables.sh"
| SH_csh -> "variables.csh"
| SH_fish -> "variables.fish"
| SH_pwsh | SH_win_cmd | SH_win_powershell ->
| SH_pwsh _ | SH_win_cmd ->
(* N/A because not present in `shells_list` yet *) "variables.sh"

let init_file = function
| SH_sh | SH_bash -> "init.sh"
| SH_zsh -> "init.zsh"
| SH_csh -> "init.csh"
| SH_fish -> "init.fish"
| SH_pwsh | SH_win_cmd | SH_win_powershell ->
| SH_pwsh _ | SH_win_cmd ->
(* N/A because not present in `shells_list` yet *) "init.sh"

let complete_script = function
| SH_sh | SH_bash -> Some OpamScript.complete
| SH_zsh -> Some OpamScript.complete_zsh
| SH_csh | SH_fish -> None
| SH_pwsh | SH_win_cmd | SH_win_powershell -> None
| SH_pwsh _ | SH_win_cmd -> None

let env_hook_script_base = function
| SH_sh | SH_bash -> Some OpamScript.env_hook
| SH_zsh -> Some OpamScript.env_hook_zsh
| SH_csh -> Some OpamScript.env_hook_csh
| SH_fish -> Some OpamScript.env_hook_fish
| SH_pwsh | SH_win_cmd | SH_win_powershell -> None
| SH_pwsh _ | SH_win_cmd -> None

let export_in_shell shell =
let make_comment comment_opt =
Expand Down Expand Up @@ -512,7 +512,7 @@ let export_in_shell shell =
| SH_zsh | SH_bash | SH_sh -> sh
| SH_fish -> fish
| SH_csh -> csh
| SH_pwsh | SH_win_powershell -> pwsh
| SH_pwsh _ -> pwsh
| SH_win_cmd -> win_cmd

let env_hook_script shell =
Expand All @@ -535,9 +535,9 @@ let source root shell f =
Printf.sprintf "[[ ! -r %s ]] || source %s > /dev/null 2> /dev/null\n"
fname fname
| SH_win_cmd ->
Printf.sprintf "if exist \"%s\" call \"%s\" >NUL 2>NUL\n" fname fname
| SH_pwsh | SH_win_powershell ->
Printf.sprintf ". \"%s\" > $null 2> $null\n" fname
Printf.sprintf "if exist \"%s\" ( \"%s\" >NUL 2>NUL )\n" fname fname
| SH_pwsh _ ->
Printf.sprintf "& \"%s\" > $null 2> $null\n" fname

let if_interactive_script shell t e =
let ielse else_opt = match else_opt with
Expand All @@ -562,9 +562,9 @@ let if_interactive_script shell t e =
| SH_fish ->
Printf.sprintf "if isatty\n %s%send\n" t @@ ielse e
| SH_win_cmd ->
Printf.sprintf "timeout 0 >nul 2>nul\nif not errorlevel 1 (\n%s%s)\n" t @@ ielse_cmd e
| SH_pwsh | SH_win_powershell ->
Printf.sprintf "if ([Environment]::UserInteractive -and -not [Console]::IsInputRedirected) {\n %s%s}\n" t @@ ielse_pwsh e
Printf.sprintf "echo %%cmdcmdline%% | find /i \"%%~0\" >nul\nif errorlevel 1 (\n%s%s)\n" t @@ ielse_cmd e
| SH_pwsh _ ->
Printf.sprintf "if ([Environment]::UserInteractive) {\n %s%s}\n" t @@ ielse_pwsh e

let init_script root shell =
let interactive =
Expand Down

0 comments on commit 092945f

Please sign in to comment.