Skip to content

Commit 94ef0e4

Browse files
rjboukit-ty-kate
authored andcommitted
Redirect opam on Windows if path contains a space.
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`.
1 parent b397ed1 commit 94ef0e4

File tree

7 files changed

+107
-77
lines changed

7 files changed

+107
-77
lines changed

master_changes.md

+1
Original file line numberDiff line numberDiff line change
@@ -28,6 +28,7 @@ users)
2828
* Skip Git-for-Windows menu if the Git binary resolved in PATH is Git-for-Windows [#5963 @dra27 - fix #5835]
2929
* Enhance the Git menu by warning if the user appears to need to restart the shell to pick up PATH changes [#5963 @dra27]
3030
* Include Git for Windows installations in the list of possibilities where the user instructed Git-for-Windows setup not to update PATH [#5963 @dra27]
31+
* Redirect the opam root to C:\opamroot when the opam root contains spaces on Windows [#5457 @rjbou]
3132

3233
## Config report
3334

src/client/opamClient.ml

+36-1
Original file line numberDiff line numberDiff line change
@@ -1235,7 +1235,42 @@ let init
12351235
shell =
12361236
log "INIT %a"
12371237
(slog @@ OpamStd.Option.to_string OpamRepositoryBackend.to_string) repo;
1238-
let root = OpamStateConfig.(!r.root_dir) in
1238+
let root =
1239+
let root = OpamStateConfig.(!r.root_dir) in
1240+
let has_space s = OpamStd.String.contains_char s ' ' in
1241+
if Sys.win32 &&
1242+
has_space (OpamFilename.Dir.to_string root) then
1243+
(let default = "C:\\opamroot" in
1244+
let rec ask () =
1245+
match OpamConsole.read "Opam root: " with
1246+
| Some r ->
1247+
if has_space r then
1248+
(OpamConsole.msg
1249+
"Given path '%s' contains space, please choose another one.\n"
1250+
(OpamConsole.colorise `bold r);
1251+
ask ())
1252+
else r
1253+
| None -> default
1254+
in
1255+
let new_root_f =
1256+
if OpamConsole.confirm ~default:false
1257+
"Your opam root path '%s' contains a space, we'll redirect to \
1258+
'%s'.\nDo you want to choose and enter another spaceless folder?"
1259+
(OpamFilename.Dir.to_string root) default then
1260+
ask ()
1261+
else default
1262+
in
1263+
let new_root = OpamFilename.Dir.of_string new_root_f in
1264+
OpamFilename.write (OpamPath.redirected root) new_root_f;
1265+
(* Add the readme file in C:\opamroot as redirected *)
1266+
OpamFilename.write
1267+
OpamFilename.Op.(root // "readme.txt")
1268+
(Printf.sprintf "Opam root redirected from %s"
1269+
(OpamFilename.Dir.to_string OpamStateConfig.(!r.root_dir)));
1270+
OpamStateConfig.update ~root_dir:new_root ();
1271+
new_root)
1272+
else root
1273+
in
12391274
let config_f = OpamPath.config root in
12401275
let root_empty =
12411276
not (OpamFilename.exists_dir root) || OpamFilename.dir_is_empty root in

src/client/opamClientConfig.ml

+9
Original file line numberDiff line numberDiff line change
@@ -210,6 +210,15 @@ let opam_init ?root_dir ?strict ?solver =
210210

211211
(* (i) get root dir *)
212212
let root = OpamStateConfig.opamroot ?root_dir () in
213+
if Sys.win32
214+
(* if default, redirection will be handled by opam init, or should have
215+
been handled *)
216+
&& (root_dir <> None || OpamStateConfig.E.root () <> None)
217+
&& OpamStd.String.contains_char (OpamFilename.Dir.to_string root) ' ' then
218+
OpamConsole.error "You opam root directory contains a space, this may lead \
219+
to several malfunction... bzzz.... nooo%s"
220+
(* NOTE: UTF-8 Collision emoji *)
221+
(if OpamConsole.color () then "\xF0\x9F\x92\xA5" else "");
213222

