Skip to content

Commit

Permalink
Update vendored opam
Browse files Browse the repository at this point in the history
Signed-off-by: Stephen Sherratt <stephen@sherra.tt>
  • Loading branch information
gridbugs authored and rgrinberg committed May 24, 2023
1 parent 705f875 commit ee38933
Show file tree
Hide file tree
Showing 7 changed files with 12 additions and 163 deletions.
138 changes: 1 addition & 137 deletions vendor/opam/src/state/opamEnv.ml
Original file line number Diff line number Diff line change
Expand Up @@ -468,7 +468,7 @@ let eval_string gt ?(set_opamswitch=false) switch =
let opamroot_env =
OpamStd.Option.Op.(
OpamStateConfig.E.root () +!
OpamFilename.Dir.to_string OpamStateConfig.(default.root_dir)
OpamFilename.Dir.to_string OpamStateConfig.(Lazy.force default.root_dir)
) in
if opamroot_cur <> opamroot_env then
Some opamroot_cur
Expand Down Expand Up @@ -530,19 +530,6 @@ let init_file = function
| SH_pwsh _ | SH_win_cmd ->
(* N/A because not present in `shells_list` yet *) "init.sh"

let complete_script = function
| SH_sh | SH_bash -> Some OpamScript.complete
| SH_zsh -> Some OpamScript.complete_zsh
| SH_csh | SH_fish -> None
| SH_pwsh _ | SH_win_cmd -> None

let env_hook_script_base = function
| SH_sh | SH_bash -> Some OpamScript.env_hook
| SH_zsh -> Some OpamScript.env_hook_zsh
| SH_csh -> Some OpamScript.env_hook_csh
| SH_fish -> Some OpamScript.env_hook_fish
| SH_pwsh _ | SH_win_cmd -> None

let export_in_shell shell =
let make_comment comment_opt =
OpamStd.Option.to_string (Printf.sprintf "# %s\n") comment_opt
Expand Down Expand Up @@ -593,12 +580,6 @@ let export_in_shell shell =
| SH_pwsh _ -> pwsh
| SH_win_cmd -> win_cmd

let env_hook_script shell =
OpamStd.Option.map (fun script ->
export_in_shell shell ("OPAMNOENVNOTICE", "true", None)
^ script)
(env_hook_script_base shell)

