Skip to content

Commit

Permalink
Tweak OpamSysInteract.Cygwin.check_setup more
Browse files Browse the repository at this point in the history
The ability to copy setup-x86_64.exe is no longer needed - but restore
the previous functionality which only downloaded setup if it didn't
exist and use this when displaying a command to the user. In this mode,
we only download setup-x86_64.exe so that the command we give to the
user actually works.

If we're actually going to run setup-x86_64.exe, then we download the
latest version.
  • Loading branch information
dra27 committed Jun 10, 2024
1 parent affdbab commit c0cd8f4
Show file tree
Hide file tree
Showing 3 changed files with 17 additions and 22 deletions.
6 changes: 4 additions & 2 deletions src/client/opamSolution.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1189,8 +1189,10 @@ let install_sys_packages ~map_sysmap ~confirm env config sys_packages t =
| `Ignore -> bypass t
| `Quit -> give_up_msg (); OpamStd.Sys.exit_because `Aborted
and print_command sys_packages =
(* Ensure that setup-x86_64.exe exists, so that an invalid command is not
displayed to the user. *)
if OpamSysPoll.os_distribution env = Some "cygwin" then
OpamSysInteract.Cygwin.check_setup None;
OpamSysInteract.Cygwin.check_setup ~update:false;
let commands =
OpamSysInteract.install_packages_commands ~env config sys_packages
|> List.map (fun ((`AsAdmin c | `AsUser c), a) -> c::a)
Expand Down Expand Up @@ -1222,7 +1224,7 @@ let install_sys_packages ~map_sysmap ~confirm env config sys_packages t =
and auto_install t sys_packages =
try
if OpamSysPoll.os_distribution env = Some "cygwin" then
OpamSysInteract.Cygwin.check_setup None;
OpamSysInteract.Cygwin.check_setup ~update:true;
OpamSysInteract.install ~env config sys_packages; (* handles dry_run *)
map_sysmap (fun _ -> OpamSysPkg.Set.empty) t
with Failure msg ->
Expand Down
24 changes: 8 additions & 16 deletions src/state/opamSysInteract.ml
Original file line number Diff line number Diff line change
Expand Up @@ -454,22 +454,9 @@ module Cygwin = struct
| `Cygwin -> root / "bin"

(* Set setup.exe in the good place, ie in .opam/.cygwin/ *)
let check_setup setup =
let check_setup ~update =
let dst = cygsetup () in
match setup with
| Some setup ->
log "Copying %s into %s"
(OpamFilename.to_string setup)
(OpamFilename.to_string dst);
let sha512 =
OpamHash.compute ~kind:`SHA512 (OpamFilename.to_string setup)
in
OpamFilename.copy ~src:setup ~dst;
let checksum_file = OpamFilename.add_extension dst "sha512" in
OpamFilename.remove checksum_file;
OpamFilename.with_open_out_bin checksum_file @@ fun c ->
output_string c (OpamHash.contents sha512)
| None ->
if update || not (OpamFilename.exists dst) then
OpamProcess.Job.run @@ download_setupexe dst
end

Expand Down Expand Up @@ -1159,8 +1146,13 @@ let update ?(env=OpamVariable.Map.empty) config =
in
match cmd with
| None ->
(* Cygwin doesn't have an update database per se, but one is supposed to use
the most current setup program when downloading setup.ini (which is the
package database (cf. the --no-version-check option).
Also, when #5839 is addressed, we'll need to cache setup.ini, and that
will want to be updated here too. *)
if family = Cygwin then
Cygwin.check_setup None
Cygwin.check_setup ~update:true
else
OpamConsole.warning
"Unknown update command for %s, skipping system update"
Expand Down
9 changes: 5 additions & 4 deletions src/state/opamSysInteract.mli
Original file line number Diff line number Diff line change
Expand Up @@ -74,10 +74,11 @@ module Cygwin : sig
(* Returns true if Cygwin install is internal *)
val is_internal: OpamFile.Config.t -> bool

(* [check_setup path] checks and store Cygwin setup executable. Is [path] is
[None], it downloads it, otherwise it copies it to
<opamroot>/.cygwin/setup-x86_64.exe. *)
val check_setup: OpamFilename.t option -> unit
(* [check_setup ~update] downloads and stores a Cygwin setup executable to
<opamroot>/.cygwin/setup-x86_64.exe. If [~update = false], this only
happens if the setup executable does not already exist, otherwise it is.
updated. *)
val check_setup: update:bool -> unit

(* Return Cygwin binary path *)
val cygbin_opt: OpamFile.Config.t -> OpamFilename.Dir.t option
Expand Down

0 comments on commit c0cd8f4

Please sign in to comment.