Skip to content

Commit 953441f

Browse files
committed
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 5bcf07d commit 953441f

File tree

5 files changed

+83
-37
lines changed

5 files changed

+83
-37
lines changed

src/client/opamClient.ml

+14-1
Original file line numberDiff line numberDiff line change
@@ -713,7 +713,20 @@ let init
713713
shell =
714714
log "INIT %a"
715715
(slog @@ OpamStd.Option.to_string OpamRepositoryBackend.to_string) repo;
716-
let root = OpamStateConfig.(!r.root_dir) in
716+
let root =
717+
let root = OpamStateConfig.(!r.root_dir) in
718+
if Sys.win32 &&
719+
OpamStd.String.contains_char (OpamFilename.Dir.to_string root) ' ' then
720+
(let new_root_f = "/tmp/opamroot" in
721+
OpamConsole.note
722+
"Your opam root path '%s' contains a space, we'll redirect to '%s'"
723+
(OpamFilename.Dir.to_string root) new_root_f;
724+
let new_root = OpamFilename.Dir.of_string new_root_f in
725+
OpamFilename.write (OpamPath.redirected root) new_root_f;
726+
OpamStateConfig.update ~root_dir:new_root ();
727+
new_root)
728+
else root
729+
in
717730
let config_f = OpamPath.config root in
718731
let root_empty =
719732
not (OpamFilename.exists_dir root) || OpamFilename.dir_is_empty root in

src/state/opamStateConfig.ml

+26-18
Original file line numberDiff line numberDiff line change
@@ -70,24 +70,31 @@ 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+
(* CSIDL_LOCAL_APPDATA = 0x1c *)
92+
Dir.of_string (OpamStubs.(shGetFolderPath 0x1c SHGFP_TYPE_CURRENT))
93+
in
94+
concat_and_resolve local_appdata "opam"
95+
7396
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-
(* CSIDL_LOCAL_APPDATA = 0x1c *)
87-
Dir.of_string (OpamStubs.(shGetFolderPath 0x1c SHGFP_TYPE_CURRENT))
88-
in
89-
concat_and_resolve local_appdata "opam"
90-
);
97+
root_dir = default_root () |> win_space_redirection;
9198
original_root_dir = default_root ();
9299
current_switch = None;
93100
switch_from = `Default;
@@ -181,7 +188,7 @@ let initk k =
181188
| Some s -> Some (OpamSwitch.of_string s), Some `Env
182189
in
183190
setk (setk (fun c -> r := c; k)) !r
184-
?root_dir:(E.root () >>| OpamFilename.Dir.of_string)
191+
?root_dir:(E.root () >>| OpamFilename.Dir.of_string >>| win_space_redirection)
185192
?original_root_dir:(E.root () >>| OpamFilename.Dir.of_string)
186193
?current_switch
187194
?switch_from
@@ -209,6 +216,7 @@ let opamroot ?root_dir () =
209216
(root_dir >>+ fun () ->
210217
OpamStd.Env.getopt "OPAMROOT" >>| OpamFilename.Dir.of_string)
211218
+! default.root_dir
219+
|> win_space_redirection
212220

213221
let is_newer_raw = function
214222
| Some v ->

tests/reftests/dune.inc

+20
Original file line numberDiff line numberDiff line change
@@ -441,6 +441,26 @@
441441
%{targets}
442442
(run ./run.exe %{exe:../../src/client/opamMain.exe.exe} %{dep:env.test} %{read-lines:testing-env}))))
443443

444+
(rule
445+
(alias reftest-env.unix)
446+
(enabled_if (= %{os_type} "Unix"))
447+
(action
448+
(diff env.unix.test env.unix.out)))
449+
450+
(alias
451+
(name reftest)
452+
(enabled_if (= %{os_type} "Unix"))
453+
(deps (alias reftest-env.unix)))
454+
455+
(rule
456+
(targets env.unix.out)
457+
(deps root-N0REP0)
458+
(enabled_if (= %{os_type} "Unix"))
459+
(action
460+
(with-stdout-to
461+
%{targets}
462+
(run ./run.exe %{exe:../../src/client/opamMain.exe.exe} %{dep:env.unix.test} %{read-lines:testing-env}))))
463+
444464
(rule
445465
(alias reftest-env.win32)
446466
(enabled_if (= %{os_type} "Win32"))

tests/reftests/env.test

-18
Original file line numberDiff line numberDiff line change
@@ -106,21 +106,3 @@ NV_VARS4='': export NV_VARS4:
106106
### opam exec -- opam env --revert | grep "NV_VARS" | ';' -> ':'
107107
NV_VARS3='/yet/another/different/path': export NV_VARS3:
108108
NV_VARS4='': export NV_VARS4:
109-
### : root and switch with spaces :
110-
### RT="$BASEDIR/root 2"
111-
### SW="switch w spaces"
112-
### OPAMNOENVNOTICE=0
113-
### opam init -na --bare --bypass-check --disable-sandbox --root "$RT" defaut ./REPO
114-
No configuration file found, using built-in defaults.
115-
116-
<><> Fetching repository information ><><><><><><><><><><><><><><><><><><><><><>
117-
[defaut] Initialised
118-
### opam switch create "./$SW" nv --root "$RT"
119-
120-
<><> Installing new switch packages <><><><><><><><><><><><><><><><><><><><><><>
121-
Switch invariant: ["nv"]
122-
123-
<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
124-
-> installed nv.1
125-
Done.
126-
# Run eval $(opam env '--root=${BASEDIR}/root 2' '--switch=${BASEDIR}/switch w spaces') to update the current shell environment

tests/reftests/env.unix.test

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

0 commit comments

Comments
 (0)