Skip to content

Commit

Permalink
Merge pull request #4844 from jonahbeckford/feature-win32-env-cygpath
Browse files Browse the repository at this point in the history
Cygpath the PATH from opam env
  • Loading branch information
kit-ty-kate authored Jul 23, 2022
2 parents d4a2984 + a1a0a64 commit 6875b92
Show file tree
Hide file tree
Showing 4 changed files with 41 additions and 5 deletions.
1 change: 1 addition & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -261,6 +261,7 @@ users)
* [BUG] Catch `EACCES` in lock function [#4948 @oandrieu - fix #4944]
* Permissions: chmod+unlink before copy [#4827 @jonahbeckford @dra27]
* Support MSYS2: two-phase rsync on MSYS2 to allow MSYS2's behavior of copying rather than symlinking [#4817 @jonahbeckford]
* Environment: translate PATH from Windows to Unix during opam env. [#4844 @jonahbeckford]

## Test
* Update crowbar with compare functions [#4918 @rjbou]
Expand Down
17 changes: 12 additions & 5 deletions src/client/opamConfigCommand.ml
Original file line number Diff line number Diff line change
Expand Up @@ -65,15 +65,20 @@ let list t ns =
OpamStd.Format.align_table |>
OpamConsole.print_table stdout ~sep:" "

let possibly_unix_path_env_value k v =
if k = "PATH" then (Lazy.force OpamSystem.get_cygpath_path_transform) v
else v

let rec print_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
then (
let v' = possibly_unix_path_env_value k v in
OpamConsole.msg "%s='%s'; export %s;\n"
k (OpamStd.Env.escape_single_quotes v) k;
k (OpamStd.Env.escape_single_quotes v') k);
print_env r

let rec print_csh_env = function
Expand All @@ -82,9 +87,10 @@ let rec print_csh_env = function
if OpamConsole.verbose () then
OpamStd.Option.iter (OpamConsole.msg ": %s;\n") comment;
if not (List.exists (fun (k1, _, _) -> k = k1) r) || OpamConsole.verbose ()
then
then (
let v' = possibly_unix_path_env_value k v in
OpamConsole.msg "setenv %s '%s';\n"
k (OpamStd.Env.escape_single_quotes v);
k (OpamStd.Env.escape_single_quotes v'));
print_csh_env r

let print_sexp_env env =
Expand Down Expand Up @@ -130,7 +136,8 @@ let rec print_fish_env env =
(* This function assumes that `v` does not include any variable
* expansions and that the directory names are written in full. See the
* opamState.ml for details *)
set_arr_cmd k v
let v' = possibly_unix_path_env_value k v in
set_arr_cmd k v'
| "MANPATH" ->
manpath_cmd v
| _ ->
Expand Down
22 changes: 22 additions & 0 deletions src/core/opamSystem.ml
Original file line number Diff line number Diff line change
Expand Up @@ -485,6 +485,28 @@ let get_cygpath_function =
let f = Lazy.from_val (fun x -> x) in
fun ~command:_ -> f
let apply_cygpath_path_transform path =
let r =
OpamProcess.run
(OpamProcess.command ~name:(temp_file "command") ~verbose:false "cygpath" ["--path"; "--"; path])
in
OpamProcess.cleanup ~force:true r;
if OpamProcess.is_success r then
List.hd r.OpamProcess.r_stdout
else
OpamConsole.error_and_exit `Internal_error "Could not apply cygpath --path to %s" path
let get_cygpath_path_transform =
(* We are running in a functioning Cygwin or MSYS2 environment if and only
if `cygpath` is in the PATH. *)
if Sys.win32 then
lazy (
match resolve_command "cygpath" with
| Some _ -> apply_cygpath_path_transform
| None -> fun x -> x)
else
Lazy.from_val (fun x -> x)
let runs = ref []
let print_stats () =
match !runs with
Expand Down
6 changes: 6 additions & 0 deletions src/core/opamSystem.mli
Original file line number Diff line number Diff line change
Expand Up @@ -190,6 +190,12 @@ val resolve_command: ?env:string array -> ?dir:string -> string -> string option
the identity function otherwise. *)
val get_cygpath_function: command:string -> (string -> string) lazy_t

(** Returns a function which should be applied to a PATH environment variable
if in a functioning Cygwin or MSYS2 environment, translating the Windows or a
Unix PATH variable into a Unix PATH variable. Returns the identity function
otherwise. *)
val get_cygpath_path_transform: (string -> string) lazy_t

(** [command cmd] executes the command [cmd] in the correct OPAM
environment. *)
val command: ?verbose:bool -> ?env:string array -> ?name:string ->
Expand Down

0 comments on commit 6875b92

Please sign in to comment.