summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--byterun/io.c32
-rw-r--r--otherlibs/bigarray/mmap_unix.c29
-rw-r--r--otherlibs/unix/lseek.c11
3 files changed, 58 insertions, 14 deletions
diff --git a/byterun/io.c b/byterun/io.c
index f8f186e50..44d1f293c 100644
--- a/byterun/io.c
+++ b/byterun/io.c
@@ -62,7 +62,9 @@ CAMLexport struct channel * caml_open_descriptor_in(int fd)
channel = (struct channel *) caml_stat_alloc(sizeof(struct channel));
channel->fd = fd;
- channel->offset = lseek (fd, 0, SEEK_CUR);
+ caml_enter_blocking_section();
+ channel->offset = lseek(fd, 0, SEEK_CUR);
+ caml_leave_blocking_section();
channel->curr = channel->max = channel->buff;
channel->end = channel->buff + IO_BUFFER_SIZE;
channel->mutex = NULL;
@@ -111,13 +113,21 @@ CAMLexport void caml_close_channel(struct channel *channel)
CAMLexport file_offset caml_channel_size(struct channel *channel)
{
+ file_offset offset;
file_offset end;
+ int fd;
- end = lseek(channel->fd, 0, SEEK_END);
- if (end == -1 ||
- lseek(channel->fd, channel->offset, SEEK_SET) != channel->offset) {
+ /* We extract data from [channel] before dropping the Caml lock, in case
+ someone else touches the block. */
+ fd = channel->fd;
+ offset = channel->offset;
+ caml_enter_blocking_section();
+ end = lseek(fd, 0, SEEK_END);
+ if (end == -1 || lseek(fd, offset, SEEK_SET) != offset) {
+ caml_leave_blocking_section();
caml_sys_error(NO_ARG);
}
+ caml_leave_blocking_section();
return end;
}
@@ -245,7 +255,12 @@ CAMLexport void caml_really_putblock(struct channel *channel,
CAMLexport void caml_seek_out(struct channel *channel, file_offset dest)
{
caml_flush(channel);
- if (lseek(channel->fd, dest, SEEK_SET) != dest) caml_sys_error(NO_ARG);
+ caml_enter_blocking_section();
+ if (lseek(channel->fd, dest, SEEK_SET) != dest) {
+ caml_leave_blocking_section();
+ caml_sys_error(NO_ARG);
+ }
+ caml_leave_blocking_section();
channel->offset = dest;
}
@@ -340,7 +355,12 @@ CAMLexport void caml_seek_in(struct channel *channel, file_offset dest)
dest <= channel->offset) {
channel->curr = channel->max - (channel->offset - dest);
} else {
- if (lseek(channel->fd, dest, SEEK_SET) != dest) caml_sys_error(NO_ARG);
+ caml_enter_blocking_section();
+ if (lseek(channel->fd, dest, SEEK_SET) != dest) {
+ caml_leave_blocking_section();
+ caml_sys_error(NO_ARG);
+ }
+ caml_leave_blocking_section();
channel->offset = dest;
channel->curr = channel->max = channel->buff;
}
diff --git a/otherlibs/bigarray/mmap_unix.c b/otherlibs/bigarray/mmap_unix.c
index 5cfb63571..f75e63578 100644
--- a/otherlibs/bigarray/mmap_unix.c
+++ b/otherlibs/bigarray/mmap_unix.c
@@ -65,10 +65,17 @@ CAMLprim value caml_ba_map_file(value vfd, value vkind, value vlayout,
caml_invalid_argument("Bigarray.create: negative dimension");
}
/* Determine file size */
+ caml_enter_blocking_section();
currpos = lseek(fd, 0, SEEK_CUR);
- if (currpos == -1) caml_sys_error(NO_ARG);
+ if (currpos == -1) {
+ caml_leave_blocking_section();
+ caml_sys_error(NO_ARG);
+ }
file_size = lseek(fd, 0, SEEK_END);
- if (file_size == -1) caml_sys_error(NO_ARG);
+ if (file_size == -1) {
+ caml_leave_blocking_section();
+ caml_sys_error(NO_ARG);
+ }
/* Determine array size in bytes (or size of array without the major
dimension if that dimension wasn't specified) */
array_size = caml_ba_element_size[flags & CAML_BA_KIND_MASK];
@@ -77,20 +84,29 @@ CAMLprim value caml_ba_map_file(value vfd, value vkind, value vlayout,
/* Check if the major dimension is unknown */
if (dim[major_dim] == -1) {
/* Determine major dimension from file size */
- if (file_size < startpos)
+ if (file_size < startpos) {
+ caml_leave_blocking_section();
caml_failwith("Bigarray.mmap: file position exceeds file size");
+ }
data_size = file_size - startpos;
dim[major_dim] = (uintnat) (data_size / array_size);
array_size = dim[major_dim] * array_size;
- if (array_size != data_size)
+ if (array_size != data_size) {
+ caml_leave_blocking_section();
caml_failwith("Bigarray.mmap: file size doesn't match array dimensions");
+ }
} else {
/* Check that file is large enough, and grow it otherwise */
if (file_size < startpos + array_size) {
- if (lseek(fd, startpos + array_size - 1, SEEK_SET) == -1)
+ if (lseek(fd, startpos + array_size - 1, SEEK_SET) == -1) {
+ caml_leave_blocking_section();
caml_sys_error(NO_ARG);
+ }
c = 0;
- if (write(fd, &c, 1) != 1) caml_sys_error(NO_ARG);
+ if (write(fd, &c, 1) != 1) {
+ caml_leave_blocking_section();
+ caml_sys_error(NO_ARG);
+ }
}
}
/* Restore original file position */
@@ -102,6 +118,7 @@ CAMLprim value caml_ba_map_file(value vfd, value vkind, value vlayout,
shared = Bool_val(vshared) ? MAP_SHARED : MAP_PRIVATE;
addr = mmap(NULL, array_size + delta, PROT_READ | PROT_WRITE,
shared, fd, startpos - delta);
+ caml_leave_blocking_section();
if (addr == (void *) MAP_FAILED) caml_sys_error(NO_ARG);
addr = (void *) ((uintnat) addr + delta);
/* Build and return the Caml bigarray */
diff --git a/otherlibs/unix/lseek.c b/otherlibs/unix/lseek.c
index 6dece9503..cb59bb551 100644
--- a/otherlibs/unix/lseek.c
+++ b/otherlibs/unix/lseek.c
@@ -39,8 +39,10 @@ static int seek_command_table[] = {
CAMLprim value unix_lseek(value fd, value ofs, value cmd)
{
file_offset ret;
+ caml_enter_blocking_section();
ret = lseek(Int_val(fd), Long_val(ofs),
seek_command_table[Int_val(cmd)]);
+ caml_leave_blocking_section();
if (ret == -1) uerror("lseek", Nothing);
if (ret > Max_long) unix_error(EOVERFLOW, "lseek", Nothing);
return Val_long(ret);
@@ -49,8 +51,13 @@ CAMLprim value unix_lseek(value fd, value ofs, value cmd)
CAMLprim value unix_lseek_64(value fd, value ofs, value cmd)
{
file_offset ret;
- ret = lseek(Int_val(fd), File_offset_val(ofs),
- seek_command_table[Int_val(cmd)]);
+ /* [ofs] is an Int64, which is stored as a custom block; we must therefore
+ extract its contents before dropping the runtime lock, or it might be
+ moved. */
+ file_offset ofs_c = File_offset_val(ofs);
+ caml_enter_blocking_section();
+ ret = lseek(Int_val(fd), ofs_c, seek_command_table[Int_val(cmd)]);
+ caml_leave_blocking_section();
if (ret == -1) uerror("lseek", Nothing);
return Val_file_offset(ret);
}