214223
(* (ii) load conf file and set defaults *)
215224
(* the init for OpamFormat is done in advance since (a) it has an effect on

src/state/opamStateConfig.ml

+27-17
Original file line numberDiff line numberDiff line change
@@ -70,23 +70,30 @@ type t = {
7070
no_depexts: bool;
7171
}
7272

73+
let win_space_redirection root =
74+
let redirected = OpamPath.redirected root in
75+
if OpamFilename.exists redirected then
76+
OpamFilename.Dir.of_string (OpamFilename.read redirected)
77+
else root
78+
79+
let default_root () =
80+
(* On Windows, if a .opam directory is found in %HOME% or %USERPROFILE% then
81+
then we'll use it. Otherwise, we use %LOCALAPPDATA%. *)
82+
let home_location =
83+
let open OpamFilename in
84+
concat_and_resolve (Dir.of_string (OpamStd.Sys.home ())) ".opam"
85+
in
86+
if not Sys.win32 || OpamFilename.exists_dir home_location then
87+
home_location
88+
else
89+
let open OpamFilename in
90+
let local_appdata =
91+
Dir.of_string (OpamStubs.getPathToLocalAppData ())
92+
in
93+
concat_and_resolve local_appdata "opam"
94+
7395
let default = {
74-
root_dir = (
75-
(* On Windows, if a .opam directory is found in %HOME% or %USERPROFILE% then
76-
then we'll use it. Otherwise, we use %LOCALAPPDATA%. *)
77-
let home_location =
78-
let open OpamFilename in
79-
concat_and_resolve (Dir.of_string (OpamStd.Sys.home ())) ".opam"
80-
in
81-
if not Sys.win32 || OpamFilename.exists_dir home_location then
82-
home_location
83-
else
84-
let open OpamFilename in
85-
let local_appdata =
86-
Dir.of_string (OpamStubs.getPathToLocalAppData ())
87-
in
88-
concat_and_resolve local_appdata "opam"
89-
);
96+
root_dir = default_root () |> win_space_redirection;
9097
original_root_dir = default_root ();
9198
current_switch = None;
9299
switch_from = `Default;
@@ -180,7 +187,9 @@ let initk k =
180187
| Some s -> Some (OpamSwitch.of_string s), Some `Env
181188
in
182189
setk (setk (fun c -> r := c; k)) !r
183-
?root_dir:(E.root () >>| OpamFilename.Dir.of_string)
190+
?root_dir:(E.root ()
191+
>>| OpamFilename.Dir.of_string
192+
>>| win_space_redirection)
184193
?original_root_dir:(E.root () >>| OpamFilename.Dir.of_string)
185194
?current_switch
186195
?switch_from
@@ -208,6 +217,7 @@ let opamroot ?root_dir () =
208217
(root_dir >>+ fun () ->
209218
OpamStd.Env.getopt "OPAMROOT" >>| OpamFilename.Dir.of_string)
210219
+! default.root_dir
220+
|> win_space_redirection
211221

212222
let is_newer_raw = function
213223
| Some v ->

tests/reftests/env.test

-54
Original file line numberDiff line numberDiff line change
@@ -439,60 +439,6 @@ The following actions will be performed:
439439
Done.
440440
### 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"
441441
FOO=''; export FOO;
442-
### : root and switch with spaces :
443-
### RT="$BASEDIR/root 2"
444-
### SW="switch w spaces"
445-
### OPAMNOENVNOTICE=0
446-
### opam init -na --bare --bypass-check --disable-sandbox --root "$RT" defaut ./REPO | grep -v Cygwin
447-
No configuration file found, using built-in defaults.
448-
449-
<><> Fetching repository information ><><><><><><><><><><><><><><><><><><><><><>
450-
[defaut] Initialised
451-
### opam switch create "./$SW" nv --root "$RT"
452-
453-
<><> Installing new switch packages <><><><><><><><><><><><><><><><><><><><><><>
454-
Switch invariant: ["nv"]
455-
456-
<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
457-
-> installed nv.1
458-
Done.
459-
# Run eval $(opam env '--root=${BASEDIR}/root 2' '--switch=${BASEDIR}/switch w spaces') to update the current shell environment
460-
### opam env --root "$RT" --switch "./$SW" | grep "NV_VARS" | ';' -> ':'
461-
NV_VARS3='foo:/yet/another/different/path': export NV_VARS3:
462-
NV_VARS4='': export NV_VARS4:
463-
NV_VARS_5925_1='foo': export NV_VARS_5925_1:
464-
NV_VARS_5925_2='foo': export NV_VARS_5925_2:
465-
NV_VARS_5925_3='foo': export NV_VARS_5925_3:
466-
NV_VARS_5925_4='foo': export NV_VARS_5925_4:
467-
NV_VARS_5925_5='foo:': export NV_VARS_5925_5:
468-
NV_VARS_5925_6='foo:': export NV_VARS_5925_6:
469-
NV_VARS_5925_7=':foo': export NV_VARS_5925_7:
470-
NV_VARS_5925_8=':foo': export NV_VARS_5925_8:
471-
NV_VARS_5926_L_1='b::a': export NV_VARS_5926_L_1:
472-
NV_VARS_5926_L_2='b::a': export NV_VARS_5926_L_2:
473-
NV_VARS_5926_L_3=':a:b': export NV_VARS_5926_L_3:
474-
NV_VARS_5926_L_4=':a:b': export NV_VARS_5926_L_4:
475-
NV_VARS_5926_L_5='b::a': export NV_VARS_5926_L_5:
476-
NV_VARS_5926_L_6='b::a': export NV_VARS_5926_L_6:
477-
NV_VARS_5926_L_7=':a:b': export NV_VARS_5926_L_7:
478-
NV_VARS_5926_L_8=':a:b': export NV_VARS_5926_L_8:
479-
NV_VARS_5926_M_1='b:a1::a2': export NV_VARS_5926_M_1:
480-
NV_VARS_5926_M_2='a1::a2:b': export NV_VARS_5926_M_2:
481-
NV_VARS_5926_M_3='b:a1::a2': export NV_VARS_5926_M_3:
482-
NV_VARS_5926_M_4='a1::a2:b': export NV_VARS_5926_M_4:
483-
NV_VARS_5926_S_1='a:': export NV_VARS_5926_S_1:
484-
NV_VARS_5926_S_2=':a': export NV_VARS_5926_S_2:
485-
NV_VARS_5926_S_3='a:': export NV_VARS_5926_S_3:
486-
NV_VARS_5926_S_4=':a': export NV_VARS_5926_S_4:
487-
NV_VARS_5926_T_1='b:a:': export NV_VARS_5926_T_1:
488-
NV_VARS_5926_T_2='b:a:': export NV_VARS_5926_T_2:
489-
NV_VARS_5926_T_3='a::b': export NV_VARS_5926_T_3:
490-
NV_VARS_5926_T_4='a::b': export NV_VARS_5926_T_4:
491-
NV_VARS_5926_T_5='b:a:': export NV_VARS_5926_T_5:
492-
NV_VARS_5926_T_6='b:a:': export NV_VARS_5926_T_6:
493-
NV_VARS_5926_T_7='a::b': export NV_VARS_5926_T_7:
494-
NV_VARS_5926_T_8='a::b': export NV_VARS_5926_T_8:
495-
### OPAMNOENVNOTICE=1
496442
### : Env hooks :
497443
### <pkg:av.1>
498444
opam-version: "2.0"

tests/reftests/env.unix.test

+26
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,30 @@
11
N0REP0
2+
### : root and switches with spaces :
3+
### <pkg:nv.1>
4+
opam-version: "2.0"
5+
flags: compiler
6+
### RT="$BASEDIR/root 2"
7+
### SW="switch w spaces"
8+
### OPAMNOENVNOTICE=0
9+
### opam init -na --bare --bypass-check --disable-sandbox --root "$RT" defaut ./REPO
10+
No configuration file found, using built-in defaults.
11+
12+
<><> Fetching repository information ><><><><><><><><><><><><><><><><><><><><><>
13+
[defaut] Initialised
14+
### opam switch create "./$SW" nv --root "$RT"
15+
16+
<><> Installing new switch packages <><><><><><><><><><><><><><><><><><><><><><>
17+
Switch invariant: ["nv"]
18+
19+
<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
20+
-> installed nv.1
21+
Done.
22+
# Run eval $(opam env '--root=${BASEDIR}/root 2' '--switch=${BASEDIR}/switch w spaces') to update the current shell environment
23+
### opam env --root "$RT" --switch "./$SW" | grep "PREFIX" | ';' -> ':'
24+
OPAM_SWITCH_PREFIX='${BASEDIR}/switch w spaces/_opam': export OPAM_SWITCH_PREFIX:
25+
### opam var root --root "$RT"
26+
${BASEDIR}/root 2
27+
### OPAMNOENVNOTICE=1
228
### : setenv & build env rewriting :
329
### opam switch create rewriting --empty
430
### ::::::::::::::::::

tests/reftests/init.win32.test

+8-5
Original file line numberDiff line numberDiff line change
@@ -3,24 +3,27 @@ N0REP0
33
### rm -rf $OPAMROOT
44
### OPAMROOT="roots/with path"
55
### opam init --no-setup --bare --bypass-checks default REPO/
6+
[ERROR] You opam root directory contains a space, this may lead to several malfunction... bzzz.... nooo
67
No configuration file found, using built-in defaults.
8+
Your opam root path '${BASEDIR}/roots/with path' contains a space, we'll redirect to 'C:\opamroot'.
9+
Do you want to choose and enter another spaceless folder? [y/n] n
710
[NOTE] Configured with Cygwin at C:\cygwin64 for depexts
811

912
<><> Fetching repository information ><><><><><><><><><><><><><><><><><><><><><>
1013
[default] Initialised
1114
### opam var root --debug --debug-level=-1
1215
CLI Parsing CLI version 2.2
13-
GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/roots/with path
14-
${BASEDIR}/roots/with path
16+
GSTATE LOAD-GLOBAL-STATE @ C:\opamroot
17+
C:\opamroot
1518
### cat 'roots/with path/redirected-opamroot'
16-
/usr/bin/cat: 'roots/with path/redirected-opamroot': No such file or directory
17-
# Return code 1 #
19+
C:\opamroot
1820
### opam switch create --empty test
1921
### opam switch --debug --debug-level=-1
2022
CLI Parsing CLI version 2.2
21-
GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/roots/with path
23+
GSTATE LOAD-GLOBAL-STATE @ C:\opamroot
2224
SWITCH list
2325
# switch compiler description
2426
-> test test
2527
### echo $OPAMROOT
2628
roots/with path
29+
### rm -rf 'C:\opamroot'

0 commit comments

Comments
 (0)