Skip to content

Commit

Permalink
fixup MP commit: Add OpamSysInteract.Cygwin.bindir_for_root
Browse files Browse the repository at this point in the history
Factor out the computation of the expected bindir.
  • Loading branch information
dra27 committed Jun 8, 2024
1 parent 696d86b commit 0ddcf2b
Show file tree
Hide file tree
Showing 3 changed files with 16 additions and 9 deletions.
14 changes: 5 additions & 9 deletions src/client/opamClient.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1054,7 +1054,7 @@ let rec cygwin_menu ~bypass_checks header =
options, `Chosen (`Cygwin, `Internal), None
| Some (Ok (kind, root)) ->
let pacman =
OpamFilename.Op.(root / "usr" / "bin" // "pacman.exe")
OpamFilename.Op.(OpamSysInteract.Cygwin.bindir_for_root `Msys2 root // "pacman.exe")
|> OpamFilename.to_string
in
let root = OpamFilename.Dir.to_string root in
Expand Down Expand Up @@ -1219,11 +1219,12 @@ let string_of_git_location_cli = function
| Right () -> "git-location disabled via CLI"

let initialise_msys2 root =
let pacman = OpamFilename.Op.(root / "usr" / "bin" // "pacman.exe") in
let bindir = OpamSysInteract.Cygwin.bindir_for_root `Msys2 root in
let pacman = OpamFilename.Op.(bindir // "pacman.exe") in
let gnupg_dir = OpamFilename.Op.(root / "etc" / "pacman.d" / "gnupg") in
if OpamFilename.exists pacman && not (OpamFilename.exists_dir gnupg_dir) then
let cmd =
OpamFilename.Op.(root / "usr" / "bin" // "bash.exe")
OpamFilename.Op.(bindir // "bash.exe")
|> OpamFilename.to_string
in
let answer =
Expand Down Expand Up @@ -1460,12 +1461,7 @@ let determine_windows_configuration ?cygwin_setup ?git_location
in
apply cygcheck, None
| `Root root ->
let bindir =
if kind = `Msys2 then
root / "usr" / "bin"
else
root / "bin"
in
let bindir = OpamSysInteract.Cygwin.bindir_for_root kind root in
(* If the user has specified --no-git-location and Git for Windows was
in PATH and the given location occludes it, then this is our last
chance to warn about it. *)
Expand Down
6 changes: 6 additions & 0 deletions src/state/opamSysInteract.ml
Original file line number Diff line number Diff line change
Expand Up @@ -447,6 +447,12 @@ module Cygwin = struct
in
Result.bind cygbin identify

let bindir_for_root kind root =
let open OpamFilename.Op in
match kind with
| `Msys2 -> root / "usr" / "bin"
| `Cygwin -> root / "bin"

(* Set setup.exe in the good place, ie in .opam/.cygwin/ *)
let check_setup ~update =
let dst = cygsetup () in
Expand Down
5 changes: 5 additions & 0 deletions src/state/opamSysInteract.mli
Original file line number Diff line number Diff line change
Expand Up @@ -66,6 +66,11 @@ module Cygwin : sig
val analyse_install:
string -> ([ `Cygwin | `Msys2 ] * OpamFilename.Dir.t, string) result

(* [bindir_for_root kind root] returns the bin directory for the given
installation root and [kind], as returned by {!analyse_install}. *)
val bindir_for_root:
[ `Cygwin | `Msys2 ] -> OpamFilename.Dir.t -> OpamFilename.Dir.t

(* Returns true if Cygwin install is internal *)
val is_internal: OpamFile.Config.t -> bool

Expand Down

0 comments on commit 0ddcf2b

Please sign in to comment.