Skip to content

Commit 394d364

Browse files
committed
Diff-reducing refactor in OpamClient
1 parent 945a14f commit 394d364

File tree

2 files changed

+162
-155
lines changed

2 files changed

+162
-155
lines changed

master_changes.md

+1
Original file line numberDiff line numberDiff line change
@@ -124,6 +124,7 @@ users)
124124
## Shell
125125

126126
## Internal
127+
* Noisy code refactor renaming `OpamClient.git_for_windows_check` to `OpamClient.git_for_windows` [#5997 @dra27]
127128

128129
## Internal: Windows
129130
* Set the console to use UTF-8 on Windows using SetConsoleCP and SetConsoleOutputCP [#5970 @kit-ty-kate]

src/client/opamClient.ml

+161-155
Original file line numberDiff line numberDiff line change
@@ -654,167 +654,168 @@ let is_git_for_windows git =
654654
end
655655
| _ -> false
656656

657-
let git_for_windows_check =
658-
if not Sys.win32 then fun ?git_location:_ () -> None else
659-
fun ?git_location () ->
660-
let header () = OpamConsole.header_msg "Git" in
661-
let contains_git p =
662-
OpamSystem.resolve_command ~env:[||] (Filename.concat p "git.exe")
663-
in
664-
let gits =
665-
OpamStd.Env.get "PATH"
666-
|> OpamStd.Sys.split_path_variable
667-
|> OpamStd.List.filter_map (fun p ->
668-
match contains_git p with
669-
| Some git ->
670-
Some (git, OpamSystem.bin_contains_bash p)
671-
| None -> None)
672-
in
673-
let abort_action = "install Git for Windows." in
674-
let gits, gfw_message, abort_action =
675-
if gits = [] then
676-
(* Git has not been found in PATH. See if it instead can be found in the
677-
initial environment. This deals with the possibility that the user
678-
has installed Git for Windows, but not restarted the terminal (so
679-
PATH has not been updated) *)
680-
let env = OpamStubs.get_initial_environment () in
681-
match OpamSystem.resolve_command ~env:(Array.of_list env) "git" with
682-
| Some git when is_git_for_windows git ->
683-
[], Some "It looks as though Git for Windows has been installed but \
684-
the shell needs to be restarted. You may wish to abort and \
685-
re-run opam init from a fresh session.",
686-
"restart your shell."
687-
| _ ->
688-
(* Git is neither in the current nor the initial PATH. There is one
689-
further possibility: the user may have installed Git for Windows
690-
but selected the option not to update the environment. The final
691-
hint given searches the Windows Registry for both a system-wide
692-
and user-specific installation and, if found, both displays a
693-
warning suggesting that the machine be reconfigured to enable them
694-
in PATH, but also gives the opportunity to use the git-location
695-
mechanism to select it for opam's internal use. *)
696-
let test_for_installation ((gits, gfw_message, abort_action) as acc) (hive, key) =
697-
let process root =
698-
let git_location = Filename.concat root "cmd" in
699-
let git = Filename.concat git_location "git.exe" in
700-
if OpamSystem.resolve_command ~env:[||] git <> None
701-
&& is_git_for_windows git then
702-
let gits =
703-
(git, OpamSystem.bin_contains_bash git_location)::gits
704-
and message, action =
705-
Some "It looks as though Git for Windows has been installed, \
706-
but configured not to put the git binary in your PATH. \
707-
You can either abort and reconfigure your environment \
708-
(or re-run the Git for Windows installer) to enable \
709-
this, or you can use the menu below to have opam use \
710-
this Git installation internally.",
711-
"reconfigure Git for Windows."
712-
in
713-
if message = None then
714-
gits, gfw_message, action
715-
else
716-
gits, message, abort_action
657+
let git_for_windows ?git_location () =
658+
let header () = OpamConsole.header_msg "Git" in
659+
let contains_git p =
660+
OpamSystem.resolve_command ~env:[||] (Filename.concat p "git.exe")
661+
in
662+
let gits =
663+
OpamStd.Env.get "PATH"
664+
|> OpamStd.Sys.split_path_variable
665+
|> OpamStd.List.filter_map (fun p ->
666+
match contains_git p with
667+
| Some git ->
668+
Some (git, OpamSystem.bin_contains_bash p)
669+
| None -> None)
670+
in
671+
let abort_action = "install Git for Windows." in
672+
let gits, gfw_message, abort_action =
673+
if gits = [] then
674+
(* Git has not been found in PATH. See if it instead can be found in the
675+
initial environment. This deals with the possibility that the user
676+
has installed Git for Windows, but not restarted the terminal (so
677+
PATH has not been updated) *)
678+
let env = OpamStubs.get_initial_environment () in
679+
match OpamSystem.resolve_command ~env:(Array.of_list env) "git" with
680+
| Some git when is_git_for_windows git ->
681+
[], Some "It looks as though Git for Windows has been installed but \
682+
the shell needs to be restarted. You may wish to abort and \
683+
re-run opam init from a fresh session.",
684+
"restart your shell."
685+
| _ ->
686+
(* Git is neither in the current nor the initial PATH. There is one
687+
further possibility: the user may have installed Git for Windows
688+
but selected the option not to update the environment. The final
689+
hint given searches the Windows Registry for both a system-wide
690+
and user-specific installation and, if found, both displays a
691+
warning suggesting that the machine be reconfigured to enable them
692+
in PATH, but also gives the opportunity to use the git-location
693+
mechanism to select it for opam's internal use. *)
694+
let test_for_installation ((gits, gfw_message, abort_action) as acc)
695+
(hive, key) =
696+
let process root =
697+
let git_location = Filename.concat root "cmd" in
698+
let git = Filename.concat git_location "git.exe" in
699+
if OpamSystem.resolve_command ~env:[||] git <> None
700+
&& is_git_for_windows git then
701+
let gits =
702+
(git, OpamSystem.bin_contains_bash git_location)::gits
703+
and message, action =
704+
Some "It looks as though Git for Windows has been installed, \
705+
but configured not to put the git binary in your PATH. \
706+
You can either abort and reconfigure your environment \
707+
(or re-run the Git for Windows installer) to enable \
708+
this, or you can use the menu below to have opam use \
709+
this Git installation internally.",
710+
"reconfigure Git for Windows."
711+
in
712+
if message = None then
713+
gits, gfw_message, action
717714
else
718-
acc
719-
in
720-
let key = Filename.concat key "GitForWindows" in
721-
OpamStubs.readRegistry hive key "InstallPath" OpamStubsTypes.REG_SZ
722-
|> OpamStd.Option.map_default process acc
715+
gits, message, abort_action
716+
else
717+
acc
723718
in
724-
let installations = [
725-
(* Machine-wide installation *)
726-
(OpamStubsTypes.HKEY_LOCAL_MACHINE, "SOFTWARE");
727-
(* User-specific installation *)
728-
(OpamStubsTypes.HKEY_CURRENT_USER, "Software");
729-
] in
730-
List.fold_left test_for_installation (gits, None, abort_action) installations
731-
else
732-
gits, None, abort_action
733-
in
734-
let get_git_location ?git_location () =
735-
let bin =
736-
match git_location with
737-
| Some _ -> git_location
738-
| None ->
739-
OpamConsole.read "Please enter the path containing git.exe (e.g. C:\\Program Files\\Git\\cmd):"
740-
in
741-
match bin with
742-
| None -> None
743-
| Some git_location ->
744-
match contains_git git_location, OpamSystem.bin_contains_bash git_location with
745-
| Some _, false ->
746-
OpamConsole.msg "Using Git from %s" git_location;
747-
Some git_location
748-
| Some _, true ->
749-
OpamConsole.error
750-
"A bash executable was found in %s, which will override \
751-
Cygwin's bash. Please check your binary path."
752-
git_location;
753-
None
754-
| None, _ ->
755-
OpamConsole.error "No Git executable found in %s." git_location;
756-
None
719+
let key = Filename.concat key "GitForWindows" in
720+
OpamStubs.readRegistry hive key "InstallPath" OpamStubsTypes.REG_SZ
721+
|> OpamStd.Option.map_default process acc
722+
in
723+
let installations = [
724+
(* Machine-wide installation *)
725+
(OpamStubsTypes.HKEY_LOCAL_MACHINE, "SOFTWARE");
726+
(* User-specific installation *)
727+
(OpamStubsTypes.HKEY_CURRENT_USER, "Software");
728+
] in
729+
List.fold_left test_for_installation (gits, None, abort_action) installations
730+
else
731+
gits, None, abort_action
732+
in
733+
let get_git_location ?git_location () =
734+
let bin =
735+
match git_location with
736+
| Some _ -> git_location
737+
| None ->
738+
OpamConsole.read "Please enter the path containing git.exe (e.g. C:\\Program Files\\Git\\cmd):"
757739
in
758-
let rec loop ?git_location () =
759-
match get_git_location ?git_location () with
760-
| Some _ as git_location -> git_location
761-
| None -> menu ()
762-
and menu () =
763-
let prompt () =
764-
let options =
765-
(`Default, "Use default Cygwin Git")
766-
:: (List.filter_map (fun (git, bash) ->
767-
if bash then None else
740+
match bin with
741+
| None -> None
742+
| Some git_location ->
743+
match contains_git git_location, OpamSystem.bin_contains_bash git_location with
744+
| Some _, false ->
745+
OpamConsole.msg "Using Git from %s" git_location;
746+
Some git_location
747+
| Some _, true ->
748+
OpamConsole.error
749+
"A bash executable was found in %s, which will override \
750+
Cygwin's bash. Please check your binary path."
751+
git_location;
752+
None
753+
| None, _ ->
754+
OpamConsole.error "No Git executable found in %s." git_location;
755+
None
756+
in
757+
let rec loop ?git_location () =
758+
match get_git_location ?git_location () with
759+
| Some _ as git_location -> git_location
760+
| None -> menu ()
761+
and menu () =
762+
let prompt () =
763+
let options =
764+
(`Default, "Use default Cygwin Git")
765+
:: (List.filter_map (fun (git, bash) ->
766+
if bash then
767+
None
768+
else
768769
let bin = Filename.dirname git in
769770
Some (`Location bin, "Use found git in "^bin))
770-
gits)
771-
@ [
772-
`Specify, "Enter the location of installed Git";
773-
`Abort, ("Abort initialisation to " ^ abort_action);
774-
]
775-
in
776-
OpamStd.Option.iter (OpamConsole.warning "%s\n") gfw_message;
777-
OpamConsole.menu "Which Git should opam use?"
778-
~default:`Default ~no:`Default ~options
771+
gits)
772+
@ [
773+
`Specify, "Enter the location of installed Git";
774+
`Abort, ("Abort initialisation to " ^ abort_action);
775+
]
779776
in
780-
match prompt () with
781-
| `Default -> None
782-
| `Specify -> loop ()
783-
| `Location git_location -> loop ~git_location ()
784-
| `Abort ->
785-
OpamConsole.note "Once your choosen Git installed, open a new PowerShell or Command Prompt window, and relaunch opam init.";
786-
OpamStd.Sys.exit_because `Aborted
777+
OpamStd.Option.iter (OpamConsole.warning "%s\n") gfw_message;
778+
OpamConsole.menu "Which Git should opam use?"
779+
~default:`Default ~no:`Default ~options
787780
in
788-
let git_location =
789-
match git_location with
790-
| Some (Right ()) -> None
791-
| Some (Left git_location) ->
792-
header ();
793-
get_git_location ~git_location:(OpamFilename.Dir.to_string git_location) ()
794-
| None ->
795-
let git_found =
796-
match OpamSystem.resolve_command "git" with
797-
| None -> false
798-
| Some git -> is_git_for_windows git
799-
in
800-
if not git_found && OpamStd.Sys.tty_out then
801-
(header ();
802-
OpamConsole.msg
803-
"Cygwin Git is functional but can have credentials issues for private repositories, \
804-
we recommend using:\n%s\n"
805-
(OpamStd.Format.itemize (fun s -> s)
806-
[ "Install via 'winget install Git.Git'";
807-
"Git for Windows can be downloaded and installed from https://gitforwindows.org" ]);
808-
menu ())
809-
else
810-
None
811-
in
812-
OpamStd.Option.iter (fun _ ->
813-
OpamConsole.msg
814-
"You can change that later with \
815-
'opam option \"git-location=C:\\A\\Path\\bin\"'")
816-
git_location;
817-
git_location
781+
match prompt () with
782+
| `Default -> None
783+
| `Specify -> loop ()
784+
| `Location git_location -> loop ~git_location ()
785+
| `Abort ->
786+
OpamConsole.note "Once your choosen Git installed, open a new PowerShell or Command Prompt window, and relaunch opam init.";
787+
OpamStd.Sys.exit_because `Aborted
788+
in
789+
let git_location =
790+
match git_location with
791+
| Some (Right ()) -> None
792+
| Some (Left git_location) ->
793+
header ();
794+
get_git_location ~git_location:(OpamFilename.Dir.to_string git_location) ()
795+
| None ->
796+
let git_found =
797+
match OpamSystem.resolve_command "git" with
798+
| None -> false
799+
| Some git -> is_git_for_windows git
800+
in
801+
if not git_found && OpamStd.Sys.tty_out then
802+
(header ();
803+
OpamConsole.msg
804+
"Cygwin Git is functional but can have credentials issues for private repositories, \
805+
we recommend using:\n%s\n"
806+
(OpamStd.Format.itemize (fun s -> s)
807+
[ "Install via 'winget install Git.Git'";
808+
"Git for Windows can be downloaded and installed from https://gitforwindows.org" ]);
809+
menu ())
810+
else
811+
None
812+
in
813+
OpamStd.Option.iter (fun _ ->
814+
OpamConsole.msg
815+
"You can change that later with \
816+
'opam option \"git-location=C:\\A\\Path\\bin\"'")
817+
git_location;
818+
git_location
818819

819820
let windows_checks ?cygwin_setup ?git_location config =
820821
if (not (Unix.has_symlink ())) then begin
@@ -851,7 +852,12 @@ let windows_checks ?cygwin_setup ?git_location config =
851852
(OpamFilename.Dir.to_string gl_cli) ;
852853
Some (Left gl_cli)
853854
in
854-
let git_location = git_for_windows_check ?git_location () in
855+
let git_location =
856+
if Sys.win32 then
857+
git_for_windows ?git_location ()
858+
else
859+
None
860+
in
855861
OpamCoreConfig.update ?git_location ();
856862
let config =
857863
match git_location with

0 commit comments

Comments
 (0)