more lock file refactoring
Also fixes a test suite failures introduced in recent commits, where inAnnexSafe failed in indirect mode, since it tried to open the lock file ReadWrite. This is why the new checkLocked opens it ReadOnly. This commit was sponsored by Chad Horohoe.
This commit is contained in:
parent
e386e26ef2
commit
1994771215
4 changed files with 68 additions and 39 deletions
|
@ -101,23 +101,21 @@ inAnnexSafe key = inAnnex' (fromMaybe False) (Just False) go key
|
||||||
=<< contentLockFile key
|
=<< contentLockFile key
|
||||||
|
|
||||||
#ifndef mingw32_HOST_OS
|
#ifndef mingw32_HOST_OS
|
||||||
checkindirect f = liftIO $ openExistingLockFile f >>= check is_missing
|
checkindirect contentfile = liftIO $ checkOr is_missing contentfile
|
||||||
{- In direct mode, the content file must exist, but
|
{- In direct mode, the content file must exist, but
|
||||||
- the lock file often generally won't exist unless a removal is in
|
- the lock file generally won't exist unless a removal is in
|
||||||
- process. This does not create the lock file, it only checks for
|
- process. -}
|
||||||
- it. -}
|
|
||||||
checkdirect contentfile lockfile = liftIO $
|
checkdirect contentfile lockfile = liftIO $
|
||||||
ifM (doesFileExist contentfile)
|
ifM (doesFileExist contentfile)
|
||||||
( openExistingLockFile lockfile >>= check is_unlocked
|
( checkOr is_unlocked lockfile
|
||||||
, return is_missing
|
, return is_missing
|
||||||
)
|
)
|
||||||
check _ (Just h) = do
|
checkOr def lockfile = do
|
||||||
v <- getLock h (ReadLock, AbsoluteSeek, 0, 0)
|
v <- checkLocked lockfile
|
||||||
closeFd h
|
|
||||||
return $ case v of
|
return $ case v of
|
||||||
Just _ -> is_locked
|
Nothing -> def
|
||||||
Nothing -> is_unlocked
|
Just True -> is_locked
|
||||||
check def Nothing = return def
|
Just False -> is_unlocked
|
||||||
#else
|
#else
|
||||||
checkindirect f = liftIO $ ifM (doesFileExist f)
|
checkindirect f = liftIO $ ifM (doesFileExist f)
|
||||||
( do
|
( do
|
||||||
|
@ -161,7 +159,7 @@ lockContent key a = do
|
||||||
contentfile <- calcRepo $ gitAnnexLocation key
|
contentfile <- calcRepo $ gitAnnexLocation key
|
||||||
lockfile <- contentLockFile key
|
lockfile <- contentLockFile key
|
||||||
maybe noop setuplockfile lockfile
|
maybe noop setuplockfile lockfile
|
||||||
bracket (liftIO $ lock contentfile lockfile) (unlock lockfile) (const a)
|
bracket (lock contentfile lockfile) (unlock lockfile) (const a)
|
||||||
where
|
where
|
||||||
alreadylocked = error "content is locked"
|
alreadylocked = error "content is locked"
|
||||||
setuplockfile lockfile = modifyContent lockfile $
|
setuplockfile lockfile = modifyContent lockfile $
|
||||||
|
@ -171,8 +169,11 @@ lockContent key a = do
|
||||||
void $ liftIO $ tryIO $
|
void $ liftIO $ tryIO $
|
||||||
nukeFile lockfile
|
nukeFile lockfile
|
||||||
#ifndef mingw32_HOST_OS
|
#ifndef mingw32_HOST_OS
|
||||||
lock contentfile Nothing = opencontentforlock contentfile >>= dolock
|
lock contentfile Nothing = liftIO $
|
||||||
lock _ (Just lockfile) = createLockFile Nothing lockfile >>= dolock . Just
|
opencontentforlock contentfile >>= dolock
|
||||||
|
lock _ (Just lockfile) = do
|
||||||
|
mode <- annexFileMode
|
||||||
|
liftIO $ createLockFile mode lockfile >>= dolock . Just
|
||||||
{- Since content files are stored with the write bit disabled, have
|
{- Since content files are stored with the write bit disabled, have
|
||||||
- to fiddle with permissions to open for an exclusive lock. -}
|
- to fiddle with permissions to open for an exclusive lock. -}
|
||||||
opencontentforlock f = catchDefaultIO Nothing $
|
opencontentforlock f = catchDefaultIO Nothing $
|
||||||
|
@ -189,7 +190,8 @@ lockContent key a = do
|
||||||
maybe noop cleanuplockfile mlockfile
|
maybe noop cleanuplockfile mlockfile
|
||||||
liftIO $ maybe noop closeFd mfd
|
liftIO $ maybe noop closeFd mfd
|
||||||
#else
|
#else
|
||||||
lock _ (Just lockfile) = maybe alreadylocked (return . Just) =<< lockExclusive lockfile
|
lock _ (Just lockfile) = liftIO $
|
||||||
|
maybe alreadylocked (return . Just) =<< lockExclusive lockfile
|
||||||
lock _ Nothing = return Nothing
|
lock _ Nothing = return Nothing
|
||||||
unlock mlockfile mlockhandle = do
|
unlock mlockfile mlockhandle = do
|
||||||
liftIO $ maybe noop dropLock mlockhandle
|
liftIO $ maybe noop dropLock mlockhandle
|
||||||
|
|
11
Annex/Ssh.hs
11
Annex/Ssh.hs
|
@ -152,13 +152,12 @@ sshCleanup = mapM_ cleanup =<< enumSocketFiles
|
||||||
let lockfile = socket2lock socketfile
|
let lockfile = socket2lock socketfile
|
||||||
unlockFile lockfile
|
unlockFile lockfile
|
||||||
mode <- annexFileMode
|
mode <- annexFileMode
|
||||||
fd <- liftIO $ noUmask mode $ createLockFile (Just mode) lockfile
|
v <- liftIO $ noUmask mode $ tryLockExclusive (Just mode) lockfile
|
||||||
v <- liftIO $ tryIO $
|
|
||||||
setLock fd (WriteLock, AbsoluteSeek, 0, 0)
|
|
||||||
case v of
|
case v of
|
||||||
Left _ -> noop
|
Nothing -> noop
|
||||||
Right _ -> forceStopSsh socketfile
|
Just lck -> do
|
||||||
liftIO $ closeFd fd
|
forceStopSsh socketfile
|
||||||
|
liftIO $ dropLock lck
|
||||||
#else
|
#else
|
||||||
forceStopSsh socketfile
|
forceStopSsh socketfile
|
||||||
#endif
|
#endif
|
||||||
|
|
|
@ -83,18 +83,12 @@ runHooks r starthook stophook a = do
|
||||||
unlockFile lck
|
unlockFile lck
|
||||||
#ifndef mingw32_HOST_OS
|
#ifndef mingw32_HOST_OS
|
||||||
mode <- annexFileMode
|
mode <- annexFileMode
|
||||||
fd <- liftIO $ noUmask mode $ createLockFile (Just mode) lck
|
v <- liftIO $ noUmask mode $ tryLockExclusive (Just mode) lck
|
||||||
v <- liftIO $ tryIO $
|
|
||||||
setLock fd (WriteLock, AbsoluteSeek, 0, 0)
|
|
||||||
case v of
|
|
||||||
Left _ -> noop
|
|
||||||
Right _ -> run stophook
|
|
||||||
liftIO $ closeFd fd
|
|
||||||
#else
|
#else
|
||||||
v <- liftIO $ lockExclusive lck
|
v <- liftIO $ lockExclusive lck
|
||||||
|
#endif
|
||||||
case v of
|
case v of
|
||||||
Nothing -> noop
|
Nothing -> noop
|
||||||
Just lockhandle -> do
|
Just lockhandle -> do
|
||||||
run stophook
|
run stophook
|
||||||
liftIO $ dropLock lockhandle
|
liftIO $ dropLock lockhandle
|
||||||
#endif
|
|
||||||
|
|
|
@ -9,15 +9,21 @@ module Utility.LockFile.Posix (
|
||||||
LockHandle,
|
LockHandle,
|
||||||
lockShared,
|
lockShared,
|
||||||
lockExclusive,
|
lockExclusive,
|
||||||
dropLock,
|
tryLockExclusive,
|
||||||
createLockFile,
|
createLockFile,
|
||||||
openExistingLockFile,
|
openExistingLockFile,
|
||||||
|
isLocked,
|
||||||
|
checkLocked,
|
||||||
|
dropLock,
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Utility.Exception
|
import Utility.Exception
|
||||||
|
import Utility.Applicative
|
||||||
|
|
||||||
import System.IO
|
import System.IO
|
||||||
import System.Posix
|
import System.Posix
|
||||||
|
import Data.Maybe
|
||||||
|
import Control.Applicative
|
||||||
|
|
||||||
type LockFile = FilePath
|
type LockFile = FilePath
|
||||||
|
|
||||||
|
@ -31,27 +37,55 @@ lockShared = lock ReadLock
|
||||||
lockExclusive :: Maybe FileMode -> LockFile -> IO LockHandle
|
lockExclusive :: Maybe FileMode -> LockFile -> IO LockHandle
|
||||||
lockExclusive = lock WriteLock
|
lockExclusive = lock WriteLock
|
||||||
|
|
||||||
-- The FileMode is used when creating a new lock file.
|
-- Tries to take an exclusive lock, but does not block.
|
||||||
|
tryLockExclusive :: Maybe FileMode -> LockFile -> IO (Maybe LockHandle)
|
||||||
|
tryLockExclusive mode lockfile = do
|
||||||
|
l <- openLockFile mode lockfile
|
||||||
|
v <- tryIO $ setLock l (WriteLock, AbsoluteSeek, 0, 0)
|
||||||
|
case v of
|
||||||
|
Left _ -> do
|
||||||
|
closeFd l
|
||||||
|
return Nothing
|
||||||
|
Right _ -> return $ Just $ LockHandle l
|
||||||
|
|
||||||
|
-- Setting the FileMode allows creation of a new lock file.
|
||||||
|
-- If it's Nothing then this only succeeds when the lock file already exists.
|
||||||
lock :: LockRequest -> Maybe FileMode -> LockFile -> IO LockHandle
|
lock :: LockRequest -> Maybe FileMode -> LockFile -> IO LockHandle
|
||||||
lock lockreq mode lockfile = do
|
lock lockreq mode lockfile = do
|
||||||
l <- createLockFile mode lockfile
|
l <- openLockFile mode lockfile
|
||||||
waitToSetLock l (lockreq, AbsoluteSeek, 0, 0)
|
waitToSetLock l (lockreq, AbsoluteSeek, 0, 0)
|
||||||
return (LockHandle l)
|
return (LockHandle l)
|
||||||
|
|
||||||
-- Create and opens lock file; does not lock it.
|
-- Create and opens lock file; does not lock it.
|
||||||
createLockFile :: Maybe FileMode -> LockFile -> IO Fd
|
createLockFile :: FileMode -> LockFile -> IO Fd
|
||||||
createLockFile = openLockFile ReadWrite
|
createLockFile filemode = openLockFile (Just filemode)
|
||||||
|
|
||||||
-- Opens an existing lock file; does not lock it or create it.
|
-- Opens an existing lock file; does not lock it, and if it does not exist,
|
||||||
|
-- returns Nothing.
|
||||||
openExistingLockFile :: LockFile -> IO (Maybe Fd)
|
openExistingLockFile :: LockFile -> IO (Maybe Fd)
|
||||||
openExistingLockFile = catchMaybeIO . openLockFile ReadOnly Nothing
|
openExistingLockFile = catchMaybeIO . openLockFile Nothing
|
||||||
|
|
||||||
-- Close on exec flag is set so child processes do not inherit the lock.
|
-- Close on exec flag is set so child processes do not inherit the lock.
|
||||||
openLockFile :: OpenMode -> Maybe FileMode -> LockFile -> IO Fd
|
openLockFile :: Maybe FileMode -> LockFile -> IO Fd
|
||||||
openLockFile openmode filemode lockfile = do
|
openLockFile filemode lockfile = do
|
||||||
l <- openFd lockfile openmode filemode defaultFileFlags
|
l <- openFd lockfile ReadWrite filemode defaultFileFlags
|
||||||
setFdOption l CloseOnExec True
|
setFdOption l CloseOnExec True
|
||||||
return l
|
return l
|
||||||
|
|
||||||
|
-- Check if a file is locked, either exclusively, or with shared lock.
|
||||||
|
-- When the file doesn't exist, it's considered not locked.
|
||||||
|
isLocked :: LockFile -> IO Bool
|
||||||
|
isLocked = fromMaybe False <$$> checkLocked
|
||||||
|
|
||||||
|
checkLocked :: LockFile -> IO (Maybe Bool)
|
||||||
|
checkLocked lockfile = go =<< catchMaybeIO open
|
||||||
|
where
|
||||||
|
open = openFd lockfile ReadOnly Nothing defaultFileFlags
|
||||||
|
go Nothing = return Nothing
|
||||||
|
go (Just h) = do
|
||||||
|
ret <- isJust <$> getLock h (ReadLock, AbsoluteSeek, 0, 0)
|
||||||
|
closeFd h
|
||||||
|
return $ Just ret
|
||||||
|
|
||||||
dropLock :: LockHandle -> IO ()
|
dropLock :: LockHandle -> IO ()
|
||||||
dropLock (LockHandle fd) = closeFd fd
|
dropLock (LockHandle fd) = closeFd fd
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue