Skip to content
Draft
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
6 changes: 2 additions & 4 deletions src/client/opamAction.ml
Original file line number Diff line number Diff line change
Expand Up @@ -584,16 +584,14 @@ let compilation_env t opam =
in
let scrub = OpamClientConfig.(!r.scrubbed_environment_variables) in
OpamEnv.get_full ~scrub ~set_opamroot:true ~set_opamswitch:true
~force_path:true t ~updates:([
~force_path:true ~build_env t ~updates:([
cdpath;
makeflags;
makelevel;
pkg_name;
pkg_version;
cli
] @
build_env
@ cygwin_env)
] @ cygwin_env)

let installed_opam_opt st nv =
OpamStd.Option.Op.(
Expand Down
2 changes: 1 addition & 1 deletion src/client/opamConfigCommand.ml
Original file line number Diff line number Diff line change
Expand Up @@ -220,7 +220,7 @@ let regenerate_env ~set_opamroot ~set_opamswitch ~force_path
gt switch env_file =
OpamSwitchState.with_ `Lock_none ~switch gt @@ fun st ->
let upd =
OpamEnv.updates ~set_opamroot ~set_opamswitch ~force_path st
OpamEnv.updates ~set_opamroot ~set_opamswitch ~force_path ~build_env:[] st
in
if not (OpamCoreConfig.(!r.safe_mode)) then
(let _, st =
Expand Down
3 changes: 2 additions & 1 deletion src/client/opamSolution.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1101,7 +1101,8 @@ let confirmation ?ask requested solution =
OpamConsole.confirm "\nProceed with %s?" (OpamSolver.string_of_stats stats)

let run_hook_job t name ?(local=[]) ?(allow_stdout=false) w =
let shell_env = OpamEnv.get_full ~set_opamroot:true ~set_opamswitch:true ~force_path:true t in
(* TODO: ????? *)
let shell_env = OpamEnv.get_full ~set_opamroot:true ~set_opamswitch:true ~force_path:true ~build_env:[] t in
Comment on lines 1103 to +1105
Copy link
Member Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

should pre-command hooks and the like have build-env? It feels like they should

let mk_cmd = function
| cmd :: args ->
let text = OpamProcess.make_command_text name ~args cmd in
Expand Down
2 changes: 1 addition & 1 deletion src/client/opamSwitchCommand.ml
Original file line number Diff line number Diff line change
Expand Up @@ -200,7 +200,7 @@ let install_compiler
not OpamStateConfig.(!r.dryrun) then
OpamFile.Environment.write
(OpamPath.Switch.environment t.switch_global.root t.switch)
(OpamEnv.compute_updates t);
(OpamEnv.compute_updates ~build_env:[] t);
OpamEnv.check_and_print_env_warning t);
t
end else
Expand Down
22 changes: 11 additions & 11 deletions src/state/opamEnv.ml
Original file line number Diff line number Diff line change
Expand Up @@ -613,7 +613,7 @@ let env_update_resolved_with_default ?comment var =
let rewrite = Some (SPF_Resolved (Some (default_sep_fmt_str var))) in
env_update_resolved ?comment ~rewrite var

let compute_updates ?(force_path=false) st =
let compute_updates ?(force_path=false) ~build_env st =
(* Todo: put these back into their packages!
let perl5 = OpamPackage.Name.of_string "perl5" in
let add_to_perl5lib = OpamPath.Switch.lib t.root t.switch t.switch_config perl5 in
Expand Down Expand Up @@ -660,7 +660,7 @@ let compute_updates ?(force_path=false) st =
in
List.map resolve_separator_and_format updates
in
switch_env @ pkg_env @ man_path @ [path]
pkg_env @ build_env @ switch_env @ man_path @ [path]

let updates_common ~set_opamroot ~set_opamswitch root switch =
let root =
Expand Down Expand Up @@ -688,18 +688,18 @@ let updates_nix st =
| Some env -> List.map resolve_separator_and_format env)
| _ -> []

let updates ~set_opamroot ~set_opamswitch ?force_path st =
let updates ~set_opamroot ~set_opamswitch ?force_path ~build_env st =
let common =
updates_common ~set_opamroot ~set_opamswitch st.switch_global.root st.switch
in
common @ compute_updates ?force_path st @ updates_nix st
compute_updates ?force_path ~build_env st @ common @ updates_nix st
Copy link
Member Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

common and nix updates should probably be moved in compute_updates to centralise the ordering in one function. I also don't think nix env should be able to take priority over every others


let get_pure ?(updates=[]) () =
let env = List.map (fun (v,va) -> v,va,None) (OpamStd.Env.list ()) in
add env updates

let get_opam ~set_opamroot ~set_opamswitch ~force_path st =
add [] (updates ~set_opamroot ~set_opamswitch ~force_path st)
add [] (updates ~set_opamroot ~set_opamswitch ~force_path ~build_env:[] st)

let get_opam_raw_updates ~set_opamroot ~set_opamswitch ~force_path root switch =
let env_file = OpamPath.Switch.environment root switch in
Expand Down Expand Up @@ -740,7 +740,7 @@ let hash_env_updates upd =
|> Digest.to_hex

let get_full
~set_opamroot ~set_opamswitch ~force_path ?updates:(u=[]) ?(scrub=[])
~set_opamroot ~set_opamswitch ~force_path ~build_env ?updates:(u=[]) ?(scrub=[])
st =
let env =
let env = OpamStd.Env.list () in
Expand All @@ -753,10 +753,10 @@ let get_full
List.filter (fun (name, _) -> not (OpamStd.Env.Name.Set.mem name scrub)) env
in
let env0 = List.map (fun (v,va) -> v,va,None) env in
let u =
(List.map resolve_separator_and_format u) in
let u = List.map resolve_separator_and_format u in
let build_env = List.map resolve_separator_and_format build_env in
let updates =
u @ updates ~set_opamroot ~set_opamswitch ~force_path st in
u @ updates ~set_opamroot ~set_opamswitch ~force_path ~build_env st in
add env0 updates

let is_up_to_date_raw ?(skip=OpamStateConfig.(!r.no_env_notice)) updates =
Expand Down Expand Up @@ -821,7 +821,7 @@ let full_with_path ~force_path ?(updates=[]) root switch =

let is_up_to_date ?skip st =
is_up_to_date_raw ?skip
(updates ~set_opamroot:false ~set_opamswitch:false ~force_path:false st)
(updates ~set_opamroot:false ~set_opamswitch:false ~force_path:false ~build_env:[] st)

(** Returns shell-appropriate statement to evaluate [cmd]. *)
let shell_eval_invocation shell cmd =
Expand Down Expand Up @@ -1206,7 +1206,7 @@ let write_dynamic_init_scripts st =
| _ -> true
in
let updates =
updates ~set_opamroot:false ~set_opamswitch:false st
updates ~set_opamroot:false ~set_opamswitch:false ~build_env:[] st
|> List.filter is_not_empty_update
in
try
Expand Down
13 changes: 10 additions & 3 deletions src/state/opamEnv.mli
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,9 @@ val resolve_separator_and_format:
remove from the environment. *)
val get_full:
set_opamroot:bool -> set_opamswitch:bool -> force_path:bool ->
?updates: ('r, euok_internal) env_update list -> ?scrub:string list -> 'a switch_state -> env
build_env:('r, euok_internal) env_update list ->
?updates: ('r, euok_internal) env_update list ->
?scrub:string list -> 'a switch_state -> env

(** Get only environment modified by OPAM. If [force_path], the PATH is modified
to ensure opam dirs are leading. [set_opamroot] and [set_opamswitch] can be
Expand Down Expand Up @@ -76,7 +78,8 @@ val add: env -> (spf_resolved, euok_internal) env_update list -> env
these [updates] instead of the new environment. *)
val updates:
set_opamroot:bool -> set_opamswitch:bool -> ?force_path:bool ->
'a switch_state -> (spf_resolved, [> euok_writeable ]) env_update list
build_env:(spf_resolved, 'k) env_update list ->
'a switch_state -> (spf_resolved, [> euok_writeable ] as 'k) env_update list

(** Check if the shell environment is in sync with the current OPAM switch,
unless [skip] is true (it's default value is OPAMNOENVNOTICE *)
Expand All @@ -89,7 +92,11 @@ val is_up_to_date_switch: dirname -> switch -> bool

(** Returns the current environment updates to configure the current switch with
its set of installed packages *)
val compute_updates: ?force_path:bool -> 'a switch_state -> (spf_resolved, [> euok_writeable ]) env_update list
val compute_updates:
?force_path:bool ->
build_env:(spf_resolved, 'k) env_update list ->
'a switch_state ->
(spf_resolved, [> euok_writeable ] as 'k) env_update list

(** Returns shell-appropriate statement to evaluate [cmd]. *)
val shell_eval_invocation:
Expand Down
2 changes: 1 addition & 1 deletion src/state/opamSwitchAction.ml
Original file line number Diff line number Diff line change
Expand Up @@ -95,7 +95,7 @@ let write_selections st =
let f = OpamPath.Switch.selections st.switch_global.root st.switch in
let env = OpamPath.Switch.environment st.switch_global.root st.switch in
OpamFile.SwitchSelections.write f (OpamSwitchState.selections st);
OpamFile.Environment.write env (OpamEnv.compute_updates st)
OpamFile.Environment.write env (OpamEnv.compute_updates ~build_env:[] st)

let add_to_reinstall st ~unpinned_only packages =
log "add-to-reinstall unpinned_only:%b packages:%a" unpinned_only
Expand Down
2 changes: 1 addition & 1 deletion tests/reftests/env.test
Original file line number Diff line number Diff line change
Expand Up @@ -44,8 +44,8 @@ NV_VARS='hej!!'; export NV_VARS;
NV_VARS='hej!!'; export NV_VARS;
OPAM_SWITCH_PREFIX='${BASEDIR}/OPAM/conffile'; export OPAM_SWITCH_PREFIX;
### opam exec -- opam env --revert | grep "^NV_VARS|^OPAM_SWITCH_PREFIX|${OPAM}"
OPAM_SWITCH_PREFIX=''; export OPAM_SWITCH_PREFIX;
NV_VARS=''; export NV_VARS;
OPAM_SWITCH_PREFIX=''; export OPAM_SWITCH_PREFIX;
### opam exec -- env | grep '^NV_VARS|^OPAM_SWITCH_PREFIX|${OPAM}'
NV_VARS=hej!!
OPAM=${OPAM}
Expand Down
Loading