Skip to content

Commit

Permalink
Expand Cygwin.check_install to analyse_install
Browse files Browse the repository at this point in the history
Includes more checks and also returns the kind of installation which was
found.
  • Loading branch information
dra27 committed Jun 6, 2024
1 parent 02e31b9 commit 8a231f9
Show file tree
Hide file tree
Showing 3 changed files with 111 additions and 67 deletions.
18 changes: 8 additions & 10 deletions src/client/opamClient.ml
Original file line number Diff line number Diff line change
Expand Up @@ -999,9 +999,8 @@ let windows_checks ?cygwin_setup ?git_location config =
in
(* Check for default cygwin installation path *)
let default =
match OpamSysInteract.Cygwin.(check_install
~variant:true default_cygroot) with
| Ok cygcheck ->
match OpamSysInteract.Cygwin.(analyse_install default_cygroot) with
| Ok (_, cygcheck) ->
let prompt_cygroot () =
let options = [
`manual,
Expand Down Expand Up @@ -1032,10 +1031,10 @@ let windows_checks ?cygwin_setup ?git_location config =
| None -> None
| Some entry ->
let cygcheck =
OpamSysInteract.Cygwin.check_install ~variant:true entry
OpamSysInteract.Cygwin.analyse_install entry
in
match cygcheck with
| Ok cygcheck -> Some cygcheck
| Ok (_, cygcheck) -> Some cygcheck
| Error msg -> OpamConsole.error "%s" msg; None
in
(* And finally ask for setup.exe *)
Expand Down Expand Up @@ -1109,9 +1108,8 @@ let windows_checks ?cygwin_setup ?git_location config =
| `default_location -> OpamSysInteract.Cygwin.default_cygroot
| `location dir -> OpamFilename.Dir.to_string dir
in
(match OpamSysInteract.Cygwin.check_install ~variant:true
cygroot with
| Ok cygcheck -> cygcheck
(match OpamSysInteract.Cygwin.analyse_install cygroot with
| Ok (_, cygcheck) -> cygcheck
| Error msg ->
OpamConsole.error_and_exit `Not_found
"Error while checking %sCygwin install (%s): %s"
Expand All @@ -1127,9 +1125,9 @@ let windows_checks ?cygwin_setup ?git_location config =
(* We check that current install is good *)
(match OpamSysInteract.Cygwin.cygroot_opt config with
| Some cygroot ->
(match OpamSysInteract.Cygwin.check_install ~variant:true
(match OpamSysInteract.Cygwin.analyse_install
(OpamFilename.Dir.to_string cygroot) with
| Ok cygcheck ->
| Ok (_, cygcheck) ->
OpamSysInteract.Cygwin.check_setup None;
success cygcheck
| Error err -> OpamConsole.error "%s" err; get_cygwin None)
Expand Down
137 changes: 87 additions & 50 deletions src/state/opamSysInteract.ml
Original file line number Diff line number Diff line change
Expand Up @@ -8,8 +8,6 @@
(* *)
(**************************************************************************)

open OpamTypes

let log fmt = OpamConsole.log "XSYS" fmt

(* Run commands *)
Expand Down Expand Up @@ -232,10 +230,15 @@ module Cygwin = struct
let cygroot_opt config =
cygbin_opt config
>>| OpamFilename.dirname_dir
let get_opt = function
let cygroot config =
match cygroot_opt config with
| Some c -> c
| None -> failwith "Cygwin install not found"
let cygroot config = get_opt (cygroot_opt config)
| None ->
match OpamSystem.resolve_command "cygcheck.exe" with
| Some cygcheck ->
OpamFilename.dirname_dir (OpamFilename.Dir.of_string (Filename.dirname cygcheck))
| None ->
failwith "Cygwin install not found"

let internal_cygwin =
let internal =
Expand Down Expand Up @@ -375,53 +378,87 @@ module Cygwin = struct

let default_cygroot = "C:\\cygwin64"

let check_install ~variant path =
let is_cygwin =
if variant then OpamStd.Sys.is_cygwin_variant_cygcheck
else OpamStd.Sys.is_cygwin_cygcheck
in
if not (Sys.file_exists path) then
Error (Printf.sprintf "%s not found!" path)
else if Filename.basename path = "cygcheck.exe" then
(* We have cygcheck.exe path *)
let cygbin = Some (Filename.dirname path) in
if is_cygwin ~cygbin then
Ok (OpamFilename.of_string path)
else
Error
(Printf.sprintf
"%s found, but it is not from a Cygwin installation"
path)
else if not (Sys.is_directory path) then
Error (Printf.sprintf "%s is not a directory" path)
else
(* We have cygroot alike path *)
let bin = Filename.concat path "bin" in
let usr_bin = Filename.concat (Filename.concat path "usr") "bin" in
let check cygbin =
if Sys.file_exists cygbin then
if is_cygwin ~cygbin:(Some cygbin) then
Some (Left (OpamFilename.of_string
(Filename.concat cygbin "cygcheck.exe")))
else
Some (Right cygbin)
let analysis_cache = Hashtbl.create 17

let analyse_install path =
let cygbin =
if not (Sys.file_exists path) then
Error (path ^ " not found!")
else if Filename.remove_extension (Filename.basename path) = "cygcheck" then
(* path refers to cygcheck directly *)
Ok (Filename.dirname path)
else if not (Sys.is_directory path) then
Error (Printf.sprintf "%s neither a directory nor cygcheck.exe" path)
else
None
(* path is a directory - search path, path\bin and path\usr\bin *)
let contains_cygcheck dir =
Sys.file_exists (Filename.concat dir "cygcheck.exe")
in
let tests = [
path; (* e.g. C:\cygwin64\bin / C:\msys64\usr\bin *)
Filename.concat path "bin"; (* e.g. C:\cygwin64 *)
Filename.concat (Filename.concat path "usr") "bin" (* e.g. C:\msys64 *)
] in
match List.filter contains_cygcheck tests with
| [] ->
Error (Printf.sprintf
"cygcheck.exe not found in %s, or subdirectories bin and usr\\bin"
path)
| _::_::_ ->
Error (Printf.sprintf
"cygcheck.exe found in multiple places in %s which suggests it is \
not a Cygwin/MSYS2 installation" path)
| [path] ->
Ok path
in
let identify dir =
try Hashtbl.find analysis_cache dir
with Not_found ->
let result =
let cygpath = Filename.concat dir "cygpath.exe" in
if not (Sys.file_exists cygpath) then
Error (Printf.sprintf
"cygcheck.exe found in %s, but cygpath.exe was not" dir)
else
match OpamStd.Sys.get_windows_executable_variant ~search_in_first:dir cygpath with
| `Native | `Tainted _ ->
Error (Printf.sprintf
"cygcheck.exe found in %s; but it does not appear to be part of a \
Cygwin or MSYS2 installation" dir)
| (`Msys2 | `Cygwin) as kind ->
(* Check that pacman.exe is present with MSYS2: it is typically
not present with a Git-for-Windows Git Bash session, and as
these are basically unusable (they don't have all the required
tools, and we have no package manager with which to add them),
it's better to exclude them). *)
if kind = `Msys2
&& not (Sys.file_exists (Filename.concat dir "pacman.exe")) then
Error (Printf.sprintf
"cygcheck.exe found in %s, which appears to be from an MSYS2 \
installation, but pacman.exe was not" dir)
else
let r =
OpamProcess.run
(OpamProcess.command ~name:(OpamSystem.temp_file "command")
~allow_stdin:false cygpath ["-w"; "--"; "/"])
in
OpamProcess.cleanup ~force:true r;
if OpamProcess.is_success r then
match r.OpamProcess.r_stdout with
| [] ->
Error ("Unexpected error translating \"/\" with " ^ cygpath)
| _::_ ->
let cygcheck =
OpamFilename.of_string (Filename.concat dir "cygpath.exe")
in
Ok (kind, cygcheck)
else
Error ("Could not determine the root for " ^ cygpath)
in
Hashtbl.add analysis_cache dir result;
result
in
(* We need to keep that order, to have a better error message *)
match check bin, check usr_bin with
| Some (Left cygcheck), _ | _, Some (Left cygcheck) ->
Ok cygcheck
| Some (Right cygbin), _ | _, Some (Right cygbin) ->
Error
(Printf.sprintf
"%s found, but it does not appear to be a Cygwin installation"
cygbin)
| _, None ->
Error
(Printf.sprintf
"cygcheck.exe not found in %s subdirectories bin or usr\bin"
path)
Result.bind cygbin identify

(* Set setup.exe in the good place, ie in .opam/.cygwin/ *)
let check_setup setup =
Expand Down
23 changes: 16 additions & 7 deletions src/state/opamSysInteract.mli
Original file line number Diff line number Diff line change
Expand Up @@ -49,13 +49,22 @@ module Cygwin : sig
(* Install an internal Cygwin install, in <root>/.cygwin *)
val install: OpamSysPkg.t list -> OpamFilename.t

(* [check_install ~variant path] checks a Cygwin install at [path]. It checks
that 'path\cygcheck.exe', 'path\bin\cygcheck.exe', or
'path\usr\bin\cygcheck.exe' exists.
If [~variant] is false, checks that it is strictly a Cygwin install,
otherwise a Cygwin-like install as MSYS2. *)
val check_install:
variant:bool -> string -> (OpamFilename.t, string) result
(* [analyse_install path] searches for and identifies Cygwin/MSYS2
installations. [path] may be able the location of cygcheck.exe itself
(with or without the .exe) or just a directory. If [path] is just a
directory, then the function searches for 'path\cygcheck.exe',
'path\bin\cygcheck.exe', or 'path\usr\bin\cygcheck.exe'. If exactly one
is found, and cygpath.exe is found with it, then cygpath is used both to
identify whether the installation is Cygwin or MSYS2 and to translate the
root directory [/] to its Windows path (i.e. to get the canonical root
directory of the installation). MSYS2 is additionally required to have
pacman.exe in the same directory as cygcheck.exe and cygpath.exe.
On success, the result is the kind of installation (Cygwin/MSYS2) along
with the full path to cygcheck.exe, otherwise a description of the problem
encountered is returned. *)
val analyse_install:
string -> ([ `Cygwin | `Msys2 ] * OpamFilename.t, string) result

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

0 comments on commit 8a231f9

Please sign in to comment.