Skip to content

Commit

Permalink
Expose OpamStd.Sys.resolve_in_path
Browse files Browse the repository at this point in the history
Exposes the portion of OpamStd.Sys.resolve_command which searches the
PATH environment for a given basename.
  • Loading branch information
dra27 committed Jun 6, 2024
1 parent 0e59caa commit f1b2b8d
Show file tree
Hide file tree
Showing 3 changed files with 40 additions and 23 deletions.
1 change: 1 addition & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -177,3 +177,4 @@ users)
* `OpamStubs.readRegistry`: on Windows, complements `OpamStubs.writeRegistry` [#5963 @dra27]
* `OpamStubs.get_initial_environment`: on Windows, returns the pristine environment for new shells [#5963 @dra27]
* `OpamStd.Sys.resolve_command`: extracted the logic from `OpamSystem.resolve_command`, without the default environment handling from OpamProcess. [#5991 @dra27]
* `OpamStd.Sys.resolve_in_path`: split the logic of `OpamStd.Sys.resolve_command` to allow searching for an arbitrary file in the search path [#5991 @dra27]
56 changes: 33 additions & 23 deletions src/core/opamStd.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1220,19 +1220,31 @@ module OpamSys = struct
in
aux 0

let is_external_cmd name =
let forward_to_back =
if Sys.win32 then
String.map (function '/' -> '\\' | c -> c)
else
fun x -> x
in
let name = forward_to_back name in
OpamString.contains_char name Filename.dir_sep.[0]

let resolve_in_path env name =
if not (Filename.is_relative name) || is_external_cmd name then
invalid_arg "OpamStd.Sys.resolve_in_path: bare command expected"
else
let path = split_path_variable (env_var env "PATH") in
List.filter_map (fun path ->
let candidate = Filename.concat path name in
match Sys.is_directory candidate with
| false -> Some candidate
| true | exception (Sys_error _) -> None)
path

(* OCaml 4.05.0 no longer follows the updated PATH to resolve commands. This
makes unqualified commands absolute as a workaround. *)
let resolve_command =
let is_external_cmd name =
let forward_to_back =
if Sys.win32 then
String.map (function '/' -> '\\' | c -> c)
else
fun x -> x
in
let name = forward_to_back name in
OpamString.contains_char name Filename.dir_sep.[0]
in
let check_perms =
if Sys.win32 then fun f ->
try (Unix.stat f).Unix.st_kind = Unix.S_REG
Expand Down Expand Up @@ -1277,24 +1289,16 @@ module OpamSys = struct
else `Cmd cmd
end else
(* bare command, lookup in PATH *)
(* Following the shell sematics for looking up PATH, programs with the
expected name but not the right permissions are skipped silently.
Therefore, only two outcomes are possible in that case, [`Cmd ..] or
[`Not_found]. *)
let path = split_path_variable (env_var env "PATH") in
let name =
if Sys.win32 && not (Filename.check_suffix name ".exe") then
name ^ ".exe"
else name
in
let possibles =
List.filter_map (fun path ->
let candidate = Filename.concat path name in
match Sys.is_directory candidate with
| false -> Some candidate
| true | exception (Sys_error _) -> None)
path
in
let possibles = resolve_in_path env name in
(* Following the shell sematics for looking up PATH, programs with the
expected name but not the right permissions are skipped silently.
Therefore, only two outcomes are possible in that case, [`Cmd ..] or
[`Not_found]. *)
match List.find check_perms possibles with
| cmdname -> `Cmd cmdname
| exception Not_found ->
Expand All @@ -1307,6 +1311,12 @@ module OpamSys = struct
let env = match env with None -> Env.raw_env () | Some e -> e in
resolve env ?dir name

let resolve_in_path ?env name =
let env = match env with None -> Env.raw_env () | Some e -> e in
match resolve_in_path env name with
| result::_ -> Some result
| [] -> None

let get_windows_executable_variant =
if Sys.win32 then
let results = Hashtbl.create 17 in
Expand Down
6 changes: 6 additions & 0 deletions src/core/opamStd.mli
Original file line number Diff line number Diff line change
Expand Up @@ -553,6 +553,12 @@ module Sys : sig
val resolve_command: ?env:string array -> ?dir:string -> string ->
[ `Cmd of string | `Denied | `Not_found ]

(** Search for an arbitrary file in PATH. Unlike {!resolve_command}, no
transformations take place on the name in Windows (i.e. .exe, etc. is
never appended) and no executable check takes place. The name passed
must be a basename (no directory component). *)
val resolve_in_path: ?env:string array -> string -> string option

(** For native Windows builds, returns [`Cygwin] if the command is a Cygwin-
compiled executable, [`Msys2] if the command is a MSYS2-compiled
executable, and [`Tainted of [ `Msys2 | `Cygwin ]] if the command links
Expand Down

0 comments on commit f1b2b8d

Please sign in to comment.