Skip to content

Commit d42f4a7

Browse files
authored
Merge pull request #339 from ocaml/win2
No longer call into cmd.exe to execute a posix shell on windows
2 parents c8eacc1 + 389d255 commit d42f4a7

File tree

9 files changed

+116
-83
lines changed

9 files changed

+116
-83
lines changed

.depend

Lines changed: 2 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -37,8 +37,6 @@ src/command.cmo : \
3737
src/my_unix.cmi \
3838
src/my_std.cmi \
3939
src/log.cmi \
40-
src/lexers.cmi \
41-
src/const.cmo \
4240
src/command.cmi
4341
src/command.cmx : \
4442
src/tags.cmx \
@@ -47,8 +45,6 @@ src/command.cmx : \
4745
src/my_unix.cmx \
4846
src/my_std.cmx \
4947
src/log.cmx \
50-
src/lexers.cmx \
51-
src/const.cmx \
5248
src/command.cmi
5349
src/command.cmi : \
5450
src/tags.cmi \
@@ -499,8 +495,10 @@ src/ocaml_utils.cmi : \
499495
src/ocamlbuild_config.cmo :
500496
src/ocamlbuild_config.cmx :
501497
src/ocamlbuild_executor.cmo : \
498+
src/my_std.cmi \
502499
src/ocamlbuild_executor.cmi
503500
src/ocamlbuild_executor.cmx : \
501+
src/my_std.cmx \
504502
src/ocamlbuild_executor.cmi
505503
src/ocamlbuild_executor.cmi :
506504
src/ocamlbuild_where.cmo : \

src/command.ml

Lines changed: 7 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -91,22 +91,6 @@ let atomize l = S(List.map (fun x -> A x) l)
9191
let atomize_paths l = S(List.map (fun x -> P x) l)
9292
(* ***)
9393

94-
let env_path = lazy begin
95-
let path_var = Sys.getenv "PATH" in
96-
let parse_path =
97-
if Sys.win32 then
98-
Lexers.parse_environment_path_w
99-
else
100-
Lexers.parse_environment_path
101-
in
102-
let paths =
103-
parse_path Const.Source.path (Lexing.from_string path_var) in
104-
let norm_current_dir_name path =
105-
if path = "" then Filename.current_dir_name else path
106-
in
107-
List.map norm_current_dir_name paths
108-
end
109-
11094
let virtual_solvers = Hashtbl.create 32
11195
let setup_virtual_command_solver virtual_command solver =
11296
Hashtbl.replace virtual_solvers virtual_command solver
@@ -136,7 +120,7 @@ let search_in_path cmd =
136120
else file_or_exe_exists (filename_concat path cmd)
137121
in
138122
if Filename.is_implicit cmd then
139-
let path = List.find try_path !*env_path in
123+
let path = List.find try_path !*My_std.env_path in
140124
(* We're not trying to append ".exe" here because all windows shells are
141125
* capable of understanding the command without the ".exe" suffix. *)
142126
filename_concat path cmd
@@ -145,7 +129,8 @@ let search_in_path cmd =
145129

