File 2421-file-allow-open-2-to-work-on-directories.patch of Package erlang

From bd3f4f05bb6dafdedbae5671ee50c769a3560021 Mon Sep 17 00:00:00 2001
From: Andre Nathan <andre@digirati.com.br>
Date: Thu, 18 Apr 2019 17:45:04 -0300
Subject: [PATCH] file: allow open/2 to work on directories

This is useful mainly to ensure that a new file has been persisted
to disk by calling file:sync/1 or file:datasync/1 on file's parent
directory.
---
 erts/emulator/nifs/common/prim_file_nif.c |  3 ++
 erts/emulator/nifs/common/prim_file_nif.h |  2 ++
 erts/emulator/nifs/unix/unix_prim_file.c  | 49 ++++++++++++++++++-------------
 erts/emulator/nifs/win32/win_prim_file.c  | 30 ++++++++++++++++---
 lib/kernel/doc/src/file.xml               | 10 +++++--
 lib/kernel/src/file.erl                   |  4 +--
 lib/kernel/test/file_SUITE.erl            | 11 +++++++
 7 files changed, 80 insertions(+), 29 deletions(-)

diff --git a/erts/emulator/nifs/common/prim_file_nif.c b/erts/emulator/nifs/common/prim_file_nif.c
index 3df04e42e2..9e9a14844e 100644
--- a/erts/emulator/nifs/common/prim_file_nif.c
+++ b/erts/emulator/nifs/common/prim_file_nif.c
@@ -231,6 +231,7 @@ static int load(ErlNifEnv *env, void** priv_data, ERL_NIF_TERM prim_file_pid)
     am_append = enif_make_atom(env, "append");
     am_sync = enif_make_atom(env, "sync");
     am_skip_type_check = enif_make_atom(env, "skip_type_check");
+    am_directory = enif_make_atom(env, "directory");
 
     am_read_write = enif_make_atom(env, "read_write");
     am_none = enif_make_atom(env, "none");
