add lockContentShared

Also, rename lockContent to lockContentExclusive

inAnnexSafe should perhaps be eliminated, and instead use
`lockContentShared inAnnex`. However, I'm waiting on that, as there are
only 2 call sites for inAnnexSafe and it's fiddly.
This commit is contained in:
Joey Hess 2015-10-08 14:27:37 -04:00
parent f52d4b684d
commit 4d50958ed7
Failed to extract signature
11 changed files with 100 additions and 50 deletions

View file

@ -12,7 +12,8 @@ module Annex.Content (
inAnnex',
inAnnexSafe,
inAnnexCheck,
lockContent,
lockContentShared,
lockContentExclusive,
getViaTmp,
getViaTmp',
checkDiskSpaceToGet,
@ -165,57 +166,104 @@ contentLockFile key = ifM isDirect
contentLockFile key = Just <$> calcRepo (gitAnnexContentLock key)
#endif
newtype ContentLock = ContentLock Key
{- Content is exclusively locked while running an action that might remove
- it. (If the content is not present, no locking is done.)
{- Prevents the content from being removed while the action is running.
- Uses a shared lock.
-
- Does not actually check if the content is present. Use inAnnex for that.
- However, since the contentLockFile is the content file in indirect mode,
- if the content is not present, locking it will fail.
-
- If locking fails, throws an exception rather than running the action.
-
- Note that, in direct mode, nothing prevents the user from directly
- editing or removing the content, even while it's locked by this.
-}
lockContent :: Key -> (ContentLock -> Annex a) -> Annex a
lockContent key a = do
lockContentShared :: Key -> Annex a -> Annex a
lockContentShared = lockContentUsing lock
where
#ifndef mingw32_HOST_OS
lock contentfile Nothing = liftIO $ tryLockShared Nothing contentfile
lock _ (Just lockfile) = posixLocker tryLockShared lockfile
#else
lock = winLocker lockShared
#endif
newtype ContentLockExclusive = ContentLockExclusive Key
{- Exclusively locks content, while performing an action that
- might remove it.
-
- (If the content is not present, no locking is done.)
-}
lockContentExclusive :: Key -> (ContentLockExclusive -> Annex a) -> Annex a
lockContentExclusive key a = lockContentUsing lock key $
a $ ContentLockExclusive key
where
#ifndef mingw32_HOST_OS
{- Since content files are stored with the write bit disabled, have
- to fiddle with permissions to open for an exclusive lock. -}
lock contentfile Nothing = bracket_
(thawContent contentfile)
(freezeContent contentfile)
(liftIO $ tryLockExclusive Nothing contentfile)
lock _ (Just lockfile) = posixLocker tryLockExclusive lockfile
#else
lock = winLocker lockExclusive
#endif
{- Passed the object content file, and maybe a separate lock file to use,
- when the content file itself should not be locked. -}
type ContentLocker = FilePath -> Maybe LockFile -> Annex (Maybe LockHandle)
#ifndef mingw32_HOST_OS
posixLocker :: (Maybe FileMode -> LockFile -> IO (Maybe LockHandle)) -> LockFile -> Annex (Maybe LockHandle)
posixLocker takelock lockfile = do
mode <- annexFileMode
modifyContent lockfile $
liftIO $ takelock (Just mode) lockfile
#else
winLocker :: (LockFile -> IO (Maybe LockHandle)) -> ContentLocker
winLocker takelock _ (Just lockfile) = do
modifyContent lockfile $
void $ liftIO $ tryIO $
writeFile lockfile ""
liftIO $ takelock lockfile
-- never reached; windows always uses a separate lock file
winLocker _ _ Nothing = return Nothing
#endif
lockContentUsing :: ContentLocker -> Key -> Annex a -> Annex a
lockContentUsing locker key a = do
contentfile <- calcRepo $ gitAnnexLocation key
lockfile <- contentLockFile key
bracket
(lock contentfile lockfile)
(unlock lockfile)
(const $ a $ ContentLock key )
(const $ a)
where
alreadylocked = error "content is locked"
cleanuplockfile lockfile = modifyContent lockfile $
void $ liftIO $ tryIO $
nukeFile lockfile
#ifndef mingw32_HOST_OS
{- Since content files are stored with the write bit disabled, have
- to fiddle with permissions to open for an exclusive lock. -}
lock contentfile Nothing = trylock $ bracket_
(thawContent contentfile)
(freezeContent contentfile)
failedtolock e = error $ "failed to lock content: " ++ show e
lock contentfile lockfile =
(maybe alreadylocked return
=<< liftIO (tryLockExclusive Nothing contentfile))
lock _ (Just lockfile) = trylock $ do
mode <- annexFileMode
maybe alreadylocked return
=<< modifyContent lockfile
(liftIO $ tryLockExclusive (Just mode) lockfile)
=<< locker contentfile lockfile)
`catchIO` failedtolock
#ifndef mingw32_HOST_OS
unlock mlockfile lck = do
maybe noop cleanuplockfile mlockfile
liftIO $ dropLock lck
failedtolock e = error $ "failed to lock content: " ++ show e
trylock locker = locker `catchIO` failedtolock
#else
lock _ (Just lockfile) = do
modifyContent lockfile $
void $ liftIO $ tryIO $
writeFile lockfile ""
maybe alreadylocked (return . Just)
=<< liftIO (lockExclusive lockfile)
-- never reached; windows always uses a separate lock file
lock _ Nothing = return Nothing
unlock mlockfile mlockhandle = do
liftIO $ maybe noop dropLock mlockhandle
maybe noop cleanuplockfile mlockfile
#endif
cleanuplockfile lockfile = modifyContent lockfile $
void $ liftIO $ tryIO $
nukeFile lockfile
{- Runs an action, passing it the temp file to get,
- and if the action succeeds, verifies the file matches
- the key and moves the file into the annex as a key's content. -}
@ -497,8 +545,8 @@ cleanObjectLoc key cleaner = do
- In direct mode, deletes the associated files or files, and replaces
- them with symlinks.
-}
removeAnnex :: ContentLock -> Annex ()
removeAnnex (ContentLock key) = withObjectLoc key remove removedirect
removeAnnex :: ContentLockExclusive -> Annex ()
removeAnnex (ContentLockExclusive key) = withObjectLoc key remove removedirect
where
remove file = cleanObjectLoc key $ do
secureErase file

View file

@ -77,7 +77,7 @@ expireUnused duration = do
forM_ oldkeys $ \k -> do
debug ["removing old unused key", key2file k]
liftAnnex $ do
lockContent k removeAnnex
lockContentExclusive k removeAnnex
logStatus k InfoMissing
where
boundry = durationToPOSIXTime <$> duration

View file

@ -97,7 +97,7 @@ startDistributionDownload d = go =<< liftIO . newVersionLocation d =<< liftIO ol
, transferKey = k
}
cleanup = liftAnnex $ do
lockContent k removeAnnex
lockContentExclusive k removeAnnex
setUrlMissing webUUID k u
logStatus k InfoMissing

