@@ -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+
278356let 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 *)
287367let filename_concat x y =
0 commit comments