Skip to content

Commit

Permalink
Rename uerror to caml_uerror
Browse files Browse the repository at this point in the history
  • Loading branch information
dra27 committed May 26, 2022
1 parent ca68931 commit 768df92
Show file tree
Hide file tree
Showing 109 changed files with 197 additions and 190 deletions.
2 changes: 1 addition & 1 deletion otherlibs/unix/accept_unix.c
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,7 @@ CAMLprim value unix_accept(value cloexec, value sock)
retcode = accept(Int_val(sock), &addr.s_gen, &addr_len);
#endif
caml_leave_blocking_section();
if (retcode == -1) uerror("accept", Nothing);
if (retcode == -1) caml_uerror("accept", Nothing);
#if !(defined(HAS_ACCEPT4) && defined(SOCK_CLOEXEC))
if (clo) unix_set_cloexec(retcode, "accept", Nothing);
#endif
Expand Down
2 changes: 1 addition & 1 deletion otherlibs/unix/accept_win32.c
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,7 @@ CAMLprim value unix_accept(value cloexec, value sock)
caml_leave_blocking_section();
if (snew == INVALID_SOCKET) {
caml_win32_maperr(err);
uerror("accept", Nothing);
caml_uerror("accept", Nothing);
}
caml_win32_set_cloexec((HANDLE) snew, cloexec);
fd = caml_win32_alloc_socket(snew);
Expand Down
2 changes: 1 addition & 1 deletion otherlibs/unix/access.c
Original file line number Diff line number Diff line change
Expand Up @@ -62,6 +62,6 @@ CAMLprim value unix_access(value path, value perms)
caml_leave_blocking_section();
caml_stat_free(p);
if (ret == -1)
uerror("access", path);
caml_uerror("access", path);
CAMLreturn(Val_unit);
}
2 changes: 1 addition & 1 deletion otherlibs/unix/bind_unix.c
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,7 @@ CAMLprim value unix_bind(value socket, value address)

unix_get_sockaddr(address, &addr, &addr_len);
ret = bind(Int_val(socket), &addr.s_gen, addr_len);
if (ret == -1) uerror("bind", Nothing);
if (ret == -1) caml_uerror("bind", Nothing);
return Val_unit;
}

