Skip to content

Commit

Permalink
Move last-env OPAM_LAST_ENV files outside the switch.
Browse files Browse the repository at this point in the history
The last-env files are now stored in `~/.opam/.last-env` dir.
  • Loading branch information
moyodiallo committed May 17, 2024
1 parent 1508180 commit 3298ffd
Show file tree
Hide file tree
Showing 8 changed files with 30 additions and 29 deletions.
1 change: 1 addition & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -35,6 +35,7 @@ users)
* Allow to parse opam 2.1 switch import files containing extra-files [#5943 @kit-ty-kate - fix #5941]

## Config
* Move last-env `OPAM_LAST_ENV` files outside the switch to be in the `opam root` [#5962 @moyodiallo - fix #5823]

## Pin

Expand Down
2 changes: 1 addition & 1 deletion src/client/opamCommands.ml
Original file line number Diff line number Diff line change
Expand Up @@ -4203,7 +4203,6 @@ let clean cli =
cleandir (OpamPath.Switch.build_dir root sw);
cleandir (OpamPath.Switch.remove_dir root sw);
cleandir (OpamPath.Switch.extra_files_dir root sw);
cleandir (OpamPath.Switch.last_env root sw);
let pinning_overlay_dirs =
List.map
(fun nv -> OpamPath.Switch.Overlay.package root sw nv.name)
Expand All @@ -4223,6 +4222,7 @@ let clean cli =
List.iter (fun d ->
if not (List.mem d keep_sources_dir) then rmdir d))
switches);
if all_switches then cleandir (OpamPath.last_env root);
if repos then
(OpamFilename.with_flock `Lock_write (OpamPath.repos_lock gt.root)
@@ fun _lock ->
Expand Down
6 changes: 3 additions & 3 deletions src/client/opamConfigCommand.ml
Original file line number Diff line number Diff line change
Expand Up @@ -259,9 +259,9 @@ let load_and_verify_env ~set_opamroot ~set_opamswitch ~force_path
(* Returns [Some file] where [file] contains [updates]. [hash] should be
[OpamEnv.hash_env_updates updates] and [n] should initially be [0]. If for
whatever reason the file cannot be created, returns [None]. *)
let write_last_env_file gt switch updates =
let write_last_env_file gt updates =
let updates = check_writeable updates in
let temp_dir = OpamPath.Switch.last_env gt.root switch in
let temp_dir = OpamPath.last_env gt.root in
let hash = OpamEnv.hash_env_updates updates in
let rec aux n =
(* The principal aim here is not to spam /tmp with gazillions of files, but
Expand Down Expand Up @@ -310,7 +310,7 @@ let ensure_env_aux ?(base=[]) ?(set_opamroot=false) ?(set_opamswitch=false)
updates
in
let last_env_file =
write_last_env_file gt switch
write_last_env_file gt
(* We remove OPAMSWITCH & OPAMROOT as they are not supposed
to be reverted *)
(List.filter (fun upd ->
Expand Down
2 changes: 1 addition & 1 deletion src/format/opamFile.ml
Original file line number Diff line number Diff line change
Expand Up @@ -548,7 +548,7 @@ external open_env_updates:
(* cf. tests/lib/typeGymnastics.ml *)

(** Cached environment updates (<switch>/.opam-switch/environment
<switch>/.opam-switch/last-env/env-* last env files) *)
<opam-root>/.last-env/env-* last env files) *)

module Environment = struct include LineFile(struct

Expand Down
4 changes: 2 additions & 2 deletions src/format/opamPath.ml
Original file line number Diff line number Diff line change
Expand Up @@ -79,6 +79,8 @@ let plugin t name =
assert (sname <> "bin");
plugins t / sname

let last_env t = t / ".last-env"

module type LAYOUT = sig
type ctx
val root : dirname -> ctx -> dirname
Expand Down Expand Up @@ -140,8 +142,6 @@ module Switch = struct

let environment t a = meta t a /- env_filename

let last_env t a = meta t a / "last-env"

let env_relative_to_prefix pfx = pfx / meta_dirname /- env_filename

let installed_opams t a = meta t a / "packages"
Expand Down
5 changes: 3 additions & 2 deletions src/format/opamPath.mli
Original file line number Diff line number Diff line change
Expand Up @@ -78,6 +78,9 @@ val plugin_bin: t -> name -> filename
forbidden. *)
val plugin: t -> name -> dirname

(** The last environment used regardless the switch *)
val last_env: t -> dirname

module type LAYOUT = sig
type ctx
val root : dirname -> ctx -> dirname
Expand Down Expand Up @@ -174,8 +177,6 @@ module Switch: sig
(** Cached environment updates. *)
val environment: t -> switch -> OpamFile.Environment.t OpamFile.t

val last_env: t -> switch -> dirname

(** Like [environment], but from the switch prefix dir *)
val env_relative_to_prefix: dirname -> OpamFile.Environment.t OpamFile.t

Expand Down
1 change: 0 additions & 1 deletion tests/reftests/clean.test
Original file line number Diff line number Diff line change
Expand Up @@ -73,7 +73,6 @@ rm -rf "${BASEDIR}/OPAM/clean/.opam-switch/backup"/*
rm -rf "${BASEDIR}/OPAM/clean/.opam-switch/build"/*
rm -rf "${BASEDIR}/OPAM/clean/.opam-switch/remove"/*
rm -rf "${BASEDIR}/OPAM/clean/.opam-switch/extra-files-cache"/*
rm -rf "${BASEDIR}/OPAM/clean/.opam-switch/last-env"/*
### opam clean --untracked
Cleaning up switch clean
Remaining directories and files:
Expand Down
38 changes: 19 additions & 19 deletions tests/reftests/env.test
Original file line number Diff line number Diff line change
Expand Up @@ -518,13 +518,13 @@ Done.
### opam env --readonly --debug-level=-3 | grep "A_VAR\|FILE\\(environment\\)\|CONFIG\|^STATE" | '[0-9a-f]{32}' -> 'hash' | ';' -> ':'
CONFIG config-env
FILE(environment) Read ${BASEDIR}/OPAM/switch1/.opam-switch/environment in 0.000s
FILE(environment) Wrote ${BASEDIR}/OPAM/switch1/.opam-switch/last-env/env-hash-0 atomically in 0.000s
FILE(environment) Read ${BASEDIR}/OPAM/switch1/.opam-switch/last-env/env-hash-0 in 0.000s
FILE(environment) Wrote ${BASEDIR}/OPAM/.last-env/env-hash-0 atomically in 0.000s
FILE(environment) Read ${BASEDIR}/OPAM/.last-env/env-hash-0 in 0.000s
A_VAR='${BASEDIR}/OPAM/switch1/lib': export A_VAR:
### opam env --debug-level=-3 | grep "A_VAR\|FILE\\(environment\\)\|CONFIG\|^STATE" | '[0-9a-f]{32}' -> 'hash' | ';' -> ':'
CONFIG config-env
FILE(environment) Read ${BASEDIR}/OPAM/switch1/.opam-switch/environment in 0.000s
FILE(environment) Read ${BASEDIR}/OPAM/switch1/.opam-switch/last-env/env-hash-0 in 0.000s
FILE(environment) Read ${BASEDIR}/OPAM/.last-env/env-hash-0 in 0.000s
A_VAR='${BASEDIR}/OPAM/switch1/lib': export A_VAR:
### # missing environment file
### rm $OPAMROOT/switch1/.opam-switch/environment
Expand All @@ -533,27 +533,27 @@ CONFIG config-env
CONFIG Missing environment file, regenerate it
STATE LOAD-SWITCH-STATE @ switch1
STATE Switch state loaded in 0.000s
FILE(environment) Read ${BASEDIR}/OPAM/switch1/.opam-switch/last-env/env-hash-0 in 0.000s
FILE(environment) Read ${BASEDIR}/OPAM/.last-env/env-hash-0 in 0.000s
A_VAR='${BASEDIR}/OPAM/switch1/lib': export A_VAR:
### opam env --debug-level=-3 | grep "A_VAR\|FILE\\(environment\\)\|CONFIG\|^STATE" | '[0-9a-f]{32}' -> 'hash' | ';' -> ':'
CONFIG config-env
CONFIG Missing environment file, regenerate it
STATE LOAD-SWITCH-STATE @ switch1
STATE Switch state loaded in 0.000s
FILE(environment) Wrote ${BASEDIR}/OPAM/switch1/.opam-switch/environment atomically in 0.000s
FILE(environment) Read ${BASEDIR}/OPAM/switch1/.opam-switch/last-env/env-hash-0 in 0.000s
FILE(environment) Read ${BASEDIR}/OPAM/.last-env/env-hash-0 in 0.000s
A_VAR='${BASEDIR}/OPAM/switch1/lib': export A_VAR:
### # set via OPAMSWITCH
### OPAMSWITCH=switch2 opam env --readonly --debug-level=-3 | grep "A_VAR\|FILE\\(environment\\)\|CONFIG\|^STATE" | '[0-9a-f]{32}' -> 'hash' | ';' -> ':'
CONFIG config-env
FILE(environment) Read ${BASEDIR}/OPAM/switch2/.opam-switch/environment in 0.000s
FILE(environment) Wrote ${BASEDIR}/OPAM/switch2/.opam-switch/last-env/env-hash-0 atomically in 0.000s
FILE(environment) Read ${BASEDIR}/OPAM/switch2/.opam-switch/last-env/env-hash-0 in 0.000s
FILE(environment) Wrote ${BASEDIR}/OPAM/.last-env/env-hash-0 atomically in 0.000s
FILE(environment) Read ${BASEDIR}/OPAM/.last-env/env-hash-0 in 0.000s
A_VAR='${BASEDIR}/OPAM/switch2/lib': export A_VAR:
### OPAMSWITCH=switch2 opam env --debug-level=-3 | grep "A_VAR\|FILE\\(environment\\)\|CONFIG\|^STATE" | '[0-9a-f]{32}' -> 'hash' | ';' -> ':'
CONFIG config-env
FILE(environment) Read ${BASEDIR}/OPAM/switch2/.opam-switch/environment in 0.000s
FILE(environment) Read ${BASEDIR}/OPAM/switch2/.opam-switch/last-env/env-hash-0 in 0.000s
FILE(environment) Read ${BASEDIR}/OPAM/.last-env/env-hash-0 in 0.000s
A_VAR='${BASEDIR}/OPAM/switch2/lib': export A_VAR:
### # entering directory
### mkdir local-sw
Expand All @@ -568,13 +568,13 @@ Done.
### sh -c "cd local-sw ; opam env --readonly --debug-level=-3" | grep "A_VAR\|FILE\\(environment\\)\|CONFIG\|^STATE" | '[0-9a-f]{32}' -> 'hash' | "\(\\\\\|/\)_opam\(\\\\|/\)lib" -> '/_opam/lib' | ';' -> ':'
CONFIG config-env
FILE(environment) Read ${BASEDIR}/local-sw/_opam/.opam-switch/environment in 0.000s
FILE(environment) Wrote ${BASEDIR}/local-sw/_opam/.opam-switch/last-env/env-hash-0 atomically in 0.000s
FILE(environment) Read ${BASEDIR}/local-sw/_opam/.opam-switch/last-env/env-hash-0 in 0.000s
FILE(environment) Wrote ${BASEDIR}/OPAM/.last-env/env-hash-0 atomically in 0.000s
FILE(environment) Read ${BASEDIR}/OPAM/.last-env/env-hash-0 in 0.000s
A_VAR='${BASEDIR}/local-sw/_opam/lib': export A_VAR:
### sh -c "cd local-sw ; opam env --debug-level=-3" | grep "A_VAR\|FILE\\(environment\\)\|CONFIG\|^STATE" | '[0-9a-f]{32}' -> 'hash' | "\(\\\\\|/\)_opam\(\\\\|/\)lib" -> '/_opam/lib' | ';' -> ':'
CONFIG config-env
FILE(environment) Read ${BASEDIR}/local-sw/_opam/.opam-switch/environment in 0.000s
FILE(environment) Read ${BASEDIR}/local-sw/_opam/.opam-switch/last-env/env-hash-0 in 0.000s
FILE(environment) Read ${BASEDIR}/OPAM/.last-env/env-hash-0 in 0.000s
A_VAR='${BASEDIR}/local-sw/_opam/lib': export A_VAR:
### # moving a switch
### mv local-sw local-sw.new
Expand All @@ -585,8 +585,8 @@ CONFIG Switch has moved from ${BASEDIR}/local-sw/_opam
CONFIG Regenerating environment file
STATE LOAD-SWITCH-STATE @ ${BASEDIR}/local-sw.new
STATE Switch state loaded in 0.000s
FILE(environment) Wrote ${BASEDIR}/local-sw.new/_opam/.opam-switch/last-env/env-hash-0 atomically in 0.000s
FILE(environment) Read ${BASEDIR}/local-sw.new/_opam/.opam-switch/last-env/env-hash-0 in 0.000s
FILE(environment) Wrote ${BASEDIR}/OPAM/.last-env/env-hash-0 atomically in 0.000s
FILE(environment) Read ${BASEDIR}/OPAM/.last-env/env-hash-0 in 0.000s
A_VAR='${BASEDIR}/local-sw.new/_opam/lib': export A_VAR:
### opam env --switch ./local-sw.new --debug-level=-3 | grep "A_VAR\|FILE\\(environment\\)\|CONFIG\|^STATE" | '[0-9a-f]{32}' -> 'hash' | "\(\\\\\|/\)_opam\(\\\\|/\)lib" -> '/_opam/lib' | ';' -> ':'
CONFIG config-env
Expand All @@ -596,33 +596,33 @@ CONFIG Regenerating environment file
STATE LOAD-SWITCH-STATE @ ${BASEDIR}/local-sw.new
STATE Switch state loaded in 0.000s
FILE(environment) Wrote ${BASEDIR}/local-sw.new/_opam/.opam-switch/environment atomically in 0.000s
FILE(environment) Read ${BASEDIR}/local-sw.new/_opam/.opam-switch/last-env/env-hash-0 in 0.000s
FILE(environment) Read ${BASEDIR}/OPAM/.last-env/env-hash-0 in 0.000s
A_VAR='${BASEDIR}/local-sw.new/_opam/lib': export A_VAR:
### opam env --switch ./local-sw.new --debug-level=-3 | grep "A_VAR\|FILE\\(environment\\)\|CONFIG\|^STATE" | '[0-9a-f]{32}' -> 'hash' | "\(\\\\\|/\)_opam\(\\\\|/\)lib" -> '/_opam/lib' | ';' -> ':'
CONFIG config-env
FILE(environment) Read ${BASEDIR}/local-sw.new/_opam/.opam-switch/environment in 0.000s
FILE(environment) Read ${BASEDIR}/local-sw.new/_opam/.opam-switch/last-env/env-hash-0 in 0.000s
FILE(environment) Read ${BASEDIR}/OPAM/.last-env/env-hash-0 in 0.000s
A_VAR='${BASEDIR}/local-sw.new/_opam/lib': export A_VAR:
### : opam exec & environment regeneration :
### opam exec --debug-level=-3 -- sh -c "echo $A_VAR" | grep "A_VAR\|FILE\\(environment\\)\|CONFIG\|^STATE" | grep -v PROC | '[0-9a-f]{32}' -> 'hash' | ';' -> ':'
CONFIG config-exec command=sh -c echo $A_VAR
FILE(environment) Read ${BASEDIR}/OPAM/switch1/.opam-switch/environment in 0.000s
FILE(environment) Read ${BASEDIR}/OPAM/switch1/.opam-switch/last-env/env-hash-0 in 0.000s
FILE(environment) Read ${BASEDIR}/OPAM/.last-env/env-hash-0 in 0.000s
### rm $OPAMROOT/switch1/.opam-switch/environment
### opam exec --readonly --debug-level=-3 -- sh -c "echo $A_VAR" | grep "A_VAR\|FILE\\(environment\\)\|CONFIG\|^STATE" | grep -v PROC | '[0-9a-f]{32}' -> 'hash' | ';' -> ':'
CONFIG config-exec command=sh -c echo $A_VAR
CONFIG Missing environment file, regenerate it
STATE LOAD-SWITCH-STATE @ switch1
STATE Switch state loaded in 0.000s
FILE(environment) Read ${BASEDIR}/OPAM/switch1/.opam-switch/last-env/env-hash-0 in 0.000s
FILE(environment) Read ${BASEDIR}/OPAM/.last-env/env-hash-0 in 0.000s
### opam exec --debug-level=-3 -- sh -c "echo $A_VAR" | grep "A_VAR\|FILE\\(environment\\)\|CONFIG\|^STATE" | grep -v PROC | '[0-9a-f]{32}' -> 'hash' | ';' -> ':'
CONFIG config-exec command=sh -c echo $A_VAR
CONFIG Missing environment file, regenerate it
STATE LOAD-SWITCH-STATE @ switch1
STATE Switch state loaded in 0.000s
FILE(environment) Wrote ${BASEDIR}/OPAM/switch1/.opam-switch/environment atomically in 0.000s
FILE(environment) Read ${BASEDIR}/OPAM/switch1/.opam-switch/last-env/env-hash-0 in 0.000s
FILE(environment) Read ${BASEDIR}/OPAM/.last-env/env-hash-0 in 0.000s
### opam exec --debug-level=-3 -- sh -c "echo $A_VAR" | grep "A_VAR\|FILE\\(environment\\)\|CONFIG\|^STATE" | grep -v PROC | '[0-9a-f]{32}' -> 'hash' | ';' -> ':'
CONFIG config-exec command=sh -c echo $A_VAR
FILE(environment) Read ${BASEDIR}/OPAM/switch1/.opam-switch/environment in 0.000s
FILE(environment) Read ${BASEDIR}/OPAM/switch1/.opam-switch/last-env/env-hash-0 in 0.000s
FILE(environment) Read ${BASEDIR}/OPAM/.last-env/env-hash-0 in 0.000s

0 comments on commit 3298ffd

Please sign in to comment.