avoid failure to lock content of removed file causing drop etc to fail
This was already prevented in other ways, but as seen in commit
c30fd24d91, those were a bit fragile.
And I'm not sure races were avoided in every case before. At least a
race between two separate git-annex processes, dropping the same
content, seemed possible.
This way, if locking fails, and the content is not present, it will
always do the right thing. Also, it avoids the overhead of an unncessary
inAnnex check for every file.
This commit was sponsored by Denis Dzyubenko on Patreon.
	
	
This commit is contained in:
		
					parent
					
						
							
								c30fd24d91
							
						
					
				
			
			
				commit
				
					
						2a45b5ae9a
					
				
			
		
					 11 changed files with 65 additions and 40 deletions
				
			
		|  | @ -194,13 +194,15 @@ contentLockFile key = Just <$> calcRepo (gitAnnexContentLock key) | |||
|  - rather than running the action. | ||||
|  -} | ||||
| lockContentShared :: Key -> (VerifiedCopy -> Annex a) -> Annex a | ||||
| lockContentShared key a = lockContentUsing lock key $ ifM (inAnnex key) | ||||
| lockContentShared key a = lockContentUsing lock key notpresent $ | ||||
| 	ifM (inAnnex key) | ||||
| 		( do | ||||
| 			u <- getUUID | ||||
| 			withVerifiedCopy LockedCopy u (return True) a | ||||
| 	, giveup $ "failed to lock content: not present" | ||||
| 		, notpresent | ||||
| 		) | ||||
|   where | ||||
| 	notpresent = giveup $ "failed to lock content: not present" | ||||
| #ifndef mingw32_HOST_OS | ||||
| 	lock contentfile Nothing = tryLockShared Nothing contentfile | ||||
| 	lock _ (Just lockfile) = posixLocker tryLockShared lockfile | ||||
|  | @ -212,9 +214,12 @@ lockContentShared key a = lockContentUsing lock key $ ifM (inAnnex key) | |||
|  - might remove it. | ||||
|  - | ||||
|  - If locking fails, throws an exception rather than running the action. | ||||
|  - | ||||
|  - But, if locking fails because the the content is not present, runs the | ||||
|  - fallback action instead. | ||||
|  -} | ||||
| lockContentForRemoval :: Key -> (ContentRemovalLock -> Annex a) -> Annex a | ||||
| lockContentForRemoval key a = lockContentUsing lock key $  | ||||
| lockContentForRemoval :: Key -> Annex a -> (ContentRemovalLock -> Annex a) -> Annex a | ||||
| lockContentForRemoval key fallback a = lockContentUsing lock key fallback $  | ||||
| 	a (ContentRemovalLock key) | ||||
|   where | ||||
| #ifndef mingw32_HOST_OS | ||||
|  | @ -251,22 +256,31 @@ winLocker takelock _ (Just lockfile) = do | |||
| winLocker _ _ Nothing = return Nothing | ||||
| #endif | ||||
| 
 | ||||
| lockContentUsing :: ContentLocker -> Key -> Annex a -> Annex a | ||||
| lockContentUsing locker key a = do | ||||
| {- The fallback action is run if the ContentLocker throws an IO exception | ||||
|  - and the content is not present. It's not guaranteed to always run when | ||||
|  - the content is not present, because the content file is not always | ||||
|  - the file that is locked eg on Windows a different file is locked. -} | ||||
| lockContentUsing :: ContentLocker -> Key -> Annex a -> Annex a -> Annex a | ||||
| lockContentUsing locker key fallback a = do | ||||
| 	contentfile <- fromRawFilePath <$> calcRepo (gitAnnexLocation key) | ||||
| 	lockfile <- contentLockFile key | ||||
| 	bracket | ||||
| 		(lock contentfile lockfile) | ||||
| 		(unlock lockfile) | ||||
| 		(const a) | ||||
| 		(either (const noop) (unlock lockfile)) | ||||
| 		go | ||||
|   where | ||||
| 	alreadylocked = giveup "content is locked" | ||||
| 	failedtolock e = giveup $ "failed to lock content: " ++ show e | ||||
| 
 | ||||
