#3231: Permission denied error with runProcess/openFile
-----------------------------+----------------------------------------------
  Reporter:  NeilMitchell    |          Owner:  simonmar        
      Type:  bug             |         Status:  new             
  Priority:  normal          |      Milestone:  7.6.1           
 Component:  libraries/base  |        Version:  6.10.4          
Resolution:                  |       Keywords:                  
        Os:  Windows         |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown    |     Difficulty:  Unknown         
  Testcase:                  |      Blockedby:                  
  Blocking:                  |        Related:                  
-----------------------------+----------------------------------------------
Changes (by simonmar):

  * priority:  high => normal
  * component:  Runtime System => libraries/base
  * milestone:  7.4.1 => 7.6.1


Comment:

 '''Current status of this ticket'''

  * We have implemented automatic delay+retry for many of the filesystem
 operations in the `win32` package
 (085b11285b6adbc6484d9c21f5e0b8105556869c), and this behaviour is
 inherited by `System.Directory`.  This means that accidental sharing
 violations for things like `removeFile` do not happen any more.

  * However, we have not implemented delay+retry for `System.IO.openFile`.
 It is not clear how to do that easily, because `openFile` calls into
 `msvcrt` rather than `Win32` directly.  Ideally we should rewrite the IO
 library to call `Win32` rather than `msvcrt` or `mingw` APIs.

 I'll reproduce the test case from above.  First, compile this C file with
 `gcc tmp.c`:

 {{{
 #include <windows.h>

 #include <stdlib.h>
 #include <stdio.h>
 #include <assert.h>

 #define PIPE_NAME "\\\\.\\pipe\\MySmallPipe"
 #define PIPE_BUF_SIZE 10
 #define TIMEOUT 1000

 #define NCLIENTS 30

 int main(int argc, char *argv[]) {
         if( 1 == argc ) {
                 //Caller

                 struct {
                         HANDLE hProcess;
                         HANDLE hPipe;
                         OVERLAPPED ov;
                 } data[NCLIENTS];

                 //Start clients
                 int i;
                 for(i = 0; i < NCLIENTS; ++i) {
                         fprintf(stderr, "Starting %d\n", i);

                         data[i].hPipe = CreateNamedPipe(
                                 PIPE_NAME,
                                 PIPE_ACCESS_DUPLEX | FILE_FLAG_OVERLAPPED,
                                 PIPE_TYPE_BYTE | PIPE_READMODE_BYTE |
 PIPE_WAIT,
                                 100,
                                 PIPE_BUF_SIZE,
                                 PIPE_BUF_SIZE,
                                 TIMEOUT,
                                 0
                         );
                         assert(INVALID_HANDLE_VALUE != data[i].hPipe);

                         STARTUPINFO si;
                         memset(&si, 0, sizeof (STARTUPINFO));
                         si.cb = sizeof(STARTUPINFO);

                         PROCESS_INFORMATION pi;

                         BOOL res = CreateProcess(0, strdup("a.exe 1"), 0,
 0, TRUE, 0, 0, 0, &si, &pi);
                         assert(res);

                         data[i].hProcess = pi.hProcess;

                         ConnectNamedPipe(data[i].hPipe, &data[i].ov);
                 } //i

                 fprintf(stderr, "Delay\n");
                 Sleep(TIMEOUT);

                 //Kill clients
                 for(i = 0; i < NCLIENTS; ++i) {
                         fprintf(stderr, "Terminating %d\n", i);
                         BOOL res = TerminateProcess(data[i].hProcess, 0);

                         DisconnectNamedPipe(data[i].hPipe);
                         CloseHandle(data[i].hPipe);
                 } //i
         } else {
                 //Callee

                 fprintf(stderr, "Started\n");

                 BOOL res = WaitNamedPipe(PIPE_NAME, TIMEOUT);
                 assert(res);

                 HANDLE hPipe = CreateFile(
                         PIPE_NAME,
                         GENERIC_READ | GENERIC_WRITE,
                         0,
                         0,
                         OPEN_EXISTING,
                         0,
                         0
                 );

                 //Sleep forever
                 char buf[PIPE_BUF_SIZE];
                 DWORD n;
                 res = ReadFile(
                         hPipe,
                         buf,
                         PIPE_BUF_SIZE,
                         &n,
                         0
                 );
         }

         return 0;
 }
 }}}

 Now, compile this Haskell file with `ghc bug.hs`:

 {{{
 module Main where

 -- import System
 import System.IO
 import System.Process (runProcess, waitForProcess)
 import System.Directory (removeFile)

 import Control.Monad (replicateM_)

 import qualified Data.ByteString as B

 run :: FilePath -> IO ()
 run exe = do
   let tempFile = "mytempfile.txt"

   h <- openFile tempFile WriteMode

   exitCode <- waitForProcess =<< runProcess exe [] Nothing Nothing Nothing
 (Just h) (Just h)

   hClose h >> {- (if exitCode /= ExitSuccess then return () else
 B.readFile tempFile >>= B.putStr) >> -} removeFile tempFile

 main = replicateM_ 100 (putStrLn "Next:" >> run "a.exe")
 }}}

 And run with `./bug.exe`.

  * As is, the program will succeed with GHC 7.4.1 (but not earlier),
 because we fixed `removeFile`.
  * If the `(if exitCode ...)` is uncommented, then the program will fail,
 because we have not fixed `openFile` yet.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3231#comment:44>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to