Branch win32-sockets: move do_read and do_write to OS-specific file.
This way, error handling is done in the OS-specific file (unix.c or win32.c). In turn, this makes it easier to report a good Sys_error exception in case of Win32 socket I/O error.master
parent
bdc8db8649
commit
aacb6d5861
|
@ -19,16 +19,20 @@
|
|||
#include "misc.h"
|
||||
|
||||
/* Read at most [n] bytes from file descriptor [fd] into buffer [buf].
|
||||
[is_socket] is true if [fd] refers to a socket. (This distinction
|
||||
matters for Win32, but not for Unix.) Return number of bytes
|
||||
read, or -1 if error. */
|
||||
extern int caml_read_fd(int fd, int is_socket, void * buf, int n);
|
||||
[flags] indicates whether [fd] is a socket
|
||||
(bit [CHANNEL_FLAG_FROM_SOCKET] is set in this case, see [io.h]).
|
||||
(This distinction matters for Win32, but not for Unix.)
|
||||
Return number of bytes read.
|
||||
In case of error, raises [Sys_error] or [Sys_blocked_io]. */
|
||||
extern int caml_read_fd(int fd, int flags, void * buf, int n);
|
||||
|
||||
/* Write at most [n] bytes from buffer [buf] onto file descriptor [fd].
|
||||
[is_socket] is true if [fd] refers to a socket. (This distinction
|
||||
matters for Win32, but not for Unix.) Return number of bytes
|
||||
written, or -1 if error. */
|
||||
extern int caml_write_fd(int fd, int is_socket, void * buf, int n);
|
||||
[flags] indicates whether [fd] is a socket
|
||||
(bit [CHANNEL_FLAG_FROM_SOCKET] is set in this case, see [io.h]).
|
||||
(This distinction matters for Win32, but not for Unix.)
|
||||
Return number of bytes written.
|
||||
In case of error, raises [Sys_error] or [Sys_blocked_io]. */
|
||||
extern int caml_write_fd(int fd, int flags, void * buf, int n);
|
||||
|
||||
/* Decompose the given path into a list of directories, and add them
|
||||
to the given table. Return the block to be freed later. */
|
||||
|
|
58
byterun/io.c
58
byterun/io.c
|
@ -149,27 +149,6 @@ CAMLexport int caml_channel_binary_mode(struct channel *channel)
|
|||
|
||||
/* Output */
|
||||
|
||||
#ifndef EINTR
|
||||
#define EINTR (-1)
|
||||
#endif
|
||||
#ifndef EAGAIN
|
||||
#define EAGAIN (-1)
|
||||
#endif
|
||||
#ifndef EWOULDBLOCK
|
||||
#define EWOULDBLOCK (-1)
|
||||
#endif
|
||||
|
||||
static int do_write(int fd, int flags, char *p, int n)
|
||||
{
|
||||
int retcode;
|
||||
caml_enter_blocking_section();
|
||||
retcode = caml_write_fd(fd, flags & CHANNEL_FLAG_FROM_SOCKET, p, n);
|
||||
caml_leave_blocking_section();
|
||||
if (retcode == -1) caml_sys_io_error(NO_ARG);
|
||||
CAMLassert (retcode > 0);
|
||||
return retcode;
|
||||
}
|
||||
|
||||
/* Attempt to flush the buffer. This will make room in the buffer for
|
||||
at least one character. Returns true if the buffer is empty at the
|
||||
end of the flush, or false if some data remains in the buffer.
|
||||
|
@ -182,7 +161,8 @@ CAMLexport int caml_flush_partial(struct channel *channel)
|
|||
towrite = channel->curr - channel->buff;
|
||||
CAMLassert (towrite >= 0);
|
||||
if (towrite > 0) {
|
||||
written = do_write(channel->fd, channel->flags, channel->buff, towrite);
|
||||
written = caml_write_fd(channel->fd, channel->flags,
|
||||
channel->buff, towrite);
|
||||
channel->offset += written;
|
||||
if (written < towrite)
|
||||
memmove(channel->buff, channel->buff + written, towrite - written);
|
||||
|
@ -226,7 +206,8 @@ CAMLexport int caml_putblock(struct channel *channel, char *p, intnat len)
|
|||
fits to buffer and write the buffer */
|
||||
memmove(channel->curr, p, free);
|
||||
towrite = channel->end - channel->buff;
|
||||
written = do_write(channel->fd, channel->flags, channel->buff, towrite);
|
||||
written = caml_write_fd(channel->fd, channel->flags,
|
||||
channel->buff, towrite);
|
||||
if (written < towrite)
|
||||
memmove(channel->buff, channel->buff + written, towrite - written);
|
||||
channel->offset += written;
|
||||
|
@ -265,29 +246,18 @@ CAMLexport file_offset caml_pos_out(struct channel *channel)
|
|||
|
||||
/* Input */
|
||||
|
||||
static int do_read(int fd, int flags, char *p, unsigned int n)
|
||||
{
|
||||
int retcode;
|
||||
|
||||
caml_enter_blocking_section();
|
||||
retcode = caml_read_fd(fd, flags & CHANNEL_FLAG_FROM_SOCKET, p, n);
|
||||
caml_leave_blocking_section();
|
||||
if (retcode == -1) caml_sys_io_error(NO_ARG);
|
||||
return retcode;
|
||||
}
|
||||
|
||||
/* caml_do_read is exported for Cash */
|
||||
CAMLexport int caml_do_read(int fd, char *p, unsigned int n)
|
||||
{
|
||||
return do_read(fd, 0, p, n);
|
||||
return caml_read_fd(fd, 0, p, n);
|
||||
}
|
||||
|
||||
CAMLexport unsigned char caml_refill(struct channel *channel)
|
||||
{
|
||||
int n;
|
||||
|
||||
n = do_read(channel->fd, channel->flags,
|
||||
channel->buff, channel->end - channel->buff);
|
||||
n = caml_read_fd(channel->fd, channel->flags,
|
||||
channel->buff, channel->end - channel->buff);
|
||||
if (n == 0) caml_raise_end_of_file();
|
||||
channel->offset += n;
|
||||
channel->max = channel->buff + n;
|
||||
|
@ -324,8 +294,8 @@ CAMLexport int caml_getblock(struct channel *channel, char *p, intnat len)
|
|||
channel->curr += avail;
|
||||
return avail;
|
||||
} else {
|
||||
nread = do_read(channel->fd, channel->flags, channel->buff,
|
||||
channel->end - channel->buff);
|
||||
nread = caml_read_fd(channel->fd, channel->flags, channel->buff,
|
||||
channel->end - channel->buff);
|
||||
channel->offset += nread;
|
||||
channel->max = channel->buff + nread;
|
||||
if (n > nread) n = nread;
|
||||
|
@ -394,8 +364,8 @@ CAMLexport intnat caml_input_scan_line(struct channel *channel)
|
|||
return -(channel->max - channel->curr);
|
||||
}
|
||||
/* Fill the buffer as much as possible */
|
||||
n = do_read(channel->fd, channel->flags,
|
||||
channel->max, channel->end - channel->max);
|
||||
n = caml_read_fd(channel->fd, channel->flags,
|
||||
channel->max, channel->end - channel->max);
|
||||
if (n == 0) {
|
||||
/* End-of-file encountered. Return the number of characters in the
|
||||
buffer, with negative sign since we haven't encountered
|
||||
|
@ -594,7 +564,7 @@ CAMLprim value caml_ml_set_binary_mode(value vchannel, value mode)
|
|||
#if defined(_WIN32)
|
||||
/* The implementation of [caml_read_fd] and [caml_write_fd] in win32.c
|
||||
doesn't support socket I/O with CRLF conversion. */
|
||||
if (channel->flags & CHANNEL_FLAG_FROM_SOCKET != 0
|
||||
if ((channel->flags & CHANNEL_FLAG_FROM_SOCKET) != 0
|
||||
&& ! Bool_val(mode)) {
|
||||
errno = EINVAL;
|
||||
caml_sys_error(NO_ARG);
|
||||
|
@ -762,7 +732,7 @@ CAMLprim value caml_ml_input(value vchannel, value buff, value vstart,
|
|||
|
||||
Lock(channel);
|
||||
/* We cannot call caml_getblock here because buff may move during
|
||||
caml_do_read */
|
||||
caml_read_fd */
|
||||
start = Long_val(vstart);
|
||||
len = Long_val(vlength);
|
||||
n = len >= INT_MAX ? INT_MAX : (int) len;
|
||||
|
@ -775,7 +745,7 @@ CAMLprim value caml_ml_input(value vchannel, value buff, value vstart,
|
|||
channel->curr += avail;
|
||||
n = avail;
|
||||
} else {
|
||||
nread = do_read(channel->fd, channel->flags, channel->buff,
|
||||
nread = caml_read_fd(channel->fd, channel->flags, channel->buff,
|
||||
channel->end - channel->buff);
|
||||
channel->offset += nread;
|
||||
channel->max = channel->buff + nread;
|
||||
|
|
|
@ -47,20 +47,35 @@
|
|||
#define S_ISREG(mode) (((mode) & S_IFMT) == S_IFREG)
|
||||
#endif
|
||||
|
||||
int caml_read_fd(int fd, int is_socket, void * buf, int n)
|
||||
#ifndef EINTR
|
||||
#define EINTR (-1)
|
||||
#endif
|
||||
#ifndef EAGAIN
|
||||
#define EAGAIN (-1)
|
||||
#endif
|
||||
#ifndef EWOULDBLOCK
|
||||
#define EWOULDBLOCK (-1)
|
||||
#endif
|
||||
|
||||
int caml_read_fd(int fd, int flags, void * buf, int n)
|
||||
{
|
||||
int retcode;
|
||||
do {
|
||||
caml_enter_blocking_section();
|
||||
retcode = read(fd, buf, n);
|
||||
caml_leave_blocking_section();
|
||||
} while (retcode == -1 && errno == EINTR);
|
||||
if (retcode == -1) caml_sys_io_error(NO_ARG);
|
||||
return retcode;
|
||||
}
|
||||
|
||||
int caml_write_fd(int fd, int is_socket, void * buf, int n)
|
||||
int caml_write_fd(int fd, int flags, void * buf, int n)
|
||||
{
|
||||
int retcode;
|
||||
again:
|
||||
caml_enter_blocking_section();
|
||||
retcode = write(fd, buf, n);
|
||||
caml_leave_blocking_section();
|
||||
if (retcode == -1) {
|
||||
if (errno == EINTR) goto again;
|
||||
if ((errno == EAGAIN || errno == EWOULDBLOCK) && n > 1) {
|
||||
|
@ -72,6 +87,8 @@ int caml_write_fd(int fd, int is_socket, void * buf, int n)
|
|||
n = 1; goto again;
|
||||
}
|
||||
}
|
||||
if (retcode == -1) caml_sys_io_error(NO_ARG);
|
||||
CAMLassert (retcode > 0);
|
||||
return retcode;
|
||||
}
|
||||
|
||||
|
|
|
@ -13,7 +13,10 @@
|
|||
|
||||
/* Win32-specific stuff */
|
||||
|
||||
#include <windows.h>
|
||||
#define WIN32_LEAN_AND_MEAN
|
||||
#include <wtypes.h>
|
||||
#include <winbase.h>
|
||||
#include <winsock2.h>
|
||||
#include <stdlib.h>
|
||||
#include <stdio.h>
|
||||
#include <stdarg.h>
|
||||
|
@ -21,13 +24,14 @@
|
|||
#include <fcntl.h>
|
||||
#include <sys/types.h>
|
||||
#include <sys/stat.h>
|
||||
#include <winsock2.h>
|
||||
#include <ctype.h>
|
||||
#include <errno.h>
|
||||
#include <string.h>
|
||||
#include <signal.h>
|
||||
#include "caml/alloc.h"
|
||||
#include "caml/address_class.h"
|
||||
#include "caml/fail.h"
|
||||
#include "caml/io.h"
|
||||
#include "caml/memory.h"
|
||||
#include "caml/misc.h"
|
||||
#include "caml/osdeps.h"
|
||||
|
@ -40,32 +44,65 @@
|
|||
#define S_ISREG(mode) (((mode) & S_IFMT) == S_IFREG)
|
||||
#endif
|
||||
|
||||
int caml_read_fd(int fd, int is_socket, void * buf, int n)
|
||||
CAMLnoreturn_start
|
||||
static void caml_win32_sys_error (int errnum)
|
||||
CAMLnoreturn_end;
|
||||
|
||||
static void caml_win32_sys_error(int errnum)
|
||||
{
|
||||
char buffer[512];
|
||||
value msg;
|
||||
if (FormatMessage(FORMAT_MESSAGE_FROM_SYSTEM | FORMAT_MESSAGE_IGNORE_INSERTS,
|
||||
NULL,
|
||||
errnum,
|
||||
0,
|
||||
buffer,
|
||||
sizeof(buffer),
|
||||
NULL)) {
|
||||
msg = caml_copy_string(buffer);
|
||||
} else {
|
||||
msg = caml_alloc_sprintf("unknown error #%d", errnum);
|
||||
}
|
||||
caml_raise_sys_error(msg);
|
||||
}
|
||||
|
||||
int caml_read_fd(int fd, int flags, void * buf, int n)
|
||||
{
|
||||
int retcode;
|
||||
if (! is_socket) {
|
||||
if ((flags & CHANNEL_FLAG_FROM_SOCKET) == 0) {
|
||||
caml_enter_blocking_section();
|
||||
retcode = read(fd, buf, n);
|
||||
/* Large reads from console can fail with ENOMEM. Reduce requested size
|
||||
and try again. */
|
||||
if (retcode == -1 && errno == ENOMEM && n > 16384) {
|
||||
retcode = read(fd, p, 16384);
|
||||
retcode = read(fd, buf, 16384);
|
||||
}
|
||||
caml_leave_blocking_section();
|
||||
if (retcode == -1) caml_sys_io_error(NO_ARG);
|
||||
} else {
|
||||
retcode = recv((SOCKET) _getosfhandle(fd), buf, n, 0);
|
||||
if (ret == -1) _dosmaperr(WSAGetLastError());
|
||||
caml_enter_blocking_section();
|
||||
retcode = recv((SOCKET) _get_osfhandle(fd), buf, n, 0);
|
||||
caml_leave_blocking_section();
|
||||
if (retcode == -1) caml_win32_sys_error(WSAGetLastError());
|
||||
}
|
||||
return retcode;
|
||||
}
|
||||
|
||||
int caml_write_fd(int fd, int is_socket, void * buf, int n)
|
||||
int caml_write_fd(int fd, int flags, void * buf, int n)
|
||||
{
|
||||
int retcode;
|
||||
if (! is_socket) {
|
||||
if ((flags & CHANNEL_FLAG_FROM_SOCKET) == 0) {
|
||||
caml_enter_blocking_section();
|
||||
retcode = write(fd, buf, n);
|
||||
caml_leave_blocking_section();
|
||||
if (retcode == -1) caml_sys_io_error(NO_ARG);
|
||||
} else {
|
||||
retcode = send((SOCKET) _getosfhandle(fd), buf, n, 0);
|
||||
if (ret == -1) _dosmaperr(WSAGetLastError());
|
||||
caml_enter_blocking_section();
|
||||
retcode = send((SOCKET) _get_osfhandle(fd), buf, n, 0);
|
||||
caml_leave_blocking_section();
|
||||
if (retcode == -1) caml_win32_sys_error(WSAGetLastError());
|
||||
}
|
||||
CAMLassert (retcode > 0);
|
||||
return retcode;
|
||||
}
|
||||
|
||||
|
@ -349,7 +386,7 @@ void caml_signal_thread(void * lpParam)
|
|||
char *endptr;
|
||||
HANDLE h;
|
||||
/* Get an hexa-code raw handle through the environment */
|
||||
h = (HANDLE) strtol(getenv("CAMLSIGPIPE"), &endptr, 16);
|
||||
h = (HANDLE) (uintptr_t) strtol(getenv("CAMLSIGPIPE"), &endptr, 16);
|
||||
while (1) {
|
||||
DWORD numread;
|
||||
BOOL ret;
|
||||
|
|
Loading…
Reference in New Issue