| 	lock contentfile lockfile = | ||||
| 		(maybe alreadylocked return  | ||||
| 			=<< locker contentfile lockfile) | ||||
| 		`catchIO` failedtolock | ||||
| 	lock contentfile lockfile = tryIO $ | ||||
| 		maybe alreadylocked return  | ||||
| 			=<< locker contentfile lockfile | ||||
| 	 | ||||
| 	go (Right _) = a | ||||
| 	go (Left e) = ifM (inAnnex key) | ||||
| 		( failedtolock e | ||||
| 		, fallback  | ||||
| 		) | ||||
| 
 | ||||
| #ifndef mingw32_HOST_OS | ||||
| 	unlock mlockfile lck = do | ||||
|  |  | |||
|  | @ -17,7 +17,6 @@ import qualified Command.Drop | |||
| import Command | ||||
| import Annex.Wanted | ||||
| import Annex.SpecialRemote.Config | ||||
| import Annex.Content | ||||
| import qualified Database.Keys | ||||
| import Git.FilePath | ||||
| 
 | ||||
|  |  | |||
|  | @ -76,7 +76,7 @@ expireUnused duration = do | |||
| 	forM_ oldkeys $ \k -> do | ||||
| 		debug ["removing old unused key", serializeKey k] | ||||
| 		liftAnnex $ tryNonAsync $ do | ||||
| 			lockContentForRemoval k removeAnnex | ||||
| 			lockContentForRemoval k noop removeAnnex | ||||
| 			logStatus k InfoMissing | ||||
|   where | ||||
| 	boundry = durationToPOSIXTime <$> duration | ||||
|  |  | |||
|  | @ -99,7 +99,7 @@ startDistributionDownload d = go =<< liftIO . newVersionLocation d =<< liftIO ol | |||
| 		, transferKeyData = fromKey id k | ||||
| 		} | ||||
| 	cleanup = liftAnnex $ do | ||||
| 		lockContentForRemoval k removeAnnex | ||||
| 		lockContentForRemoval k noop removeAnnex | ||||
| 		setUrlMissing k u | ||||
| 		logStatus k InfoMissing | ||||
| 
 | ||||
|  |  | |||
|  | @ -99,11 +99,6 @@ startKeys o from (key, ai) = start' o from key (AssociatedFile Nothing) ai | |||
| 
 | ||||
| startLocal :: AssociatedFile -> ActionItem -> NumCopies -> Key -> [VerifiedCopy] -> CommandStart | ||||
| startLocal afile ai numcopies key preverified = | ||||
| 	-- This is a redundant check, because checkContentPresent was | ||||
| 	-- enabled when seeking. However, when two files have the same key, | ||||
| 	-- the content may have already been removed, which would cause | ||||
| 	-- this to fail, so it has to be checked again. | ||||
| 	stopUnless (inAnnex key) $ | ||||
| 	starting "drop" (OnlyActionOn key ai) $ | ||||
| 		performLocal key afile numcopies preverified | ||||
| 
 | ||||
|  | @ -113,7 +108,7 @@ startRemote afile ai numcopies key remote = | |||
| 		performRemote key afile numcopies remote | ||||
| 
 | ||||
| performLocal :: Key -> AssociatedFile -> NumCopies -> [VerifiedCopy] -> CommandPerform | ||||
| performLocal key afile numcopies preverified = lockContentForRemoval key $ \contentlock -> do | ||||
| performLocal key afile numcopies preverified = lockContentForRemoval key fallback $ \contentlock -> do | ||||
| 	u <- getUUID | ||||
| 	(tocheck, verified) <- verifiableCopies key [u] | ||||
| 	doDrop u (Just contentlock) key afile numcopies [] (preverified ++ verified) tocheck | ||||
|  | @ -130,6 +125,13 @@ performLocal key afile numcopies preverified = lockContentForRemoval key $ \cont | |||
| 			notifyDrop afile False | ||||
| 			stop | ||||
| 		) | ||||
|   where | ||||
| 	-- This occurs when, for example, two files are being dropped | ||||
| 	-- and have the same content. The seek stage checks if the content | ||||
| 	-- is present, but due to buffering, may find it present for the | ||||
| 	-- second file before the first is dropped. If so, nothing remains | ||||
| 	-- to be done except for cleaning up. | ||||
| 	fallback = next $ cleanupLocal key | ||||
| 
 | ||||
