Skip to content

Commit

Permalink
Fix the value of the 'arch' variable when the current OS is 32bit on …
Browse files Browse the repository at this point in the history
…a 64bit machine
  • Loading branch information
kit-ty-kate committed May 10, 2024
1 parent e11ebbf commit d1a09ab
Show file tree
Hide file tree
Showing 3 changed files with 28 additions and 8 deletions.
13 changes: 8 additions & 5 deletions src/core/opamStd.ml
Original file line number Diff line number Diff line change
Expand Up @@ -991,19 +991,22 @@ module OpamSys = struct

let etc () = "/etc"

let uname =
let memo_command =
let memo = Hashtbl.create 7 in
fun arg ->
try Hashtbl.find memo arg with Not_found ->
fun cmd arg ->
try Hashtbl.find memo (cmd, arg) with Not_found ->
let r =
try
with_process_in "uname" arg
with_process_in cmd arg
(fun ic -> Some (OpamString.strip (input_line ic)))
with Unix.Unix_error _ | Sys_error _ | Not_found -> None
in
Hashtbl.add memo arg r;
Hashtbl.add memo (cmd, arg) r;
r

let uname = memo_command "uname"
let getconf = memo_command "getconf"

let system =
let system = Lazy.from_fun OpamStubs.getPathToSystem in
fun () -> Lazy.force system
Expand Down
3 changes: 3 additions & 0 deletions src/core/opamStd.mli
Original file line number Diff line number Diff line change
Expand Up @@ -507,6 +507,9 @@ module Sys : sig
(** The output of the command "uname", with the given argument. Memoised. *)
val uname: string -> string option

(** The output of the command "getconf", with the given argument. Memoised. *)
val getconf: string -> string option

(** Append .exe (only if missing) to executable filenames on Windows *)
val executable_name : string -> string

Expand Down
20 changes: 17 additions & 3 deletions src/state/opamSysPoll.ml
Original file line number Diff line number Diff line change
Expand Up @@ -47,9 +47,23 @@ let poll_arch () =
end
| _ -> None
in
match raw with
| None | Some "" -> None
| Some a -> Some (normalise_arch a)
let normalised =
match raw with
| None | Some "" -> None
| Some a -> Some (normalise_arch a)
in
match Sys.os_type with
| "Unix" | "Cygwin" ->
(match normalised with
| Some ("x86_64" | "arm64" | "ppc64" as arch) ->
(match OpamStd.Sys.getconf "LONG_BIT", arch with
| Some "32", "x86_64" -> Some "x86_32"
| Some "32", "arm64" -> Some "arm32"
| Some "32", "ppc64" -> Some "ppc32"
| _ -> normalised
| exception (Unix.Unix_error _ | Sys_error _ | Not_found) -> normalised)
| _ -> normalised)
| _ -> normalised
let arch = Lazy.from_fun poll_arch

let normalise_os raw =
Expand Down

0 comments on commit d1a09ab

Please sign in to comment.