Skip to content

Commit 314500f

Browse files
authored
Merge pull request #5843 from rjbou/init-msys2
Opam 2.2 init with MSYS2
2 parents b5dba01 + 44c74ba commit 314500f

10 files changed

+182
-64
lines changed

master_changes.md

+8
Original file line numberDiff line numberDiff line change
@@ -23,6 +23,7 @@ users)
2323
* Disable ACL in Cygwin internal install to avoid permission mismatch errors [#5796 @kit-ty-kate - fix #5781]
2424
* Add `sys-pkg-manager-cmd` as an accepted field in opamrc files [#5847 @rjbou - fix #5844]
2525
* Fix `git-location` handling in init config file [#5848 @rjbou - fix #5845]
26+
* Fix MSYS2 support [#5843 @rjbou - fix #5683]
2627

2728
## Config report
2829

@@ -131,15 +132,22 @@ users)
131132

132133
# API updates
133134
## opam-client
135+
* `OpamClient.windows_checks`: On existing cygwin install, permit to detect msys2 and store `os-distribution=msys2` in `global-variables` config file field [#5843 @rjbou]
136+
* `OpamClient.windows_checks`: When updating config file for msys2, resolve `pacman` path and store it in `sys-pkg-manager-cmd` for msys2 [#5843 @rjbou]
137+
* `OpamArg.apply_global_options`: load MSYS2 Cygwin binary path too [#5843 @rjbou]
134138

135139
## opam-repository
136140

137141
## opam-state
138142
* `OpamEnv.env_expansion`: Fix detection of out-of-date environment variables, a filter predicate was inverted [#5837 @dra27]
143+
* `OpamSysInteract.Cygwin.check_install`: add `variant` argument to permit checking that it is an Cygwin-like install if it is set to true, keep checking that it is a strictly Cygwin install if false [#5843 @rjbou]
144+
* `OpamSysInteract.Cygwin.check_install`: look for `cygcheck.exe` in `usr/bin` also as MSYS2 doesn't have "bin" [#5843 @rjbou]
145+
* `OpamGlobalState.load_config`: load MSYS2 Cygwin binary path too at config file loading [#5843 @rjbou]
139146

140147
## opam-solver
141148

142149
## opam-format
143150
* `OpamFile.InitConfig`: add `sys-pkg-manager-cmd` field [#5847 @rjbou]
144151

145152
## opam-core
153+
* `OpamStd.Sys`: add `is_cygwin_variant_cygcheck` that returns true if in path `cygcheck` is from a Cygwin or MSYS2 installation [#5843 @rjbou]

src/client/opamArg.ml

+15
Original file line numberDiff line numberDiff line change
@@ -600,6 +600,21 @@ let apply_global_options cli o =
600600
| _, element::elements -> aux (Some element) elements
601601
in
602602
aux None elements
603+
| { pelem = Variable ({ pelem = "global-variables"; _},
604+
{pelem = List { pelem = elements; _}; _}); _} ->
605+
let rec aux last elements =
606+
match last, elements with
607+
| _, [] -> ()
608+
| Some { pelem = Ident "os-distribution"; _},
609+
{ pelem = String "msys2"; _}::_ ->
610+
let cygbin =
611+
OpamStd.Option.map Filename.dirname
612+
(OpamSystem.resolve_command "cygcheck")
613+
in
614+
OpamCoreConfig.update ?cygbin ()
615+
| _, element::elements -> aux (Some element) elements
616+
in
617+
aux None elements
603618
| { pelem = Variable ({ pelem = "git-location"; _},
604619
{pelem = String git_location; _}); _} ->
605620
OpamCoreConfig.update ~git_location ()

src/client/opamClient.ml

+82-35
Original file line numberDiff line numberDiff line change
@@ -775,18 +775,29 @@ let windows_checks ?cygwin_setup ?git_location config =
775775
| None -> config
776776
in
777777
(* Cygwin handling *)
778+
let is_cygwin cygcheck =
779+
OpamStd.Sys.is_cygwin_cygcheck
780+
~cygbin:(Some OpamFilename.(Dir.to_string (dirname cygcheck)))
781+
in
782+
let is_variant cygcheck =
783+
OpamStd.Sys.is_cygwin_variant_cygcheck
784+
~cygbin:(Some OpamFilename.(Dir.to_string (dirname cygcheck)))
785+
in
786+
let is_msys2 cygcheck = is_variant cygcheck && not (is_cygwin cygcheck) in
778787
let success cygcheck =
788+
let cygbin = OpamFilename.dirname cygcheck in
789+
let distrib = if is_cygwin cygcheck then "cygwin" else "msys2" in
779790
let config =
780791
let os_distribution = OpamVariable.of_string "os-distribution" in
781792
let update vars =
782793
OpamFile.Config.with_global_variables
783-
((os_distribution, S "cygwin", "Set by opam init")::vars)
794+
((os_distribution, S distrib, "Set by opam init")::vars)
784795
config
785796
in
786797
match OpamStd.List.pick (fun (v,_,_) ->
787798
OpamVariable.equal v os_distribution)
788799
vars with
789-
| Some (_, S "cygwin", _), _ -> config
800+
| Some (_, S d, _), _ when String.equal d distrib -> config
790801
| None, vars -> update vars
791802
| Some (_, vc, _), vars ->
792803
OpamConsole.warning
@@ -802,17 +813,41 @@ let windows_checks ?cygwin_setup ?git_location config =
802813
OpamStd.Sys.exit_because `Aborted
803814
in
804815
let config =
805-
OpamFile.Config.with_sys_pkg_manager_cmd
806-
(OpamStd.String.Map.add "cygwin" cygcheck
807-
(OpamFile.Config.sys_pkg_manager_cmd config))
808-
config
816+
if is_msys2 cygcheck then
817+
let env =
818+
OpamStd.Env.cyg_env ~cygbin:(OpamFilename.Dir.to_string cygbin)
819+
~git_location:None
820+
in
821+
match OpamSystem.resolve_command ~env "pacman.exe" with
822+
| Some pacman ->
823+
if OpamConsole.confirm
824+
"Found package manager pacman binary at %s.\n\
825+
Do you want to use it for depexts?"
826+
pacman then
827+
OpamFile.Config.with_sys_pkg_manager_cmd
828+
(OpamStd.String.Map.add distrib (OpamFilename.of_string pacman)
829+
(OpamFile.Config.sys_pkg_manager_cmd config))
830+
config
831+
else config
832+
| None -> config
833+
else
834+
OpamFile.Config.with_sys_pkg_manager_cmd
835+
(OpamStd.String.Map.add distrib cygcheck
836+
(OpamFile.Config.sys_pkg_manager_cmd config))
837+
config
809838
in
810839
OpamConsole.note "Configured with %s for depexts"
811-
(if OpamSysInteract.Cygwin.is_internal config then
812-
"internal Cygwin install"
840+
(if is_cygwin cygcheck then
841+
if OpamSysInteract.Cygwin.is_internal config then
842+
"internal Cygwin install"
843+
else
844+
(* cygcheck is in CYGWINROOT/bin *)
845+
Printf.sprintf "Cygwin at %s"
846+
OpamFilename.(Dir.to_string (dirname_dir cygbin))
813847
else
814-
Printf.sprintf "Cygwin at %s"
815-
OpamFilename.(Dir.to_string (dirname_dir (dirname cygcheck))));
848+
(* cygcheck is in MSYS2ROOT/usr/bin *)
849+
Printf.sprintf "MSYS2 at %s"
850+
OpamFilename.(Dir.to_string (dirname_dir (dirname_dir cygbin))));
816851
config
817852
in
818853
let install_cygwin_tools () =
@@ -826,12 +861,10 @@ let windows_checks ?cygwin_setup ?git_location config =
826861
OpamSysInteract.Cygwin.install ~packages
827862
in
828863
let header () = OpamConsole.header_msg "Unix support infrastructure" in
864+
829865
let get_cygwin = function
830-
| Some cygcheck
831-
when OpamFilename.exists cygcheck
832-
&& OpamStd.Sys.is_cygwin_cygcheck
833-
~cygbin:(Some OpamFilename.(Dir.to_string (dirname cygcheck))) ->
834-
success cygcheck
866+
| Some cygcheck when OpamFilename.exists cygcheck && is_variant cygcheck ->
867+
success cygcheck
835868
| Some _ | None ->
836869
let rec menu () =
837870
let enter_paths () =
@@ -862,7 +895,8 @@ let windows_checks ?cygwin_setup ?git_location config =
862895
in
863896
(* Check for default cygwin installation path *)
864897
let default =
865-
match OpamSysInteract.Cygwin.(check_install default_cygroot) with
898+
match OpamSysInteract.Cygwin.(check_install
899+
~variant:true default_cygroot) with
866900
| Ok cygcheck ->
867901
let prompt_cygroot () =
868902
let options = [
@@ -894,7 +928,7 @@ let windows_checks ?cygwin_setup ?git_location config =
894928
| None -> None
895929
| Some entry ->
896930
let cygcheck =
897-
OpamSysInteract.Cygwin.check_install entry
931+
OpamSysInteract.Cygwin.check_install ~variant:true entry
898932
in
899933
match cygcheck with
900934
| Ok cygcheck -> Some cygcheck
@@ -903,7 +937,8 @@ let windows_checks ?cygwin_setup ?git_location config =
903937
(* And finally ask for setup.exe *)
904938
match cygcheck with
905939
| Some cygcheck ->
906-
OpamSysInteract.Cygwin.check_setup (enter_setup ());
940+
if is_cygwin cygcheck then
941+
OpamSysInteract.Cygwin.check_setup (enter_setup ());
907942
Some (success cygcheck)
908943
| None -> None
909944
in
@@ -967,31 +1002,34 @@ let windows_checks ?cygwin_setup ?git_location config =
9671002
| `default_location -> OpamSysInteract.Cygwin.default_cygroot
9681003
| `location dir -> OpamFilename.Dir.to_string dir
9691004
in
970-
(match OpamSysInteract.Cygwin.check_install cygroot with
971-
| Ok cygcheck -> cygcheck
972-
| Error msg ->
973-
OpamConsole.error_and_exit `Not_found
974-
"Error while checking %sCygwin install (%s): %s"
975-
(match setup with
976-
| `default_location -> " default"
977-
| `location _ -> "")
978-
(OpamSysInteract.Cygwin.default_cygroot) msg)
1005+
(match OpamSysInteract.Cygwin.check_install ~variant:true
1006+
cygroot with
1007+
| Ok cygcheck -> cygcheck
1008+
| Error msg ->
1009+
OpamConsole.error_and_exit `Not_found
1010+
"Error while checking %sCygwin install (%s): %s"
1011+
(match setup with
1012+
| `default_location -> " default"
1013+
| `location _ -> "")
1014+
(OpamSysInteract.Cygwin.default_cygroot) msg)
9791015
in
980-
OpamSysInteract.Cygwin.check_setup None;
1016+
if is_cygwin cygcheck then
1017+
OpamSysInteract.Cygwin.check_setup None;
9811018
success cygcheck)
982-
| Some "cygwin" ->
1019+
| Some "cygwin" | Some "msys2" ->
9831020
(* We check that current install is good *)
9841021
(match OpamSysInteract.Cygwin.cygroot_opt config with
9851022
| Some cygroot ->
986-
(match OpamSysInteract.Cygwin.check_install
1023+
(match OpamSysInteract.Cygwin.check_install ~variant:true
9871024
(OpamFilename.Dir.to_string cygroot) with
9881025
| Ok cygcheck ->
9891026
OpamSysInteract.Cygwin.check_setup None;
9901027
success cygcheck
9911028
| Error err -> OpamConsole.error "%s" err; get_cygwin None)
9921029
| None ->
993-
(* Cygwin is detected from environment (path), we check the install
994-
in that case and stores it in config *)
1030+
(* A Cygwin install (Cygwin or MSYS2) is detected from environment
1031+
(path), we check the install in that case and stores it in
1032+
config *)
9951033
OpamSystem.resolve_command "cygcheck"
9961034
|> OpamStd.Option.map OpamFilename.of_string
9971035
|> get_cygwin
@@ -1000,9 +1038,18 @@ let windows_checks ?cygwin_setup ?git_location config =
10001038
else
10011039
config
10021040
in
1003-
let cygbin = OpamStd.Option.Op.(
1004-
OpamSysInteract.Cygwin.cygbin_opt config
1005-
>>| OpamFilename.Dir.to_string)
1041+
let cygbin =
1042+
match OpamSysInteract.Cygwin.cygbin_opt config with
1043+
| Some cygbin -> Some (OpamFilename.Dir.to_string cygbin)
1044+
| None ->
1045+
if List.exists (function
1046+
| (v, S "msys2", _) ->
1047+
String.equal (OpamVariable.to_string v) "os-distribution"
1048+
| _ -> false) (OpamFile.Config.global_variables config)
1049+
then
1050+
OpamStd.Option.map Filename.dirname
1051+
(OpamSystem.resolve_command "cygcheck")
1052+
else None
10061053
in
10071054
OpamCoreConfig.update ?cygbin ();
10081055
config

src/core/opamCoreConfig.ml

+1
Original file line numberDiff line numberDiff line change
@@ -63,6 +63,7 @@ type t = {
6363
errlog_length: int;
6464
merged_output: bool;
6565
precise_tracking: bool;
66+
(* Updated in OpamGlobalState.load_config and OpamArg.opam_init *)
6667
cygbin: string option;
6768
git_location: string option;
6869
set: bool;

src/core/opamCoreConfig.mli

+3
Original file line numberDiff line numberDiff line change
@@ -72,7 +72,10 @@ type t = private {
7272
(** If set, will take full md5 of all files when checking diffs (to track
7373
installations), rather than rely on just file size and mtime *)
7474
cygbin: string option;
75+
(** Windows specific: the path of binary directory (bin/) of currently used
76+
Cygwin install: internal or external Cygwin, or MSYS2. *)
7577
git_location: string option;
78+
(** Windows specific: the full path of the git binary to use on Windows. *)
7679
set : bool;
7780
(** Options have not yet been initialised (i.e. defaults are active) *)
7881
}

src/core/opamStd.ml

+14-8
Original file line numberDiff line numberDiff line change
@@ -1254,14 +1254,6 @@ module OpamSys = struct
12541254
else
12551255
fun ~cygbin:_ _ -> `Native
12561256

1257-
let is_cygwin_cygcheck ~cygbin =
1258-
match cygbin with
1259-
| Some cygbin ->
1260-
let cygpath = Filename.concat cygbin "cygpath.exe" in
1261-
Sys.file_exists cygpath
1262-
&& (get_windows_executable_variant ~cygbin:(Some cygbin) cygpath = `Cygwin)
1263-
| None -> false
1264-
12651257
let get_cygwin_variant ~cygbin cmd =
12661258
(* Treat MSYS2's variant of `cygwin1.dll` called `msys-2.0.dll` equivalently.
12671259
Confer https://www.msys2.org/wiki/How-does-MSYS2-differ-from-Cygwin/ *)
@@ -1274,6 +1266,20 @@ module OpamSys = struct
12741266
let is_cygwin_variant ~cygbin cmd =
12751267
get_cygwin_variant ~cygbin cmd = `Cygwin
12761268

1269+
let is_cygwin_cygcheck_t ~variant ~cygbin =
1270+
match cygbin with
1271+
| Some cygbin ->
1272+
let cygpath = Filename.concat cygbin "cygpath.exe" in
1273+
Sys.file_exists cygpath
1274+
&& (variant ~cygbin:(Some cygbin) cygpath = `Cygwin)
1275+
| None -> false
1276+
1277+
let is_cygwin_variant_cygcheck ~cygbin =
1278+
is_cygwin_cygcheck_t ~variant:get_cygwin_variant ~cygbin
1279+
1280+
let is_cygwin_cygcheck ~cygbin =
1281+
is_cygwin_cygcheck_t ~variant:get_windows_executable_variant ~cygbin
1282+
12771283
exception Exit of int
12781284
exception Exec of string * string array * string array
12791285

src/core/opamStd.mli

+5-1
Original file line numberDiff line numberDiff line change
@@ -545,10 +545,14 @@ module Sys : sig
545545
string -> [ `Native | `Cygwin | `Tainted of [ `Msys2 | `Cygwin] | `Msys2 ]
546546

547547
(** Determines if cygcheck in given cygwin binary directory comes from a
548-
Cygwin or MSYS2 installation. Determined by analysing the cygpath command
548+
Cygwin installation. Determined by analysing the cygpath command
549549
found with it. *)
550550
val is_cygwin_cygcheck : cygbin:string option -> bool
551551

552+
(** As [is_cygwin_cygcheck], but returns true if it is a Cygwin variant
553+
(Cygwin, Msys2). *)
554+
val is_cygwin_variant_cygcheck : cygbin:string option -> bool
555+
552556
(** For native Windows builds, returns [`Cygwin] if the command is a Cygwin-
553557
or Msys2- compiled executable, and [`CygLinked] if the command links to a
554558
library which is itself Cygwin/Msys2-compiled, or [`Native] otherwise.

src/state/opamGlobalState.ml

+16-4
Original file line numberDiff line numberDiff line change
@@ -38,10 +38,22 @@ let load_config lock_kind global_lock root =
3838
let config =
3939
OpamFormatUpgrade.as_necessary lock_kind global_lock root config
4040
in
41-
OpamStd.Option.iter
42-
(fun cygbin ->
43-
OpamCoreConfig.update ~cygbin:(OpamFilename.Dir.to_string cygbin) ())
44-
(OpamSysInteract.Cygwin.cygbin_opt (fst config));
41+
(* Update Cygwin variants cygbin *)
42+
let cygbin =
43+
let config = fst config in
44+
match OpamSysInteract.Cygwin.cygbin_opt config with
45+
| Some cygbin -> Some (OpamFilename.Dir.to_string cygbin)
46+
| None ->
47+
if List.exists (function
48+
| (v, S "msys2", _) ->
49+
String.equal (OpamVariable.to_string v) "os-distribution"
50+
| _ -> false) (OpamFile.Config.global_variables config)
51+
then
52+
OpamStd.Option.map Filename.dirname
53+
(OpamSystem.resolve_command "cygcheck")
54+
else None
55+
in
56+
OpamCoreConfig.update ?cygbin ();
4557
config
4658

4759
let inferred_from_system = "Inferred from system"

0 commit comments

Comments
 (0)