Skip to content

Commit

Permalink
Redirect opam on Windows if path contains a space.
Browse files Browse the repository at this point in the history
It is needed for Cygwin installation, that doesn't handle paths with
space.
At init, detection and redirection are done, afterwards opam always load
redirected opam root.
Original root directory is stored in
`OpamStateConfig.!r.original_root_dir`.

Co-authored-by: David Allsopp <david.allsopp@metastack.com>
  • Loading branch information
rjbou and dra27 committed Jun 10, 2024
1 parent f6baa94 commit ddc6389
Show file tree
Hide file tree
Showing 5 changed files with 174 additions and 63 deletions.
1 change: 1 addition & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -29,6 +29,7 @@ users)
* Enhance the Git menu by warning if the user appears to need to restart the shell to pick up PATH changes [#5963 @dra27]
* Include Git for Windows installations in the list of possibilities where the user instructed Git-for-Windows setup not to update PATH [#5963 @dra27]
* [BUG] Fail if `--git-location` points to a directory not containing git [#6000 @dra27]
* Redirect the opam root to `C:\opamroot-xxx` when the opam root contains spaces on Windows [#5457 @rjbou @dra27]

## Config report

Expand Down
142 changes: 137 additions & 5 deletions src/client/opamClient.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1645,6 +1645,114 @@ let reinit ?(init_config=OpamInitDefaults.init_config()) ~interactive
in
OpamRepositoryState.drop rt

let has_space s = OpamStd.String.contains_char s ' '

let default_redirect_root = OpamFilename.Dir.of_string "C:\\opamroot"

let setup_redirection target =
let {contents = {OpamStateConfig.original_root_dir = root; _}} =
OpamStateConfig.r
in
let target =
match target with
| Some target -> target
| None ->
OpamFilename.mkdir default_redirect_root;
let readme = OpamFilename.Op.(default_redirect_root // "ReadMe.txt") in
if not (OpamFilename.exists readme) then
OpamFilename.write readme
"This directory is used to contain redirected opam roots.\n\n\
The contents may be shared with other users on this system.";
OpamSystem.mk_unique_dir ~dir:(OpamFilename.Dir.to_string default_redirect_root) ()
in
let root_dir = OpamFilename.Dir.of_string target in
OpamFilename.write (OpamPath.redirected root) target;
OpamStateConfig.update ~root_dir ();
root_dir

let get_redirected_root () =
let {contents = {OpamStateConfig.original_root_dir = root; root_from; _}} =
OpamStateConfig.r
in
let r = OpamConsole.colorise `bold (OpamFilename.Dir.to_string root) in
let collision =
let collision = OpamConsole.utf8_symbol OpamConsole.Symbols.collision "" in
if collision = "" then
""
else
" " ^ collision
in
let options = [
`Redirect, Printf.sprintf
"Redirect files to a directory in %s"
(OpamConsole.colorise `bold (OpamFilename.Dir.to_string default_redirect_root));
`Ask, "Redirect files to an alternate directory";
`Endure, Printf.sprintf
"Do not redirect anything and stick with %s%s" r collision;
`Quit, "Abort initialisation"
] in
let default, explanation =
match root_from with
| `Command_line ->
(* The user has been explicit with --root; nemo salvet modo... *)
`Endure,
"You have specified a root directory for opam containing a space."
| `Env ->
(* The user has perhaps carelessly set an environment variable *)
`Redirect,
"Your OPAMROOT environment variable contains a space."
| `Default ->
(* The user has fallen victim to the defaults of Windows Setup and has a
space in their user name *)
`Redirect,
Printf.sprintf
"By default, opam would store its data in:\n\
%s\n\
however, this directory contains a space." r
in
let rec ask () =
let check r =
if Filename.is_relative r then begin
OpamConsole.msg
"That path is relative!\n\
Please enter an absolute path without spaces.\n";
ask ()
end else if has_space r then begin
OpamConsole.msg
"That path contains contains a space!\n\
Please enter an absolute path without spaces.\n";
ask ()
end else
Some (Some r)
in
OpamStd.Option.replace check (OpamConsole.read "Root directory for opam: ")
in
let rec menu () =
match OpamConsole.menu "Where should opam store files?" ~default ~options
~no:default with
| `Redirect ->
Some None
| `Endure ->
None
| `Ask ->
let r = ask () in
if r = None then
menu ()
else
r
| `Quit ->
OpamStd.Sys.exit_because `Aborted
in
OpamConsole.header_msg "opam root file store";
OpamConsole.msg
"\n\
%s\n\
\n\
Many parts of the OCaml ecosystem do not presently work correctly\n\
when installed to directories containing spaces. You have been warned!%s\n\
\n" explanation collision;
Option.map setup_redirection (menu ())

let init
~init_config ~interactive
?repo ?(bypass_checks=false)
Expand All @@ -1654,10 +1762,34 @@ let init
shell =
log "INIT %a"
(slog @@ OpamStd.Option.to_string OpamRepositoryBackend.to_string) repo;
let original_root = OpamStateConfig.(!r.original_root_dir) in
let root_empty =
not (OpamFilename.exists_dir original_root)
|| OpamFilename.dir_is_empty original_root in
let root = OpamStateConfig.(!r.root_dir) in
let root, remove_root =
let ignore_non_fatal f x =
try f x
with e -> OpamStd.Exn.fatal e
in
let new_root =
if root_empty &&
Sys.win32 &&
has_space (OpamFilename.Dir.to_string root) then
get_redirected_root ()
else
None
in
match new_root with
| None ->
root, (fun () -> ignore_non_fatal OpamFilename.rmdir root)
| Some root ->
root, (fun () ->
ignore_non_fatal OpamFilename.rmdir root;
ignore_non_fatal OpamFilename.rmdir original_root
)
in
let config_f = OpamPath.config root in
let root_empty =
not (OpamFilename.exists_dir root) || OpamFilename.dir_is_empty root in

let gt, rt, default_compiler =
if OpamFile.exists config_f then (
Expand All @@ -1671,7 +1803,7 @@ let init
) else (
if not root_empty then (
OpamConsole.warning "%s exists and is not empty"
(OpamFilename.Dir.to_string root);
(OpamFilename.Dir.to_string original_root);
if not (OpamConsole.confirm "Proceed?") then
OpamStd.Sys.exit_because `Aborted);
try
Expand Down Expand Up @@ -1743,7 +1875,7 @@ let init
in
if failed <> [] then
(if root_empty then
(try OpamFilename.rmdir root with _ -> ());
remove_root ();
OpamConsole.error_and_exit `Sync_error
"Initial download of repository failed.");
let default_compiler =
Expand Down Expand Up @@ -1778,7 +1910,7 @@ let init
OpamStd.Exn.finalise e @@ fun () ->
if not (OpamConsole.debug ()) && root_empty then begin
OpamSystem.release_all_locks ();
OpamFilename.rmdir root
remove_root ()
end)
in
OpamEnv.setup root ~interactive
Expand Down
14 changes: 10 additions & 4 deletions src/state/opamStateConfig.ml
Original file line number Diff line number Diff line change
Expand Up @@ -71,6 +71,12 @@ type t = {
no_depexts: bool;
}

let win_space_redirection root =
let redirected = OpamPath.redirected root in
if OpamFilename.exists redirected then
OpamFilename.Dir.of_string (OpamFilename.read redirected)
else root

let default_root =
(* On Windows, if a .opam directory is found in %HOME% or %USERPROFILE% then
then we'll use it. Otherwise, we use %LOCALAPPDATA%. *)
Expand All @@ -88,7 +94,7 @@ let default_root =
concat_and_resolve local_appdata "opam"

let default = {
root_dir = default_root;
root_dir = win_space_redirection default_root;
original_root_dir = default_root;
root_from = `Default;
current_switch = None;
Expand Down Expand Up @@ -185,7 +191,7 @@ let initk k =
| None -> None, None, None
| Some root ->
let root = OpamFilename.Dir.of_string root in
Some root, Some root, Some `Env
Some (win_space_redirection root), Some root, Some `Env
in
let current_switch, switch_from =
match E.switch () with
Expand Down Expand Up @@ -219,11 +225,11 @@ let init ?noop:_ = initk (fun () -> ())

let opamroot ?root_dir () =
match root_dir with
| Some root -> `Command_line, root
| Some root -> `Command_line, win_space_redirection root
| None ->
match OpamStd.Env.getopt "OPAMROOT" with
| Some root ->
`Env, OpamFilename.Dir.of_string root
`Env, win_space_redirection (OpamFilename.Dir.of_string root)
| None ->
`Default, default.root_dir

Expand Down
54 changes: 0 additions & 54 deletions tests/reftests/env.test
Original file line number Diff line number Diff line change
Expand Up @@ -439,60 +439,6 @@ The following actions will be performed:
Done.
### opam exec -- sh -c "eval $(opam env | tr -d '\\r'); opam remove foo; opam env; eval $(opam env | tr -d '\\r'); opam env" | grep "FOO"
FOO=''; export FOO;
### : root and switch with spaces :
### RT="$BASEDIR/root 2"
### SW="switch w spaces"
### OPAMNOENVNOTICE=0
### opam init -na --bare --bypass-check --disable-sandbox --root "$RT" defaut ./REPO | grep -v Cygwin
No configuration file found, using built-in defaults.

<><> Fetching repository information ><><><><><><><><><><><><><><><><><><><><><>
[defaut] Initialised
### opam switch create "./$SW" nv --root "$RT"

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

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
-> installed nv.1
Done.
# Run eval $(opam env '--root=${BASEDIR}/root 2' '--switch=${BASEDIR}/switch w spaces') to update the current shell environment
### opam env --root "$RT" --switch "./$SW" | grep "NV_VARS" | ';' -> ':'
NV_VARS3='foo:/yet/another/different/path': export NV_VARS3:
NV_VARS4='': export NV_VARS4:
NV_VARS_5925_1='foo': export NV_VARS_5925_1:
NV_VARS_5925_2='foo': export NV_VARS_5925_2:
NV_VARS_5925_3='foo': export NV_VARS_5925_3:
NV_VARS_5925_4='foo': export NV_VARS_5925_4:
NV_VARS_5925_5='foo:': export NV_VARS_5925_5:
NV_VARS_5925_6='foo:': export NV_VARS_5925_6:
NV_VARS_5925_7=':foo': export NV_VARS_5925_7:
NV_VARS_5925_8=':foo': export NV_VARS_5925_8:
NV_VARS_5926_L_1='b::a': export NV_VARS_5926_L_1:
NV_VARS_5926_L_2='b::a': export NV_VARS_5926_L_2:
NV_VARS_5926_L_3=':a:b': export NV_VARS_5926_L_3:
NV_VARS_5926_L_4=':a:b': export NV_VARS_5926_L_4:
NV_VARS_5926_L_5='b::a': export NV_VARS_5926_L_5:
NV_VARS_5926_L_6='b::a': export NV_VARS_5926_L_6:
NV_VARS_5926_L_7=':a:b': export NV_VARS_5926_L_7:
NV_VARS_5926_L_8=':a:b': export NV_VARS_5926_L_8:
NV_VARS_5926_M_1='b:a1::a2': export NV_VARS_5926_M_1:
NV_VARS_5926_M_2='a1::a2:b': export NV_VARS_5926_M_2:
NV_VARS_5926_M_3='b:a1::a2': export NV_VARS_5926_M_3:
NV_VARS_5926_M_4='a1::a2:b': export NV_VARS_5926_M_4:
NV_VARS_5926_S_1='a:': export NV_VARS_5926_S_1:
NV_VARS_5926_S_2=':a': export NV_VARS_5926_S_2:
NV_VARS_5926_S_3='a:': export NV_VARS_5926_S_3:
NV_VARS_5926_S_4=':a': export NV_VARS_5926_S_4:
NV_VARS_5926_T_1='b:a:': export NV_VARS_5926_T_1:
NV_VARS_5926_T_2='b:a:': export NV_VARS_5926_T_2:
NV_VARS_5926_T_3='a::b': export NV_VARS_5926_T_3:
NV_VARS_5926_T_4='a::b': export NV_VARS_5926_T_4:
NV_VARS_5926_T_5='b:a:': export NV_VARS_5926_T_5:
NV_VARS_5926_T_6='b:a:': export NV_VARS_5926_T_6:
NV_VARS_5926_T_7='a::b': export NV_VARS_5926_T_7:
NV_VARS_5926_T_8='a::b': export NV_VARS_5926_T_8:
### OPAMNOENVNOTICE=1
### : Env hooks :
### <pkg:av.1>
opam-version: "2.0"
Expand Down
26 changes: 26 additions & 0 deletions tests/reftests/env.unix.test
Original file line number Diff line number Diff line change
@@ -1,4 +1,30 @@
N0REP0
### : root and switches with spaces :
### <pkg:nv.1>
opam-version: "2.0"
flags: compiler
### RT="$BASEDIR/root 2"
### SW="switch w spaces"
### OPAMNOENVNOTICE=0
### opam init -na --bare --bypass-check --disable-sandbox --root "$RT" defaut ./REPO
No configuration file found, using built-in defaults.

<><> Fetching repository information ><><><><><><><><><><><><><><><><><><><><><>
[defaut] Initialised
### opam switch create "./$SW" nv --root "$RT"

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

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
-> installed nv.1
Done.
# Run eval $(opam env '--root=${BASEDIR}/root 2' '--switch=${BASEDIR}/switch w spaces') to update the current shell environment
### opam env --root "$RT" --switch "./$SW" | grep "PREFIX" | ';' -> ':'
OPAM_SWITCH_PREFIX='${BASEDIR}/switch w spaces/_opam': export OPAM_SWITCH_PREFIX:
### opam var root --root "$RT"
${BASEDIR}/root 2
### OPAMNOENVNOTICE=1
### : setenv & build env rewriting :
### opam switch create rewriting --empty
### ::::::::::::::::::
Expand Down

0 comments on commit ddc6389

Please sign in to comment.