git-annex/Command/Drop.hs

242 lines
8.2 KiB
Haskell
Raw Normal View History

{- git-annex command
-
- Copyright 2010-2021 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
{-# LANGUAGE OverloadedStrings #-}
module Command.Drop where
import Command
import qualified Remote
import qualified Annex
import Annex.UUID
2011-10-15 20:21:08 +00:00
import Logs.Location
import Logs.Trust
import Logs.PreferredContent
2015-04-30 18:02:56 +00:00
import Annex.NumCopies
2011-10-04 04:40:47 +00:00
import Annex.Content
import Annex.Wanted
2014-03-22 19:01:48 +00:00
import Annex.Notification
cmd :: Command
cmd = withGlobalOptions [jobsOption, jsonOptions, annexedMatchingOptions] $
command "drop" SectionCommon
"remove content of files from repository"
paramPaths (seek <$$> optParser)
2015-07-08 21:59:06 +00:00
data DropOptions = DropOptions
{ dropFiles :: CmdParams
, dropFrom :: Maybe (DeferredParse Remote)
2015-07-08 21:59:06 +00:00
, autoMode :: Bool
, keyOptions :: Maybe KeyOptions
2016-07-06 15:54:46 +00:00
, batchOption :: BatchMode
2015-07-08 21:59:06 +00:00
}
optParser :: CmdParamsDesc -> Parser DropOptions
optParser desc = DropOptions
<$> cmdParams desc
<*> optional parseDropFromOption
2015-07-08 21:59:06 +00:00
<*> parseAutoOption
<*> optional parseKeyOptions
2016-07-06 15:54:46 +00:00
<*> parseBatchOption
2015-07-08 21:59:06 +00:00
parseDropFromOption :: Parser (DeferredParse Remote)
parseDropFromOption = parseRemoteOption <$> strOption
2015-07-09 14:41:17 +00:00
( long "from" <> short 'f' <> metavar paramRemote
<> help "drop content from a remote"
<> completeRemotes
2015-07-08 21:59:06 +00:00
)
seek :: DropOptions -> CommandSeek
seek o = startConcurrency commandStages $ do
from <- case dropFrom o of
Nothing -> pure Nothing
Just f -> getParsed f >>= \remote -> do
u <- getUUID
if Remote.uuid remote == u
then pure Nothing
else pure (Just remote)
let seeker = AnnexedFileSeeker
{ startAction = start o from
, checkContentPresent = case from of
Nothing -> Just True
Just _ -> Nothing
, usesLocationLog = True
}
2016-07-06 15:54:46 +00:00
case batchOption o of
Batch fmt -> batchAnnexedFilesMatching fmt seeker
NoBatch -> withKeyOptions (keyOptions o) (autoMode o) seeker
(commandAction . startKeys o from)
(withFilesInGitAnnex ww seeker)
=<< workTreeItems ww (dropFiles o)
2016-07-06 15:54:46 +00:00
where
ww = WarnUnmatchLsFiles
2015-07-08 21:59:06 +00:00
start :: DropOptions -> Maybe Remote -> SeekInput -> RawFilePath -> Key -> CommandStart
start o from si file key = start' o from key afile ai si
where
afile = AssociatedFile (Just file)
2019-06-06 16:53:24 +00:00
ai = mkActionItem (key, afile)
2015-07-08 21:59:06 +00:00
start' :: DropOptions -> Maybe Remote -> Key -> AssociatedFile -> ActionItem -> SeekInput -> CommandStart
start' o from key afile ai si =
checkDropAuto (autoMode o) from afile key $ \numcopies mincopies ->
stopUnless wantdrop $
2015-07-08 21:59:06 +00:00
case from of
Nothing -> startLocal pcc afile ai si numcopies mincopies key []
Just remote -> startRemote pcc afile ai si numcopies mincopies key remote
where
wantdrop
| autoMode o = wantDrop False (Remote.uuid <$> from) (Just key) afile Nothing
| otherwise = return True
pcc = PreferredContentChecked (autoMode o)
2015-07-08 21:59:06 +00:00
startKeys :: DropOptions -> Maybe Remote -> (SeekInput, Key, ActionItem) -> CommandStart
startKeys o from (si, key, ai) = start' o from key (AssociatedFile Nothing) ai si
startLocal :: PreferredContentChecked -> AssociatedFile -> ActionItem -> SeekInput -> NumCopies -> MinCopies -> Key -> [VerifiedCopy] -> CommandStart
startLocal pcc afile ai si numcopies mincopies key preverified =
starting "drop" (OnlyActionOn key ai) si $
performLocal pcc key afile numcopies mincopies preverified
startRemote :: PreferredContentChecked -> AssociatedFile -> ActionItem -> SeekInput -> NumCopies -> MinCopies -> Key -> Remote -> CommandStart
startRemote pcc afile ai si numcopies mincopies key remote =
starting ("drop " ++ Remote.name remote) (OnlyActionOn key ai) si $
performRemote pcc key afile numcopies mincopies remote
performLocal :: PreferredContentChecked -> Key -> AssociatedFile -> NumCopies -> MinCopies -> [VerifiedCopy] -> CommandPerform
performLocal pcc key afile numcopies mincopies preverified = lockContentForRemoval key fallback $ \contentlock -> do
u <- getUUID
(tocheck, verified) <- verifiableCopies key [u]
doDrop pcc u (Just contentlock) key afile numcopies mincopies [] (preverified ++ verified) tocheck
( \proof -> do
fastDebug "Command.Drop" $ unwords
[ "Dropping from here"
, "proof:"
, show proof
]
removeAnnex contentlock
2014-03-22 19:01:48 +00:00
notifyDrop afile True
next $ cleanupLocal key
2015-10-09 15:09:46 +00:00
, do
2014-03-22 19:01:48 +00:00
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 :: PreferredContentChecked -> Key -> AssociatedFile -> NumCopies -> MinCopies -> Remote -> CommandPerform
performRemote pcc key afile numcopies mincopies remote = do
2019-10-21 17:51:38 +00:00
-- Filter the uuid it's being dropped from out of the lists of
-- places assumed to have the key, and places to check.
(tocheck, verified) <- verifiableCopies key [uuid]
doDrop pcc uuid Nothing key afile numcopies mincopies [uuid] verified tocheck
( \proof -> do
fastDebug "Command.Drop" $ unwords
[ "Dropping from remote"
, show remote
, "proof:"
, show proof
]
2020-05-14 18:19:28 +00:00
ok <- Remote.action (Remote.removeKey remote key)
2015-10-09 15:09:46 +00:00
next $ cleanupRemote key remote ok
, stop
)
2012-12-13 04:45:27 +00:00
where
2012-11-12 05:05:04 +00:00
uuid = Remote.uuid remote
cleanupLocal :: Key -> CommandCleanup
cleanupLocal key = do
logStatus key InfoMissing
return True
2011-12-31 08:11:39 +00:00
cleanupRemote :: Key -> Remote -> Bool -> CommandCleanup
cleanupRemote key remote ok = do
when ok $
Remote.logStatus remote key InfoMissing
return ok
2015-10-09 15:09:46 +00:00
{- Before running the dropaction, checks specified remotes to
- verify that enough copies of a key exist to allow it to be
- safely removed (with no data loss).
-
- --force overrides and always allows dropping.
-}
doDrop
:: PreferredContentChecked
-> UUID
-> Maybe ContentRemovalLock
-> Key
-> AssociatedFile
-> NumCopies
-> MinCopies
-> [UUID]
-> [VerifiedCopy]
-> [UnVerifiedCopy]
-> (Maybe SafeDropProof -> CommandPerform, CommandPerform)
-> CommandPerform
doDrop pcc dropfrom contentlock key afile numcopies mincopies skip preverified check (dropaction, nodropaction) =
2015-04-30 18:02:56 +00:00
ifM (Annex.getState Annex.force)
( dropaction Nothing
, ifM (checkRequiredContent pcc dropfrom key afile)
( verifyEnoughCopiesToDrop nolocmsg key
contentlock numcopies mincopies
skip preverified check
(dropaction . Just)
(forcehint nodropaction)
2015-10-09 15:09:46 +00:00
, stop
)
2015-04-30 18:02:56 +00:00
)
2012-11-12 05:05:04 +00:00
where
2015-04-30 18:02:56 +00:00
nolocmsg = "Rather than dropping this file, try using: git annex move"
2015-10-09 15:09:46 +00:00
forcehint a = do
showLongNote "(Use --force to override this check, or adjust numcopies.)"
a
{- Checking preferred content also checks required content, so when
- auto mode causes preferred content to be checked, it's redundant
- for checkRequiredContent to separately check required content, and
- providing this avoids that extra work. -}
newtype PreferredContentChecked = PreferredContentChecked Bool
checkRequiredContent :: PreferredContentChecked -> UUID -> Key -> AssociatedFile -> Annex Bool
checkRequiredContent (PreferredContentChecked True) _ _ _ = return True
checkRequiredContent (PreferredContentChecked False) u k afile =
checkDrop isRequiredContent False (Just u) (Just k) afile Nothing >>= \case
Nothing -> return True
Just afile' -> do
if afile == afile'
then showLongNote "That file is required content. It cannot be dropped!"
else showLongNote $ "That file has the same content as another file"
++ case afile' of
AssociatedFile (Just f) -> " (" ++ fromRawFilePath f ++ "),"
AssociatedFile Nothing -> ""
++ " which is required content. It cannot be dropped!"
showLongNote "(Use --force to override this check, or adjust required content configuration.)"
return False
{- In auto mode, only runs the action if there are enough
- copies on other semitrusted repositories. -}
checkDropAuto :: Bool -> Maybe Remote -> AssociatedFile -> Key -> (NumCopies -> MinCopies -> CommandStart) -> CommandStart
checkDropAuto automode mremote afile key a =
go =<< getSafestNumMinCopies afile key
where
go (numcopies, mincopies)
2015-07-08 21:59:06 +00:00
| automode = do
locs <- Remote.keyLocations key
uuid <- getUUID
let remoteuuid = fromMaybe uuid $ Remote.uuid <$> mremote
locs' <- trustExclude UnTrusted $ filter (/= remoteuuid) locs
if NumCopies (length locs') >= numcopies
then a numcopies mincopies
else stop
| otherwise = a numcopies mincopies