git-annex/Command/Drop.hs

195 lines
6.4 KiB
Haskell
Raw Normal View History

{- git-annex command
-
- Copyright 2010 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Command.Drop where
2011-10-05 20:02:51 +00:00
import Common.Annex
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
import qualified Data.Set as S
cmd :: Command
cmd = withGlobalOptions 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
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 False)
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 = withKeyOptions (keyOptions o) (autoMode o)
(startKeys o)
(withFilesInGit $ whenAnnexed $ start o)
(dropFiles o)
start :: DropOptions -> FilePath -> Key -> CommandStart
start o file key = start' o key (Just file)
start' :: DropOptions -> Key -> AssociatedFile -> CommandStart
start' o key afile = do
from <- maybe (pure Nothing) (Just <$$> getParsed) (dropFrom o)
2015-07-08 21:59:06 +00:00
checkDropAuto (autoMode o) from afile key $ \numcopies ->
stopUnless (want from) $
case from of
Nothing -> startLocal afile numcopies key Nothing
Just remote -> do
u <- getUUID
if Remote.uuid remote == u
then startLocal afile numcopies key Nothing
else startRemote afile numcopies key remote
where
want from
| autoMode o = wantDrop False (Remote.uuid <$> from) (Just key) afile
| otherwise = return True
startKeys :: DropOptions -> Key -> CommandStart
startKeys o key = start' o key Nothing
startLocal :: AssociatedFile -> NumCopies -> Key -> Maybe Remote -> CommandStart
2014-01-01 21:39:33 +00:00
startLocal afile numcopies key knownpresentremote = stopUnless (inAnnex key) $ do
2014-01-26 19:53:01 +00:00
showStart' "drop" key afile
2014-03-22 19:01:48 +00:00
next $ performLocal key afile numcopies knownpresentremote
startRemote :: AssociatedFile -> NumCopies -> Key -> Remote -> CommandStart
2014-01-01 21:39:33 +00:00
startRemote afile numcopies key remote = do
2014-01-26 19:53:01 +00:00
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
-- or more remotes are trying to remove a key at the same time, and each
-- see the key is present on the other.
2014-03-22 19:01:48 +00:00
performLocal :: Key -> AssociatedFile -> NumCopies -> Maybe Remote -> CommandPerform
performLocal key afile numcopies knownpresentremote = lockContent key $ \contentlock -> do
(remotes, trusteduuids) <- Remote.keyPossibilitiesTrusted key
2012-11-24 20:30:15 +00:00
let trusteduuids' = case knownpresentremote of
Nothing -> trusteduuids
Just r -> Remote.uuid r:trusteduuids
untrusteduuids <- trustGet UnTrusted
2012-11-24 20:30:15 +00:00
let tocheck = Remote.remotesWithoutUUID remotes (trusteduuids'++untrusteduuids)
u <- getUUID
ifM (canDrop u key afile numcopies trusteduuids' tocheck [])
2014-03-22 19:01:48 +00:00
( do
removeAnnex contentlock
2014-03-22 19:01:48 +00:00
notifyDrop afile True
next $ cleanupLocal key
, do
notifyDrop afile False
stop
)
performRemote :: Key -> AssociatedFile -> NumCopies -> Remote -> CommandPerform
performRemote key afile numcopies remote = do
-- Filter the remote it's being dropped from out of the lists of
-- places assumed to have the key, and places to check.
-- When the local repo has the key, that's one additional copy,
2015-04-30 18:02:56 +00:00
-- as long as the local repo is not untrusted.
(remotes, trusteduuids) <- knownCopies key
let have = filter (/= uuid) trusteduuids
untrusteduuids <- trustGet UnTrusted
let tocheck = filter (/= remote) $
Remote.remotesWithoutUUID remotes (have++untrusteduuids)
stopUnless (canDrop uuid key afile numcopies have tocheck [uuid]) $ do
ok <- Remote.removeKey remote key
next $ cleanupRemote key remote ok
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
{- Checks specified remotes to verify that enough copies of a key exist to
- allow it to be safely removed (with no data loss). Can be provided with
- some locations where the key is known/assumed to be present.
-
- Also checks if it's required content, and refuses to drop if so.
-
- --force overrides and always allows dropping.
-}
canDrop :: UUID -> Key -> AssociatedFile -> NumCopies -> [UUID] -> [Remote] -> [UUID] -> Annex Bool
2015-04-30 18:02:56 +00:00
canDrop dropfrom key afile numcopies have check skip =
ifM (Annex.getState Annex.force)
( return True
, ifM (checkRequiredContent dropfrom key afile
<&&> verifyEnoughCopies nolocmsg key numcopies skip have check
)
( return True
, do
hint
return False
)
)
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"
hint = showLongNote "(Use --force to override this check, or adjust numcopies.)"
checkRequiredContent :: UUID -> Key -> AssociatedFile -> Annex Bool
checkRequiredContent u k afile =
ifM (isRequiredContent (Just u) S.empty (Just k) afile False)
( requiredContent
, return True
)
requiredContent :: Annex Bool
requiredContent = do
showLongNote "That file 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 -> CommandStart) -> CommandStart
2015-07-08 21:59:06 +00:00
checkDropAuto automode mremote afile key a = go =<< maybe getNumCopies getFileNumCopies afile
where
go numcopies
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
else stop
| otherwise = a numcopies