Skip to content

Commit 6bbb1c0

Browse files
authored
Add a tests for long commands (#344)
1 parent 42450af commit 6bbb1c0

File tree

5 files changed

+90
-14
lines changed

5 files changed

+90
-14
lines changed

src/my_std.ml

Lines changed: 55 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -342,15 +342,65 @@ let windows_shell = lazy begin
342342
shell
343343
end
344344

345+
let string_exists p s =
346+
let n = String.length s in
347+
let rec loop i =
348+
if i = n then false
349+
else if p (String.get s i) then true
350+
else loop (succ i) in
351+
loop 0
352+
345353
let prepare_command_for_windows cmd =
346354
(* The best way to prevent bash from switching to its windows-style
347355
quote-handling is to prepend an empty string before the command name.
348356
Space seems to work, too - and the ouput is nicer *)
349357
let cmd = " " ^ cmd in
350-
Array.append (Lazy.force windows_shell) [|"-c"; cmd|]
358+
let shell = Lazy.force windows_shell in
359+
let all = Array.append shell [|"-c"; cmd|] in
360+
(* Over approximate the size the command as computed by "unix_win32.ml" in [make_cmdline] *)
361+
let size = Array.fold_left (fun acc x ->
362+
acc
363+
+ 1 (* space separate *)
364+
+ (String.length (Filename.quote x))) 0 all
365+
in
366+
(* cygwin seems to truncate command line at 8k (sometimes).
367+
See https://cygwin.com/pipermail/cygwin/2014-May/215364.html.
368+
While the limit might be 8192, some experiment show that it might be a bit less.
369+
Such logic exists in the fdopen repo with a limit of 7900. Let's reuse that as it
370+
has been tested for a while.
371+
*)
372+
if size <= 7900
373+
then all, None
374+
else
375+
let oc_closed = ref false in
376+
let file_deleted = ref false in
377+
let fname,oc =
378+
Filename.open_temp_file
379+
~mode:[Open_binary]
380+
"ocamlbuildtmp"
381+
".sh"
382+
in
383+
let cleanup () =
384+
if not !file_deleted then begin
385+
file_deleted:= true;
386+
try Sys.remove fname with _ -> ()
387+
end
388+
in
389+
try
390+
output_string oc cmd;
391+
oc_closed:= true;
392+
close_out oc;
393+
Array.append shell [| "-e" ; fname |], Some cleanup
394+
with
395+
| x ->
396+
if not !oc_closed then
397+
close_out_noerr oc;
398+
cleanup ();
399+
raise x
351400

352401
let sys_command_win32 cmd =
353-
let args = prepare_command_for_windows cmd in
402+
let args, cleanup = prepare_command_for_windows cmd in
403+
let res =
354404
try
355405
let oc = Unix.open_process_args_out args.(0) args in
356406
match Unix.close_process_out oc with
@@ -362,6 +412,9 @@ let sys_command_win32 cmd =
362412
raise *)
363413
log.dprintf (-1) "%s: %s" cmd (Printexc.to_string x);
364414
1
415+
in
416+
Option.iter (fun f -> f ()) cleanup;
417+
res
365418

366419
let sys_command =
367420
if Sys.win32 then

src/my_std.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -70,7 +70,7 @@ val lexbuf_of_string : ?name:string -> string -> Lexing.lexbuf
7070
val split_ocaml_version : (int * int * int * string) option
7171
(** (major, minor, patchlevel, rest) *)
7272

73-
val prepare_command_for_windows : string -> string array
73+
val prepare_command_for_windows : string -> string array * (unit -> unit) option
7474

7575
val env_path : string list Lazy.t
7676

src/my_unix.ml

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

6060
let run_and_open s kont =
61-
let ic =
61+
let ic, cleanup =
6262
if Sys.win32
6363
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
64+
let args, cleanup = My_std.prepare_command_for_windows s in
65+
Unix.open_process_args_in args.(0) args, cleanup
66+
else Unix.open_process_in s, None in
6767
let close () =
6868
match Unix.close_process_in ic with
69-
| Unix.WEXITED 0 -> ()
69+
| Unix.WEXITED 0 -> Option.iter (fun f -> f ()) cleanup
7070
| Unix.WEXITED _ | Unix.WSIGNALED _ | Unix.WSTOPPED _ ->
71-
failwith (Printf.sprintf "Error while running: %s" s) in
71+
Option.iter (fun f -> f ()) cleanup;
72+
failwith (Printf.sprintf "Error while running: %s" s) in
7273
let res = try
7374
kont ic
7475
with e -> (close (); raise e)

src/ocamlbuild_executor.ml

Lines changed: 8 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -38,6 +38,7 @@ type job = {
3838
job_stdin : out_channel;
3939
job_stderr : in_channel;
4040
job_buffer : Buffer.t;
41+
job_cleanup : (unit -> unit) option;
4142
mutable job_dying : bool;
4243
};;
4344

@@ -137,12 +138,12 @@ let execute
137138
(*** add_job *)
138139
let add_job cmd rest result id =
139140
(*display begin fun oc -> fp oc "Job %a is %s\n%!" print_job_id id cmd; end;*)
140-
let (stdout', stdin', stderr') =
141+
let (stdout', stdin', stderr'), cleanup =
141142
if Sys.win32
142143
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
144+
let args, cleanup = My_std.prepare_command_for_windows cmd in
145+
open_process_args_full args.(0) args env, cleanup
146+
else open_process_full cmd env, None in
146147
incr jobs_active;
147148
if not Sys.win32 then begin
148149
set_nonblock (doi stdout');
@@ -157,7 +158,8 @@ let execute
157158
job_stdin = stdin';
158159
job_stderr = stderr';
159160
job_buffer = Buffer.create 1024;
160-
job_dying = false }
161+
job_dying = false;
162+
job_cleanup = cleanup }
161163
in
162164
outputs := FDM.add (doi stdout') job (FDM.add (doi stderr') job !outputs);
163165
jobs := JS.add job !jobs;
@@ -265,6 +267,7 @@ let execute
265267
outputs := FDM.remove (doi job.job_stdout) (FDM.remove (doi job.job_stderr) !outputs);
266268
jobs := JS.remove job !jobs;
267269
let status = close_process_full (job.job_stdout, job.job_stdin, job.job_stderr) in
270+
Option.iter (fun f -> f ()) job.job_cleanup;
268271

269272
let shown = ref false in
270273

testsuite/internal.ml

Lines changed: 19 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,24 @@
11
#use "internal_test_header.ml";;
22

3+
let () =
4+
let long_file i = Printf.sprintf "f%0100d" i in
5+
let last1 = ref "0" in
6+
let last2 = ref "1" in
7+
let files = List.init 200 (fun i ->
8+
let name = long_file i in
9+
let prev1 = !last1 in
10+
let prev2 = !last2 in
11+
last1 := !last2;
12+
last2 := (String.capitalize_ascii name) ^".x";
13+
T.f (name ^ ".ml") ~content:(Printf.sprintf "let x = %s + %s" prev1 prev2)
14+
)
15+
in
16+
let files = T.f "fib.ml" ~content:(Printf.sprintf "print_int %s" !last2) :: files in
17+
test "LongCommand"
18+
~options:[]
19+
~description:"Check that ocamlbuild can handle long commands"
20+
~tree:files
21+
~targets:("fib.byte",[]) ();;
322

423
let () = test "Preprocess"
524
~description:"Check that preprocessor works"

0 commit comments

Comments
 (0)