#2924: createDirectory: permission denied
----------------------------------+-----------------------------------------
Reporter: simonmar | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 6.10 branch
Component: libraries/directory | Version: 6.10.1
Severity: normal | Keywords:
Difficulty: Unknown | Testcase:
Os: Windows | Architecture: x86
----------------------------------+-----------------------------------------
The following program results in an odd "permission denied" error from
`createDirectory` on Windows. It is derived from the
`createDirectoryIfMIssing001` test, but doesn't involve calling
`createDirectoryIfMissing`, only `createDirectory`.
There are two threads, each of which is repeatedly creating a directory
and using `removeDirectoryRecursive` to remove it.
Test program:
{{{
import System.IO
import System.Directory
import Control.Monad
import Control.Concurrent
import Control.Exception
import System.IO.Error
testdir = "foo"
main = do
cleanup
m <- newEmptyMVar
forkIO $ do replicateM_ 1000 (do create; cleanup); putMVar m ()
forkIO $ do replicateM_ 1000 (do create; cleanup); putMVar m ()
replicateM_ 2 $ takeMVar m
cleanup
create =
tryJust (guard . isAlreadyExistsError) $ createDirectory testdir
cleanup =
tryJust (guard . isDoesNotExistError) $ removeDirectoryRecursive testdir
}}}
The result is usually:
{{{
test.exe: CreateDirectory: permission denied (Access is denied.)
}}}
It's not clear (to me at least) why we get this error. Running the
program under !ProcMon shows that there is a `CreateFile` call that
returns `DELETE PENDING`, but as far as I can tell this doesn't give rise
to an `ERROR_DELETE_PENDING` return from `CreateDirectory`, because that
would give a different error message. Perhaps somewhere in the bowels of
the Win32 API a `DELETE_PENDING` is being turned into a permission denied,
or something.
This deserves investigation, because I think it might be related to other
spurious "permission denied" errors we occasionally see on Windows.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2924>
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