Skip to content

Commit

Permalink
Merge pull request #5930 from moyodiallo/cygwin-packages-cli-option
Browse files Browse the repository at this point in the history
Add CLI option to specify additional packages for internal Cygwin.
  • Loading branch information
kit-ty-kate committed May 13, 2024
2 parents df4a390 + 8bc1214 commit 036e26f
Show file tree
Hide file tree
Showing 4 changed files with 49 additions and 20 deletions.
2 changes: 2 additions & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,7 @@ users)
## Plugins

## Init
* ◈ New option `opam init --cygwin-extra-packages=CYGWIN_PKGS --cygwin-internal-install`, to specify additional packages for internal Cygwin [#5930 @moyodiallo - fix #5834]

## Config report

Expand Down Expand Up @@ -124,6 +125,7 @@ users)

# API updates
## opam-client
* `OpamClient.init` and `OpamClient.reinit`: now can have additional cygwin packages to install [#5930 @moyodiallo]

## opam-repository

Expand Down
16 changes: 10 additions & 6 deletions src/client/opamClient.ml
Original file line number Diff line number Diff line change
Expand Up @@ -850,15 +850,19 @@ let windows_checks ?cygwin_setup ?git_location config =
OpamFilename.(Dir.to_string (dirname_dir (dirname_dir cygbin))));
config
in
let install_cygwin_tools () =
let packages =
let install_cygwin_tools packages =
let default_packages =
match OpamSystem.resolve_command "git" with
| None -> OpamInitDefaults.required_packages_for_cygwin
| Some _ ->
List.filter (fun c -> not OpamSysPkg.(equal (of_string "git") c))
OpamInitDefaults.required_packages_for_cygwin
in
OpamSysInteract.Cygwin.install ~packages
(* packages comes last so that the user can override any potential version
constraints in default_packages (although, with the current version of
setup, and with the list of default_packages in OpamInitDefaults, this at
present doesn't matter too much). *)
OpamSysInteract.Cygwin.install ~packages:(default_packages @ packages)
in
let header () = OpamConsole.header_msg "Unix support infrastructure" in

Expand Down Expand Up @@ -956,7 +960,7 @@ let windows_checks ?cygwin_setup ?git_location config =
match prompt () with
| `Abort -> OpamStd.Sys.exit_because `Aborted
| `Internal ->
let cygcheck = install_cygwin_tools () in
let cygcheck = install_cygwin_tools [] in
let config = success cygcheck in
config
| `Specify ->
Expand All @@ -975,7 +979,7 @@ let windows_checks ?cygwin_setup ?git_location config =
let config =
match cygwin_setup with
| Some `no -> config
| (Some (`internal | `default_location | `location _) | None)
| (Some (`internal _ | `default_location | `location _) | None)
as cygwin_setup ->
if OpamSysPoll.os env = Some "win32" then
match OpamSysPoll.os_distribution env with
Expand All @@ -995,7 +999,7 @@ let windows_checks ?cygwin_setup ?git_location config =
header ();
let cygcheck =
match setup with
| `internal -> install_cygwin_tools ()
| `internal pkgs -> install_cygwin_tools pkgs
| (`default_location | `location _ as setup) ->
let cygroot =
match setup with
Expand Down
4 changes: 2 additions & 2 deletions src/client/opamClient.mli
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ val init:
?env_hook:bool ->
?completion:bool ->
?check_sandbox:bool ->
?cygwin_setup: [ `internal | `default_location | `location of dirname | `no ] ->
?cygwin_setup: [ `internal of OpamSysPkg.t list | `default_location | `location of dirname | `no ] ->
?git_location:(dirname, unit) either ->
shell ->
rw global_state * unlocked repos_state * atom list
Expand All @@ -46,7 +46,7 @@ val reinit:
?init_config:OpamFile.InitConfig.t -> interactive:bool -> ?dot_profile:filename ->
?update_config:bool -> ?env_hook:bool -> ?completion:bool -> ?inplace:bool ->
?check_sandbox:bool -> ?bypass_checks:bool ->
?cygwin_setup: [ `internal | `default_location | `location of dirname | `no ] ->
?cygwin_setup: [ `internal of OpamSysPkg.t list | `default_location | `location of dirname | `no ] ->
?git_location:(dirname, unit) either ->
OpamFile.Config.t -> shell -> unit

Expand Down
47 changes: 35 additions & 12 deletions src/client/opamCommands.ml
Original file line number Diff line number Diff line change
Expand Up @@ -319,6 +319,16 @@ let init cli =
else
Term.const `none
in
let cygwin_extra_packages =
if Sys.win32 then
mk_opt ~cli (cli_from ~experimental:true cli2_2)
["cygwin-extra-packages"] "CYGWIN_PACKAGES"
"Specify additional packages to install \
with $(b,--cygwin-internal-install)"
Arg.(some (list string)) None
else
Term.const None
in
let cygwin_location =
if Sys.win32 then
mk_opt ~cli (cli_from ~experimental:true cli2_2)
Expand Down Expand Up @@ -351,7 +361,8 @@ let init cli =
interactive update_config completion env_hook no_sandboxing shell
dot_profile_o compiler no_compiler config_file no_config_file reinit
show_opamrc bypass_checks
cygwin_internal cygwin_location git_location no_git_location
cygwin_internal cygwin_location cygwin_extra_packages
git_location no_git_location
() =
apply_global_options cli global_options;
apply_build_options cli build_options;
Expand Down Expand Up @@ -408,17 +419,28 @@ let init cli =
OpamStd.Sys.guess_dot_profile shell >>| OpamFilename.of_string)
in
let cygwin_setup =
match cygwin_internal, cygwin_location with
| `internal, Some _ ->
let bad_arg arg1 arg2 =
OpamConsole.error_and_exit `Bad_arguments
"Options --cygwin-internal-install and \
--cygwin-location are incompatible";
| `no, Some _ ->
OpamConsole.note "Ignoring argument --cygwin-location";
Some `no
| `none, None -> None
| (`default_location | `none), Some dir -> Some (`location dir)
| (`internal | `default_location | `no) as setup, None -> Some setup
"Options --%s and --%s are incompatible"
arg1 arg2
in
match cygwin_internal, cygwin_location, cygwin_extra_packages with
| `internal, Some _, _ ->
bad_arg "cygwin-internal-install" "cygwin-location"
| `default_location, _, Some _ ->
bad_arg "cygwin-local-install" "cygwin-extra-packages"
| `no, Some _, _ ->
bad_arg "no-cygwin-setup" "cygwin-location"
| `no, _, Some _ ->
bad_arg "no-cygwin-setup" "cygwin-extra-packages"
| `none, Some _, Some _ ->
bad_arg "cygwin-location" "cygwin-extra-packages"
| (`internal | `none), None, pkgs ->
Some (`internal
(OpamStd.Option.default [] pkgs
|> List.map OpamSysPkg.of_string))
| (`default_location | `none), Some dir, None -> Some (`location dir)
| (`default_location | `no) as setup, None, None -> Some setup
in
let git_location =
match git_location, no_git_location with
Expand Down Expand Up @@ -527,7 +549,8 @@ let init cli =
$setup_completion $env_hook $no_sandboxing $shell_opt cli
cli_original $dot_profile_flag cli cli_original $compiler
$no_compiler $config_file $no_config_file $reinit $show_default_opamrc
$bypass_checks $cygwin_internal $cygwin_location $git_location $no_git_location)
$bypass_checks $cygwin_internal $cygwin_location $cygwin_extra_packages
$git_location $no_git_location)

(* LIST *)
let list_doc = "Display the list of available packages."
Expand Down

0 comments on commit 036e26f

Please sign in to comment.