Skip to content
New issue

Have a question about this project? # for a free GitHub account to open an issue and contact its maintainers and the community.

By clicking “#”, you agree to our terms of service and privacy statement. We’ll occasionally send you account related emails.

Already on GitHub? # to your account

Ensure package variables are available at package install #4841

Merged
merged 5 commits into from
Oct 18, 2021
Merged
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
2 changes: 2 additions & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -36,6 +36,7 @@ users)
* Put back support for switch creation with packages argument and
`--packages` option with cli 2.0, and a specific error message for cli 2.1
[#4853 @rjbou - fix #4843]
* Ensure setenv can use package variables defined during the build [#4841 @dra27]

## Pin
*
Expand Down Expand Up @@ -143,6 +144,7 @@ users)
* opam root version: add local switch cases [#4763 @rjbou] [2.1.0~rc2 #4715]
* opam root version: add reinit test casess [#4763 @rjbou] [2.1.0~rc2 #4750]
* Add `opam-cat` to normalise opam file printing [#4763 @rjbou @dra27] [2.1.0~rc2 #4715]
* Add & update env tests [#4861 #4841 @rjbou @dra27]

## Github Actions
* Add solver backends compile test [#4723 @rjbou] [2.1.0~rc2 #4720]
Expand Down
56 changes: 29 additions & 27 deletions src/client/opamAction.ml
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ module PackageActionGraph = OpamSolver.ActionGraph
(* Preprocess install: returns a list of files to install, and their respective
install functions *)
let preprocess_dot_install_t st nv build_dir =
if not (OpamFilename.exists_dir build_dir) then [] else
if not (OpamFilename.exists_dir build_dir) then [], None else
let root = st.switch_global.root in
let switch_prefix = OpamPath.Switch.root root st.switch in
let file_wo_prefix f = OpamFilename.remove_prefix switch_prefix f in
Expand All @@ -37,7 +37,7 @@ let preprocess_dot_install_t st nv build_dir =
OpamFile.Dot_install.write install_loc install;

(* .config *)
let files_and_installs =
let (files_and_installs, config) =
let config_f = OpamPath.Builddir.config build_dir nv in
let config = OpamFile.Dot_config.read_opt config_f in
(match config with
Expand All @@ -51,8 +51,8 @@ let preprocess_dot_install_t st nv build_dir =
let dot_config = OpamPath.Switch.config root st.switch name in
OpamFile.Dot_config.write dot_config config; None
in
[(file, inst)]
| None -> [])
([(file, inst)], Some config)
| None -> ([], None))
in

let check ~src ~dst base =
Expand Down Expand Up @@ -183,11 +183,11 @@ let preprocess_dot_install_t st nv build_dir =
(file, inst)) (I.misc install)
in

List.rev_append files_and_installs misc_files
List.rev_append files_and_installs misc_files, config

(* Returns function to install package files from [.install] *)
let preprocess_dot_install st nv build_dir =
let files_and_installs = preprocess_dot_install_t st nv build_dir in
let files_and_installs, config = preprocess_dot_install_t st nv build_dir in
let root = st.switch_global.root in
let files, installs = List.split files_and_installs in
let really_process_dot_install () =
Expand Down Expand Up @@ -235,7 +235,7 @@ let preprocess_dot_install st nv build_dir =
if had_windows_warnings () then
failwith "Strict mode is enabled - previous warnings considered fatal"
in
files, really_process_dot_install
files, really_process_dot_install, config

let download_package st nv =
log "download_package: %a" (slog OpamPackage.to_string) nv;
Expand Down Expand Up @@ -947,30 +947,32 @@ let install_package t ?(test=false) ?(doc=false) ?build_dir nv =
let install_job () =
pre_install ()
@@+ function
| Some (_, result) -> Done (Some (OpamSystem.Process_error result))
| Some (_, result) -> Done (Right (OpamSystem.Process_error result))
| None ->
run_commands commands @@| function
| Some e -> Some e
| Some e -> Right e
| None ->
try
let _, process_dot_install = preprocess_dot_install t nv dir in
let _, process_dot_install, config = preprocess_dot_install t nv dir in
process_dot_install ();
None
with e -> Some e
Left config
with e -> Right e
in
let install_and_track_job () =
pre_install ()
@@+ function
| Some (_, result) ->
Done (Some (OpamSystem.Process_error result), OpamStd.String.Map.empty)
Done (Right (OpamSystem.Process_error result), OpamStd.String.Map.empty)
| None ->
let installed_files, process_dot_install =
let installed_files, process_dot_install, config =
preprocess_dot_install t nv dir
in
OpamDirTrack.track_files ~prefix:switch_prefix installed_files
(fun () -> process_dot_install () ; Done None)
@@+ function
| _, changes -> Done (Left config, changes)
in
let post_install error changes =
let post_install status changes =
let local =
let added =
let open OpamDirTrack in
Expand All @@ -979,8 +981,8 @@ let install_package t ?(test=false) ?(doc=false) ?build_dir nv =
| _ -> None)
(OpamStd.String.Map.bindings changes)
in
opam_local_env_of_status (match error with
| Some (OpamSystem.Process_error r) -> Some r
opam_local_env_of_status (match status with
| Right (OpamSystem.Process_error r) -> Some r
| _ -> None) |>
OpamVariable.Map.add
(OpamVariable.of_string "installed-files")
Expand All @@ -993,17 +995,17 @@ let install_package t ?(test=false) ?(doc=false) ?build_dir nv =
OpamProcess.Job.of_fun_list ~keep_going:true
(List.map (fun cmd () -> mk_cmd cmd) hooks)
@@+ fun error_post ->
match error, error_post with
| Some err, _ -> Done (Some err, changes)
| None, Some (_cmd, r) -> Done (Some (OpamSystem.Process_error r), changes)
| None, None ->
match status, error_post with
| Right err, _ -> Done (Right err, changes)
| _, Some (_cmd, r) -> Done (Right (OpamSystem.Process_error r), changes)
| Left config, None ->
let changes =
if has_hooks then
OpamDirTrack.update switch_prefix changes
else
changes
in
Done (None, changes)
Done (Left config, changes)
in
let rel_meta_dir =
OpamFilename.(Base.of_string (remove_prefix_dir switch_prefix
Expand All @@ -1015,13 +1017,13 @@ let install_package t ?(test=false) ?(doc=false) ?build_dir nv =
OpamDirTrack.track switch_prefix
~except:(OpamFilename.Base.Set.singleton rel_meta_dir)
install_job)
@@+ fun (error, changes) -> post_install error changes
@@+ fun (status, changes) -> post_install status changes
@@+ function
| Some e, changes ->
| Right e, changes ->
remove_package t ~silent:true ~changes ~build_dir:dir nv @@+ fun () ->
OpamStd.Exn.fatal e;
Done (Some e)
| None, changes ->
Done (Right e)
| Left config, changes ->
let changes_f = OpamPath.Switch.changes root t.switch nv.name in
OpamFile.Changes.write changes_f changes;
OpamConsole.msg "%s installed %s.%s\n"
Expand All @@ -1045,4 +1047,4 @@ let install_package t ?(test=false) ?(doc=false) ?build_dir nv =
OpamConsole.warning "%s claims to be a plugin but no %s file was found"
name (OpamFilename.to_string target)
);
Done None
Done (Left config)
2 changes: 1 addition & 1 deletion src/client/opamAction.mli
Original file line number Diff line number Diff line change
Expand Up @@ -48,7 +48,7 @@ val build_package:
metadata. See {!build_package} to build the package. *)
val install_package:
rw switch_state -> ?test:bool -> ?doc:bool -> ?build_dir:dirname -> package ->
exn option OpamProcess.job
(OpamFile.Dot_config.t option, exn) OpamCompat.Either.t OpamProcess.job

(** Find out if the package source is needed for uninstall *)
val removal_needs_download: 'a switch_state -> package -> bool
Expand Down
17 changes: 11 additions & 6 deletions src/client/opamSolution.ml
Original file line number Diff line number Diff line change
Expand Up @@ -351,9 +351,14 @@ let parallel_apply t

let bypass_ref = ref (t.switch_config.OpamFile.Switch_config.depext_bypass) in

let add_to_install nv =
let add_to_install nv conf =
let root = OpamPackage.Name.Set.mem nv.name root_installs in
t_ref := OpamSwitchAction.add_to_installed !t_ref ~root nv;
let t = !t_ref in
let conf_files =
let add_conf conf = OpamPackage.Name.Map.add nv.name conf t.conf_files in
OpamStd.Option.map_default add_conf t.conf_files conf
in
t_ref := OpamSwitchAction.add_to_installed {t with conf_files} ~root nv;
let missing_depexts =
(* Turns out these depexts weren't needed after all. Remember that and
make the bypass permanent. *)
Expand Down Expand Up @@ -544,7 +549,7 @@ let parallel_apply t
| `Install nv ->
OpamConsole.msg "Faking installation of %s\n"
(OpamPackage.to_string nv);
add_to_install nv;
add_to_install nv None;
Done (`Successful (OpamPackage.Set.add nv installed, removed))
| `Remove nv ->
remove_from_install nv;
Expand Down Expand Up @@ -602,11 +607,11 @@ let parallel_apply t
in
let build_dir = OpamPackage.Map.find_opt nv inplace in
(OpamAction.install_package t ~test ~doc ?build_dir nv @@+ function
| None ->
add_to_install nv;
| Left conf ->
add_to_install nv conf;
store_time ();
Done (`Successful (OpamPackage.Set.add nv installed, removed))
| Some exn ->
| Right exn ->
store_time ();
Done (`Exception exn))
| `Remove nv ->
Expand Down
11 changes: 11 additions & 0 deletions src/core/opamCompat.ml
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,17 @@ module String = String

module Char = Char

module Either =
#if OCAML_VERSION >= (4, 12, 0)
Either
#else
struct
type ('a, 'b) t =
| Left of 'a
| Right of 'b
end
#endif

module Printexc =
#if OCAML_VERSION >= (4, 5, 0)
Printexc
Expand Down
11 changes: 11 additions & 0 deletions src/core/opamCompat.mli
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,17 @@ module String = String

module Char = Char

module Either
#if OCAML_VERSION >= (4, 12, 0)
= Either
#else
: sig
type ('a, 'b) t =
| Left of 'a
| Right of 'b
end
#endif

module Printexc
#if OCAML_VERSION >= (4, 5, 0)
= Printexc
Expand Down
4 changes: 4 additions & 0 deletions src/format/opamTypes.mli
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,10 @@ type 'a error = [
]
type ('a,'b) status = [ 'a success | 'b error ]

type ('a, 'b) either = ('a, 'b) OpamCompat.Either.t =
| Left of 'a
| Right of 'b

(** {2 Filenames} *)

(** Basenames *)
Expand Down
24 changes: 24 additions & 0 deletions tests/reftests/env.test
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
N0REP0
### : Revert env :
### <pkg:nv.1>
opam-version: "2.0"
setenv: [ NV_VARS += "%{_:doc}%:%{_:share}%" ]
Expand All @@ -25,3 +26,26 @@ NV_VARS=''- export NV_VARS-
NV_VARS='${BASEDIR}/OPAM/setenv/doc/nv-${OPAMTMP}/OPAM/setenv/share/nv-/another/path'- export NV_VARS-
### opam exec -- opam env --revert | grep "NV_VARS" | '[:;]' -> '-'
NV_VARS='/another/path'- export NV_VARS-
### : package variable available at install stage :
### <pkg:nv.1>
opam-version: "2.0"
setenv: [NV_VARS = "%{_:nv_config}%"]
flags: compiler
### <pkg:nv.1:nv.config>
opam-version: "2.0"
variables { nv_config: "hej!!" }
### opam update

<><> Updating package repositories ><><><><><><><><><><><><><><><><><><><><><><>
[default] synchronised from file://${BASEDIR}/REPO
Now run 'opam upgrade' to apply any package updates.
### opam switch create conffile nv

<><> Installing new switch packages <><><><><><><><><><><><><><><><><><><><><><>
Switch invariant: ["nv"]

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
-> installed nv.1
Done.
### opam env | grep NV_VARS
NV_VARS='hej!!'; export NV_VARS;