Expand Down
2 changes: 1 addition & 1 deletion otherlibs/unix/bind_win32.c
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ CAMLprim value unix_bind(socket, address)
ret = bind(Socket_val(socket), &addr.s_gen, addr_len);
if (ret == -1) {
caml_win32_maperr(WSAGetLastError());
uerror("bind", Nothing);
caml_uerror("bind", Nothing);
}
return Val_unit;
}
6 changes: 3 additions & 3 deletions otherlibs/unix/channels_win32.c
Original file line number Diff line number Diff line change
Expand Up @@ -66,7 +66,7 @@ int caml_win32_CRT_fd_of_filedescr(value handle)
return CRT_fd_val(handle);
} else {
int fd = _open_osfhandle((intptr_t) Handle_val(handle), O_BINARY);
if (fd == -1) uerror("channel_of_descr", Nothing);
if (fd == -1) caml_uerror("channel_of_descr", Nothing);
CRT_fd_val(handle) = fd;
return fd;
}
Expand All @@ -85,7 +85,7 @@ CAMLprim value unix_inchannel_of_filedescr(value handle)
err = check_stream_semantics(handle);
if (err != 0) {
caml_win32_maperr(err);
uerror("in_channel_of_descr", Nothing);
caml_uerror("in_channel_of_descr", Nothing);
}
chan = caml_open_descriptor_in(caml_win32_CRT_fd_of_filedescr(handle));
chan->flags |= CHANNEL_FLAG_MANAGED_BY_GC;
Expand All @@ -107,7 +107,7 @@ CAMLprim value unix_outchannel_of_filedescr(value handle)
err = check_stream_semantics(handle);
if (err != 0) {
caml_win32_maperr(err);
uerror("out_channel_of_descr", Nothing);
caml_uerror("out_channel_of_descr", Nothing);
}
chan = caml_open_descriptor_out(caml_win32_CRT_fd_of_filedescr(handle));
chan->flags |= CHANNEL_FLAG_MANAGED_BY_GC;
Expand Down
2 changes: 1 addition & 1 deletion otherlibs/unix/chdir.c
Original file line number Diff line number Diff line change
Expand Up @@ -32,6 +32,6 @@ CAMLprim value unix_chdir(value path)
ret = chdir_os(p);
caml_leave_blocking_section();
caml_stat_free(p);
if (ret == -1) uerror("chdir", path);
if (ret == -1) caml_uerror("chdir", path);
CAMLreturn(Val_unit);
}
2 changes: 1 addition & 1 deletion otherlibs/unix/chmod.c
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,6 @@ CAMLprim value unix_chmod(value path, value perm)
ret = chmod_os(p, Int_val(perm));
caml_leave_blocking_section();
caml_stat_free(p);
if (ret == -1) uerror("chmod", path);
if (ret == -1) caml_uerror("chmod", path);
CAMLreturn(Val_unit);
}
2 changes: 1 addition & 1 deletion otherlibs/unix/chown.c
Original file line number Diff line number Diff line change
Expand Up @@ -29,6 +29,6 @@ CAMLprim value unix_chown(value path, value uid, value gid)
ret = chown(p, Int_val(uid), Int_val(gid));
caml_leave_blocking_section();
caml_stat_free(p);
if (ret == -1) uerror("chown", path);
if (ret == -1) caml_uerror("chown", path);
CAMLreturn(Val_unit);
}
2 changes: 1 addition & 1 deletion otherlibs/unix/chroot.c
Original file line number Diff line number Diff line change
Expand Up @@ -29,6 +29,6 @@ CAMLprim value unix_chroot(value path)
ret = chroot(p);
caml_leave_blocking_section();
caml_stat_free(p);
if (ret == -1) uerror("chroot", path);
if (ret == -1) caml_uerror("chroot", path);
CAMLreturn(Val_unit);
}
4 changes: 2 additions & 2 deletions otherlibs/unix/close_on.c
Original file line number Diff line number Diff line change
Expand Up @@ -20,13 +20,13 @@
CAMLprim value unix_set_close_on_exec(value fd)
{
if (caml_win32_set_inherit(Handle_val(fd), FALSE) == -1)
uerror("set_close_on_exec", Nothing);
caml_uerror("set_close_on_exec", Nothing);
return Val_unit;
}

CAMLprim value unix_clear_close_on_exec(value fd)
{
if (caml_win32_set_inherit(Handle_val(fd), TRUE) == -1)
uerror("clear_close_on_exec", Nothing);
caml_uerror("clear_close_on_exec", Nothing);
return Val_unit;
}
2 changes: 1 addition & 1 deletion otherlibs/unix/close_unix.c
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,6 @@ CAMLprim value unix_close(value fd)
caml_enter_blocking_section();
ret = close(Int_val(fd));
caml_leave_blocking_section();
if (ret == -1) uerror("close", Nothing);
if (ret == -1) caml_uerror("close", Nothing);
return Val_unit;
}
6 changes: 3 additions & 3 deletions otherlibs/unix/close_win32.c
Original file line number Diff line number Diff line change
Expand Up @@ -22,19 +22,19 @@ CAMLprim value unix_close(value fd)
if (Descr_kind_val(fd) == KIND_SOCKET) {
if (closesocket(Socket_val(fd)) != 0) {
caml_win32_maperr(WSAGetLastError());
uerror("close", Nothing);
caml_uerror("close", Nothing);
}
} else {
/* If we have an fd then closing it also closes
* the underlying handle. Also, closing only
* the handle and not the fd leads to fd leaks. */
if (CRT_fd_val(fd) != NO_CRT_FD) {
if (_close(CRT_fd_val(fd)) != 0)
uerror("close", Nothing);
caml_uerror("close", Nothing);
} else {
if (! CloseHandle(Handle_val(fd))) {
caml_win32_maperr(GetLastError());
uerror("close", Nothing);
caml_uerror("close", Nothing);
}
}
}
Expand Down
2 changes: 1 addition & 1 deletion otherlibs/unix/connect_unix.c
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ CAMLprim value unix_connect(value socket, value address)
caml_enter_blocking_section();
retcode = connect(Int_val(socket), &addr.s_gen, addr_len);
caml_leave_blocking_section();
if (retcode == -1) uerror("connect", Nothing);
if (retcode == -1) caml_uerror("connect", Nothing);
return Val_unit;
}

