Skip to content

Commit

Permalink
Add CLI option to specify additional packages for internal Cygwin.
Browse files Browse the repository at this point in the history
  • Loading branch information
moyodiallo committed Apr 23, 2024
1 parent bd96d2a commit f21d65a
Show file tree
Hide file tree
Showing 3 changed files with 26 additions and 8 deletions.
3 changes: 2 additions & 1 deletion src/client/opamClient.ml
Original file line number Diff line number Diff line change
Expand Up @@ -975,7 +975,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 | `internal_with_pkgs _ | `default_location | `location _) | None)
as cygwin_setup ->
if OpamSysPoll.os env = Some "win32" then
match OpamSysPoll.os_distribution env with
Expand All @@ -996,6 +996,7 @@ let windows_checks ?cygwin_setup ?git_location config =
let cygcheck =
match setup with
| `internal -> install_cygwin_tools ()
| `internal_with_pkgs _ -> install_cygwin_tools ()
| (`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 | `internal_with_pkgs 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 | `internal_with_pkgs of OpamSysPkg.t list | `default_location | `location of dirname | `no ] ->
?git_location:(dirname, unit) either ->
OpamFile.Config.t -> shell -> unit

Expand Down
27 changes: 22 additions & 5 deletions src/client/opamCommands.ml
Original file line number Diff line number Diff line change
Expand Up @@ -308,7 +308,7 @@ let init cli =
mk_vflag ~cli `none [
cli_from ~experimental:true cli2_2,
`internal, ["cygwin-internal-install"],
"Let opam setup and manage an internal Cygwin install (recommended)";
"Let opam setup and manage an internal Cygwin install";
cli_from ~experimental:true cli2_2,
`default_location, ["cygwin-local-install"],
"Use preexistent Cygwin install";
Expand All @@ -319,6 +319,14 @@ let init cli =
else
Term.const `none
in
let cygwin_packages =
if Sys.win32 then
mk_opt ~cli (cli_from ~experimental:true cli2_2)
["cygwin-packages"] "CYGWIN_PACKAGES" "Specify Cygwin's packages to 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 +359,7 @@ 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 git_location no_git_location cygwin_packages
() =
apply_global_options cli global_options;
apply_build_options cli build_options;
Expand Down Expand Up @@ -408,8 +416,16 @@ let init cli =
OpamStd.Sys.guess_dot_profile shell >>| OpamFilename.of_string)
in
let cygwin_setup =
let cygwin_internal =
match cygwin_internal, cygwin_packages with
| `internal, Some pkgs -> `internal_with_pkgs (List.map OpamSysPkg.of_string pkgs)
| _, Some _ ->
OpamConsole.error_and_exit `Bad_arguments
"Option --cygwin-packages is only compatible with --cygwin-internal-install";
| _ as setup, None -> setup
in
match cygwin_internal, cygwin_location with
| `internal, Some _ ->
| (`internal | `internal_with_pkgs _) , Some _ ->
OpamConsole.error_and_exit `Bad_arguments
"Options --cygwin-internal-install and \
--cygwin-location are incompatible";
Expand All @@ -418,7 +434,7 @@ let init cli =
Some `no
| `none, None -> None
| (`default_location | `none), Some dir -> Some (`location dir)
| (`internal | `default_location | `no) as setup, None -> Some setup
| (`internal | `internal_with_pkgs _ | `default_location | `no) as setup, None -> Some setup
in
let git_location =
match git_location, no_git_location with
Expand Down Expand Up @@ -527,7 +543,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 $git_location $no_git_location
$cygwin_packages)

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

0 comments on commit f21d65a

Please sign in to comment.