@@ -447,6 +448,8 @@ static enum efile_modes_t efile_translate_modelist(ErlNifEnv *env, ERL_NIF_TERM
             modes |= EFILE_MODE_SYNC;
         } else if(enif_is_identical(head, am_skip_type_check)) {
             modes |= EFILE_MODE_SKIP_TYPE_CHECK;
+        } else if (enif_is_identical(head, am_directory)) {
+            modes |= EFILE_MODE_DIRECTORY;
         } else {
             /* Modes like 'raw', 'ram', 'delayed_writes' etc are handled
              * further up the chain. */
diff --git a/erts/emulator/nifs/common/prim_file_nif.h b/erts/emulator/nifs/common/prim_file_nif.h
index b2e30c59dd..020714a03b 100644
--- a/erts/emulator/nifs/common/prim_file_nif.h
+++ b/erts/emulator/nifs/common/prim_file_nif.h
@@ -30,6 +30,8 @@ enum efile_modes_t {
     EFILE_MODE_SKIP_TYPE_CHECK = (1 << 5), /* Special for device files on Unix. */
     EFILE_MODE_NO_TRUNCATE = (1 << 6), /* Special for reopening on VxWorks. */
 
+    EFILE_MODE_DIRECTORY = (1 << 7),
+
     EFILE_MODE_READ_WRITE = EFILE_MODE_READ | EFILE_MODE_WRITE
 };
 
diff --git a/erts/emulator/nifs/unix/unix_prim_file.c b/erts/emulator/nifs/unix/unix_prim_file.c
index 169b193993..20021b9358 100644
--- a/erts/emulator/nifs/unix/unix_prim_file.c
+++ b/erts/emulator/nifs/unix/unix_prim_file.c
@@ -107,7 +107,7 @@ ERL_NIF_TERM efile_get_handle(ErlNifEnv *env, efile_data_t *d) {
     return result;
 }
 
-static int open_file_type_check(const efile_path_t *path, int fd) {
+static int open_file_is_dir(const efile_path_t *path, int fd) {
     struct stat file_info;
     int error;
 
@@ -119,27 +119,14 @@ static int open_file_type_check(const efile_path_t *path, int fd) {
     (void)path;
 #endif
 
-    if(error < 0) {
-        /* If we failed to stat assume success and let the next call handle the
-         * error. The old driver checked whether the file was to be used
-         * immediately in a read within the call, but the new implementation
-         * never does that. */
-         return 1;
-    }
-
-    /* Allow everything that isn't a directory, and error out on the next call
-     * if it's unsupported. */
-    if(S_ISDIR(file_info.st_mode)) {
-        return 0;
-    }
-
-    return 1;
+    /* Assume not a directory on error. */
+    return error == 0 && S_ISDIR(file_info.st_mode);
 }
 
 posix_errno_t efile_open(const efile_path_t *path, enum efile_modes_t modes,
         ErlNifResourceType *nif_type, efile_data_t **d) {
 
-    int flags, fd;
+    int mode, flags, fd;
 
     flags = 0;
 
@@ -174,18 +161,38 @@ posix_errno_t efile_open(const efile_path_t *path, enum efile_modes_t modes,
 #endif
     }
 
+    if(modes & EFILE_MODE_DIRECTORY) {
+        mode = DIR_MODE;
+#ifdef O_DIRECTORY
+        flags |= O_DIRECTORY;
+#endif
+    } else {
+        mode = FILE_MODE;
+    }
+
     do {
-        fd = open((const char*)path->data, flags, FILE_MODE);
+        fd = open((const char*)path->data, flags, mode);
     } while(fd == -1 && errno == EINTR);
 
     if(fd != -1) {
         efile_unix_t *u;
 
-        if(!(modes & EFILE_MODE_SKIP_TYPE_CHECK) && !open_file_type_check(path, fd)) {
+#ifndef O_DIRECTORY
+        /* On platforms without O_DIRECTORY support, ensure that using the
+         * directory flag to open a file fails. */
+        if(!(modes & EFILE_MODE_SKIP_TYPE_CHECK) &&
+           (modes & EFILE_MODE_DIRECTORY) && !open_file_is_dir(path, fd)) {
             close(fd);
+            return ENOTDIR;
+        }
+#endif
 
-            /* This is blatantly incorrect, but we're documented as returning
-             * this for everything that isn't a file. */
+        /* open() works on directories without the O_DIRECTORY flag but for
+         * consistency across platforms we require that the user has requested
+         * directory mode. */
+        if(!(modes & EFILE_MODE_SKIP_TYPE_CHECK) &&
+           !(modes & EFILE_MODE_DIRECTORY) && open_file_is_dir(path, fd)) {
+            close(fd);
             return EISDIR;
         }
 
diff --git a/erts/emulator/nifs/win32/win_prim_file.c b/erts/emulator/nifs/win32/win_prim_file.c
index e7d3924240..13306104c0 100644
--- a/erts/emulator/nifs/win32/win_prim_file.c
+++ b/erts/emulator/nifs/win32/win_prim_file.c
@@ -269,6 +269,17 @@ static int normalize_path_result(ErlNifBinary *path) {
     return enif_realloc_binary(path, length * sizeof(WCHAR));
 }
 
+/* @brief Checks whether all the given attributes are set on the object at the
+ * given handle. Note that it assumes false on errors. */
+static int handle_has_file_attributes(HANDLE handle, DWORD mask) {
+    BY_HANDLE_FILE_INFORMATION native_file_info;
+    if(!GetFileInformationByHandle(handle, &native_file_info)) {
+        return 0;
+    }
+
+    return !!((native_file_info.dwFileAttributes & mask) == mask);
+}
+
 /** @brief Checks whether all the given attributes are set on the object at the
  * given path. Note that it assumes false on errors. */
 static int has_file_attributes(const efile_path_t *path, DWORD mask) {
@@ -412,10 +423,15 @@ posix_errno_t efile_open(const efile_path_t *path, enum efile_modes_t modes,
 
     ASSERT_PATH_FORMAT(path);
 
+    attributes = 0;
     access_flags = 0;
     open_mode = 0;
 
-    if(modes & EFILE_MODE_READ && !(modes & EFILE_MODE_WRITE)) {
+    if(modes & EFILE_MODE_DIRECTORY) {
+        attributes = FILE_FLAG_BACKUP_SEMANTICS;
+        access_flags = GENERIC_READ;
+        open_mode = OPEN_EXISTING;
+    } else if(modes & EFILE_MODE_READ && !(modes & EFILE_MODE_WRITE)) {
         access_flags = GENERIC_READ;
         open_mode = OPEN_EXISTING;
     } else if(modes & EFILE_MODE_WRITE && !(modes & EFILE_MODE_READ)) {
@@ -438,9 +454,9 @@ posix_errno_t efile_open(const efile_path_t *path, enum efile_modes_t modes,
     }
 
     if(modes & EFILE_MODE_SYNC) {
-        attributes = FILE_FLAG_WRITE_THROUGH;
+        attributes |= FILE_FLAG_WRITE_THROUGH;
     } else {
-        attributes = FILE_ATTRIBUTE_NORMAL;
+        attributes |= FILE_ATTRIBUTE_NORMAL;
     }
 
     handle = CreateFileW((WCHAR*)path->data, access_flags,
@@ -449,6 +465,12 @@ posix_errno_t efile_open(const efile_path_t *path, enum efile_modes_t modes,
     if(handle != INVALID_HANDLE_VALUE) {
         efile_win_t *w;
 
+        /* Directory mode specified, but path is not a directory. */
+        if((modes & EFILE_MODE_DIRECTORY) && !handle_has_file_attributes(handle, FILE_ATTRIBUTE_DIRECTORY)) {
+            CloseHandle(handle);
+            return ENOTDIR;
+        }
+
         w = (efile_win_t*)enif_alloc_resource(nif_type, sizeof(efile_win_t));
         w->handle = handle;
 
@@ -461,7 +483,7 @@ posix_errno_t efile_open(const efile_path_t *path, enum efile_modes_t modes,
 
         /* Rewrite all failures on directories to EISDIR to match the old
          * driver. */
-        if(has_file_attributes(path, FILE_ATTRIBUTE_DIRECTORY)) {
+        if(!(modes & EFILE_MODE_DIRECTORY) && has_file_attributes(path, FILE_ATTRIBUTE_DIRECTORY)) {
             return EISDIR;
         }
 
diff --git a/lib/kernel/doc/src/file.xml b/lib/kernel/doc/src/file.xml
index fc25e83d40..b3e8149cc2 100644
--- a/lib/kernel/doc/src/file.xml
+++ b/lib/kernel/doc/src/file.xml
@@ -939,6 +939,10 @@ f.txt:  {person, "kalle", 25}.
             support for POSIX <c>O_SYNC</c> or equivalent, use of the <c>sync</c>
 	    flag causes <c>open</c> to return <c>{error, enotsup}</c>.</p>
           </item>
+          <tag><c>directory</c></tag>
+          <item>
+            <p>Allows <c>open</c> to work on directories.</p>
+          </item>
         </taglist>
         <p>Returns:</p>
         <taglist>
@@ -985,8 +989,10 @@ f.txt:  {person, "kalle", 25}.
           </item>
           <tag><c>enotdir</c></tag>
           <item>
-            <p>A component of the filename is not a directory. On some
-              platforms, <c>enoent</c> is returned instead.</p>
+            <p>A component of the filename is not a directory, or the
+              filename itself is not a directory if <c>directory</c>
+              mode was specified. On some platforms, <c>enoent</c> is
+              returned instead.</p>
           </item>
           <tag><c>enospc</c></tag>
           <item>
diff --git a/lib/kernel/src/file.erl b/lib/kernel/src/file.erl
index 1d4e37196c..a0616da670 100644
--- a/lib/kernel/src/file.erl
+++ b/lib/kernel/src/file.erl
@@ -460,7 +460,7 @@ raw_write_file_info(Name, #file_info{} = Info) ->
 -spec open(File, Modes) -> {ok, IoDevice} | {error, Reason} when
       File :: Filename | iodata(),
       Filename :: name_all(),
-      Modes :: [mode() | ram],
+      Modes :: [mode() | ram | directory],
       IoDevice :: io_device(),
       Reason :: posix() | badarg | system_limit.
 
@@ -1143,7 +1143,7 @@ path_script(Path, File, Bs) ->
              {ok, IoDevice, FullName} | {error, Reason} when
       Path :: [Dir :: name_all()],
       Filename :: name_all(),
-      Modes :: [mode()],
+      Modes :: [mode() | directory],
       IoDevice :: io_device(),
       FullName :: filename_all(),
       Reason :: posix() | badarg | system_limit.
diff --git a/lib/kernel/test/file_SUITE.erl b/lib/kernel/test/file_SUITE.erl
index 3bc8e6e828..21aaefa654 100644
--- a/lib/kernel/test/file_SUITE.erl
+++ b/lib/kernel/test/file_SUITE.erl
@@ -989,6 +989,14 @@ new_modes(Config) when is_list(Config) ->
 	     ok
      end,
 
+     % open directory
+     {ok, Fd9} = ?FILE_MODULE:open(NewDir, [directory]),
+     ok = ?FILE_MODULE:close(Fd9),
+
+     % open raw directory
+     {ok, Fd10} = ?FILE_MODULE:open(NewDir, [raw, directory]),
+     ok = ?FILE_MODULE:close(Fd10),
+
      [] = flush(),
      ok.
 
@@ -1238,6 +1246,9 @@ open_errors(Config) when is_list(Config) ->
     {error, E4} = ?FILE_MODULE:open(DataDirSlash, [write]),
     {eisdir,eisdir,eisdir,eisdir} = {E1,E2,E3,E4},
 
+    Real = filename:join(DataDir, "realmen.html"),
+    {error, enotdir} = ?FILE_MODULE:open(Real, [directory]),
+
     {'EXIT', {badarg, _}} = (catch ?FILE_MODULE:open("foo", [raw, ram])),
     [] = flush(),
     ok.
-- 
2.16.4

openSUSE Build Service is sponsored by