Skip to content

Commit

Permalink
Add OPAMNOEVALENV in OpamStateConfig
Browse files Browse the repository at this point in the history
  • Loading branch information
rjbou committed Apr 30, 2018
1 parent a53c22f commit 1bf4b95
Show file tree
Hide file tree
Showing 4 changed files with 11 additions and 7 deletions.
1 change: 1 addition & 0 deletions src/client/opamClientConfig.mli
Original file line number Diff line number Diff line change
Expand Up @@ -89,6 +89,7 @@ val opam_init:
?makecmd:string Lazy.t ->
?ignore_constraints_on:OpamPackage.Name.Set.t ->
?unlock_base:bool ->
?noeval_env:bool ->
?cudf_file:string option ->
?solver:(module OpamCudfSolver.S) Lazy.t ->
?best_effort:bool ->
Expand Down
9 changes: 2 additions & 7 deletions src/state/opamEnv.ml
Original file line number Diff line number Diff line change
Expand Up @@ -659,9 +659,7 @@ let display_setup root ~dot_profile shell =
not_set
else ok in
let eval_env =
try
if bool_of_string @@ OpamStd.Config.env_bool "NOEVALENV" then ok else not_set
with Not_found -> not_set
if OpamStateConfig.(!r.noeval_env) then ok else not_set
in
[ ("init-script" , Printf.sprintf "%s" pretty_init_file);
("auto-completion" , completion);
Expand All @@ -680,10 +678,7 @@ let check_and_print_env_warning st =
(OpamFilename.of_string @@
OpamStd.Sys.(guess_dot_profile @@ guess_shell_compat ()))) = `yes
in
let opam_noeval_env =
try bool_of_string @@ OpamStd.Config.env_bool "NOEVALENV"
with Not_found -> false
in
let opam_noeval_env = OpamStateConfig.(!r.noeval_env) in
if (OpamFile.Config.switch st.switch_global.config = Some st.switch ||
OpamStateConfig.(!r.switch_from <> `Command_line)) &&
(outdated_env && (dot_profile_not_configured || opam_noeval_env))
Expand Down
6 changes: 6 additions & 0 deletions src/state/opamStateConfig.ml
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,7 @@ type t = {
makecmd: string Lazy.t;
ignore_constraints_on: name_set;
unlock_base: bool;
noeval_env: bool;
}

let default = {
Expand All @@ -42,6 +43,7 @@ let default = {
);
ignore_constraints_on = OpamPackage.Name.Set.empty;
unlock_base = false;
noeval_env = false;
}

type 'a options_fun =
Expand All @@ -56,6 +58,7 @@ type 'a options_fun =
?makecmd:string Lazy.t ->
?ignore_constraints_on:name_set ->
?unlock_base:bool ->
?noeval_env:bool ->
'a

let setk k t
Expand All @@ -70,6 +73,7 @@ let setk k t
?makecmd
?ignore_constraints_on
?unlock_base
?noeval_env
=
let (+) x opt = match opt with Some x -> x | None -> x in
k {
Expand All @@ -85,6 +89,7 @@ let setk k t
makecmd = t.makecmd + makecmd;
ignore_constraints_on = t.ignore_constraints_on + ignore_constraints_on;
unlock_base = t.unlock_base + unlock_base;
noeval_env = t.noeval_env + noeval_env
}

let set t = setk (fun x () -> x) t
Expand Down Expand Up @@ -117,6 +122,7 @@ let initk k =
List.map OpamPackage.Name.of_string |>
OpamPackage.Name.Set.of_list)
?unlock_base:(env_bool "UNLOCKBASE")
?noeval_env:(env_bool "NOEVALENV")

let init ?noop:_ = initk (fun () -> ())

Expand Down
2 changes: 2 additions & 0 deletions src/state/opamStateConfig.mli
Original file line number Diff line number Diff line change
Expand Up @@ -25,6 +25,7 @@ type t = private {
makecmd: string Lazy.t;
ignore_constraints_on: name_set;
unlock_base: bool;
noeval_env: bool;
}

type 'a options_fun =
Expand All @@ -39,6 +40,7 @@ type 'a options_fun =
?makecmd:string Lazy.t ->
?ignore_constraints_on:name_set ->
?unlock_base:bool ->
?noeval_env:bool ->
'a

include OpamStd.Config.Sig
Expand Down

0 comments on commit 1bf4b95

Please sign in to comment.