diff options
-rw-r--r-- | otherlibs/win32unix/close_on.c | 70 | ||||
-rw-r--r-- | otherlibs/win32unix/createprocess.c | 15 | ||||
-rw-r--r-- | otherlibs/win32unix/unix.ml | 2 | ||||
-rw-r--r-- | otherlibs/win32unix/winwait.c | 9 |
4 files changed, 68 insertions, 28 deletions
diff --git a/otherlibs/win32unix/close_on.c b/otherlibs/win32unix/close_on.c index ba32350a2..324c16209 100644 --- a/otherlibs/win32unix/close_on.c +++ b/otherlibs/win32unix/close_on.c @@ -48,42 +48,76 @@ value win_clear_close_on_exec(fd) /* ML */ #else -extern int _set_osfhnd(int fd, long value); +/* This works on Win 95, but is a terrible hack. + Bug: the opening flags of the file descriptor (O_APPEND, O_TEXT) are lost. */ -static int win_realloc_handle(fd, inherit) - int fd; - BOOL inherit; +static int win_open_osfhandle2(handle, flags, reqd_fd) + HANDLE handle; + int flags; + int reqd_fd; { - HANDLE oldh, newh; + int fd, retcode; + HANDLE new_handle; + fd = _open_osfhandle((long)handle, flags); + if (fd == -1) + return -1; + if (fd == reqd_fd) + return 0; /* Got it! */ + /* Make a copy of the handle, since we're going to close "handle" when + we close "fd". */ + if (! DuplicateHandle(GetCurrentProcess(), handle, + GetCurrentProcess(), &new_handle, + 0L, FALSE, DUPLICATE_SAME_ACCESS)) { + _dosmaperr(GetLastError()); + return -1; + } + /* Keep fd open during the recursive call, thus forcing _open_osfhandle + to return reqd_fd eventually. */ + retcode = win_open_osfhandle2(new_handle, flags, reqd_fd); + close(fd); /* Also closes "handle" */ + return retcode; +} + +static int win_set_noninherit(fd) + int fd; +{ + HANDLE oldh, newh; oldh = (HANDLE) _get_osfhandle(fd); if (oldh == (HANDLE) -1) return -1; if (! DuplicateHandle(GetCurrentProcess(), oldh, - GetCurrentProcess(), &newh, - 0L, inherit, DUPLICATE_SAME_ACCESS)) { - _dosmaperr(GetLastError()); + GetCurrentProcess(), &newh, + 0L, FALSE, DUPLICATE_SAME_ACCESS)) { + _dosmaperr(GetLastError()); return -1; } - _close(fd); - _set_osfhnd(fd, (long) newh); - return 0; + if (close(fd) == -1) return -1; + return win_open_osfhandle2(newh, 0, fd); } -value win_set_close_on_exec(fd) /* ML */ - value fd; +value win_set_close_on_exec(vfd) /* ML */ + value vfd; { - if (win_realloc_handle(Int_val(fd), FALSE) == -1) { + if (win_set_noninherit(Int_val(vfd)) == -1) uerror("set_close_on_exec", Nothing); - } return Val_unit; } -value win_clear_close_on_exec(fd) /* ML */ - value fd; +value win_clear_close_on_exec(vfd) /* ML */ + value vfd; { - if (win_realloc_handle(Int_val(fd), TRUE) == -1) { + int fd, newfd; + + fd = Int_val(vfd); + newfd = dup(fd); + if (newfd == -1) { + uerror("clear_close_on_exec", Nothing); + } + if (dup2(newfd, fd) == -1) { + close(newfd); uerror("clear_close_on_exec", Nothing); } + close(newfd); return Val_unit; } diff --git a/otherlibs/win32unix/createprocess.c b/otherlibs/win32unix/createprocess.c index c49b3da8f..8f44254db 100644 --- a/otherlibs/win32unix/createprocess.c +++ b/otherlibs/win32unix/createprocess.c @@ -15,13 +15,18 @@ #include <mlvalues.h> #include "unixsupport.h" -value win_create_process_native(exe, cmdline, env, fd1, fd2, fd3) - value exe, cmdline, env, fd1, fd2, fd3; +/* From the Caml runtime */ +extern char * searchpath(char * name); + +value win_create_process_native(cmd, cmdline, env, fd1, fd2, fd3) + value cmd, cmdline, env, fd1, fd2, fd3; { PROCESS_INFORMATION pi; STARTUPINFO si; - char * envp; + char * exefile, * envp; + exefile = searchpath(String_val(cmd)); + if (exefile == NULL) exefile = String_val(cmd); if (env != Val_int(0)) { envp = String_val(Field(env, 0)); } else { @@ -33,10 +38,10 @@ value win_create_process_native(exe, cmdline, env, fd1, fd2, fd3) si.hStdInput = (HANDLE) _get_osfhandle(Int_val(fd1)); si.hStdOutput = (HANDLE) _get_osfhandle(Int_val(fd2)); si.hStdError = (HANDLE) _get_osfhandle(Int_val(fd3)); - if (! CreateProcess(String_val(exe), String_val(cmdline), NULL, NULL, + if (! CreateProcess(exefile, String_val(cmdline), NULL, NULL, TRUE, 0, envp, NULL, &si, &pi)) { _dosmaperr(GetLastError()); - uerror("create_process", exe); + uerror("create_process", exefile); } return Val_int(pi.hProcess); } diff --git a/otherlibs/win32unix/unix.ml b/otherlibs/win32unix/unix.ml index b1a99c857..1674ad97b 100644 --- a/otherlibs/win32unix/unix.ml +++ b/otherlibs/win32unix/unix.ml @@ -412,7 +412,7 @@ let create_process prog args fd1 fd2 fd3 = let create_process_env prog args env fd1 fd2 fd3 = win_create_process prog (String.concat " " (Array.to_list args)) - (Some(String.concat "\000" (Array.to_list env))) + (Some(String.concat "\000" (Array.to_list env) ^ "\000")) fd1 fd2 fd3 external system: string -> process_status = "win_system" diff --git a/otherlibs/win32unix/winwait.c b/otherlibs/win32unix/winwait.c index ac1865cf0..6b078a9cc 100644 --- a/otherlibs/win32unix/winwait.c +++ b/otherlibs/win32unix/winwait.c @@ -37,11 +37,12 @@ static value alloc_process_status(pid, status) return res; } -value win_waitpid(flags, pid_req) - value flags, pid_req; +value win_waitpid(flags, vpid_req) + value flags, vpid_req; { - int status; - if (_cwait(&status,Int_val(pid_req), 0/* ignored by win32 */) == -1) + int status, pid_req; + pid_req = Int_val(vpid_req); + if (_cwait(&status, pid_req, 0/* ignored by win32 */) == -1) uerror("waitpid", Nothing); return alloc_process_status(pid_req, status); } |