File 0503-Fix-efile_allocate-on-Mac.patch of Package erlang

From 4c024f1d700cb8d75d13ed8ac6bf36ae98ce9ab6 Mon Sep 17 00:00:00 2001
From: Julius Putra Tanu Setiaji <indocomsoft@gmail.com>
Date: Fri, 13 Sep 2019 16:12:16 +0800
Subject: [PATCH] Fix efile_allocate on Mac

---
 erts/emulator/nifs/unix/unix_prim_file.c | 42 +++++++++++++++++++++++++++++---
 lib/kernel/test/file_SUITE.erl           | 26 +++++++++++++++++++-
 2 files changed, 64 insertions(+), 4 deletions(-)

diff --git a/erts/emulator/nifs/unix/unix_prim_file.c b/erts/emulator/nifs/unix/unix_prim_file.c
index 169b193993..fbf312a3b8 100644
--- a/erts/emulator/nifs/unix/unix_prim_file.c
+++ b/erts/emulator/nifs/unix/unix_prim_file.c
@@ -559,18 +559,54 @@ int efile_allocate(efile_data_t *d, Sint64 offset, Sint64 length) {
     } while(ret < 0 && errno == EINTR);
 #elif defined(F_PREALLOCATE)
     /* Mac-specific */
+    off_t original_position, eof_offset;
     fstore_t fs = {};
 
+    if(offset < 0 || length < 0 || (offset > ERTS_SINT64_MAX - length)) {
+        u->common.posix_errno = EINVAL;
+        return 0;
+    }
+
+    original_position = lseek(u->fd, 0, SEEK_CUR);
+
+    if(original_position < 0) {
+        u->common.posix_errno = errno;
+        return 0;
+    }
+
+    eof_offset = lseek(u->fd, 0, SEEK_END);
+
+    if(eof_offset < 0 || lseek(u->fd, original_position, SEEK_SET) < 0) {
+        u->common.posix_errno = errno;
+        return 0;
+    }
+
+    if(offset + length <= eof_offset) {
+        /* File is already large enough. */
+        return 1;
+    }
+
     fs.fst_flags = F_ALLOCATECONTIG;
-    fs.fst_posmode = F_VOLPOSMODE;
-    fs.fst_offset = offset;
-    fs.fst_length = length;
+    fs.fst_posmode = F_PEOFPOSMODE;
+    fs.fst_offset = 0;
+    fs.fst_length = (offset + length) - eof_offset;
 
     ret = fcntl(u->fd, F_PREALLOCATE, &fs);
     if(ret < 0) {
         fs.fst_flags = F_ALLOCATEALL;
         ret = fcntl(u->fd, F_PREALLOCATE, &fs);
     }
+
+    if(ret >= 0) {
+        /* We MUST truncate since F_PREALLOCATE works relative to end-of-file,
+         * otherwise we will expand the file on repeated calls to
+         * file:allocate/3 with the same arguments. */
+        ret = ftruncate(u->fd, offset + length);
+        if(ret < 0) {
+            u->common.posix_errno = errno;
+            return 0;
+        }
+    }
 #elif !defined(HAVE_POSIX_FALLOCATE)
     u->common.posix_errno = ENOTSUP;
     return 0;
diff --git a/lib/kernel/test/file_SUITE.erl b/lib/kernel/test/file_SUITE.erl
index 3bc8e6e828..7686aeee7d 100644
--- a/lib/kernel/test/file_SUITE.erl
+++ b/lib/kernel/test/file_SUITE.erl
@@ -94,6 +94,8 @@
 
 -export([allocate/1]).
 
+-export([allocate_file_size/1]).
+
 -export([standard_io/1,mini_server/1]).
 
 -export([old_io_protocol/1]).
@@ -145,7 +147,7 @@ groups() ->
      {files, [],
       [{group, open}, {group, pos}, {group, file_info},
        {group, consult}, {group, eval}, {group, script},
-       truncate, sync, datasync, advise, allocate]},
+       truncate, sync, datasync, advise, allocate, allocate_file_size]},
      {open, [],
       [open1, old_modes, new_modes, path_open, close, access,
        read_write, pread_write, append, open_errors,
@@ -2036,6 +2038,28 @@ allocate_and_assert(Fd, Offset, Length) ->
             _ = Result
     end.
 
+%% Tests that asserts that file:allocate/3 changes file size
+allocate_file_size(Config) when is_list(Config) ->
+    case os:type() of
+        {win32, _} ->
+            {skip, "Windows does not support file:allocate/3"};
+
+        {unix, linux} ->
+            {skip, "file:allocate/3 on Linux does not change file size"};
+
+        _ ->
+            PrivDir = proplists:get_value(priv_dir, Config),
+            Allocate = filename:join(PrivDir, atom_to_list(?MODULE)++"_allocate_file"),
+
+            {ok, Fd} = ?FILE_MODULE:open(Allocate, [write]),
+            ok = ?FILE_MODULE:allocate(Fd, 0, 1024),
+            {ok, 1024} = ?FILE_MODULE:position(Fd, eof),
+            ok = ?FILE_MODULE:close(Fd),
+
+            [] = flush(),
+            ok
+    end.
+
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
 delete(Config) when is_list(Config) ->
-- 
2.16.4

openSUSE Build Service is sponsored by