| performRemote :: Key -> AssociatedFile -> NumCopies -> Remote -> CommandPerform | ||||
| performRemote key afile numcopies remote = do | ||||
|  |  | |||
|  | @ -47,7 +47,7 @@ start key = starting "dropkey" (mkActionItem key) $ | |||
| 
 | ||||
| perform :: Key -> CommandPerform | ||||
| perform key = ifM (inAnnex key) | ||||
| 	( lockContentForRemoval key $ \contentlock -> do | ||||
| 	( lockContentForRemoval key (next $ cleanup key) $ \contentlock -> do | ||||
| 		removeAnnex contentlock | ||||
| 		next $ cleanup key | ||||
| 	, next $ return True | ||||
|  |  | |||
|  | @ -155,7 +155,7 @@ toPerform dest removewhen key afile fastcheck isthere = | |||
| 		RemoveNever -> do | ||||
| 			setpresentremote | ||||
| 			next $ return True | ||||
| 		RemoveSafe -> lockContentForRemoval key $ \contentlock -> do | ||||
| 		RemoveSafe -> lockContentForRemoval key lockfailed $ \contentlock -> do | ||||
| 			srcuuid <- getUUID | ||||
| 			let destuuid = Remote.uuid dest | ||||
| 			willDropMakeItWorse srcuuid destuuid deststartedwithcopy key afile >>= \case | ||||
|  | @ -189,6 +189,13 @@ toPerform dest removewhen key afile fastcheck isthere = | |||
| 			() <- setpresentremote | ||||
| 			return False | ||||
| 	 | ||||
| 	-- This occurs when, for example, two files are being dropped | ||||
| 	-- and have the same content. The seek stage checks if the content | ||||
| 	-- is present, but due to buffering, may find it present for the | ||||
| 	-- second file before the first is dropped. If so, nothing remains | ||||
| 	-- to be done except for cleaning up. | ||||
| 	lockfailed = next $ Command.Drop.cleanupLocal key | ||||
| 
 | ||||
| fromStart :: RemoveWhen -> AssociatedFile -> Key -> ActionItem -> Remote -> CommandStart | ||||
| fromStart removewhen afile key ai src =  | ||||
| 	stopUnless (fromOk src key) $ | ||||
|  |  | |||
|  | @ -245,7 +245,7 @@ test runannex mkr mkk = | |||
| 		whenwritable r $ isRight <$> tryNonAsync (store r k) | ||||
| 	, check ("present " ++ show True) $ \r k -> present r k True | ||||
| 	, check "retrieveKeyFile" $ \r k -> do | ||||
| 		lockContentForRemoval k removeAnnex | ||||
| 		lockContentForRemoval k noop removeAnnex | ||||
| 		get r k | ||||
| 	, check "fsck downloaded object" fsck | ||||
| 	, check "retrieveKeyFile resume from 33%" $ \r k -> do | ||||
|  | @ -255,20 +255,20 @@ test runannex mkr mkk = | |||
| 			sz <- hFileSize h | ||||
| 			L.hGet h $ fromInteger $ sz `div` 3 | ||||
| 		liftIO $ L.writeFile tmp partial | ||||
| 		lockContentForRemoval k removeAnnex | ||||
| 		lockContentForRemoval k noop removeAnnex | ||||
| 		get r k | ||||
| 	, check "fsck downloaded object" fsck | ||||
| 	, check "retrieveKeyFile resume from 0" $ \r k -> do | ||||
| 		tmp <- prepTmp k | ||||
| 		liftIO $ writeFile tmp "" | ||||
| 		lockContentForRemoval k removeAnnex | ||||
| 		lockContentForRemoval k noop removeAnnex | ||||
| 		get r k | ||||
| 	, check "fsck downloaded object" fsck | ||||
| 	, check "retrieveKeyFile resume from end" $ \r k -> do | ||||
| 		loc <- fromRawFilePath <$> Annex.calcRepo (gitAnnexLocation k) | ||||
| 		tmp <- prepTmp k | ||||
| 		void $ liftIO $ copyFileExternal CopyAllMetaData loc tmp | ||||
| 		lockContentForRemoval k removeAnnex | ||||
| 		lockContentForRemoval k noop removeAnnex | ||||
| 		get r k | ||||
| 	, check "fsck downloaded object" fsck | ||||
| 	, check "removeKey when present" $ \r k ->  | ||||
|  | @ -393,7 +393,7 @@ cleanup rs ks ok | |||
| 	| all Remote.readonly rs = return ok | ||||
| 	| otherwise = do | ||||
| 		forM_ rs $ \r -> forM_ ks (Remote.removeKey r) | ||||
| 		forM_ ks $ \k -> lockContentForRemoval k removeAnnex | ||||
| 		forM_ ks $ \k -> lockContentForRemoval k noop removeAnnex | ||||
| 		return ok | ||||
| 
 | ||||
| chunkSizes :: Int -> Bool -> [Int] | ||||
|  |  | |||
|  | @ -115,7 +115,7 @@ removeUnannexed = go [] | |||
| 	go c [] = return c | ||||
| 	go c (k:ks) = ifM (inAnnexCheck k $ liftIO . enoughlinks) | ||||
| 		( do | ||||
| 			lockContentForRemoval k removeAnnex | ||||
| 			lockContentForRemoval k noop removeAnnex | ||||
| 			go c ks | ||||
| 		, go (k:c) ks | ||||
| 		) | ||||
|  |  | |||
							
								
								
									
										10
									
								
								P2P/Annex.hs
									
										
									
									
									
								
							
							
						
						
									
										10
									
								
								P2P/Annex.hs
									
										
									
									
									
								
							|  | @ -107,12 +107,14 @@ runLocal runst runner a = case a of | |||
| 			Left e -> return $ Left $ ProtoFailureException e | ||||
| 			Right result -> runner (next result) | ||||
| 	RemoveContent k next -> do | ||||
| 		v <- tryNonAsync $ | ||||
| 			ifM (Annex.Content.inAnnex k) | ||||
| 				( lockContentForRemoval k $ \contentlock -> do | ||||
| 					removeAnnex contentlock | ||||
| 		let cleanup = do | ||||
| 			logStatus k InfoMissing | ||||
| 			return True | ||||
| 		v <- tryNonAsync $ | ||||
| 			ifM (Annex.Content.inAnnex k) | ||||
| 				( lockContentForRemoval k cleanup $ \contentlock -> do | ||||
| 					removeAnnex contentlock | ||||
| 					cleanup | ||||
| 				, return True | ||||
| 				) | ||||
| 		case v of | ||||
|  |  | |||
|  | @ -436,9 +436,10 @@ dropKey' repo r st@(State connpool duc _ _ _) key | |||
| 		( guardUsable repo (giveup "cannot access remote") $ | ||||
| 			commitOnCleanup repo r st $ onLocalFast st $ do | ||||
| 				whenM (Annex.Content.inAnnex key) $ do | ||||
| 					Annex.Content.lockContentForRemoval key $ \lock -> do | ||||
| 					let cleanup = logStatus key InfoMissing | ||||
| 					Annex.Content.lockContentForRemoval key cleanup $ \lock -> do | ||||
| 						Annex.Content.removeAnnex lock | ||||
| 						logStatus key InfoMissing | ||||
| 						cleanup | ||||
| 					Annex.Content.saveState True | ||||
| 		, giveup "remote does not have expected annex.uuid value" | ||||
| 		) | ||||
|  |  | |||
		Loading…
	
	Add table
		Add a link
		
	
		Reference in a new issue
	
	 Joey Hess
				Joey Hess