Skip to content

Commit

Permalink
Extract arch and os from host triplet when available.
Browse files Browse the repository at this point in the history
  • Loading branch information
toots committed Jun 27, 2023
1 parent f67683c commit a107b30
Show file tree
Hide file tree
Showing 3 changed files with 39 additions and 11 deletions.
40 changes: 30 additions & 10 deletions src/core/opamStd.ml
Original file line number Diff line number Diff line change
Expand Up @@ -987,19 +987,31 @@ module OpamSys = struct

let etc () = "/etc"

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

let uname = get_process "uname"
let gcc = get_process "gcc"
let clang = get_process "clang"

let machine_triplet =
let machine_triplet = lazy (
match gcc "-dumpmachine" with
| None -> clang "-dumpmachine"
| v -> v
) in
fun () -> Lazy.force machine_triplet

let system () =
(* CSIDL_SYSTEM = 0x25 *)
OpamStubs.(shGetFolderPath 0x25 SHGFP_TYPE_CURRENT)
Expand All @@ -1020,14 +1032,22 @@ module OpamSys = struct
let os = lazy (
match Sys.os_type with
| "Unix" -> begin
match uname "-s" with
| Some "Darwin" -> Darwin
| Some "Linux" -> Linux
| Some "FreeBSD" -> FreeBSD
| Some "OpenBSD" -> OpenBSD
| Some "NetBSD" -> NetBSD
| Some "DragonFly" -> DragonFly
| _ -> Unix
match machine_triplet () with
| Some s when OpamString.contains ~sub:"darwin" s -> Darwin
| Some s when OpamString.contains ~sub:"linux" s -> Linux
| Some s when OpamString.contains ~sub:"freebsd" s -> FreeBSD
| Some s when OpamString.contains ~sub:"openbsd" s -> OpenBSD
| Some s when OpamString.contains ~sub:"netbsd" s -> NetBSD
| Some s when OpamString.contains ~sub:"dragonfly" s -> DragonFly
| _ -> (
match uname "-s" with
| Some "Darwin" -> Darwin
| Some "Linux" -> Linux
| Some "FreeBSD" -> FreeBSD
| Some "OpenBSD" -> OpenBSD
| Some "NetBSD" -> NetBSD
| Some "DragonFly" -> DragonFly
| _ -> Unix)
end
| "Win32" -> Win32
| "Cygwin" -> Cygwin
Expand Down
3 changes: 3 additions & 0 deletions src/core/opamStd.mli
Original file line number Diff line number Diff line change
Expand Up @@ -494,6 +494,9 @@ module Sys : sig
| Unix
| Other of string

(** Machine triplet, if found. Queried lazily. *)
val machine_triplet : unit -> string option

(** Queried lazily *)
val os: unit -> os

Expand Down
7 changes: 6 additions & 1 deletion src/state/opamSysPoll.ml
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,11 @@ let normalise_arch raw =

let poll_arch () =
let raw = match Sys.os_type with
| "Unix" | "Cygwin" -> OpamStd.Sys.uname "-m"
| "Unix" | "Cygwin" ->
begin match Option.map (String.split_on_char '-') (OpamStd.Sys.machine_triplet ()) with
| Some (arch::_) -> Some arch
| _ -> OpamStd.Sys.uname "-m"
end
| "Win32" ->
begin match OpamStubs.getArchitecture () with
| OpamStubs.AMD64 -> Some "x86_64"
Expand Down Expand Up @@ -171,6 +175,7 @@ let variables =
"os-distribution", os_distribution;
"os-version", os_version;
"os-family", os_family;
"machine-triplet", lazy (OpamStd.Sys.machine_triplet ());
]

let cores =
Expand Down

0 comments on commit a107b30

Please sign in to comment.