2014-01-19 21:35:36 +00:00
|
|
|
{- dropping of unwanted content
|
|
|
|
-
|
|
|
|
- Copyright 2012-2014 Joey Hess <joey@kitenet.net>
|
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
|
|
|
module Annex.Drop where
|
|
|
|
|
|
|
|
import Common.Annex
|
|
|
|
import Logs.Trust
|
2014-01-21 20:08:19 +00:00
|
|
|
import Logs.NumCopies
|
2014-01-19 21:35:36 +00:00
|
|
|
import Types.Remote (uuid)
|
|
|
|
import qualified Remote
|
|
|
|
import qualified Command.Drop
|
|
|
|
import Command
|
|
|
|
import Annex.Wanted
|
|
|
|
import Annex.Exception
|
|
|
|
import Config
|
|
|
|
import Annex.Content.Direct
|
|
|
|
|
|
|
|
import qualified Data.Set as S
|
|
|
|
import System.Log.Logger (debugM)
|
|
|
|
|
|
|
|
type Reason = String
|
|
|
|
|
|
|
|
{- Drop a key from local and/or remote when allowed by the preferred content
|
|
|
|
- and numcopies settings.
|
|
|
|
-
|
2014-01-20 17:31:03 +00:00
|
|
|
- The UUIDs are ones where the content is believed to be present.
|
|
|
|
- The Remote list can include other remotes that do not have the content;
|
|
|
|
- only ones that match the UUIDs will be dropped from.
|
|
|
|
- If allowed to drop fromhere, that drop will be tried first.
|
2014-01-19 21:35:36 +00:00
|
|
|
-
|
|
|
|
- A remote can be specified that is known to have the key. This can be
|
|
|
|
- used an an optimisation when eg, a key has just been uploaded to a
|
|
|
|
- remote.
|
|
|
|
-
|
|
|
|
- In direct mode, all associated files are checked, and only if all
|
|
|
|
- of them are unwanted are they dropped.
|
2014-01-20 17:31:03 +00:00
|
|
|
-
|
|
|
|
- The runner is used to run commands, and so can be either callCommand
|
|
|
|
- or commandAction.
|
2014-01-19 21:35:36 +00:00
|
|
|
-}
|
2014-01-20 17:31:03 +00:00
|
|
|
handleDropsFrom :: [UUID] -> [Remote] -> Reason -> Bool -> Key -> AssociatedFile -> Maybe Remote -> CommandActionRunner -> Annex ()
|
|
|
|
handleDropsFrom _ _ _ _ _ Nothing _ _ = noop
|
|
|
|
handleDropsFrom locs rs reason fromhere key (Just afile) knownpresentremote runner = do
|
2014-01-19 21:35:36 +00:00
|
|
|
fs <- ifM isDirect
|
|
|
|
( do
|
|
|
|
l <- associatedFilesRelative key
|
|
|
|
if null l
|
|
|
|
then return [afile]
|
|
|
|
else return l
|
|
|
|
, return [afile]
|
|
|
|
)
|
|
|
|
n <- getcopies fs
|
|
|
|
if fromhere && checkcopies n Nothing
|
|
|
|
then go fs rs =<< dropl fs n
|
|
|
|
else go fs rs n
|
|
|
|
where
|
|
|
|
getcopies fs = do
|
|
|
|
(untrusted, have) <- trustPartition UnTrusted locs
|
2014-01-21 21:08:49 +00:00
|
|
|
numcopies <- maximum <$> mapM getFileNumCopies fs
|
2014-01-21 20:08:19 +00:00
|
|
|
return (NumCopies (length have), numcopies, S.fromList untrusted)
|
2014-01-19 21:35:36 +00:00
|
|
|
|
|
|
|
{- Check that we have enough copies still to drop the content.
|
|
|
|
- When the remote being dropped from is untrusted, it was not
|
|
|
|
- counted as a copy, so having only numcopies suffices. Otherwise,
|
|
|
|
- we need more than numcopies to safely drop. -}
|
|
|
|
checkcopies (have, numcopies, _untrusted) Nothing = have > numcopies
|
|
|
|
checkcopies (have, numcopies, untrusted) (Just u)
|
|
|
|
| S.member u untrusted = have >= numcopies
|
|
|
|
| otherwise = have > numcopies
|
|
|
|
|
|
|
|
decrcopies (have, numcopies, untrusted) Nothing =
|
2014-01-21 20:08:19 +00:00
|
|
|
(NumCopies (fromNumCopies have - 1), numcopies, untrusted)
|
2014-01-19 21:35:36 +00:00
|
|
|
decrcopies v@(_have, _numcopies, untrusted) (Just u)
|
|
|
|
| S.member u untrusted = v
|
|
|
|
| otherwise = decrcopies v Nothing
|
|
|
|
|
|
|
|
go _ [] _ = noop
|
|
|
|
go fs (r:rest) n
|
|
|
|
| uuid r `S.notMember` slocs = go fs rest n
|
|
|
|
| checkcopies n (Just $ Remote.uuid r) =
|
|
|
|
dropr fs r n >>= go fs rest
|
|
|
|
| otherwise = noop
|
|
|
|
|
|
|
|
checkdrop fs n@(have, numcopies, _untrusted) u a =
|
|
|
|
ifM (allM (wantDrop True u . Just) fs)
|
2014-01-21 21:08:49 +00:00
|
|
|
( ifM (safely $ runner $ a numcopies)
|
2014-01-19 21:35:36 +00:00
|
|
|
( do
|
|
|
|
liftIO $ debugM "drop" $ unwords
|
|
|
|
[ "dropped"
|
|
|
|
, afile
|
|
|
|
, "(from " ++ maybe "here" show u ++ ")"
|
2014-01-21 20:08:19 +00:00
|
|
|
, "(copies now " ++ show (fromNumCopies have - 1) ++ ")"
|
2014-01-19 21:35:36 +00:00
|
|
|
, ": " ++ reason
|
|
|
|
]
|
|
|
|
return $ decrcopies n u
|
|
|
|
, return n
|
|
|
|
)
|
|
|
|
, return n
|
|
|
|
)
|
|
|
|
|
|
|
|
dropl fs n = checkdrop fs n Nothing $ \numcopies ->
|
|
|
|
Command.Drop.startLocal (Just afile) numcopies key knownpresentremote
|
|
|
|
|
|
|
|
dropr fs r n = checkdrop fs n (Just $ Remote.uuid r) $ \numcopies ->
|
|
|
|
Command.Drop.startRemote (Just afile) numcopies key r
|
|
|
|
|
2014-01-20 17:31:03 +00:00
|
|
|
slocs = S.fromList locs
|
|
|
|
|
2014-01-19 21:35:36 +00:00
|
|
|
safely a = either (const False) id <$> tryAnnex a
|
|
|
|
|