146130
(*** string_of_command_spec{,_with_calls *)
147131
let string_of_command_spec_with_calls call_with_tags call_with_target resolve_virtuals spec =
148-
let rec aux b spec =
132+
let rec aux spec =
133+
let b = Buffer.create 256 in
149134
let first = ref true in
150135
let put_space () =
151136
if !first then
@@ -166,21 +151,12 @@ let string_of_command_spec_with_calls call_with_tags call_with_target resolve_vi
166151
else (put_space (); Printf.bprintf b "<virtual %s>" (Shell.quote_filename_if_needed v))
167152
| S l -> List.iter do_spec l
168153
| T tags -> call_with_tags tags; do_spec (!tag_handler tags)
169-
| Quote s ->
170-
put_space ();
171-
let buf = Buffer.create 256 in
172-
aux buf s;
173-
put_filename (Buffer.contents buf)
154+
| Quote s -> put_space (); put_filename (aux s)
174155
in
175-
do_spec spec
156+
do_spec spec;
157+
Buffer.contents b
176158
in
177-
let b = Buffer.create 256 in
178-
(* The best way to prevent bash from switching to its windows-style
179-
* quote-handling is to prepend an empty string before the command name. *)
180-
if Sys.win32 then
181-
Buffer.add_string b "''";
182-
aux b spec;
183-
Buffer.contents b
159+
aux spec
184160

185161
let string_of_command_spec x = string_of_command_spec_with_calls ignore ignore false x
186162

src/lexers.mli

Lines changed: 0 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -28,15 +28,6 @@ val comma_sep_strings : Loc.source -> Lexing.lexbuf -> string list
2828
val comma_or_blank_sep_strings : Loc.source -> Lexing.lexbuf -> string list
2929
val trim_blanks : Loc.source -> Lexing.lexbuf -> string
3030

31-
(* Parse an environment path (i.e. $PATH).
32-
This is a colon separated string.
33-
Note: successive colons means an empty string.
34-
Example:
35-
":aaa:bbb:::ccc:" -> [""; "aaa"; "bbb"; ""; ""; "ccc"; ""] *)
36-
val parse_environment_path : Loc.source -> Lexing.lexbuf -> string list
37-
(* Same one, for Windows (PATH is ;-separated) *)
38-
val parse_environment_path_w : Loc.source -> Lexing.lexbuf -> string list
39-
4031
val conf_lines : string option -> Loc.source -> Lexing.lexbuf -> conf
4132
val path_scheme : bool -> Loc.source -> Lexing.lexbuf ->
4233
[ `Word of string

src/lexers.mll

Lines changed: 0 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -95,24 +95,6 @@ and comma_or_blank_sep_strings_aux source = parse
9595
| space* eof { [] }
9696
| _ { error source lexbuf "Expecting (comma|blank)-separated strings (2)" }
9797

98-
and parse_environment_path_w source = parse
99-
| ([^ ';']* as word) { word :: parse_environment_path_aux_w source lexbuf }
100-
| ';' ([^ ';']* as word) { "" :: word :: parse_environment_path_aux_w source lexbuf }
101-
| eof { [] }
102-
and parse_environment_path_aux_w source = parse
103-
| ';' ([^ ';']* as word) { word :: parse_environment_path_aux_w source lexbuf }
104-
| eof { [] }
105-
| _ { error source lexbuf "Impossible: expecting colon-separated strings" }
106-
107-
and parse_environment_path source = parse
108-
| ([^ ':']* as word) { word :: parse_environment_path_aux source lexbuf }
109-
| ':' ([^ ':']* as word) { "" :: word :: parse_environment_path_aux source lexbuf }
110-
| eof { [] }
111-
and parse_environment_path_aux source = parse
112-
| ':' ([^ ':']* as word) { word :: parse_environment_path_aux source lexbuf }
113-
| eof { [] }
114-
| _ { error source lexbuf "Impossible: expecting colon-separated strings" }
115-
11698
and conf_lines dir source = parse
11799
| space* '#' not_newline* newline { Lexing.new_line lexbuf; conf_lines dir source lexbuf }
118100
| space* '#' not_newline* eof { [] }

src/log.ml

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -79,3 +79,5 @@ let finish ?how () =
7979
| Some d -> Display.finish ?how d
8080

8181
(*let () = My_unix.at_exit_once finish*)
82+
83+
let () = My_std.log3 := (fun s -> dprintf 3 "%s\n%!" s)

src/my_std.ml

Lines changed: 86 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -275,13 +275,93 @@ let sys_file_exists x =
275275
try Array.iter (fun x -> if x = basename then raise Exit) a; false
276276
with Exit -> true
277277

278+
(* Copied from opam
279+
https://github.com/ocaml/opam/blob/ca32ab3b976aa7abc00c7605548f78a30980d35b/src/core/opamStd.ml *)
280+
let split_quoted path sep =
281+
let length = String.length path in
282+
let rec f acc index current last normal =
283+
if (index : int) = length then
284+
let current = current ^ String.sub path last (index - last) in
285+
List.rev (if current <> "" then current::acc else acc)
286+
else
287+
let c = path.[index]
288+
and next = succ index in
289+
if (c : char) = sep && normal || c = '"' then
290+
let current = current ^ String.sub path last (index - last) in
291+
if c = '"' then
292+
f acc next current next (not normal)
293+
else
294+
let acc = if current = "" then acc else current::acc in
295+
f acc next "" next true
296+
else
297+
f acc next current last normal in
298+
f [] 0 "" 0 true
299+
300+
let env_path = lazy begin
301+
let path_var = (try Sys.getenv "PATH" with Not_found -> "") in
302+
(* opam doesn't support empty path to mean working directory, let's
303+
do the same here *)
304+
if Sys.win32 then
305+
split_quoted path_var ';'
306+
else
307+
String.split_on_char ':' path_var
308+
|> List.filter ((<>) "")
309+
end
310+
311+
312+
(* Here to break the circular dep *)
313+
let log3 = ref (fun _ -> failwith "My_std.log3 not initialized")
314+
315+
let windows_shell = lazy begin
316+
let rec iter = function
317+
| [] -> raise Not_found
318+
| hd::tl ->
319+
let dash = Filename.concat hd "dash.exe" in
320+
if Sys.file_exists dash then [|dash|] else
321+
let bash = Filename.concat hd "bash.exe" in
322+
if not (Sys.file_exists bash) then iter tl else
323+
(* if sh.exe and bash.exe exist in the same dir, choose sh.exe *)
324+
let sh = Filename.concat hd "sh.exe" in
325+
if Sys.file_exists sh then [|sh|] else [|bash ; "--norc" ; "--noprofile"|]
326+
in
327+
let paths = Lazy.force env_path in
328+
let shell =
329+
try
330+
let path =
331+
List.find (fun path ->
332+
Sys.file_exists (Filename.concat path "cygcheck.exe")) paths
333+
in
334+
iter [path]
335+
with Not_found ->
336+
(try iter paths with Not_found -> failwith "no posix shell found in PATH")
337+
in
338+
!log3 (Printf.sprintf "Using shell %s" (Array.to_list shell |> String.concat " "));
339+
shell
340+
end
341+
342+
let prepare_command_for_windows cmd =
343+
(* The best way to prevent bash from switching to its windows-style
344+
* quote-handling is to prepend an empty string before the command name. *)
345+
let cmd = "''" ^ cmd in
346+
Array.append (Lazy.force windows_shell) [|"-c"; cmd|]
347+
348+
let sys_command_win32 cmd =
349+
let args = prepare_command_for_windows cmd in
350+
let oc = Unix.open_process_args_out args.(0) args in
351+
match Unix.close_process_out oc with
352+
| WEXITED x -> x
353+
| WSIGNALED _ -> 2 (* like OCaml's uncaught exceptions *)
354+
| WSTOPPED _ -> 127
355+
278356
let sys_command =
279-
match Sys.win32 with
280-
| true -> fun cmd ->
281-
if cmd = "" then 0 else
282-
let cmd = "bash --norc -c " ^ Filename.quote cmd in
283-
Sys.command cmd
284-
| false -> fun cmd -> if cmd = "" then 0 else Sys.command cmd
357+
if Sys.win32 then
358+
sys_command_win32
359+
else
360+
Sys.command
361+
362+
let sys_command cmd =
363+
if cmd = "" then 0 else
364+
sys_command cmd
285365

286366
(* FIXME warning fix and use Filename.concat *)
287367
let filename_concat x y =

src/my_std.mli

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -69,3 +69,10 @@ val lexbuf_of_string : ?name:string -> string -> Lexing.lexbuf
6969

7070
val split_ocaml_version : (int * int * int * string) option
7171
(** (major, minor, patchlevel, rest) *)
72+
73+
val prepare_command_for_windows : string -> string array
74+
75+
val env_path : string list Lazy.t
76+
77+
(*/*)
78+
val log3 : (string -> unit) ref

src/my_unix.ml

Lines changed: 6 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -58,15 +58,12 @@ let at_exit_once callback =
5858
end
5959

6060
let run_and_open s kont =
61-
let s =
62-
(* Be consistent! My_unix.run_and_open uses My_std.sys_command and
63-
sys_command uses bash. *)
64-
if Sys.win32 then
65-
"bash --norc -c " ^ Filename.quote s
66-
else
67-
s
68-
in
69-
let ic = Unix.open_process_in s in
61+
let ic =
62+
if Sys.win32
63+
then
64+
let args = My_std.prepare_command_for_windows s in
65+
Unix.open_process_args_in args.(0) args
66+
else Unix.open_process_in s in
7067
let close () =
7168
match Unix.close_process_in ic with
7269
| Unix.WEXITED 0 -> ()

src/ocamlbuild_executor.ml

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -136,13 +136,13 @@ let execute
136136
(* ***)
137137
(*** add_job *)
138138
let add_job cmd rest result id =
139-
let cmd =
140-
if Sys.win32
141-
then "bash --norc -c " ^ Filename.quote cmd
142-
else cmd
143-
in
144139
(*display begin fun oc -> fp oc "Job %a is %s\n%!" print_job_id id cmd; end;*)
145-
let (stdout', stdin', stderr') = open_process_full cmd env in
140+
let (stdout', stdin', stderr') =
141+
if Sys.win32
142+
then
143+
let args = My_std.prepare_command_for_windows cmd in
144+
open_process_args_full args.(0) args env
145+
else open_process_full cmd env in
146146
incr jobs_active;
147147
if not Sys.win32 then begin
148148
set_nonblock (doi stdout');

0 commit comments

Comments
 (0)