View file

@ -88,12 +88,12 @@ startRemote afile numcopies key remote = do
showStart' ("drop " ++ Remote.name remote) key afile
next $ performRemote key afile numcopies remote
-- Note that lockContent is called before checking if the key is present
-- on enough remotes to allow removal. This avoids a scenario where two
-- Note that lockContentExclusive is called before checking if the key is
-- present on enough remotes to allow removal. This avoids a scenario where two
-- or more remotes are trying to remove a key at the same time, and each
-- see the key is present on the other.
performLocal :: Key -> AssociatedFile -> NumCopies -> Maybe Remote -> CommandPerform
performLocal key afile numcopies knownpresentremote = lockContent key $ \contentlock -> do
performLocal key afile numcopies knownpresentremote = lockContentExclusive key $ \contentlock -> do
(remotes, trusteduuids) <- Remote.keyPossibilitiesTrusted key
let trusteduuids' = case knownpresentremote of
Nothing -> trusteduuids

View file

@ -31,7 +31,7 @@ start key = stopUnless (inAnnex key) $ do
next $ perform key
perform :: Key -> CommandPerform
perform key = lockContent key $ \contentlock -> do
perform key = lockContentExclusive key $ \contentlock -> do
removeAnnex contentlock
next $ cleanup key

View file

@ -123,7 +123,7 @@ toPerform dest move key afile fastcheck isthere =
finish
where
finish
| move = lockContent key $ \contentlock -> do
| move = lockContentExclusive key $ \contentlock -> do
removeAnnex contentlock
next $ Command.Drop.cleanupLocal key
| otherwise = next $ return True

View file

@ -120,7 +120,7 @@ test st r k =
, check "storeKey when already present" store
, present True
, check "retrieveKeyFile" $ do
lockContent k removeAnnex
lockContentExclusive k removeAnnex
get
, check "fsck downloaded object" fsck
, check "retrieveKeyFile resume from 33%" $ do
@ -130,20 +130,20 @@ test st r k =
sz <- hFileSize h
L.hGet h $ fromInteger $ sz `div` 3
liftIO $ L.writeFile tmp partial
lockContent k removeAnnex
lockContentExclusive k removeAnnex
get
, check "fsck downloaded object" fsck
, check "retrieveKeyFile resume from 0" $ do
tmp <- prepTmp k
liftIO $ writeFile tmp ""
lockContent k removeAnnex
lockContentExclusive k removeAnnex
get
, check "fsck downloaded object" fsck
, check "retrieveKeyFile resume from end" $ do
loc <- Annex.calcRepo (gitAnnexLocation k)
tmp <- prepTmp k
void $ liftIO $ copyFileExternal CopyAllMetaData loc tmp
lockContent k removeAnnex
lockContentExclusive k removeAnnex
get
, check "fsck downloaded object" fsck
, check "removeKey when present" remove
@ -189,7 +189,7 @@ testUnavailable st r k =
cleanup :: [Remote] -> [Key] -> Bool -> CommandCleanup
cleanup rs ks ok = do
forM_ rs $ \r -> forM_ ks (Remote.removeKey r)
forM_ ks $ \k -> lockContent k removeAnnex
forM_ ks $ \k -> lockContentExclusive k removeAnnex
return ok
chunkSizes :: Int -> Bool -> [Int]

View file

@ -105,7 +105,7 @@ removeUnannexed = go []
go c [] = return c
go c (k:ks) = ifM (inAnnexCheck k $ liftIO . enoughlinks)
( do
lockContent k removeAnnex
lockContentExclusive k removeAnnex
go c ks
, go (k:c) ks
)

View file

@ -350,7 +350,7 @@ dropKey r key
commitOnCleanup r $ onLocal r $ do
ensureInitialized
whenM (Annex.Content.inAnnex key) $ do
Annex.Content.lockContent key
Annex.Content.lockContentExclusive key
Annex.Content.removeAnnex
logStatus key InfoMissing
Annex.Content.saveState True

View file

@ -6,6 +6,7 @@
-}
module Utility.LockPool.Posix (
P.LockFile,
LockHandle,
lockShared,
lockExclusive,

View file

@ -6,6 +6,7 @@
-}
module Utility.LockPool.Windows (
P.LockFile,
LockHandle,
lockShared,
lockExclusive,