Skip to content

Commit

Permalink
Merge pull request #10926 from dra27/check-symbols
Browse files Browse the repository at this point in the history
Ensure C global symbols are consistently prefixed
  • Loading branch information
Octachron committed Jun 13, 2022
2 parents 9ef0373 + b6f739c commit 000d15d
Show file tree
Hide file tree
Showing 165 changed files with 1,307 additions and 1,235 deletions.
8 changes: 8 additions & 0 deletions Changes
Original file line number Diff line number Diff line change
Expand Up @@ -428,6 +428,10 @@ OCaml 4.14.0
- #10730, 10731: Fix bug in `Obj.reachable_words` causing a slowdown when called
multiple time (Alain Frisch, report by ygrek, review by Xavier Leroy)

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

### Code generation and optimizations:

- #10578: Increase the number of integer registers used for
Expand Down Expand Up @@ -535,6 +539,10 @@ OCaml 4.14.0
WSADuplicateSocket on sockets instead of DuplicateHandle.
(Antonin Décimo, review by Xavier Leroy and Nicolás Ojeda Bär)

- #10926: Prefix all C functions in the Unix library with `unix_` except for the
venerable `uerror`.
(David Allsopp, review by Kate Deplaix and Xavier Leroy)

- #10951: Introduce the Thread.Exit exception as an alternative way to
terminate threads prematurely. This alternative way will become
the standard way in 5.0.
Expand Down
4 changes: 4 additions & 0 deletions otherlibs/unix/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,10 @@ LIBNAME=unix

EXTRACAMLFLAGS=-nolabels

# This flag is used to disable compatibility definitions in header files to
# ensure that they're not accidentally used in the library itself.
OC_CPPFLAGS += -DCAML_BUILDING_UNIX

unixLabels.cmi: \
EXTRACAMLFLAGS += -pp "$(AWK) -f $(ROOTDIR)/stdlib/expand_module_aliases.awk"

Expand Down
12 changes: 6 additions & 6 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 @@ -44,11 +44,11 @@ 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);
if (clo) caml_unix_set_cloexec(retcode, "accept", Nothing);
#endif
a = 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
12 changes: 6 additions & 6 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 @@ -37,12 +37,12 @@ CAMLprim value unix_accept(value cloexec, value sock)
if (snew == INVALID_SOCKET) err = WSAGetLastError ();
caml_leave_blocking_section();
if (snew == INVALID_SOCKET) {
win32_maperr(err);
uerror("accept", Nothing);
caml_win32_maperr(err);
caml_uerror("accept", Nothing);
}
win_set_cloexec((HANDLE) snew, cloexec);
fd = win_alloc_socket(snew);
adr = alloc_sockaddr(&addr, addr_len, snew);
caml_win32_set_cloexec((HANDLE) snew, cloexec);
fd = caml_win32_alloc_socket(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
4 changes: 2 additions & 2 deletions 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 All @@ -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);
}
18 changes: 10 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,13 +42,15 @@ CAMLprim value unix_inet_addr_of_string(value s)
case AF_INET:
{
vres =
alloc_inet_addr(&((struct sockaddr_in *) res->ai_addr)->sin_addr);
caml_unix_alloc_inet_addr(
&((struct sockaddr_in *) res->ai_addr)->sin_addr);
break;
}
case AF_INET6:
{
vres =
alloc_inet6_addr(&((struct sockaddr_in6 *) res->ai_addr)->sin6_addr);
caml_unix_alloc_inet6_addr(
&((struct sockaddr_in6 *) res->ai_addr)->sin6_addr);
break;
}
default:
Expand All @@ -65,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 alloc_inet_addr(&address);
return caml_unix_alloc_inet_addr(&address);
else if (inet_pton(AF_INET6, String_val(s), &address6) > 0)
return alloc_inet6_addr(&address6);
return caml_unix_alloc_inet6_addr(&address6);
else
caml_failwith("inet_addr_of_string");
}
Expand All @@ -77,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 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 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)));
}
8 changes: 4 additions & 4 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;

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) uerror("bind", Nothing);
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
8 changes: 4 additions & 4 deletions otherlibs/unix/bind_win32.c
Original file line number Diff line number Diff line change
Expand Up @@ -17,18 +17,18 @@
#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;

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) {
win32_maperr(WSAGetLastError());
uerror("bind", Nothing);
caml_win32_maperr(WSAGetLastError());
caml_uerror("bind", Nothing);
}
return Val_unit;
}
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);
}
40 changes: 23 additions & 17 deletions otherlibs/unix/channels_win32.c
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,7 @@
UDP (datagram) sockets.
Returns 0 if OK, a Win32 error code if error. */

