use types to enforce that removeAnnex can only be called inside lockContent
This fixed one bug where it needed to be and wasn't (in Assistant.Unused). And also found one place where lockContent was used unnecessarily (by drop --from remote). A few other places like uninit probably don't really need to lockContent, but it doesn't hurt to do call it anyway. This commit was sponsored by David Wagner.
This commit is contained in:
parent
9cb78e18ad
commit
aebcc395ff
9 changed files with 35 additions and 31 deletions
|
@ -152,14 +152,20 @@ contentLockFile key = ifM isDirect
|
||||||
, return Nothing
|
, return Nothing
|
||||||
)
|
)
|
||||||
|
|
||||||
|
newtype ContentLock = ContentLock Key
|
||||||
|
|
||||||
{- Content is exclusively locked while running an action that might remove
|
{- Content is exclusively locked while running an action that might remove
|
||||||
- it. (If the content is not present, no locking is done.) -}
|
- it. (If the content is not present, no locking is done.)
|
||||||
lockContent :: Key -> Annex a -> Annex a
|
-}
|
||||||
|
lockContent :: Key -> (ContentLock -> Annex a) -> Annex a
|
||||||
lockContent key a = do
|
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 (lock contentfile lockfile) (unlock lockfile) (const a)
|
bracket
|
||||||
|
(lock contentfile lockfile)
|
||||||
|
(unlock lockfile)
|
||||||
|
(const $ a $ ContentLock key)
|
||||||
where
|
where
|
||||||
alreadylocked = error "content is locked"
|
alreadylocked = error "content is locked"
|
||||||
setuplockfile lockfile = modifyContent lockfile $
|
setuplockfile lockfile = modifyContent lockfile $
|
||||||
|
@ -426,9 +432,10 @@ cleanObjectLoc key cleaner = do
|
||||||
{- Removes a key's file from .git/annex/objects/
|
{- Removes a key's file from .git/annex/objects/
|
||||||
-
|
-
|
||||||
- In direct mode, deletes the associated files or files, and replaces
|
- In direct mode, deletes the associated files or files, and replaces
|
||||||
- them with symlinks. -}
|
- them with symlinks.
|
||||||
removeAnnex :: Key -> Annex ()
|
-}
|
||||||
removeAnnex key = withObjectLoc key remove removedirect
|
removeAnnex :: ContentLock -> Annex ()
|
||||||
|
removeAnnex (ContentLock key) = withObjectLoc key remove removedirect
|
||||||
where
|
where
|
||||||
remove file = cleanObjectLoc key $ do
|
remove file = cleanObjectLoc key $ do
|
||||||
secureErase file
|
secureErase file
|
||||||
|
|
|
@ -77,7 +77,7 @@ expireUnused duration = do
|
||||||
forM_ oldkeys $ \k -> do
|
forM_ oldkeys $ \k -> do
|
||||||
debug ["removing old unused key", key2file k]
|
debug ["removing old unused key", key2file k]
|
||||||
liftAnnex $ do
|
liftAnnex $ do
|
||||||
removeAnnex k
|
lockContent k removeAnnex
|
||||||
logStatus k InfoMissing
|
logStatus k InfoMissing
|
||||||
where
|
where
|
||||||
boundry = durationToPOSIXTime <$> duration
|
boundry = durationToPOSIXTime <$> duration
|
||||||
|
|
|
@ -96,7 +96,7 @@ startDistributionDownload d = go =<< liftIO . newVersionLocation d =<< liftIO ol
|
||||||
, transferKey = k
|
, transferKey = k
|
||||||
}
|
}
|
||||||
cleanup = liftAnnex $ do
|
cleanup = liftAnnex $ do
|
||||||
removeAnnex k
|
lockContent k removeAnnex
|
||||||
setUrlMissing k u
|
setUrlMissing k u
|
||||||
logStatus k InfoMissing
|
logStatus k InfoMissing
|
||||||
|
|
||||||
|
|
|
@ -55,8 +55,12 @@ startRemote afile numcopies key remote = do
|
||||||
showStart' ("drop " ++ Remote.name remote) key afile
|
showStart' ("drop " ++ Remote.name remote) key afile
|
||||||
next $ performRemote key afile numcopies remote
|
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
|
||||||
|
-- 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 -> AssociatedFile -> NumCopies -> Maybe Remote -> CommandPerform
|
||||||
performLocal key afile numcopies knownpresentremote = lockContent key $ do
|
performLocal key afile numcopies knownpresentremote = lockContent key $ \contentlock -> do
|
||||||
(remotes, trusteduuids) <- Remote.keyPossibilitiesTrusted key
|
(remotes, trusteduuids) <- Remote.keyPossibilitiesTrusted key
|
||||||
let trusteduuids' = case knownpresentremote of
|
let trusteduuids' = case knownpresentremote of
|
||||||
Nothing -> trusteduuids
|
Nothing -> trusteduuids
|
||||||
|
@ -66,7 +70,7 @@ performLocal key afile numcopies knownpresentremote = lockContent key $ do
|
||||||
u <- getUUID
|
u <- getUUID
|
||||||
ifM (canDrop u key afile numcopies trusteduuids' tocheck [])
|
ifM (canDrop u key afile numcopies trusteduuids' tocheck [])
|
||||||
( do
|
( do
|
||||||
removeAnnex key
|
removeAnnex contentlock
|
||||||
notifyDrop afile True
|
notifyDrop afile True
|
||||||
next $ cleanupLocal key
|
next $ cleanupLocal key
|
||||||
, do
|
, do
|
||||||
|
@ -75,7 +79,7 @@ performLocal key afile numcopies knownpresentremote = lockContent key $ do
|
||||||
)
|
)
|
||||||
|
|
||||||
performRemote :: Key -> AssociatedFile -> NumCopies -> Remote -> CommandPerform
|
performRemote :: Key -> AssociatedFile -> NumCopies -> Remote -> CommandPerform
|
||||||
performRemote key afile numcopies remote = lockContent key $ do
|
performRemote key afile numcopies remote = do
|
||||||
-- Filter the remote it's being dropped from out of the lists of
|
-- Filter the remote it's being dropped from out of the lists of
|
||||||
-- places assumed to have the key, and places to check.
|
-- places assumed to have the key, and places to check.
|
||||||
-- When the local repo has the key, that's one additional copy,
|
-- When the local repo has the key, that's one additional copy,
|
||||||
|
|
|
@ -28,8 +28,8 @@ start key = stopUnless (inAnnex key) $ do
|
||||||
next $ perform key
|
next $ perform key
|
||||||
|
|
||||||
perform :: Key -> CommandPerform
|
perform :: Key -> CommandPerform
|
||||||
perform key = lockContent key $ do
|
perform key = lockContent key $ \contentlock -> do
|
||||||
removeAnnex key
|
removeAnnex contentlock
|
||||||
next $ cleanup key
|
next $ cleanup key
|
||||||
|
|
||||||
cleanup :: Key -> CommandCleanup
|
cleanup :: Key -> CommandCleanup
|
||||||
|
|
|
@ -91,7 +91,7 @@ expectedPresent dest key = do
|
||||||
return $ dest `elem` remotes
|
return $ dest `elem` remotes
|
||||||
|
|
||||||
toPerform :: Remote -> Bool -> Key -> AssociatedFile -> Bool -> Either String Bool -> CommandPerform
|
toPerform :: Remote -> Bool -> Key -> AssociatedFile -> Bool -> Either String Bool -> CommandPerform
|
||||||
toPerform dest move key afile fastcheck isthere = moveLock move key $
|
toPerform dest move key afile fastcheck isthere = do
|
||||||
case isthere of
|
case isthere of
|
||||||
Left err -> do
|
Left err -> do
|
||||||
showNote err
|
showNote err
|
||||||
|
@ -115,8 +115,8 @@ toPerform dest move key afile fastcheck isthere = moveLock move key $
|
||||||
finish
|
finish
|
||||||
where
|
where
|
||||||
finish
|
finish
|
||||||
| move = do
|
| move = lockContent key $ \contentlock -> do
|
||||||
removeAnnex key
|
removeAnnex contentlock
|
||||||
next $ Command.Drop.cleanupLocal key
|
next $ Command.Drop.cleanupLocal key
|
||||||
| otherwise = next $ return True
|
| otherwise = next $ return True
|
||||||
|
|
||||||
|
@ -164,10 +164,3 @@ fromPerform src move key afile = ifM (inAnnex key)
|
||||||
dispatch True True = do -- finish moving
|
dispatch True True = do -- finish moving
|
||||||
ok <- Remote.removeKey src key
|
ok <- Remote.removeKey src key
|
||||||
next $ Command.Drop.cleanupRemote key src ok
|
next $ Command.Drop.cleanupRemote key src ok
|
||||||
|
|
||||||
{- Locks a key in order for it to be moved away from the current repository.
|
|
||||||
- No lock is needed when a key is being copied, or moved to the current
|
|
||||||
- repository. -}
|
|
||||||
moveLock :: Bool -> Key -> Annex a -> Annex a
|
|
||||||
moveLock True key a = lockContent key a
|
|
||||||
moveLock False _ a = a
|
|
||||||
|
|
|
@ -114,7 +114,7 @@ test st r k =
|
||||||
, check "storeKey when already present" store
|
, check "storeKey when already present" store
|
||||||
, present True
|
, present True
|
||||||
, check "retrieveKeyFile" $ do
|
, check "retrieveKeyFile" $ do
|
||||||
removeAnnex k
|
lockContent k removeAnnex
|
||||||
get
|
get
|
||||||
, check "fsck downloaded object" fsck
|
, check "fsck downloaded object" fsck
|
||||||
, check "retrieveKeyFile resume from 33%" $ do
|
, check "retrieveKeyFile resume from 33%" $ do
|
||||||
|
@ -124,20 +124,20 @@ test st r k =
|
||||||
sz <- hFileSize h
|
sz <- hFileSize h
|
||||||
L.hGet h $ fromInteger $ sz `div` 3
|
L.hGet h $ fromInteger $ sz `div` 3
|
||||||
liftIO $ L.writeFile tmp partial
|
liftIO $ L.writeFile tmp partial
|
||||||
removeAnnex k
|
lockContent k removeAnnex
|
||||||
get
|
get
|
||||||
, check "fsck downloaded object" fsck
|
, check "fsck downloaded object" fsck
|
||||||
, check "retrieveKeyFile resume from 0" $ do
|
, check "retrieveKeyFile resume from 0" $ do
|
||||||
tmp <- prepTmp k
|
tmp <- prepTmp k
|
||||||
liftIO $ writeFile tmp ""
|
liftIO $ writeFile tmp ""
|
||||||
removeAnnex k
|
lockContent k removeAnnex
|
||||||
get
|
get
|
||||||
, check "fsck downloaded object" fsck
|
, check "fsck downloaded object" fsck
|
||||||
, check "retrieveKeyFile resume from end" $ do
|
, check "retrieveKeyFile resume from end" $ do
|
||||||
loc <- Annex.calcRepo (gitAnnexLocation k)
|
loc <- Annex.calcRepo (gitAnnexLocation k)
|
||||||
tmp <- prepTmp k
|
tmp <- prepTmp k
|
||||||
void $ liftIO $ copyFileExternal loc tmp
|
void $ liftIO $ copyFileExternal loc tmp
|
||||||
removeAnnex k
|
lockContent k removeAnnex
|
||||||
get
|
get
|
||||||
, check "fsck downloaded object" fsck
|
, check "fsck downloaded object" fsck
|
||||||
, check "removeKey when present" remove
|
, check "removeKey when present" remove
|
||||||
|
@ -183,7 +183,7 @@ testUnavailable st r k =
|
||||||
cleanup :: [Remote] -> [Key] -> Bool -> CommandCleanup
|
cleanup :: [Remote] -> [Key] -> Bool -> CommandCleanup
|
||||||
cleanup rs ks ok = do
|
cleanup rs ks ok = do
|
||||||
forM_ rs $ \r -> forM_ ks (Remote.removeKey r)
|
forM_ rs $ \r -> forM_ ks (Remote.removeKey r)
|
||||||
forM_ ks removeAnnex
|
forM_ ks $ \k -> lockContent k removeAnnex
|
||||||
return ok
|
return ok
|
||||||
|
|
||||||
chunkSizes :: Int -> Bool -> [Int]
|
chunkSizes :: Int -> Bool -> [Int]
|
||||||
|
|
|
@ -103,7 +103,7 @@ removeUnannexed = go []
|
||||||
go c [] = return c
|
go c [] = return c
|
||||||
go c (k:ks) = ifM (inAnnexCheck k $ liftIO . enoughlinks)
|
go c (k:ks) = ifM (inAnnexCheck k $ liftIO . enoughlinks)
|
||||||
( do
|
( do
|
||||||
removeAnnex k
|
lockContent k removeAnnex
|
||||||
go c ks
|
go c ks
|
||||||
, go (k:c) ks
|
, go (k:c) ks
|
||||||
)
|
)
|
||||||
|
|
|
@ -339,8 +339,8 @@ dropKey r key
|
||||||
commitOnCleanup r $ onLocal r $ do
|
commitOnCleanup r $ onLocal r $ do
|
||||||
ensureInitialized
|
ensureInitialized
|
||||||
whenM (Annex.Content.inAnnex key) $ do
|
whenM (Annex.Content.inAnnex key) $ do
|
||||||
Annex.Content.lockContent key $
|
Annex.Content.lockContent key
|
||||||
Annex.Content.removeAnnex key
|
Annex.Content.removeAnnex
|
||||||
logStatus key InfoMissing
|
logStatus key InfoMissing
|
||||||
Annex.Content.saveState True
|
Annex.Content.saveState True
|
||||||
return True
|
return True
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue