Skip to content

Commit

Permalink
Use share flags for all file operations on Windows
Browse files Browse the repository at this point in the history
Some file operations provided by the Erlang file module
didn't open the target file with all the file share flags.
This made some concurrent file operations against the
same file fail on Windows, while on other platforms such
as GNU/Linux or Mac OS X they succeed. The operations will
fail only if they're performed concurrently by different
threads (async IO threads or scheduler threads).

For example, one Erlang process does a file:delete/1 call
while another Erlang process is doing a filelib:file_size/1
call. This made the former process get an eacces error from
the file:delete/1 call. On GNU/Linux or Mac OS X the call would
succeed. Another example is if one Erlang process attempts to
open a file for reading while another one is in the middle of
a file:read_file_info/1 call (after it opened the file and
before it closed the file).

It's easy to verify that if a file is not open with all the
share flags, it's impossible for other threads (even if they
belong to the same OS process) to open the file while the
file is not closed by the first thread.
The following test program shows this:

 #include <windows.h>
 #include <iostream>

// Must be an existing file
//#define SHARE_FLAGS (FILE_SHARE_READ)

static DWORD WINAPI MyThreadFunction(LPVOID lpParam);
static char *lastError();

int main(int argc, char *argv[])
{
    DWORD   threadId;
    HANDLE  threadHandle, hFile;

    hFile = CreateFile(FILENAME, GENERIC_READ, SHARE_FLAGS, NULL,
                       OPEN_EXISTING, FILE_ATTRIBUTE_NORMAL, NULL);
    if (hFile == INVALID_HANDLE_VALUE) {
        std::cerr << "File open error from main: " <<
		lastError() << std::endl;
        return 1;
    }
    std::cout << "Main thread opened file successfully" << std::endl;

    threadHandle = CreateThread(NULL, 0, MyThreadFunction, NULL, 0, &threadId);
    if (threadHandle == INVALID_HANDLE_VALUE) {
        std::cerr << "Thread create error from main: " <<
		lastError() << std::endl;
        return 1;
    }
    WaitForSingleObject(threadHandle, INFINITE);
    CloseHandle(threadHandle);
    CloseHandle(hFile);
    return 0;
}

static DWORD WINAPI MyThreadFunction( LPVOID lpParam )
{
    HANDLE hFile;

    hFile = CreateFile(FILENAME, GENERIC_READ, SHARE_FLAGS, NULL,
                       OPEN_EXISTING, FILE_ATTRIBUTE_NORMAL, NULL);
    if (hFile == INVALID_HANDLE_VALUE) {
        std::cerr << "File open error from second thread: " <<
		lastError() << std::endl;
        return 1;
    }
    std::cout << "Second thread opened file successfully" << std::endl;
    CloseHandle(hFile);
    return 0;
}

static char *lastError()
{
    static char *buf = NULL;
    DWORD dw = GetLastError();

    if (buf != NULL) {
        LocalFree((LPTSTR) &buf);
    }
    FormatMessage(FORMAT_MESSAGE_ALLOCATE_BUFFER | FORMAT_MESSAGE_FROM_SYSTEM |
                  FORMAT_MESSAGE_IGNORE_INSERTS,
                  NULL, dw, MAKELANGID(LANG_NEUTRAL, SUBLANG_DEFAULT),
                  (LPTSTR) &buf, 0, NULL);
    return buf;
}

Rnning this program with SHARE_FLAGS set to 0 (as efile_fileinfo()
does for e.g.), shows that the second thread is unable to open the
file:

    C:\cygwin\home\fdmanana\tmp>touch foo.bar
    C:\cygwin\home\fdmanana\tmp>threads_fopen_test.exe
    Main thread opened file successfully
    File open error from second thread: The process cannot access the
    file because it is being used by another process.

Changing the program's SHARE_FLAGS to FILE_SHARE_READ, shows that
both threads are able to open the file:

    C:\cygwin\home\fdmanana\tmp>touch foo.bar
    C:\cygwin\home\fdmanana\tmp>threads_test.exe
    Main thread opened file successfully
    Second thread opened file successfully

Same logic applies to opening files for writing or deleting and
renaming files while they're open by some other thread that didn't
specify the flags FILE_SHARE_WRITE and FILE_SHARE_DELETE.
  • Loading branch information
fdmanana committed Jan 17, 2013
1 parent 812f666 commit 0e02f48
Showing 1 changed file with 6 additions and 4 deletions.
10 changes: 6 additions & 4 deletions erts/emulator/drivers/win32/win_efile.c
Original file line number Diff line number Diff line change
Expand Up @@ -41,6 +41,8 @@
#define IS_DOT_OR_DOTDOT(s) \
((s)[0] == L'.' && ((s)[1] == L'\0' || ((s)[1] == L'.' && (s)[2] == L'\0')))

#define FILE_SHARE_FLAGS (FILE_SHARE_READ | FILE_SHARE_WRITE | FILE_SHARE_DELETE)

#ifndef INVALID_FILE_ATTRIBUTES
#define INVALID_FILE_ATTRIBUTES ((DWORD) 0xFFFFFFFF)
#endif
Expand Down Expand Up @@ -724,7 +726,7 @@ efile_openfile(Efile_error* errInfo, /* Where to return error codes. */
crFlags = CREATE_NEW;
}
fd = CreateFileW(wname, access,
FILE_SHARE_READ | FILE_SHARE_WRITE | FILE_SHARE_DELETE,
FILE_SHARE_FLAGS,
NULL, crFlags, FILE_ATTRIBUTE_NORMAL, NULL);

/*
Expand Down Expand Up @@ -909,7 +911,7 @@ efile_fileinfo(Efile_error* errInfo, Efile_info* pInfo,
{
HANDLE handle; /* Handle returned by CreateFile() */
BY_HANDLE_FILE_INFORMATION fileInfo; /* from CreateFile() */
if (handle = CreateFileW(name, GENERIC_READ, 0,NULL,
if (handle = CreateFileW(name, GENERIC_READ, FILE_SHARE_FLAGS, NULL,
OPEN_EXISTING, 0, NULL)) {
GetFileInformationByHandle(handle, &fileInfo);
pInfo->links = fileInfo.nNumberOfLinks;
Expand Down Expand Up @@ -1021,7 +1023,7 @@ efile_write_info(Efile_error* errInfo,
}

fd = CreateFileW(wname, GENERIC_READ|GENERIC_WRITE,
FILE_SHARE_READ | FILE_SHARE_WRITE,
FILE_SHARE_FLAGS,
NULL, OPEN_EXISTING, FILE_ATTRIBUTE_NORMAL, NULL);
if (fd != INVALID_HANDLE_VALUE) {
BOOL result = SetFileTime(fd, &CreationFileTime, &AccessFileTime, &ModifyFileTime);
Expand Down Expand Up @@ -1384,7 +1386,7 @@ efile_readlink(Efile_error* errInfo, char* name, char* buffer, size_t size)
DWORD fileAttributes = GetFileAttributesW(wname);
if ((fileAttributes & FILE_ATTRIBUTE_REPARSE_POINT)) {
BOOLEAN success = 0;
HANDLE h = CreateFileW(wname, GENERIC_READ, 0,NULL, OPEN_EXISTING, FILE_FLAG_BACKUP_SEMANTICS, NULL);
HANDLE h = CreateFileW(wname, GENERIC_READ, FILE_SHARE_FLAGS, NULL, OPEN_EXISTING, FILE_FLAG_BACKUP_SEMANTICS, NULL);
int len;
if(h != INVALID_HANDLE_VALUE) {
success = pGetFinalPathNameByHandle(h, wbuffer, size / sizeof(WCHAR),0);
Expand Down

0 comments on commit 0e02f48

Please sign in to comment.