Skip to content

Commit

Permalink
Prefix all unix_ symbols caml_unix_
Browse files Browse the repository at this point in the history
  • Loading branch information
dra27 committed Jun 13, 2022
1 parent 67a4d75 commit b6f739c
Show file tree
Hide file tree
Showing 150 changed files with 771 additions and 755 deletions.
2 changes: 1 addition & 1 deletion Changes
Original file line number Diff line number Diff line change
Expand Up @@ -430,7 +430,7 @@ OCaml 4.14.0

- #10926: Rename the two internal Windows Unicode functions with `caml_` prefix
instead of `win_`.
(David Allsopp, review by Kate Deplaix and Xavier Leroy)
(David Allsopp, review by Kate Deplaix, Damien Doligez and Xavier Leroy)

### Code generation and optimizations:

Expand Down
10 changes: 5 additions & 5 deletions otherlibs/unix/accept_unix.c
Original file line number Diff line number Diff line change
Expand Up @@ -25,15 +25,15 @@

#include "socketaddr.h"

CAMLprim value unix_accept(value cloexec, value sock)
CAMLprim value caml_unix_accept(value cloexec, value sock)
{
CAMLparam0();
CAMLlocal1(a);
int retcode;
value res;
union sock_addr_union addr;
socklen_param_type addr_len;
int clo = unix_cloexec_p(cloexec);
int clo = caml_unix_cloexec_p(cloexec);

addr_len = sizeof(addr);
caml_enter_blocking_section();
Expand All @@ -46,9 +46,9 @@ CAMLprim value unix_accept(value cloexec, value sock)
caml_leave_blocking_section();
if (retcode == -1) caml_uerror("accept", Nothing);
#if !(defined(HAS_ACCEPT4) && defined(SOCK_CLOEXEC))
if (clo) unix_set_cloexec(retcode, "accept", Nothing);
if (clo) caml_unix_set_cloexec(retcode, "accept", Nothing);
#endif
a = unix_alloc_sockaddr(&addr, addr_len, retcode);
a = caml_unix_alloc_sockaddr(&addr, addr_len, retcode);
res = caml_alloc_small(2, 0);
Field(res, 0) = Val_int(retcode);
Field(res, 1) = a;
Expand All @@ -57,7 +57,7 @@ CAMLprim value unix_accept(value cloexec, value sock)

#else

CAMLprim value unix_accept(value cloexec, value sock)
CAMLprim value caml_unix_accept(value cloexec, value sock)
{ caml_invalid_argument("accept not implemented"); }

#endif
4 changes: 2 additions & 2 deletions otherlibs/unix/accept_win32.c
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,7 @@
#include "unixsupport.h"
#include "socketaddr.h"

CAMLprim value unix_accept(value cloexec, value sock)
CAMLprim value caml_unix_accept(value cloexec, value sock)
{
CAMLparam0();
CAMLlocal2(fd, adr);
Expand All @@ -42,7 +42,7 @@ CAMLprim value unix_accept(value cloexec, value sock)
}
caml_win32_set_cloexec((HANDLE) snew, cloexec);
fd = caml_win32_alloc_socket(snew);
adr = unix_alloc_sockaddr(&addr, addr_len, snew);
adr = caml_unix_alloc_sockaddr(&addr, addr_len, snew);
res = caml_alloc_small(2, 0);
Field(res, 0) = fd;
Field(res, 1) = adr;
Expand Down
2 changes: 1 addition & 1 deletion otherlibs/unix/access.c
Original file line number Diff line number Diff line change
Expand Up @@ -48,7 +48,7 @@ static int access_permission_table[] = {
F_OK
};

CAMLprim value unix_access(value path, value perms)
CAMLprim value caml_unix_access(value path, value perms)
{
CAMLparam2(path, perms);
char_os * p;
Expand Down
16 changes: 8 additions & 8 deletions otherlibs/unix/addrofstr.c
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@

#include "socketaddr.h"

CAMLprim value unix_inet_addr_of_string(value s)
CAMLprim value caml_unix_inet_addr_of_string(value s)
{
if (! caml_string_is_c_safe(s)) caml_failwith("inet_addr_of_string");
#if defined(HAS_IPV6)
Expand All @@ -42,14 +42,14 @@ CAMLprim value unix_inet_addr_of_string(value s)
case AF_INET:
{
vres =
unix_alloc_inet_addr(
caml_unix_alloc_inet_addr(
&((struct sockaddr_in *) res->ai_addr)->sin_addr);
break;
}
case AF_INET6:
{
vres =
unix_alloc_inet6_addr(
caml_unix_alloc_inet6_addr(
&((struct sockaddr_in6 *) res->ai_addr)->sin6_addr);
break;
}
Expand All @@ -67,9 +67,9 @@ CAMLprim value unix_inet_addr_of_string(value s)
struct in_addr address;
struct in6_addr address6;
if (inet_pton(AF_INET, String_val(s), &address) > 0)
return unix_alloc_inet_addr(&address);
return caml_unix_alloc_inet_addr(&address);
else if (inet_pton(AF_INET6, String_val(s), &address6) > 0)
return unix_alloc_inet6_addr(&address6);
return caml_unix_alloc_inet6_addr(&address6);
else
caml_failwith("inet_addr_of_string");
}
Expand All @@ -79,21 +79,21 @@ CAMLprim value unix_inet_addr_of_string(value s)
struct in_addr address;
if (inet_aton(String_val(s), &address) == 0)
caml_failwith("inet_addr_of_string");
return unix_alloc_inet_addr(&address);
return caml_unix_alloc_inet_addr(&address);
}
#else
{
struct in_addr address;
address.s_addr = inet_addr(String_val(s));
if (address.s_addr == (uint32_t) -1) caml_failwith("inet_addr_of_string");
return unix_alloc_inet_addr(&address);
return caml_unix_alloc_inet_addr(&address);
}
#endif
}

#else

CAMLprim value unix_inet_addr_of_string(value s)
CAMLprim value caml_unix_inet_addr_of_string(value s)
{ caml_invalid_argument("inet_addr_of_string not implemented"); }

#endif
2 changes: 1 addition & 1 deletion otherlibs/unix/alarm.c
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@
#include <caml/mlvalues.h>
#include "unixsupport.h"

CAMLprim value unix_alarm(value t)
CAMLprim value caml_unix_alarm(value t)
{
return Val_int(alarm((unsigned int) Long_val(t)));
}
6 changes: 3 additions & 3 deletions otherlibs/unix/bind_unix.c
Original file line number Diff line number Diff line change
Expand Up @@ -21,21 +21,21 @@

#include "socketaddr.h"

CAMLprim value unix_bind(value socket, value address)
CAMLprim value caml_unix_bind(value socket, value address)
{
int ret;
union sock_addr_union addr;
socklen_param_type addr_len;

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

#else

CAMLprim value unix_bind(value socket, value address)
CAMLprim value caml_unix_bind(value socket, value address)
{ caml_invalid_argument("bind not implemented"); }

#endif
4 changes: 2 additions & 2 deletions otherlibs/unix/bind_win32.c
Original file line number Diff line number Diff line change
Expand Up @@ -17,14 +17,14 @@
#include "unixsupport.h"
#include "socketaddr.h"

CAMLprim value unix_bind(socket, address)
CAMLprim value caml_unix_bind(socket, address)
value socket, address;
{
int ret;
union sock_addr_union addr;
socklen_param_type addr_len;

unix_get_sockaddr(address, &addr, &addr_len);
caml_unix_get_sockaddr(address, &addr, &addr_len);
ret = bind(Socket_val(socket), &addr.s_gen, addr_len);
if (ret == -1) {
caml_win32_maperr(WSAGetLastError());
Expand Down
14 changes: 7 additions & 7 deletions otherlibs/unix/channels_unix.c
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,7 @@
UDP (datagram) sockets.
Returns 0 if OK, a nonzero error code if error. */

static int unix_check_stream_semantics(int fd)
static int caml_unix_check_stream_semantics(int fd)
{
struct stat buf;

Expand Down Expand Up @@ -64,22 +64,22 @@ static int unix_check_stream_semantics(int fd)
}
}

CAMLprim value unix_inchannel_of_filedescr(value fd)
CAMLprim value caml_unix_inchannel_of_filedescr(value fd)
{
int err;
caml_enter_blocking_section();
err = unix_check_stream_semantics(Int_val(fd));
err = caml_unix_check_stream_semantics(Int_val(fd));
caml_leave_blocking_section();
if (err != 0) unix_error(err, "in_channel_of_descr", Nothing);
if (err != 0) caml_unix_error(err, "in_channel_of_descr", Nothing);
return caml_ml_open_descriptor_in(fd);
}

CAMLprim value unix_outchannel_of_filedescr(value fd)
CAMLprim value caml_unix_outchannel_of_filedescr(value fd)
{
int err;
caml_enter_blocking_section();
err = unix_check_stream_semantics(Int_val(fd));
err = caml_unix_check_stream_semantics(Int_val(fd));
caml_leave_blocking_section();
if (err != 0) unix_error(err, "out_channel_of_descr", Nothing);
if (err != 0) caml_unix_error(err, "out_channel_of_descr", Nothing);
return caml_ml_open_descriptor_out(fd);
}
10 changes: 5 additions & 5 deletions otherlibs/unix/channels_win32.c
Original file line number Diff line number Diff line change
Expand Up @@ -72,7 +72,7 @@ int caml_win32_CRT_fd_of_filedescr(value handle)
}
}

CAMLprim value unix_inchannel_of_filedescr(value handle)
CAMLprim value caml_unix_inchannel_of_filedescr(value handle)
{
CAMLparam1(handle);
CAMLlocal1(vchan);
Expand All @@ -96,7 +96,7 @@ CAMLprim value unix_inchannel_of_filedescr(value handle)
CAMLreturn(vchan);
}

CAMLprim value unix_outchannel_of_filedescr(value handle)
CAMLprim value caml_unix_outchannel_of_filedescr(value handle)
{
CAMLparam1(handle);
CAMLlocal1(vchan);
Expand All @@ -118,15 +118,15 @@ CAMLprim value unix_outchannel_of_filedescr(value handle)
CAMLreturn(vchan);
}

CAMLprim value unix_filedescr_of_channel(value vchan)
CAMLprim value caml_unix_filedescr_of_channel(value vchan)
{
CAMLparam1(vchan);
CAMLlocal1(fd);
struct channel * chan;
HANDLE h;

chan = Channel(vchan);
if (chan->fd == -1) unix_error(EBADF, "descr_of_channel", Nothing);
if (chan->fd == -1) caml_unix_error(EBADF, "descr_of_channel", Nothing);
h = (HANDLE) _get_osfhandle(chan->fd);
if (chan->flags & CHANNEL_FLAG_FROM_SOCKET)
fd = caml_win32_alloc_socket((SOCKET) h);
Expand All @@ -136,7 +136,7 @@ CAMLprim value unix_filedescr_of_channel(value vchan)
CAMLreturn(fd);
}

CAMLprim value unix_filedescr_of_fd(value vfd)
CAMLprim value caml_unix_filedescr_of_fd(value vfd)
{
int crt_fd = Int_val(vfd);
/* PR#4750: do not use the _or_socket variant as it can cause performance
Expand Down
2 changes: 1 addition & 1 deletion otherlibs/unix/chdir.c
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@
#include <caml/osdeps.h>
#include "unixsupport.h"

CAMLprim value unix_chdir(value path)
CAMLprim value caml_unix_chdir(value path)
{
CAMLparam1(path);
char_os * p;
Expand Down
2 changes: 1 addition & 1 deletion otherlibs/unix/chmod.c
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@
#include <caml/osdeps.h>
#include "unixsupport.h"

CAMLprim value unix_chmod(value path, value perm)
CAMLprim value caml_unix_chmod(value path, value perm)
{
CAMLparam2(path, perm);
char_os * p;
Expand Down
2 changes: 1 addition & 1 deletion otherlibs/unix/chown.c
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@
#include <caml/signals.h>
#include "unixsupport.h"

CAMLprim value unix_chown(value path, value uid, value gid)
CAMLprim value caml_unix_chown(value path, value uid, value gid)
{
CAMLparam1(path);
char * p;
Expand Down
2 changes: 1 addition & 1 deletion otherlibs/unix/chroot.c
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@
#include <caml/signals.h>
#include "unixsupport.h"

CAMLprim value unix_chroot(value path)
CAMLprim value caml_unix_chroot(value path)
{
CAMLparam1(path);
char * p;
Expand Down
4 changes: 2 additions & 2 deletions otherlibs/unix/close_on.c
Original file line number Diff line number Diff line change
Expand Up @@ -17,14 +17,14 @@
#include "unixsupport.h"
#include <windows.h>

CAMLprim value unix_set_close_on_exec(value fd)
CAMLprim value caml_unix_set_close_on_exec(value fd)
{
if (caml_win32_set_inherit(Handle_val(fd), FALSE) == -1)
caml_uerror("set_close_on_exec", Nothing);
return Val_unit;
}

CAMLprim value unix_clear_close_on_exec(value fd)
CAMLprim value caml_unix_clear_close_on_exec(value fd)
{
if (caml_win32_set_inherit(Handle_val(fd), TRUE) == -1)
caml_uerror("clear_close_on_exec", Nothing);
Expand Down
2 changes: 1 addition & 1 deletion otherlibs/unix/close_unix.c
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@
#include <caml/signals.h>
#include "unixsupport.h"

CAMLprim value unix_close(value fd)
CAMLprim value caml_unix_close(value fd)
{
int ret;
caml_enter_blocking_section();
Expand Down
2 changes: 1 addition & 1 deletion otherlibs/unix/close_win32.c
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@
#include "unixsupport.h"
#include <caml/io.h>

CAMLprim value unix_close(value fd)
CAMLprim value caml_unix_close(value fd)
{
if (Descr_kind_val(fd) == KIND_SOCKET) {
if (closesocket(Socket_val(fd)) != 0) {
Expand Down
4 changes: 2 additions & 2 deletions otherlibs/unix/closedir.c
Original file line number Diff line number Diff line change
Expand Up @@ -25,11 +25,11 @@
#include <sys/dir.h>
#endif

CAMLprim value unix_closedir(value vd)
CAMLprim value caml_unix_closedir(value vd)
{
CAMLparam1(vd);
DIR * d = DIR_Val(vd);
if (d == (DIR *) NULL) unix_error(EBADF, "closedir", Nothing);
if (d == (DIR *) NULL) caml_unix_error(EBADF, "closedir", Nothing);
caml_enter_blocking_section();
closedir(d);
caml_leave_blocking_section();
Expand Down
6 changes: 3 additions & 3 deletions otherlibs/unix/connect_unix.c
Original file line number Diff line number Diff line change
Expand Up @@ -22,13 +22,13 @@

#include "socketaddr.h"

CAMLprim value unix_connect(value socket, value address)
CAMLprim value caml_unix_connect(value socket, value address)
{
int retcode;
union sock_addr_union addr;
socklen_param_type addr_len;

unix_get_sockaddr(address, &addr, &addr_len);
caml_unix_get_sockaddr(address, &addr, &addr_len);
caml_enter_blocking_section();
retcode = connect(Int_val(socket), &addr.s_gen, addr_len);
caml_leave_blocking_section();
Expand All @@ -38,7 +38,7 @@ CAMLprim value unix_connect(value socket, value address)

#else

CAMLprim value unix_connect(value socket, value address)
CAMLprim value caml_unix_connect(value socket, value address)
{ caml_invalid_argument("connect not implemented"); }

#endif
4 changes: 2 additions & 2 deletions otherlibs/unix/connect_win32.c
Original file line number Diff line number Diff line change
Expand Up @@ -18,15 +18,15 @@
#include "unixsupport.h"
#include "socketaddr.h"

CAMLprim value unix_connect(socket, address)
CAMLprim value caml_unix_connect(socket, address)
value socket, address;
{
SOCKET s = Socket_val(socket);
union sock_addr_union addr;
socklen_param_type addr_len;
DWORD err = 0;

unix_get_sockaddr(address, &addr, &addr_len);
caml_unix_get_sockaddr(address, &addr, &addr_len);
caml_enter_blocking_section();
if (connect(s, &addr.s_gen, addr_len) == -1)
err = WSAGetLastError();
Expand Down

0 comments on commit b6f739c

Please sign in to comment.