static DWORD win_check_stream_semantics(value handle)
static DWORD check_stream_semantics(value handle)
{
switch (Descr_kind_val(handle)) {
case KIND_HANDLE:
Expand Down Expand Up @@ -60,19 +60,19 @@ static DWORD win_check_stream_semantics(value handle)
}
}

int win_CRT_fd_of_filedescr(value handle)
int caml_win32_CRT_fd_of_filedescr(value handle)
{
if (CRT_fd_val(handle) != NO_CRT_FD) {
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;
}
}

CAMLprim value win_inchannel_of_filedescr(value handle)
CAMLprim value caml_unix_inchannel_of_filedescr(value handle)
{
CAMLparam1(handle);
CAMLlocal1(vchan);
Expand All @@ -82,9 +82,12 @@ CAMLprim value win_inchannel_of_filedescr(value handle)
#if defined(_MSC_VER) && _MSC_VER < 1400
fflush(stdin);
#endif
err = win_check_stream_semantics(handle);
if (err != 0) { win32_maperr(err); uerror("in_channel_of_descr", Nothing); }
chan = caml_open_descriptor_in(win_CRT_fd_of_filedescr(handle));
err = check_stream_semantics(handle);
if (err != 0) {
caml_win32_maperr(err);
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;
/* as in caml_ml_open_descriptor_in() */
if (Descr_kind_val(handle) == KIND_SOCKET)
Expand All @@ -93,17 +96,20 @@ CAMLprim value win_inchannel_of_filedescr(value handle)
CAMLreturn(vchan);
}

CAMLprim value win_outchannel_of_filedescr(value handle)
CAMLprim value caml_unix_outchannel_of_filedescr(value handle)
{
CAMLparam1(handle);
CAMLlocal1(vchan);
int fd;
struct channel * chan;
DWORD err;

err = win_check_stream_semantics(handle);
if (err != 0) { win32_maperr(err); uerror("out_channel_of_descr", Nothing); }
chan = caml_open_descriptor_out(win_CRT_fd_of_filedescr(handle));
err = check_stream_semantics(handle);
if (err != 0) {
caml_win32_maperr(err);
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;
/* as in caml_ml_open_descriptor_out() */
if (Descr_kind_val(handle) == KIND_SOCKET)
Expand All @@ -112,31 +118,31 @@ CAMLprim value win_outchannel_of_filedescr(value handle)
CAMLreturn(vchan);
}

CAMLprim value win_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 = win_alloc_socket((SOCKET) h);
fd = caml_win32_alloc_socket((SOCKET) h);
else
fd = win_alloc_handle(h);
fd = caml_win32_alloc_handle(h);
CRT_fd_val(fd) = chan->fd;
CAMLreturn(fd);
}

CAMLprim value win_handle_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
degradation and this function is only used with the standard
handles 0, 1, 2, which are not sockets. */
value res = win_alloc_handle((HANDLE) _get_osfhandle(crt_fd));
value res = caml_win32_alloc_handle((HANDLE) _get_osfhandle(crt_fd));
CRT_fd_val(res) = crt_fd;
return res;
}

0 comments on commit 000d15d

Please sign in to comment.