git-annex/Assistant/Drop.hs

88 lines
2.6 KiB
Haskell
Raw Normal View History

2012-10-18 19:22:28 +00:00
{- git-annex assistant dropping of unwanted content
-
- Copyright 2012 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Assistant.Drop where
import Assistant.Common
import Assistant.DaemonStatus
2012-10-18 19:22:28 +00:00
import Logs.Location
import Logs.Trust
import Types.Remote (AssociatedFile, uuid)
2012-10-18 19:22:28 +00:00
import qualified Remote
import qualified Command.Drop
import Command
import Annex.Wanted
import Annex.Exception
2012-10-18 19:22:28 +00:00
import Config
import qualified Data.Set as S
type Reason = String
2012-10-18 20:05:43 +00:00
{- Drop from local and/or remote when allowed by the preferred content and
2012-12-05 16:32:26 +00:00
- numcopies settings. -}
handleDrops :: Reason -> Bool -> Key -> AssociatedFile -> Maybe Remote -> Assistant ()
handleDrops _ _ _ Nothing _ = noop
handleDrops reason fromhere key f knownpresentremote = do
syncrs <- syncDataRemotes <$> getDaemonStatus
locs <- liftAnnex $ loggedLocations key
handleDropsFrom locs syncrs reason fromhere key f knownpresentremote
2012-10-18 19:22:28 +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 allows to drop fromhere, that drop will be tried first. -}
handleDropsFrom :: [UUID] -> [Remote] -> Reason -> Bool -> Key -> AssociatedFile -> Maybe Remote -> Assistant ()
handleDropsFrom _ _ _ _ _ Nothing _ = noop
handleDropsFrom locs rs reason fromhere key (Just f) knownpresentremote
| fromhere = do
2012-10-18 19:22:28 +00:00
n <- getcopies
if checkcopies n
then go rs =<< dropl n
else go rs n
| otherwise = go rs =<< getcopies
2012-10-31 06:34:03 +00:00
where
getcopies = liftAnnex $ do
2012-11-11 04:26:29 +00:00
have <- length <$> trustExclude UnTrusted locs
2012-10-31 06:34:03 +00:00
numcopies <- getNumCopies =<< numCopies f
return (have, numcopies)
checkcopies (have, numcopies) = have > numcopies
decrcopies (have, numcopies) = (have - 1, numcopies)
2012-10-18 19:22:28 +00:00
2012-10-31 06:34:03 +00:00
go [] _ = noop
go (r:rest) n
| uuid r `S.notMember` slocs = go rest n
2012-10-31 06:34:03 +00:00
| checkcopies n = dropr r n >>= go rest
| otherwise = noop
2012-10-18 19:22:28 +00:00
checkdrop n@(have, numcopies) u a =
ifM (liftAnnex $ wantDrop True u (Just f))
( ifM (liftAnnex $ safely $ doCommand $ a (Just numcopies))
( do
debug
[ "dropped"
, f
, "(from" ++ maybe "here" show u ++ ")"
, "(copies now " ++ show (have - 1) ++ ")"
, ": " ++ reason
]
return $ decrcopies n
, return n
)
2012-10-31 06:34:03 +00:00
, return n
)
2012-10-18 19:22:28 +00:00
2012-10-31 06:34:03 +00:00
dropl n = checkdrop n Nothing $ \numcopies ->
2012-11-24 20:30:15 +00:00
Command.Drop.startLocal f numcopies key knownpresentremote
2012-10-18 19:22:28 +00:00
2012-10-31 06:34:03 +00:00
dropr r n = checkdrop n (Just $ Remote.uuid r) $ \numcopies ->
Command.Drop.startRemote f numcopies key r
safely a = either (const False) id <$> tryAnnex a
slocs = S.fromList locs