Expand Down
2 changes: 1 addition & 1 deletion otherlibs/unix/connect_win32.c
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ CAMLprim value unix_connect(socket, address)
caml_leave_blocking_section();
if (err) {
caml_win32_maperr(err);
uerror("connect", Nothing);
caml_uerror("connect", Nothing);
}
return Val_unit;
}
2 changes: 1 addition & 1 deletion otherlibs/unix/createprocess.c
Original file line number Diff line number Diff line change
Expand Up @@ -139,7 +139,7 @@ value unix_create_process_native(value cmd, value cmdline, value env,
caml_stat_free(exefile);
if (err != ERROR_SUCCESS) {
caml_win32_maperr(err);
uerror("create_process", cmd);
caml_uerror("create_process", cmd);
}
/* Return the process handle as pseudo-PID
(this is consistent with the wait() emulation in the MSVC C library */
Expand Down
4 changes: 2 additions & 2 deletions otherlibs/unix/dup2.c
Original file line number Diff line number Diff line change
Expand Up @@ -33,9 +33,9 @@ CAMLprim value unix_dup2(value cloexec, value fd1, value fd2)
#ifdef HAS_DUP3
if (dup3(Int_val(fd1), Int_val(fd2),
unix_cloexec_p(cloexec) ? O_CLOEXEC : 0) == -1)
uerror("dup2", Nothing);
caml_uerror("dup2", Nothing);
#else
if (dup2(Int_val(fd1), Int_val(fd2)) == -1) uerror("dup2", Nothing);
if (dup2(Int_val(fd1), Int_val(fd2)) == -1) caml_uerror("dup2", Nothing);
if (unix_cloexec_p(cloexec))
unix_set_cloexec(Int_val(fd2), "dup2", Nothing);
#endif
Expand Down
2 changes: 1 addition & 1 deletion otherlibs/unix/dup_unix.c
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ CAMLprim value unix_dup(value cloexec, value fd)
#else
ret = dup(Int_val(fd));
#endif
if (ret == -1) uerror("dup", Nothing);
if (ret == -1) caml_uerror("dup", Nothing);
#ifndef F_DUPFD_CLOEXEC
if (unix_cloexec_p(cloexec)) unix_set_cloexec(ret, "dup", Nothing);
#endif
Expand Down
8 changes: 4 additions & 4 deletions otherlibs/unix/dup_win32.c
Original file line number Diff line number Diff line change
Expand Up @@ -59,15 +59,15 @@ CAMLprim value unix_dup(value cloexec, value fd)
HANDLE newh = duplicate_handle(! unix_cloexec_p(cloexec),
Handle_val(fd));
if (newh == INVALID_HANDLE_VALUE)
uerror("dup", Nothing);
caml_uerror("dup", Nothing);
newfd = caml_win32_alloc_handle(newh);
CAMLreturn(newfd);
}
case KIND_SOCKET: {
SOCKET newsock = duplicate_socket(! unix_cloexec_p(cloexec),
Socket_val(fd));
if (newsock == INVALID_SOCKET)
uerror("dup", Nothing);
caml_uerror("dup", Nothing);
newfd = caml_win32_alloc_socket(newsock);
CAMLreturn(newfd);
}
Expand All @@ -89,7 +89,7 @@ CAMLprim value unix_dup2(value cloexec, value fd1, value fd2)
newh = duplicate_handle(! unix_cloexec_p(cloexec),
Handle_val(fd1));
if (newh == INVALID_HANDLE_VALUE)
uerror("dup2", Nothing);
caml_uerror("dup2", Nothing);
Handle_val(fd2) = newh;
CloseHandle(oldh);
break;
Expand All @@ -99,7 +99,7 @@ CAMLprim value unix_dup2(value cloexec, value fd1, value fd2)
newsock = duplicate_socket(! unix_cloexec_p(cloexec),
Socket_val(fd1));
if (newsock == INVALID_SOCKET)
uerror("dup2", Nothing);
caml_uerror("dup2", Nothing);
Socket_val(fd2) = newsock;
closesocket(oldsock);
break;
Expand Down
2 changes: 1 addition & 1 deletion otherlibs/unix/execv.c
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,7 @@ CAMLprim value unix_execv(value path, value args)
(void) execv_os(wpath, EXECV_CAST argv);
caml_stat_free(wpath);
unix_cstringvect_free(argv);
uerror("execv", path);
caml_uerror("execv", path);
return Val_unit; /* never reached, but suppress warnings */
/* from smart compilers */
}
2 changes: 1 addition & 1 deletion otherlibs/unix/execve.c
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ CAMLprim value unix_execve(value path, value args, value env)
caml_stat_free(wpath);
unix_cstringvect_free(argv);
unix_cstringvect_free(envp);
uerror("execve", path);
caml_uerror("execve", path);
return Val_unit; /* never reached, but suppress warnings */
/* from smart compilers */
}
2 changes: 1 addition & 1 deletion otherlibs/unix/execvp.c
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ CAMLprim value unix_execvp(value path, value args)
(void) execvp_os((const char_os *)wpath, EXECV_CAST argv);
caml_stat_free(wpath);
unix_cstringvect_free(argv);
uerror("execvp", path);
caml_uerror("execvp", path);
return Val_unit; /* never reached, but suppress warnings */
/* from smart compilers */
}
Expand Down
2 changes: 1 addition & 1 deletion otherlibs/unix/fchmod.c
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ CAMLprim value unix_fchmod(value fd, value perm)
caml_enter_blocking_section();
result = fchmod(Int_val(fd), Int_val(perm));
caml_leave_blocking_section();
if (result == -1) uerror("fchmod", Nothing);
if (result == -1) caml_uerror("fchmod", Nothing);
return Val_unit;
}