let source root shell f =
let fname = OpamFilename.to_string (OpamPath.init root // f) in
match shell with
Expand Down Expand Up @@ -686,32 +667,6 @@ let write_init_shell_scripts root =
in
List.iter (write_script (OpamPath.init root)) scripts

let write_static_init_scripts root ?completion ?env_hook ?(inplace=false) () =
write_init_shell_scripts root;
let update_scripts filef scriptf enable =
let scripts =
OpamStd.List.filter_map (fun shell ->
match filef shell, scriptf shell with
| Some f, Some s -> Some (f, s)
| _ -> None)
shells_list
in
match enable, inplace with
| Some true, _ ->
List.iter (write_script (OpamPath.init root)) scripts
| _, true ->
List.iter (fun ((f,_) as fs) ->
if OpamFilename.exists (OpamPath.init root // f) then
write_script (OpamPath.init root) fs)
scripts
| Some false, _ ->
List.iter (fun (f,_) ->
OpamFilename.remove (OpamPath.init root // f)) scripts
| None, _ -> ()
in
update_scripts complete_file complete_script completion;
update_scripts env_hook_file env_hook_script env_hook

let write_custom_init_scripts root custom =
let hookdir = OpamPath.hooks_dir root in
let kind = `MD5 in
Expand Down Expand Up @@ -828,97 +783,6 @@ let check_and_print_env_warning st =
(OpamConsole.colorise `bold (eval_string st.switch_global
(Some st.switch)))

let setup
root ~interactive ?dot_profile ?update_config ?env_hook ?completion
?inplace shell =
let opam_root_msg =
let current = OpamFilename.prettify_dir root in
if root = OpamStateConfig.(default.root_dir) then
current
else
let default = OpamFilename.prettify_dir OpamStateConfig.(default.root_dir) in
Printf.sprintf "your opam root\n (%s by default; currently %s)" default current
in
let shell, update_dot_profile, env_hook =
match update_config, dot_profile, interactive with
| Some false, _, _ -> shell, None, env_hook
| _, None, _ -> invalid_arg "OpamEnv.setup"
| Some true, Some dot_profile, _ -> shell, Some dot_profile, env_hook
| None, _, false -> shell, None, env_hook
| None, Some dot_profile, true ->
OpamConsole.header_msg "Required setup - please read";

OpamConsole.msg
"\n\
\ In normal operation, opam only alters files within %s.\n\
\n\
\ However, to best integrate with your system, some environment variables\n\
\ should be set. If you allow it to, this initialisation step will update\n\
\ your %s configuration by adding the following line to %s:\n\
\n\
\ %s\
\n\
\ You can always re-run this setup with 'opam init' later.\n\n"
opam_root_msg
(OpamConsole.colorise `bold @@ string_of_shell shell)
(OpamConsole.colorise `cyan @@ OpamFilename.prettify dot_profile)
(OpamConsole.colorise `bold @@ source root shell (init_file shell));
if OpamCoreConfig.answer_is_yes () then begin
OpamConsole.warning "Shell not updated in non-interactive mode: use --shell-setup";
shell, None, env_hook
end else
let rec menu shell dot_profile default =
let opam_env_inv =
OpamConsole.colorise `bold @@ shell_eval_invocation shell (opam_env_invocation shell)
in
match
OpamConsole.menu "Do you want opam to configure %s?"
(OpamConsole.colorise `bold (string_of_shell shell))
~default ~no:`No ~options:[
`Yes, Printf.sprintf "Yes, update %s"
(OpamConsole.colorise `cyan (OpamFilename.prettify dot_profile));
`No_hooks, Printf.sprintf "Yes, but don't setup any hooks. You'll \
have to run %s whenever you change \
your current 'opam switch'"
opam_env_inv;
`Change_shell, "Select a different shell";
`Change_file, "Specify another config file to update instead";
`No, Printf.sprintf "No, I'll remember to run %s when I need opam"
opam_env_inv;
]
with
| `No -> shell, None, env_hook
| `Yes -> shell, Some dot_profile, Some true
| `No_hooks -> shell, Some dot_profile, Some false
| `Change_shell ->
let shell = OpamConsole.menu ~default:shell ~no:shell
"Please select a shell to configure"
~options: (List.map (fun s -> s, string_of_shell s) OpamStd.Sys.all_shells)
in
menu shell (OpamFilename.of_string (OpamStd.Sys.guess_dot_profile shell))
default
| `Change_file ->
let open OpamStd.Option.Op in
let dot_profile =
(OpamConsole.read "Enter the name of the file to update:"
>>| (fun f ->
if Filename.is_implicit f then Filename.concat (OpamStd.Sys.home ()) f
else f)
>>| OpamFilename.of_string)
+! dot_profile
in
menu shell dot_profile `Yes
in
let default = match env_hook with
| Some true -> `Yes
| Some false -> `No_hooks
| None -> `No
in
menu shell dot_profile default
in
update_user_setup root ?dot_profile:update_dot_profile shell;
write_static_init_scripts root ?completion ?env_hook ?inplace ()

let hook_env root =
let hook_vnam = OpamVariable.of_string "hooks" in
let hook_vval = Some (OpamVariable.dirname (OpamPath.hooks_dir root)) in
Expand Down
14 changes: 0 additions & 14 deletions vendor/opam/src/state/opamEnv.mli
Original file line number Diff line number Diff line change
Expand Up @@ -99,27 +99,13 @@ val env_expansion: ?opam:OpamFile.OPAM.t -> 'a switch_state -> env_update -> env

(** {2 Shell and initialisation support} *)

(** Sets the opam configuration in the user shell, after detailing the process
and asking the user if either [update_config] or [shell_hook] are unset *)
val setup:
dirname -> interactive:bool -> ?dot_profile:filename ->
?update_config:bool -> ?env_hook:bool -> ?completion:bool -> ?inplace:bool ->
shell -> unit

(* (\** Display the global and user configuration for OPAM. *\)
* val display_setup: dirname -> dot_profile:filename -> shell -> unit *)

(** Update the user configuration in $HOME for good opam integration. *)
val update_user_setup:
dirname -> ?dot_profile:filename -> shell -> unit

(** Write the generic scripts in ~/.opam/opam-init needed to import state for
various shells. If specified, completion and env_hook files can also be
written or removed (the default is to keep them as they are). If [inplace]
is true, they are updated if they exist. *)
val write_static_init_scripts:
dirname -> ?completion:bool -> ?env_hook:bool -> ?inplace:bool -> unit -> unit

(** Write into [OpamPath.hooks_dir] the given custom scripts (listed as
(filename, content)), normally provided by opamrc ([OpamFile.InitConfig]) *)
val write_custom_init_scripts:
Expand Down
2 changes: 1 addition & 1 deletion vendor/opam/src/state/opamGlobalState.ml
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ let load_config lock_kind global_lock root =
let inferred_from_system = "Inferred from system"

let load lock_kind =
let root = OpamStateConfig.(!r.root_dir) in
let root = Lazy.force OpamStateConfig.(!r.root_dir) in
log "LOAD-GLOBAL-STATE %@ %a" (slog OpamFilename.Dir.to_string) root;
(* Always take a global read lock, this is only used to prevent concurrent
~/.opam format changes *)
Expand Down
5 changes: 2 additions & 3 deletions vendor/opam/src/state/opamRepositoryState.ml
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ module Cache = struct
end)

let remove () =
let root = OpamStateConfig.(!r.root_dir) in
let root = Lazy.force OpamStateConfig.(!r.root_dir) in
let cache_dir = OpamPath.state_cache_dir root in
let remove_cache_file file =
if OpamFilename.check_suffix file ".cache" then
Expand Down Expand Up @@ -301,10 +301,9 @@ let check_last_update () =
if OpamCoreConfig.(!r.debug_level) < 0 then () else
let last_update =
OpamFilename.written_since
(OpamPath.state_cache (OpamStateConfig.(!r.root_dir)))
(OpamPath.state_cache (Lazy.force OpamStateConfig.(!r.root_dir)))
in
if last_update > float_of_int (3600*24*21) then
OpamConsole.note "It seems you have not updated your repositories \
for a while. Consider updating them with:\n%s\n"
(OpamConsole.colorise `bold "opam update");

10 changes: 5 additions & 5 deletions vendor/opam/src/state/opamStateConfig.ml
Original file line number Diff line number Diff line change
Expand Up @@ -52,7 +52,7 @@ module E = struct
end

type t = {
root_dir: OpamFilename.Dir.t;
root_dir: OpamFilename.Dir.t lazy_t;
current_switch: OpamSwitch.t option;
switch_from: provenance;
jobs: int Lazy.t;
Expand All @@ -70,7 +70,7 @@ type t = {
}

let default = {
root_dir = (
root_dir = lazy (
(* On Windows, if a .opam directory is found in %HOME% or %USERPROFILE% then
then we'll use it. Otherwise, we use %LOCALAPPDATA%. *)
let home_location =
Expand Down Expand Up @@ -144,7 +144,7 @@ let setk k t
=
let (+) x opt = match opt with Some x -> x | None -> x in
k {
root_dir = t.root_dir + root_dir;
root_dir = OpamCompat.Lazy.map (fun r -> r + root_dir) t.root_dir;
current_switch =
(match current_switch with None -> t.current_switch | s -> s);
switch_from = t.switch_from + switch_from;
Expand Down Expand Up @@ -202,7 +202,7 @@ let opamroot ?root_dir () =
let open OpamStd.Option.Op in
(root_dir >>+ fun () ->
OpamStd.Env.getopt "OPAMROOT" >>| OpamFilename.Dir.of_string)
+! default.root_dir
+! (Lazy.force default.root_dir)

let is_newer_raw = function
| Some v ->
Expand Down Expand Up @@ -396,7 +396,7 @@ let load_defaults ?lock_kind root_dir =
let get_switch_opt () =
match !r.current_switch with
| Some s ->
Some (resolve_local_switch !r.root_dir s)
Some (resolve_local_switch (Lazy.force !r.root_dir) s)
| None -> None

let get_switch () =
Expand Down
4 changes: 2 additions & 2 deletions vendor/opam/src/state/opamStateConfig.mli
Original file line number Diff line number Diff line change
Expand Up @@ -37,10 +37,10 @@ module E : sig
end

type t = private {
root_dir: OpamFilename.Dir.t;
root_dir: OpamFilename.Dir.t Lazy.t;
current_switch: OpamSwitch.t option;
switch_from: provenance;
jobs: int Lazy.t;
jobs: int lazy_t;
dl_jobs: int;
build_test: bool;
build_doc: bool;
Expand Down
2 changes: 1 addition & 1 deletion vendor/update-opam.sh
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
#!/usr/bin/env bash

version=cc62e68712e04def2716a1808d515160b2917b19
version=69bcb51db15e27563583bddb8edf5c505ae6e10f

set -e -o pipefail

Expand Down

0 comments on commit ee38933

Please sign in to comment.