Skip to content

Commit

Permalink
Use 4.12 convenience option macros in C stubs
Browse files Browse the repository at this point in the history
No change entry needed
  • Loading branch information
MisterDA committed Feb 26, 2021
1 parent aced66c commit 3b4ae00
Show file tree
Hide file tree
Showing 11 changed files with 41 additions and 44 deletions.
4 changes: 2 additions & 2 deletions otherlibs/unix/dup2.c
Original file line number Diff line number Diff line change
Expand Up @@ -23,8 +23,8 @@ CAMLprim value unix_dup2(value cloexec, value fd1, value fd2)
if (Int_val(fd2) == Int_val(fd1)) {
/* In this case, dup3 fails and dup2 does nothing. */
/* Just apply the cloexec flag to fd2, if it is given. */
if (Is_block(cloexec)) {
if (Bool_val(Field(cloexec, 0)))
if (Is_some(cloexec)) {
if (Bool_val(Some_val(cloexec)))
unix_set_cloexec(Int_val(fd2), "dup2", Nothing);
else
unix_clear_cloexec(Int_val(fd2), "dup2", Nothing);
Expand Down
7 changes: 2 additions & 5 deletions otherlibs/unix/errmsg.c
Original file line number Diff line number Diff line change
Expand Up @@ -15,14 +15,11 @@

#include <errno.h>
#include <string.h>
#include <caml/mlvalues.h>
#include <caml/alloc.h>

extern int error_table[];
#include "unixsupport.h"

CAMLprim value unix_error_message(value err)
{
int errnum;
errnum = Is_block(err) ? Int_val(Field(err, 0)) : error_table[Int_val(err)];
int errnum = code_of_unix_error(err);
return caml_copy_string(strerror(errnum));
}
6 changes: 3 additions & 3 deletions otherlibs/unix/link.c
Original file line number Diff line number Diff line change
Expand Up @@ -37,12 +37,12 @@ CAMLprim value unix_link(value follow, value path1, value path2)
p1 = caml_stat_strdup(String_val(path1));
p2 = caml_stat_strdup(String_val(path2));
caml_enter_blocking_section();
if (follow == Val_int(0) /* None */)
if (Is_none(follow))
ret = link(p1, p2);
else { /* Some bool */
else {
# ifdef AT_SYMLINK_FOLLOW
int flags =
Is_block(follow) && Bool_val(Field(follow, 0)) /* Some true */
Is_some(follow) && Bool_val(Some_val(follow))
? AT_SYMLINK_FOLLOW
: 0;
ret = linkat(AT_FDCWD, p1, AT_FDCWD, p2, flags);
Expand Down
15 changes: 6 additions & 9 deletions otherlibs/unix/sockopt.c
Original file line number Diff line number Diff line change
Expand Up @@ -205,24 +205,21 @@ unix_getsockopt_aux(char * name,
return Val_int(optval.i);
case TYPE_LINGER:
if (optval.lg.l_onoff == 0) {
return Val_int(0); /* None */
return Val_none;
} else {
value res = caml_alloc_small(1, 0); /* Some */
Field(res, 0) = Val_int(optval.lg.l_linger);
return res;
return caml_alloc_some(Val_int(optval.lg.l_linger));
}
case TYPE_TIMEVAL:
return caml_copy_double((double) optval.tv.tv_sec
+ (double) optval.tv.tv_usec / 1e6);
case TYPE_UNIX_ERROR:
if (optval.i == 0) {
return Val_int(0); /* None */
return Val_none;
} else {
value err, res;
err = unix_error_of_code(optval.i);
Begin_root(err);
res = caml_alloc_small(1, 0); /* Some */
Field(res, 0) = err;
res = caml_alloc_some(err);
End_roots();
return res;
}
Expand All @@ -248,9 +245,9 @@ unix_setsockopt_aux(char * name,
break;
case TYPE_LINGER:
optsize = sizeof(optval.lg);
optval.lg.l_onoff = Is_block (val);
optval.lg.l_onoff = Is_some(val);
if (optval.lg.l_onoff)
optval.lg.l_linger = Int_val (Field (val, 0));
optval.lg.l_linger = Int_val(Some_val(val));
break;
case TYPE_TIMEVAL:
f = Double_val(val);
Expand Down
10 changes: 5 additions & 5 deletions otherlibs/unix/spawn.c
Original file line number Diff line number Diff line change
Expand Up @@ -44,8 +44,8 @@ CAMLprim value unix_spawn(value executable, /* string */
caml_unix_check_path(executable, "create_process");
path = String_val(executable);
argv = cstringvect(args, "create_process");
if (Is_block(optenv)) {
envp = cstringvect(Field(optenv, 0), "create_process");
if (Is_some(optenv)) {
envp = cstringvect(Some_val(optenv), "create_process");
} else {
envp = environ;
}
Expand Down Expand Up @@ -76,7 +76,7 @@ CAMLprim value unix_spawn(value executable, /* string */
error:
posix_spawn_file_actions_destroy(&act);
cstringvect_free(argv);
if (Is_block(optenv)) cstringvect_free(envp);
if (Is_some(optenv)) cstringvect_free(envp);
if (r != 0) unix_error(r, "create_process", executable);
return Val_long(pid);
}
Expand Down Expand Up @@ -111,8 +111,8 @@ CAMLprim value unix_spawn(value executable, /* string */
caml_unix_check_path(executable, "create_process");
path = String_val(executable);
argv = cstringvect(args, "create_process");
if (Is_block(optenv)) {
envp = cstringvect(Field(optenv, 0), "create_process");
if (Is_some(optenv)) {
envp = cstringvect(Some_val(optenv), "create_process");
} else {
envp = NULL;
}
Expand Down
7 changes: 3 additions & 4 deletions otherlibs/unix/unixsupport.c
Original file line number Diff line number Diff line change
Expand Up @@ -276,7 +276,7 @@ value unix_error_of_code (int errcode)
return err;
}

extern int code_of_unix_error (value error)
int code_of_unix_error (value error)
{
if (Is_block(error)) {
return Int_val(Field(error, 0));
Expand Down Expand Up @@ -323,9 +323,8 @@ int unix_cloexec_default = 0;

int unix_cloexec_p(value cloexec)
{
/* [cloexec] is a [bool option]. */
if (Is_block(cloexec))
return Bool_val(Field(cloexec, 0));
if (Is_some(cloexec))
return Bool_val(Some_val(cloexec));
else
return unix_cloexec_default;
}
Expand Down
4 changes: 1 addition & 3 deletions otherlibs/win32unix/errmsg.c
Original file line number Diff line number Diff line change
Expand Up @@ -23,14 +23,12 @@
#include <caml/osdeps.h>
#include "unixsupport.h"

extern int error_table[];

CAMLprim value unix_error_message(value err)
{
int errnum;
wchar_t buffer[512];

errnum = Is_block(err) ? Int_val(Field(err, 0)) : error_table[Int_val(err)];
errnum = code_of_unix_error(err);
if (errnum > 0)
return caml_copy_string(strerror(errnum));
if (FormatMessage(FORMAT_MESSAGE_FROM_SYSTEM | FORMAT_MESSAGE_IGNORE_INSERTS,
Expand Down
2 changes: 1 addition & 1 deletion otherlibs/win32unix/link.c
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,7 @@ CAMLprim value unix_link(value follow, value path1, value path2)
tCreateHardLink pCreateHardLink;
BOOL result;
wchar_t * wpath1, * wpath2;
if (Is_block(follow) && !Bool_val(Field(follow, 0))) { /* Some false */
if (Is_some(follow) && !Bool_val(Some_val(follow))) {
errno = ENOSYS;
uerror("link", path2);
}
Expand Down
15 changes: 6 additions & 9 deletions otherlibs/win32unix/sockopt.c
Original file line number Diff line number Diff line change
Expand Up @@ -142,24 +142,21 @@ unix_getsockopt_aux(char * name,
return Val_int(optval.i);
case TYPE_LINGER:
if (optval.lg.l_onoff == 0) {
return Val_int(0); /* None */
return Val_none;
} else {
value res = caml_alloc_small(1, 0); /* Some */
Field(res, 0) = Val_int(optval.lg.l_linger);
return res;
return caml_alloc_some(Val_int(optval.lg.l_linger));
}
case TYPE_TIMEVAL:
return caml_copy_double((double) optval.tv.tv_sec
+ (double) optval.tv.tv_usec / 1e6);
case TYPE_UNIX_ERROR:
if (optval.i == 0) {
return Val_int(0); /* None */
return Val_none;
} else {
value err, res;
err = unix_error_of_code(optval.i);
Begin_root(err);
res = caml_alloc_small(1, 0); /* Some */
Field(res, 0) = err;
res = caml_alloc_some(err);
End_roots();
return res;
}
Expand All @@ -186,9 +183,9 @@ unix_setsockopt_aux(char * name,
break;
case TYPE_LINGER:
optsize = sizeof(optval.lg);
optval.lg.l_onoff = Is_block (val);
optval.lg.l_onoff = Is_some(val);
if (optval.lg.l_onoff)
optval.lg.l_linger = Int_val (Field (val, 0));
optval.lg.l_linger = Int_val(Some_val(val));
break;
case TYPE_TIMEVAL:
f = Double_val(val);
Expand Down
14 changes: 11 additions & 3 deletions otherlibs/win32unix/unixsupport.c
Original file line number Diff line number Diff line change
Expand Up @@ -284,6 +284,15 @@ value unix_error_of_code (int errcode)
return err;
}

int code_of_unix_error (value error)
{
if (Is_block(error)) {
return Int_val(Field(error, 0));
} else {
return error_table[Int_val(error)];
}
}

void unix_error(int errcode, const char *cmdname, value cmdarg)
{
value res;
Expand Down Expand Up @@ -323,9 +332,8 @@ int unix_cloexec_default = 0;

int unix_cloexec_p(value cloexec)
{
/* [cloexec] is a [bool option]. */
if (Is_block(cloexec))
return Bool_val(Field(cloexec, 0));
if (Is_some(cloexec))
return Bool_val(Some_val(cloexec));
else
return unix_cloexec_default;
}
1 change: 1 addition & 0 deletions otherlibs/win32unix/unixsupport.h
Original file line number Diff line number Diff line change
Expand Up @@ -57,6 +57,7 @@ extern int win_CRT_fd_of_filedescr(value handle);

extern void win32_maperr(DWORD errcode);
extern value unix_error_of_code (int errcode);
extern int code_of_unix_error (value error);

CAMLnoreturn_start
extern void unix_error (int errcode, const char * cmdname, value arg)
Expand Down

0 comments on commit 3b4ae00

Please sign in to comment.