use locking on Windows

This is all the easy cases, where there was already a separate lock file.
This commit is contained in:
Joey Hess 2014-01-28 14:17:14 -04:00
parent 8de4db664d
commit 891c85cd88
8 changed files with 95 additions and 40 deletions

View file

@ -1,6 +1,6 @@
{- git-annex lock pool
-
- Copyright 2012 Joey Hess <joey@kitenet.net>
- Copyright 2012, 2014 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
@ -9,13 +9,16 @@
module Annex.LockPool where
import qualified Data.Map as M
import System.Posix.Types (Fd)
import Common.Annex
import Annex
import Types.LockPool
import qualified Data.Map as M
#ifndef mingw32_HOST_OS
import Annex.Perms
#else
import Utility.WinLock
#endif
{- Create a specified lock file, and takes a shared lock. -}
@ -26,31 +29,32 @@ lockFile file = go =<< fromPool file
go Nothing = do
#ifndef mingw32_HOST_OS
mode <- annexFileMode
fd <- liftIO $ noUmask mode $
lockhandle <- liftIO $ noUmask mode $
openFd file ReadOnly (Just mode) defaultFileFlags
liftIO $ waitToSetLock fd (ReadLock, AbsoluteSeek, 0, 0)
liftIO $ waitToSetLock lockhandle (ReadLock, AbsoluteSeek, 0, 0)
#else
liftIO $ writeFile file ""
let fd = 0
lockhandle <- liftIO $ waitToLock $ lockShared file
#endif
changePool $ M.insert file fd
changePool $ M.insert file lockhandle
unlockFile :: FilePath -> Annex ()
unlockFile file = maybe noop go =<< fromPool file
where
go fd = do
go lockhandle = do
#ifndef mingw32_HOST_OS
liftIO $ closeFd fd
liftIO $ closeFd lockhandle
#else
liftIO $ dropLock lockhandle
#endif
changePool $ M.delete file
getPool :: Annex (M.Map FilePath Fd)
getPool :: Annex LockPool
getPool = getState lockpool
fromPool :: FilePath -> Annex (Maybe Fd)
fromPool :: FilePath -> Annex (Maybe LockHandle)
fromPool file = M.lookup file <$> getPool
changePool :: (M.Map FilePath Fd -> M.Map FilePath Fd) -> Annex ()
changePool :: (LockPool -> LockPool) -> Annex ()
changePool a = do
m <- getPool
changeState $ \s -> s { lockpool = a m }