Expand Down
2 changes: 1 addition & 1 deletion otherlibs/unix/fchown.c
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,7 @@ CAMLprim value unix_fchown(value fd, value uid, value gid)
caml_enter_blocking_section();
result = fchown(Int_val(fd), Int_val(uid), Int_val(gid));
caml_leave_blocking_section();
if (result == -1) uerror("fchown", Nothing);
if (result == -1) caml_uerror("fchown", Nothing);
return Val_unit;
}

Expand Down
4 changes: 2 additions & 2 deletions otherlibs/unix/fcntl.c
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,7 @@ CAMLprim value unix_set_nonblock(value fd)
retcode = fcntl(Int_val(fd), F_GETFL, 0);
if (retcode == -1 ||
fcntl(Int_val(fd), F_SETFL, retcode | O_NONBLOCK) == -1)
uerror("set_nonblock", Nothing);
caml_uerror("set_nonblock", Nothing);
return Val_unit;
}

Expand All @@ -41,7 +41,7 @@ CAMLprim value unix_clear_nonblock(value fd)
retcode = fcntl(Int_val(fd), F_GETFL, 0);
if (retcode == -1 ||
fcntl(Int_val(fd), F_SETFL, retcode & ~O_NONBLOCK) == -1)
uerror("clear_nonblock", Nothing);
caml_uerror("clear_nonblock", Nothing);
return Val_unit;
}

Expand Down
2 changes: 1 addition & 1 deletion otherlibs/unix/fork.c
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ CAMLprim value unix_fork(value unit)

ret = fork();

if (ret == -1) uerror("fork", Nothing);
if (ret == -1) caml_uerror("fork", Nothing);

