summaryrefslogtreecommitdiffstats
path: root/otherlibs/win32unix
diff options
context:
space:
mode:
Diffstat (limited to 'otherlibs/win32unix')
-rw-r--r--otherlibs/win32unix/accept.c38
-rw-r--r--otherlibs/win32unix/sendrecv.c31
-rw-r--r--otherlibs/win32unix/unixsupport.c51
-rw-r--r--otherlibs/win32unix/windir.c31
-rw-r--r--otherlibs/win32unix/winwait.c19
5 files changed, 76 insertions, 94 deletions
diff --git a/otherlibs/win32unix/accept.c b/otherlibs/win32unix/accept.c
index 6b6633b85..cbd7e1ed0 100644
--- a/otherlibs/win32unix/accept.c
+++ b/otherlibs/win32unix/accept.c
@@ -25,30 +25,30 @@ value unix_accept(sock) /* ML */
int fd;
int optionValue;
HANDLE h;
- Push_roots(a,1);
-
+ value adr = Val_unit;
/* Set sockets to synchronous mode */
optionValue = SO_SYNCHRONOUS_NONALERT;
setsockopt(INVALID_SOCKET, SOL_SOCKET, SO_OPENTYPE,
(char *)&optionValue, sizeof(optionValue));
-
- sock_addr_len = sizeof(sock_addr);
- enter_blocking_section();
- s = accept((SOCKET) _get_osfhandle(Int_val(sock)),
- &sock_addr.s_gen, &sock_addr_len);
- leave_blocking_section();
- if (s == INVALID_SOCKET) {
- _dosmaperr(WSAGetLastError());
- uerror("accept", Nothing);
- };
- a[0] = alloc_sockaddr();
- res = alloc_tuple(2);
- fd = _open_osfhandle(s, 0);
- if (fd == -1) uerror("accept", Nothing);
- Field(res, 0) = Val_int(fd);
- Field(res, 1) = a[0];
- Pop_roots();
+
+ Begin_root (adr);
+ sock_addr_len = sizeof(sock_addr);
+ enter_blocking_section();
+ s = accept((SOCKET) _get_osfhandle(Int_val(sock)),
+ &sock_addr.s_gen, &sock_addr_len);
+ leave_blocking_section();
+ if (s == INVALID_SOCKET) {
+ _dosmaperr(WSAGetLastError());
+ uerror("accept", Nothing);
+ }
+ adr = alloc_sockaddr();
+ res = alloc_tuple(2);
+ fd = _open_osfhandle(s, 0);
+ if (fd == -1) uerror("accept", Nothing);
+ Field(res, 0) = Val_int(fd);
+ Field(res, 1) = adr;
+ End_roots();
return res;
}
diff --git a/otherlibs/win32unix/sendrecv.c b/otherlibs/win32unix/sendrecv.c
index dffdea9bb..74e1965ad 100644
--- a/otherlibs/win32unix/sendrecv.c
+++ b/otherlibs/win32unix/sendrecv.c
@@ -40,22 +40,23 @@ value unix_recvfrom(sock, buff, ofs, len, flags) /* ML */
{
int retcode;
value res;
- Push_roots(a, 1);
+ value adr = Val_unit;
- buff = unix_freeze_buffer(buff);
- sock_addr_len = sizeof(sock_addr);
- enter_blocking_section();
- retcode = recvfrom((SOCKET) _get_osfhandle(Int_val(sock)),
- &Byte(buff, Long_val(ofs)), Int_val(len),
- convert_flag_list(flags, msg_flag_table),
- &sock_addr.s_gen, &sock_addr_len);
- leave_blocking_section();
- if (retcode == -1) uerror("recvfrom", Nothing);
- a[0] = alloc_sockaddr();
- res = alloc_tuple(2);
- Field(res, 0) = Val_int(retcode);
- Field(res, 1) = a[0];
- Pop_roots();
+ Begin_root (adr);
+ buff = unix_freeze_buffer(buff); /* XXX Xavier regarde ca */
+ sock_addr_len = sizeof(sock_addr);
+ enter_blocking_section();
+ retcode = recvfrom((SOCKET) _get_osfhandle(Int_val(sock)),
+ &Byte(buff, Long_val(ofs)), Int_val(len),
+ convert_flag_list(flags, msg_flag_table),
+ &sock_addr.s_gen, &sock_addr_len);
+ leave_blocking_section();
+ if (retcode == -1) uerror("recvfrom", Nothing);
+ adr = alloc_sockaddr();
+ res = alloc_tuple(2);
+ Field(res, 0) = Val_int(retcode);
+ Field(res, 1) = adr;
+ End_roots();
return res;
}
diff --git a/otherlibs/win32unix/unixsupport.c b/otherlibs/win32unix/unixsupport.c
index 029301454..b5aad5700 100644
--- a/otherlibs/win32unix/unixsupport.c
+++ b/otherlibs/win32unix/unixsupport.c
@@ -85,26 +85,24 @@ void unix_error(errcode, cmdname, cmdarg)
value cmdarg;
{
value res;
- Push_roots(r, 2);
-#define name r[0]
-#define arg r[1]
- if (unix_error_exn == NULL) {
- unix_error_exn = caml_named_value("Unix.Unix_error");
- if (unix_error_exn == NULL)
- invalid_argument("Exception Unix.Unix_error not initialized, must link unix.cma");
- }
- arg = cmdarg == Nothing ? copy_string("") : cmdarg;
- name = copy_string(cmdname);
- res = alloc(4, 0);
- Field(res, 0) = *unix_error_exn;
- Field(res, 1) =
- cst_to_constr(errcode, error_table, sizeof(error_table)/sizeof(int),
- sizeof(error_table)/sizeof(int));
- Field(res, 2) = name;
- Field(res, 3) = arg;
- Pop_roots();
-#undef name
-#undef arg
+ value name = Val_unit, arg = Val_unit;
+
+ Begin_roots2 (name, arg);
+ if (unix_error_exn == NULL) {
+ unix_error_exn = caml_named_value("Unix.Unix_error");
+ if (unix_error_exn == NULL)
+ invalid_argument("Exception Unix.Unix_error not initialized, must link unix.cma");
+ }
+ arg = cmdarg == Nothing ? copy_string("") : cmdarg;
+ name = copy_string(cmdname);
+ res = alloc(4, 0);
+ Field(res, 0) = *unix_error_exn;
+ Field(res, 1) =
+ cst_to_constr(errcode, error_table, sizeof(error_table)/sizeof(int),
+ sizeof(error_table)/sizeof(int));
+ Field(res, 2) = name;
+ Field(res, 3) = arg;
+ End_roots();
mlraise(res);
}
@@ -114,16 +112,3 @@ void uerror(cmdname, cmdarg)
{
unix_error(errno, cmdname, cmdarg);
}
-
-value unix_freeze_buffer(buf)
- value buf;
-{
- if (Is_young(buf)) {
- Push_roots(r, 1);
- r[0] = buf;
- minor_collection();
- buf = r[0];
- Pop_roots();
- }
- return buf;
-}
diff --git a/otherlibs/win32unix/windir.c b/otherlibs/win32unix/windir.c
index 0461c1e34..7009febeb 100644
--- a/otherlibs/win32unix/windir.c
+++ b/otherlibs/win32unix/windir.c
@@ -23,22 +23,21 @@ value win_findfirst(name) /* ML */
int h;
value v;
struct _finddata_t fileinfo;
- Push_roots(r,1);
-
-#define valname r[0]
-
- h = _findfirst(String_val(name),&fileinfo);
- if (h == -1) {
- if (errno == ENOENT)
- raise_end_of_file();
- else
- uerror("opendir", Nothing);
- }
- valname = copy_string(fileinfo.name);
- v = alloc_tuple(2);
- Field(v,0) = valname;
- Field(v,1) = Val_int(h);
- Pop_roots();
+ value valname = Val_unit;
+
+ Begin_root (valname);
+ h = _findfirst(String_val(name),&fileinfo);
+ if (h == -1) {
+ if (errno == ENOENT)
+ raise_end_of_file();
+ else
+ uerror("opendir", Nothing);
+ }
+ valname = copy_string(fileinfo.name);
+ v = alloc_tuple(2);
+ Field(v,0) = valname;
+ Field(v,1) = Val_int(h);
+ End_roots();
return v;
}
diff --git a/otherlibs/win32unix/winwait.c b/otherlibs/win32unix/winwait.c
index 16fbece8f..07bed46f1 100644
--- a/otherlibs/win32unix/winwait.c
+++ b/otherlibs/win32unix/winwait.c
@@ -22,18 +22,15 @@
static value alloc_process_status(pid, status)
int pid, status;
{
- value st, res;
- Push_roots(r, 1);
+ value res;
+ value st = alloc(1, 0);
-
- st = alloc(1, 0);
- Field(st, 0) = Val_int(status);
-
- r[0] = st;
- res = alloc_tuple(2);
- Field(res, 0) = Val_int(pid);
- Field(res, 1) = r[0];
- Pop_roots();
+ Begin_root (st);
+ Field(st, 0) = Val_int(status);
+ res = alloc_tuple(2);
+ Field(res, 0) = Val_int(pid);
+ Field(res, 1) = st;
+ End_roots();
return res;
}