2010-11-02 23:04:24 +00:00
|
|
|
{- git-annex command
|
|
|
|
-
|
2015-01-21 16:50:09 +00:00
|
|
|
- Copyright 2010 Joey Hess <id@joeyh.name>
|
2010-11-02 23:04:24 +00:00
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
|
|
|
module Command.Drop where
|
|
|
|
|
2011-10-05 20:02:51 +00:00
|
|
|
import Common.Annex
|
2010-11-02 23:04:24 +00:00
|
|
|
import Command
|
2011-07-05 22:31:46 +00:00
|
|
|
import qualified Remote
|
|
|
|
import qualified Annex
|
2011-10-28 21:26:38 +00:00
|
|
|
import Annex.UUID
|
2011-10-15 20:21:08 +00:00
|
|
|
import Logs.Location
|
|
|
|
import Logs.Trust
|
2014-03-29 19:20:55 +00:00
|
|
|
import Logs.PreferredContent
|
2014-01-21 22:08:56 +00:00
|
|
|
import Config.NumCopies
|
2011-10-04 04:40:47 +00:00
|
|
|
import Annex.Content
|
2012-10-08 20:06:56 +00:00
|
|
|
import Annex.Wanted
|
2014-03-22 19:01:48 +00:00
|
|
|
import Annex.Notification
|
2010-11-02 23:04:24 +00:00
|
|
|
|
2014-03-29 19:20:55 +00:00
|
|
|
import qualified Data.Set as S
|
|
|
|
|
2014-10-14 18:20:10 +00:00
|
|
|
cmd :: [Command]
|
|
|
|
cmd = [withOptions [dropFromOption] $ command "drop" paramPaths seek
|
2013-03-24 22:28:21 +00:00
|
|
|
SectionCommon "indicate content of files not currently wanted"]
|
2010-12-30 19:06:26 +00:00
|
|
|
|
2014-01-26 20:25:55 +00:00
|
|
|
dropFromOption :: Option
|
|
|
|
dropFromOption = fieldOption ['f'] "from" paramRemote "drop content from a remote"
|
more command-specific options
Made --from and --to command-specific options.
Added generic storage for values of command-specific options,
which allows removing some of the special case fields in AnnexState.
(Also added generic storage for command-specific flags, although there are
not yet any.)
Note that this storage uses a Map, so repeatedly looking up the same value
is slightly more expensive than looking up an AnnexState field. But, the
value can be looked up once in the seek stage, transformed as necessary,
and passed in a closure to the start stage, and this avoids that overhead.
Still, I'm hesitant to use this for things like force or fast flags.
It's probably best to reserve it for flags that are only used by a few
commands, or options like --from and --to that it's important only be
allowed to be used with commands that implement them, to avoid user
confusion.
2012-01-06 07:06:25 +00:00
|
|
|
|
fix inversion of control in CommandSeek (no behavior changes)
I've been disliking how the command seek actions were written for some
time, with their inversion of control and ugly workarounds.
The last straw to fix it was sync --content, which didn't fit the
Annex [CommandStart] interface well at all. I have not yet made it take
advantage of the changed interface though.
The crucial change, and probably why I didn't do it this way from the
beginning, is to make each CommandStart action be run with exceptions
caught, and if it fails, increment a failure counter in annex state.
So I finally remove the very first code I wrote for git-annex, which
was before I had exception handling in the Annex monad, and so ran outside
that monad, passing state explicitly as it ran each CommandStart action.
This was a real slog from 1 to 5 am.
Test suite passes.
Memory usage is lower than before, sometimes by a couple of megabytes, and
remains constant, even when running in a large repo, and even when
repeatedly failing and incrementing the error counter. So no accidental
laziness space leaks.
Wall clock speed is identical, even in large repos.
This commit was sponsored by an anonymous bitcoiner.
2014-01-20 08:11:42 +00:00
|
|
|
seek :: CommandSeek
|
|
|
|
seek ps = do
|
2014-01-26 20:25:55 +00:00
|
|
|
from <- getOptionField dropFromOption Remote.byNameWithUUID
|
fix inversion of control in CommandSeek (no behavior changes)
I've been disliking how the command seek actions were written for some
time, with their inversion of control and ugly workarounds.
The last straw to fix it was sync --content, which didn't fit the
Annex [CommandStart] interface well at all. I have not yet made it take
advantage of the changed interface though.
The crucial change, and probably why I didn't do it this way from the
beginning, is to make each CommandStart action be run with exceptions
caught, and if it fails, increment a failure counter in annex state.
So I finally remove the very first code I wrote for git-annex, which
was before I had exception handling in the Annex monad, and so ran outside
that monad, passing state explicitly as it ran each CommandStart action.
This was a real slog from 1 to 5 am.
Test suite passes.
Memory usage is lower than before, sometimes by a couple of megabytes, and
remains constant, even when running in a large repo, and even when
repeatedly failing and incrementing the error counter. So no accidental
laziness space leaks.
Wall clock speed is identical, even in large repos.
This commit was sponsored by an anonymous bitcoiner.
2014-01-20 08:11:42 +00:00
|
|
|
withFilesInGit (whenAnnexed $ start from) ps
|
2011-11-11 03:35:08 +00:00
|
|
|
|
2014-04-17 22:03:39 +00:00
|
|
|
start :: Maybe Remote -> FilePath -> Key -> CommandStart
|
|
|
|
start from file key = checkDropAuto from file key $ \numcopies ->
|
2014-01-23 20:37:08 +00:00
|
|
|
stopUnless (checkAuto $ wantDrop False (Remote.uuid <$> from) (Just key) (Just file)) $
|
2012-10-08 20:06:56 +00:00
|
|
|
case from of
|
2014-01-01 21:39:33 +00:00
|
|
|
Nothing -> startLocal (Just file) numcopies key Nothing
|
2012-10-08 20:06:56 +00:00
|
|
|
Just remote -> do
|
|
|
|
u <- getUUID
|
|
|
|
if Remote.uuid remote == u
|
2014-01-01 21:39:33 +00:00
|
|
|
then startLocal (Just file) numcopies key Nothing
|
|
|
|
else startRemote (Just file) numcopies key remote
|
2011-10-28 21:26:38 +00:00
|
|
|
|
2014-01-21 21:08:49 +00:00
|
|
|
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
|
2010-11-02 23:04:24 +00:00
|
|
|
|
2014-01-21 21:08:49 +00:00
|
|
|
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
|
2014-03-29 19:20:55 +00:00
|
|
|
next $ performRemote key afile numcopies remote
|
2011-10-28 21:26:38 +00:00
|
|
|
|
2014-08-21 00:08:45 +00:00
|
|
|
-- 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
|
2014-08-21 00:08:45 +00:00
|
|
|
performLocal key afile numcopies knownpresentremote = lockContent key $ \contentlock -> do
|
2011-10-28 21:26:38 +00:00
|
|
|
(remotes, trusteduuids) <- Remote.keyPossibilitiesTrusted key
|
2012-11-24 20:30:15 +00:00
|
|
|
let trusteduuids' = case knownpresentremote of
|
|
|
|
Nothing -> trusteduuids
|
|
|
|
Just r -> nub (Remote.uuid r:trusteduuids)
|
2011-10-28 21:26:38 +00:00
|
|
|
untrusteduuids <- trustGet UnTrusted
|
2012-11-24 20:30:15 +00:00
|
|
|
let tocheck = Remote.remotesWithoutUUID remotes (trusteduuids'++untrusteduuids)
|
2014-03-29 19:20:55 +00:00
|
|
|
u <- getUUID
|
|
|
|
ifM (canDrop u key afile numcopies trusteduuids' tocheck [])
|
2014-03-22 19:01:48 +00:00
|
|
|
( do
|
2014-08-21 00:08:45 +00:00
|
|
|
removeAnnex contentlock
|
2014-03-22 19:01:48 +00:00
|
|
|
notifyDrop afile True
|
|
|
|
next $ cleanupLocal key
|
|
|
|
, do
|
|
|
|
notifyDrop afile False
|
|
|
|
stop
|
|
|
|
)
|
2010-11-02 23:04:24 +00:00
|
|
|
|
2014-03-29 19:20:55 +00:00
|
|
|
performRemote :: Key -> AssociatedFile -> NumCopies -> Remote -> CommandPerform
|
2014-08-21 00:08:45 +00:00
|
|
|
performRemote key afile numcopies remote = do
|
2011-10-28 21:26:38 +00:00
|
|
|
-- Filter the remote it's being dropped from out of the lists of
|
|
|
|
-- places assumed to have the key, and places to check.
|
2014-04-17 17:31:39 +00:00
|
|
|
-- When the local repo has the key, that's one additional copy,
|
|
|
|
-- as long asthe local repo is not untrusted.
|
2011-10-28 21:26:38 +00:00
|
|
|
(remotes, trusteduuids) <- Remote.keyPossibilitiesTrusted key
|
|
|
|
present <- inAnnex key
|
|
|
|
u <- getUUID
|
2014-04-17 17:31:39 +00:00
|
|
|
trusteduuids' <- if present
|
|
|
|
then ifM ((<= SemiTrusted) <$> lookupTrust u)
|
|
|
|
( pure (u:trusteduuids)
|
|
|
|
, pure trusteduuids
|
|
|
|
)
|
|
|
|
else pure trusteduuids
|
|
|
|
let have = filter (/= uuid) trusteduuids'
|
2011-10-28 21:26:38 +00:00
|
|
|
untrusteduuids <- trustGet UnTrusted
|
|
|
|
let tocheck = filter (/= remote) $
|
|
|
|
Remote.remotesWithoutUUID remotes (have++untrusteduuids)
|
2014-03-29 19:20:55 +00:00
|
|
|
stopUnless (canDrop uuid key afile numcopies have tocheck [uuid]) $ do
|
2011-12-09 16:23:45 +00:00
|
|
|
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
|
2011-10-28 21:26:38 +00:00
|
|
|
|
|
|
|
cleanupLocal :: Key -> CommandCleanup
|
|
|
|
cleanupLocal key = do
|
2011-07-01 19:24:07 +00:00
|
|
|
logStatus key InfoMissing
|
2010-11-08 23:26:37 +00:00
|
|
|
return True
|
2011-07-05 22:31:46 +00:00
|
|
|
|
2011-12-31 08:11:39 +00:00
|
|
|
cleanupRemote :: Key -> Remote -> Bool -> CommandCleanup
|
2011-11-09 20:54:18 +00:00
|
|
|
cleanupRemote key remote ok = do
|
bugfix: drop --from an unavailable remote no longer updates the location log, incorrectly, to say the remote does not have the key.
The comments correctly noted that the remote could drop the key and
yet False be returned due to some problem that occurred afterwards.
For example, if it's a network remote, it could drop the key just
as the network goes down, and so things timeout and a nonzero exit
from ssh is propigated through and False returned.
However... Most of the time, this scenario will not have happened.
False will mean the remote was not available or could not drop the key
at all.
So, instead of assuming the worst, just trust the status we have.
If we get it wrong, and the scenario above happened, our location
log will think the remote has the key. But the remote's location
log (assuming it has one) will know it dropped it, and the next sync
will regain consistency.
For a special remote, with no location log, our location log will be wrong,
but this is no different than the situation where someone else dropped
the key from the remote and we've not synced with them. The standard
paranoia about not trusting the location log to be the last word about
whether a remote has a key will save us from these situations. Ie,
if we try to drop the file, we'll actively check the remote,
and determine the inconsistency then.
2013-03-10 23:15:53 +00:00
|
|
|
when ok $
|
|
|
|
Remote.logStatus remote key InfoMissing
|
2011-10-28 21:26:38 +00:00
|
|
|
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
|
2014-03-29 19:20:55 +00:00
|
|
|
- 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
|
|
|
|
canDrop dropfrom key afile numcopies have check skip = ifM (Annex.getState Annex.force)
|
|
|
|
( return True
|
|
|
|
, checkRequiredContent dropfrom key afile
|
|
|
|
<&&>
|
|
|
|
findCopies key numcopies skip have check
|
|
|
|
)
|
2011-10-28 21:26:38 +00:00
|
|
|
|
2014-01-21 20:08:19 +00:00
|
|
|
findCopies :: Key -> NumCopies -> [UUID] -> [UUID] -> [Remote] -> Annex Bool
|
2013-01-17 01:44:42 +00:00
|
|
|
findCopies key need skip = helper [] []
|
2012-11-12 05:05:04 +00:00
|
|
|
where
|
2013-01-17 01:44:42 +00:00
|
|
|
helper bad missing have []
|
2014-01-21 20:08:19 +00:00
|
|
|
| NumCopies (length have) >= need = return True
|
2013-01-17 01:44:42 +00:00
|
|
|
| otherwise = notEnoughCopies key need have (skip++missing) bad
|
|
|
|
helper bad missing have (r:rs)
|
2014-01-21 20:08:19 +00:00
|
|
|
| NumCopies (length have) >= need = return True
|
2012-11-12 05:05:04 +00:00
|
|
|
| otherwise = do
|
|
|
|
let u = Remote.uuid r
|
|
|
|
let duplicate = u `elem` have
|
|
|
|
haskey <- Remote.hasKey r key
|
|
|
|
case (duplicate, haskey) of
|
2013-01-17 01:44:42 +00:00
|
|
|
(False, Right True) -> helper bad missing (u:have) rs
|
|
|
|
(False, Left _) -> helper (r:bad) missing have rs
|
|
|
|
(False, Right False) -> helper bad (u:missing) have rs
|
|
|
|
_ -> helper bad missing have rs
|
2011-10-28 21:26:38 +00:00
|
|
|
|
2014-01-21 20:08:19 +00:00
|
|
|
notEnoughCopies :: Key -> NumCopies -> [UUID] -> [UUID] -> [Remote] -> Annex Bool
|
2011-10-28 21:26:38 +00:00
|
|
|
notEnoughCopies key need have skip bad = do
|
|
|
|
unsafe
|
|
|
|
showLongNote $
|
|
|
|
"Could only verify the existence of " ++
|
2014-01-21 20:08:19 +00:00
|
|
|
show (length have) ++ " out of " ++ show (fromNumCopies need) ++
|
2011-10-28 21:26:38 +00:00
|
|
|
" necessary copies"
|
|
|
|
Remote.showTriedRemotes bad
|
2015-01-16 17:29:54 +00:00
|
|
|
Remote.showLocations True key (have++skip)
|
2013-01-09 22:53:59 +00:00
|
|
|
"Rather than dropping this file, try using: git annex move"
|
2011-10-28 21:26:38 +00:00
|
|
|
hint
|
|
|
|
return False
|
2012-11-12 05:05:04 +00:00
|
|
|
where
|
|
|
|
unsafe = showNote "unsafe"
|
2014-01-20 20:47:56 +00:00
|
|
|
hint = showLongNote "(Use --force to override this check, or adjust numcopies.)"
|
2013-04-01 19:20:42 +00:00
|
|
|
|
2014-03-29 19:20:55 +00:00
|
|
|
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
|
|
|
|
|
2013-10-28 18:50:17 +00:00
|
|
|
{- In auto mode, only runs the action if there are enough
|
2014-01-21 21:08:49 +00:00
|
|
|
- copies on other semitrusted repositories. -}
|
|
|
|
checkDropAuto :: Maybe Remote -> FilePath -> Key -> (NumCopies -> CommandStart) -> CommandStart
|
2013-04-01 19:20:42 +00:00
|
|
|
checkDropAuto mremote file key a = do
|
2014-01-21 21:08:49 +00:00
|
|
|
numcopies <- getFileNumCopies file
|
|
|
|
Annex.getState Annex.auto >>= auto numcopies
|
2013-04-01 19:20:42 +00:00
|
|
|
where
|
2014-01-21 21:08:49 +00:00
|
|
|
auto numcopies False = a numcopies
|
|
|
|
auto numcopies True = do
|
2013-04-01 19:20:42 +00:00
|
|
|
locs <- Remote.keyLocations key
|
|
|
|
uuid <- getUUID
|
|
|
|
let remoteuuid = fromMaybe uuid $ Remote.uuid <$> mremote
|
|
|
|
locs' <- trustExclude UnTrusted $ filter (/= remoteuuid) locs
|
2014-01-21 21:08:49 +00:00
|
|
|
if NumCopies (length locs') >= numcopies
|
|
|
|
then a numcopies
|
2013-04-01 19:20:42 +00:00
|
|
|
else stop
|