if (ret == 0) {
caml_atfork_child();
Expand Down
2 changes: 1 addition & 1 deletion otherlibs/unix/fsync.c
Original file line number Diff line number Diff line change
Expand Up @@ -35,6 +35,6 @@ CAMLprim value unix_fsync(value v)
caml_enter_blocking_section();
ret = fsync(fd);
caml_leave_blocking_section();
if (ret == -1) uerror("fsync", Nothing);
if (ret == -1) caml_uerror("fsync", Nothing);
return Val_unit;
}
4 changes: 2 additions & 2 deletions otherlibs/unix/ftruncate.c
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ CAMLprim value unix_ftruncate(value fd, value len)
caml_enter_blocking_section();
result = ftruncate(Int_val(fd), Long_val(len));
caml_leave_blocking_section();
if (result == -1) uerror("ftruncate", Nothing);
if (result == -1) caml_uerror("ftruncate", Nothing);
return Val_unit;
}

Expand All @@ -44,7 +44,7 @@ CAMLprim value unix_ftruncate_64(value fd, value len)
caml_enter_blocking_section();
result = ftruncate(Int_val(fd), ofs);
caml_leave_blocking_section();
if (result == -1) uerror("ftruncate", Nothing);
if (result == -1) caml_uerror("ftruncate", Nothing);
return Val_unit;
}

Expand Down
2 changes: 1 addition & 1 deletion otherlibs/unix/getcwd.c
Original file line number Diff line number Diff line change
Expand Up @@ -40,7 +40,7 @@ CAMLprim value unix_getcwd(value unit)
char_os buff[PATH_MAX];
char_os * ret;
ret = getcwd_os(buff, sizeof(buff)/sizeof(*buff));
if (ret == 0) uerror("getcwd", Nothing);
if (ret == 0) caml_uerror("getcwd", Nothing);
return caml_copy_string_of_os(buff);
}

Expand Down
4 changes: 2 additions & 2 deletions otherlibs/unix/getgr.c
Original file line number Diff line number Diff line change
Expand Up @@ -49,7 +49,7 @@ CAMLprim value unix_getgrnam(value name)
entry = getgrnam(String_val(name));
if (entry == NULL) {
if (errno == EINTR) {
uerror("getgrnam", Nothing);
caml_uerror("getgrnam", Nothing);
} else {
caml_raise_not_found();
}
Expand All @@ -64,7 +64,7 @@ CAMLprim value unix_getgrgid(value gid)
entry = getgrgid(Int_val(gid));
if (entry == NULL) {
if (errno == EINTR) {
uerror("getgrgid", Nothing);
caml_uerror("getgrgid", Nothing);
} else {
caml_raise_not_found();
}
Expand Down
2 changes: 1 addition & 1 deletion otherlibs/unix/getgroups.c
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,7 @@ CAMLprim value unix_getgroups(value unit)
int i;

n = getgroups(NGROUPS_MAX, gidset);
if (n == -1) uerror("getgroups", Nothing);
if (n == -1) caml_uerror("getgroups", Nothing);
res = caml_alloc_tuple(n);
for (i = 0; i < n; i++)
Field(res, i) = Val_int(gidset[i]);
Expand Down
2 changes: 1 addition & 1 deletion otherlibs/unix/getpeername_unix.c
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,7 @@ CAMLprim value unix_getpeername(value sock)

addr_len = sizeof(addr);
retcode = getpeername(Int_val(sock), &addr.s_gen, &addr_len);
if (retcode == -1) uerror("getpeername", Nothing);
if (retcode == -1) caml_uerror("getpeername", Nothing);
return unix_alloc_sockaddr(&addr, addr_len, -1);
}

Expand Down
2 changes: 1 addition & 1 deletion otherlibs/unix/getpeername_win32.c
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ CAMLprim value unix_getpeername(value sock)
retcode = getpeername(Socket_val(sock), &addr.s_gen, &addr_len);
if (retcode == -1) {
caml_win32_maperr(WSAGetLastError());
uerror("getpeername", Nothing);
caml_uerror("getpeername", Nothing);
}
return unix_alloc_sockaddr(&addr, addr_len, -1);
}

0 comments on commit 768df92

Please sign in to comment.