@@ -342,15 +342,65 @@ let windows_shell = lazy begin
342342 shell
343343end
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+
345353let 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
352401let 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
366419let sys_command =
367420 if Sys. win32 then
0 commit comments