Skip to content

Commit

Permalink
Merge pull request #3097 from OCamlPro/depext-vars
Browse files Browse the repository at this point in the history
Following #3058, this brings the system detection code in
  • Loading branch information
AltGr authored Nov 16, 2017
2 parents 23f895f + 47462c7 commit df6d7c2
Show file tree
Hide file tree
Showing 17 changed files with 345 additions and 151 deletions.
2 changes: 2 additions & 0 deletions doc/index.html
Original file line number Diff line number Diff line change
Expand Up @@ -196,6 +196,8 @@ <h1>opam %{OPAMVERSION}% API and libraries documentation</h1>
<td>Defines the types holding global, repository and switch states</td></tr>
<tr><th><a href="ocamldoc/OpamFormatUpgrade.html">opamFormatUpgrade.ml</a></th>
<td>Handles upgrade of an opam root from earlier opam versions</td></tr>
<tr><th><a href="ocamldoc/OpamSysPoll.html">opamSysPoll.ml</a></th>
<td>Detection of host system (arch, os, distribution)</td></tr>
<tr><th><a href="ocamldoc/OpamGlobalState.html">opamGlobalState.ml</a></th>
<td>Loading and handling of the global state of an opam root</td></tr>
<tr><th><a href="ocamldoc/OpamRepositoryState.html">opamRepositoryState.ml</a></th>
Expand Down
3 changes: 2 additions & 1 deletion src/client/opamAction.ml
Original file line number Diff line number Diff line change
Expand Up @@ -375,9 +375,10 @@ let make_command st opam ?dir ?text_command (cmd, args) =
OpamProcess.make_command_text name ~args cmd
in
let context =
let open OpamStd.Option.Op in
String.concat " | " [
OpamVersion.(to_string current);
OpamStd.Sys.os_string () ^"/"^ OpamStd.Sys.arch ();
(OpamSysPoll.os () +! "unknown") ^"/"^ (OpamSysPoll.arch () +! "unknown");
(OpamStd.List.concat_map " " OpamPackage.to_string
OpamPackage.Set.(elements @@
inter st.compiler_packages st.installed_roots));
Expand Down
4 changes: 3 additions & 1 deletion src/client/opamArg.ml
Original file line number Diff line number Diff line change
Expand Up @@ -996,7 +996,9 @@ let build_options =
(or the deprecated $(b,\\$OPAMBUILDDOC)) to \"true\"." in
let make =
mk_opt ~section ["m";"make"] "MAKE"
"Use $(docv) as the default 'make' command."
"Use $(docv) as the default 'make' command. Deprecated: use $(b,opam \
config set[-global] make MAKE) instead. Has no effect if the $(i,make) \
variable is defined."
Arg.(some string) None in
let show =
mk_flag ~section ["show-actions"]
Expand Down
20 changes: 12 additions & 8 deletions src/client/opamCommands.ml
Original file line number Diff line number Diff line change
Expand Up @@ -391,16 +391,16 @@ let list ?(force_search=false) () =
let depexts =
mk_flag ["e";"external"] ~section:display_docs
"Instead of displaying the packages, display their external dependencies \
that are associated with the system as specified by $(b,--vars). This \
excludes other display options. Rather than using this directly, you \
should probably head for the `depext' plugin, that can infer your \
system's package management system and handle the system installations. \
Run `opam depext'."
that are associated with the current system. This excludes other \
display options. Rather than using this directly, you should probably \
head for the `depext' plugin, that will use your system package \
management system to handle the installation of the dependencies. Run \
`opam depext'."
in
let vars =
mk_opt ["vars"] "[VAR=STR,...]" ~section:display_docs
"Define the given variable bindings. Typically useful with \
$(b,--external) to define values for $(i,arch), $(i,os), \
$(b,--external) to override the values for $(i,arch), $(i,os), \
$(i,os-distribution), $(i,os-version), $(i,os-family)."
OpamArg.variable_bindings []
in
Expand Down Expand Up @@ -831,7 +831,11 @@ let config =
(if self_upgrade_status global_options = `Running then
OpamFilename.prettify (fst (self_upgrade_exe (OpamStateConfig.(!r.root_dir))))
else "no");
print "os" "%s" (OpamStd.Sys.os_string ());
print "system" "arch=%s os=%s os-distribution=%s os-version=%s"
OpamStd.Option.Op.(OpamSysPoll.arch () +! "unknown")
OpamStd.Option.Op.(OpamSysPoll.os () +! "unknown")
OpamStd.Option.Op.(OpamSysPoll.os_distribution () +! "unknown")
OpamStd.Option.Op.(OpamSysPoll.os_version () +! "unknown");
try
OpamGlobalState.with_ `Lock_none @@ fun gt ->
OpamSwitchState.with_ `Lock_none gt @@ fun state ->
Expand Down Expand Up @@ -870,7 +874,7 @@ let config =
nprint "local" nlocal @
nprint "version-controlled" nvcs) ^
match default with
| Some v -> Printf.sprintf "(default repo at %s)" v
| Some v -> Printf.sprintf " (default repo at %s)" v
| None -> ""
);
print "pinned" "%s"
Expand Down
4 changes: 1 addition & 3 deletions src/client/opamInitDefaults.ml
Original file line number Diff line number Diff line change
Expand Up @@ -20,14 +20,12 @@ let default_compiler =
OpamFormula.ors [
OpamFormula.Atom (OpamPackage.Name.of_string "ocaml-system",
OpamFormula.Atom
(`Geq, OpamPackage.Version.of_string "4.01.0"));
(`Geq, OpamPackage.Version.of_string "4.02.3"));
OpamFormula.Atom (OpamPackage.Name.of_string "ocaml-base-compiler",
OpamFormula.Empty);
]

let eval_variables = [
OpamVariable.of_string "arch", ["uname"; "-m"],
"Host architecture, as returned by 'uname -m'";
OpamVariable.of_string "sys-ocaml-version", ["ocamlc"; "-vnum"],
"OCaml version present on your system independently of opam, if any";
]
Expand Down
10 changes: 5 additions & 5 deletions src/core/opamProcess.ml
Original file line number Diff line number Diff line change
Expand Up @@ -249,9 +249,9 @@ let read_lines f =
with Sys_error _ -> []

(* Compat function (Windows) *)
let interrupt p = match OpamStd.Sys.os () with
| OpamStd.Sys.Win32 -> Unix.kill p.p_pid Sys.sigkill
| _ -> Unix.kill p.p_pid Sys.sigint
let interrupt p =
if OpamStd.Sys.is_windows then Unix.kill p.p_pid Sys.sigkill
else Unix.kill p.p_pid Sys.sigint

let run_background command =
let { cmd; args;
Expand Down Expand Up @@ -338,7 +338,7 @@ let set_verbose_f, print_verbose_f, isset_verbose_f, stop_verbose_f =
stop ();
(* implem relies on sigalrm, not implemented on win32.
This will fall back to buffered output. *)
if OpamStd.Sys.(os () = Win32) then () else
if OpamStd.Sys.is_windows then () else
let files = OpamStd.List.sort_nodup compare files in
let ics =
List.map
Expand Down Expand Up @@ -443,7 +443,7 @@ let dontwait p =
let dead_childs = Hashtbl.create 13
let wait_one processes =
if processes = [] then raise (Invalid_argument "wait_one");
if OpamStd.Sys.(os () = Win32) then
if OpamStd.Sys.is_windows then
(* No waiting for any child pid on Windows, this is highly sub-optimal
but should at least work. Todo: C binding for better behaviour *)
let p = List.hd processes in
Expand Down
106 changes: 37 additions & 69 deletions src/core/opamStd.ml
Original file line number Diff line number Diff line change
Expand Up @@ -618,19 +618,18 @@ module OpamSys = struct

let etc () = "/etc"

let uname_s () =
try
with_process_in "uname" "-s"
(fun ic -> Some (OpamString.strip (input_line ic)))
with Unix.Unix_error _ | Sys_error _ | Not_found ->
None

let uname_m () =
try
with_process_in "uname" "-m"
(fun ic -> Some (OpamString.strip (input_line ic)))
with Unix.Unix_error _ | Sys_error _ | Not_found ->
None
let uname =
let memo = Hashtbl.create 7 in
fun arg ->
try Hashtbl.find memo arg with Not_found ->
let r =
try
with_process_in "uname" 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

type os =
| Darwin
Expand All @@ -648,7 +647,7 @@ module OpamSys = struct
let os = lazy (
match Sys.os_type with
| "Unix" -> begin
match uname_s () with
match uname "-s" with
| Some "Darwin" -> Darwin
| Some "Linux" -> Linux
| Some "FreeBSD" -> FreeBSD
Expand All @@ -663,27 +662,6 @@ module OpamSys = struct
) in
fun () -> Lazy.force os

let arch =
let arch =
lazy (Option.default "Unknown" (uname_m ()))
in
fun () -> Lazy.force arch

let string_of_os = function
| Darwin -> "darwin"
| Linux -> "linux"
| FreeBSD -> "freebsd"
| OpenBSD -> "openbsd"
| NetBSD -> "netbsd"
| DragonFly -> "dragonfly"
| Cygwin -> "cygwin"
| Win32 -> "win32"
| Unix -> "unix"
| Other x -> x

let os_string () =
string_of_os (os ())

let shell_of_string = function
| "tcsh"
| "csh" -> `csh
Expand All @@ -692,8 +670,10 @@ module OpamSys = struct
| "fish" -> `fish
| _ -> `sh

let is_windows = Sys.os_type = "Win32"

let executable_name =
if os () = Win32 then
if is_windows then
fun name ->
if Filename.check_suffix name ".exe" then
name
Expand Down Expand Up @@ -747,41 +727,29 @@ module OpamSys = struct
(fun f -> try f () with _ -> ())
!registered_at_exit

let path_sep =
let path_sep = lazy (
match os () with
| Win32 -> ';'
| Cygwin | _ -> ':'
) in
fun () -> Lazy.force path_sep
let path_sep = if is_windows then ';' else ':'

let split_path_variable =
let f = lazy (
match os () with
| Win32 ->
fun path ->
let length = String.length path in
let rec f acc index current last normal =
if index = length
then let current = current ^ String.sub path last (index - last) in
if current <> "" then current::acc else acc
else let c = path.[index]
and next = succ index in
if c = ';' && normal || c = '"' then
let current = current ^ String.sub path last (index - last) in
if c = '"' then
f acc next current next (not normal)
else
let acc = if current = "" then acc else current::acc in
f acc next "" next true
else
f acc next current last normal in
f [] 0 "" 0 true
| _ ->
fun path ->
OpamString.split_delim path (path_sep ())
) in
fun path -> (Lazy.force f) path
if is_windows then fun path ->
let length = String.length path in
let rec f acc index current last normal =
if index = length
then let current = current ^ String.sub path last (index - last) in
if current <> "" then current::acc else acc
else let c = path.[index]
and next = succ index in
if c = ';' && normal || c = '"' then
let current = current ^ String.sub path last (index - last) in
if c = '"' then
f acc next current next (not normal)
else
let acc = if current = "" then acc else current::acc in
f acc next "" next true
else
f acc next current last normal in
f [] 0 "" 0 true
else fun path ->
OpamString.split_delim path path_sep

exception Exit of int
exception Exec of string * string array * string array
Expand Down
11 changes: 6 additions & 5 deletions src/core/opamStd.mli
Original file line number Diff line number Diff line change
Expand Up @@ -351,6 +351,9 @@ module Sys : sig
(** Queried lazily, but may change on SIGWINCH *)
val terminal_columns : unit -> int

(** True only if the host OS is Win32 (not cygwin) *)
val is_windows: bool

(** The user's home directory. Queried lazily *)
val home: unit -> string

Expand All @@ -371,10 +374,8 @@ module Sys : sig
(** Queried lazily *)
val os: unit -> os

val os_string: unit -> string

(** Queried lazily *)
val arch: unit -> string
(** The output of the command "uname", with the given argument. Memoised. *)
val uname: string -> string option

(** Append .exe (only if missing) to executable filenames on Windows *)
val executable_name : string -> string
Expand All @@ -387,7 +388,7 @@ module Sys : sig

(** The separator character used in the PATH variable (varies depending on
OS) *)
val path_sep: unit -> char
val path_sep: char

(** Splits a PATH-like variable separated with [path_sep]. More involved than
it seems, because there may be quoting on Windows. *)
Expand Down
9 changes: 4 additions & 5 deletions src/core/opamSystem.ml
Original file line number Diff line number Diff line change
Expand Up @@ -74,7 +74,7 @@ let mkdir dir =
aux dir

let rm_command =
if OpamStd.Sys.(os () = Win32) then
if OpamStd.Sys.is_windows then
"cmd /d /v:off /c rd /s /q"
else
"rm -rf"
Expand Down Expand Up @@ -302,7 +302,7 @@ let default_env =

let env_var env var =
let len = Array.length env in
let f = if OpamStd.(Sys.os () = Sys.Win32) then String.uppercase_ascii else fun x -> x in
let f = if OpamStd.Sys.is_windows then String.uppercase_ascii else fun x -> x in
let prefix = f var^"=" in
let pfxlen = String.length prefix in
let rec aux i =
Expand All @@ -317,12 +317,11 @@ let env_var env var =
(* OCaml 4.05.0 no longer follows the updated PATH to resolve commands. This
makes unqualified commands absolute as a workaround. *)
let resolve_command =
let is_windows = OpamStd.(Sys.os () = Sys.Win32) in
let is_external_cmd name =
OpamStd.String.contains_char name Filename.dir_sep.[0]
in
let check_perms =
if is_windows then fun f ->
if OpamStd.Sys.is_windows then fun f ->
try (Unix.stat f).Unix.st_kind = Unix.S_REG
with e -> OpamStd.Exn.fatal e; false
else fun f ->
Expand All @@ -346,7 +345,7 @@ let resolve_command =
in
if check_perms cmd then Some cmd else None
else (* bare command, lookup in PATH *)
if is_windows then
if OpamStd.Sys.is_windows then
let path = OpamStd.Sys.split_path_variable (env_var env "PATH") in
let name =
if Filename.check_suffix name ".exe" then name else name ^ ".exe"
Expand Down
10 changes: 7 additions & 3 deletions src/state/opamEnv.ml
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ let slog = OpamConsole.slog
let split_var v = OpamStd.Sys.split_path_variable v

let join_var l =
String.concat (String.make 1 (OpamStd.Sys.path_sep ())) l
String.concat (String.make 1 OpamStd.Sys.path_sep) l

(* To allow in-place updates, we store intermediate values of path-like as a
pair of list [(rl1, l2)] such that the value is [List.rev_append rl1 l2] and
Expand Down Expand Up @@ -123,7 +123,11 @@ let expand (updates: env_update list) : env =
let rec apply_updates reverts acc = function
| (var, op, arg, doc) :: updates ->
let zip, reverts =
let f, var = if OpamStd.Sys.(os () = Win32) then String.uppercase_ascii, String.uppercase_ascii var else (fun x -> x), var in
let f, var =
if OpamStd.Sys.is_windows then
String.uppercase_ascii, String.uppercase_ascii var
else (fun x -> x), var
in
match OpamStd.List.find_opt (fun (v, _, _) -> f v = var) acc with
| Some (_, z, _doc) -> z, reverts
| None ->
Expand All @@ -150,7 +154,7 @@ let expand (updates: env_update list) : env =

let add (env: env) (updates: env_update list) =
let env =
if OpamStd.(Sys.os () = Sys.Win32) then
if OpamStd.Sys.is_windows then
(*
* Environment variable names are case insensitive on Windows
*)
Expand Down
Loading

0 comments on commit df6d7c2

Please sign in to comment.