add additional debug info about reasons for drops
This commit is contained in:
parent
3c9cb4f05b
commit
a733271a9c
5 changed files with 40 additions and 24 deletions
|
@ -21,23 +21,24 @@ import Config
|
||||||
|
|
||||||
import qualified Data.Set as S
|
import qualified Data.Set as S
|
||||||
|
|
||||||
|
type Reason = String
|
||||||
|
|
||||||
{- Drop from local and/or remote when allowed by the preferred content and
|
{- Drop from local and/or remote when allowed by the preferred content and
|
||||||
- numcopies settings. -}
|
- numcopies settings. -}
|
||||||
handleDrops :: Bool -> Key -> AssociatedFile -> Maybe Remote -> Assistant ()
|
handleDrops :: Reason -> Bool -> Key -> AssociatedFile -> Maybe Remote -> Assistant ()
|
||||||
handleDrops _ _ Nothing _ = noop
|
handleDrops _ _ _ Nothing _ = noop
|
||||||
handleDrops fromhere key f knownpresentremote = do
|
handleDrops reason fromhere key f knownpresentremote = do
|
||||||
syncrs <- syncDataRemotes <$> getDaemonStatus
|
syncrs <- syncDataRemotes <$> getDaemonStatus
|
||||||
liftAnnex $ do
|
locs <- liftAnnex $ loggedLocations key
|
||||||
locs <- loggedLocations key
|
handleDropsFrom locs syncrs reason fromhere key f knownpresentremote
|
||||||
handleDropsFrom locs syncrs fromhere key f knownpresentremote
|
|
||||||
|
|
||||||
{- The UUIDs are ones where the content is believed to be present.
|
{- 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;
|
- The Remote list can include other remotes that do not have the content;
|
||||||
- only ones that match the UUIDs will be dropped from.
|
- only ones that match the UUIDs will be dropped from.
|
||||||
- If allows to drop fromhere, that drop will be tried first. -}
|
- If allows to drop fromhere, that drop will be tried first. -}
|
||||||
handleDropsFrom :: [UUID] -> [Remote] -> Bool -> Key -> AssociatedFile -> Maybe Remote -> Annex ()
|
handleDropsFrom :: [UUID] -> [Remote] -> Reason -> Bool -> Key -> AssociatedFile -> Maybe Remote -> Assistant ()
|
||||||
handleDropsFrom _ _ _ _ Nothing _ = noop
|
handleDropsFrom _ _ _ _ _ Nothing _ = noop
|
||||||
handleDropsFrom locs rs fromhere key (Just f) knownpresentremote
|
handleDropsFrom locs rs reason fromhere key (Just f) knownpresentremote
|
||||||
| fromhere = do
|
| fromhere = do
|
||||||
n <- getcopies
|
n <- getcopies
|
||||||
if checkcopies n
|
if checkcopies n
|
||||||
|
@ -45,7 +46,7 @@ handleDropsFrom locs rs fromhere key (Just f) knownpresentremote
|
||||||
else go rs n
|
else go rs n
|
||||||
| otherwise = go rs =<< getcopies
|
| otherwise = go rs =<< getcopies
|
||||||
where
|
where
|
||||||
getcopies = do
|
getcopies = liftAnnex $ do
|
||||||
have <- length <$> trustExclude UnTrusted locs
|
have <- length <$> trustExclude UnTrusted locs
|
||||||
numcopies <- getNumCopies =<< numCopies f
|
numcopies <- getNumCopies =<< numCopies f
|
||||||
return (have, numcopies)
|
return (have, numcopies)
|
||||||
|
@ -58,13 +59,22 @@ handleDropsFrom locs rs fromhere key (Just f) knownpresentremote
|
||||||
| checkcopies n = dropr r n >>= go rest
|
| checkcopies n = dropr r n >>= go rest
|
||||||
| otherwise = noop
|
| otherwise = noop
|
||||||
|
|
||||||
checkdrop n@(_, numcopies) u a = ifM (wantDrop True u (Just f))
|
checkdrop n@(have, numcopies) u a =
|
||||||
( ifM (safely $ doCommand $ a (Just numcopies))
|
ifM (liftAnnex $ wantDrop True u (Just f))
|
||||||
( return $ decrcopies n
|
( 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
|
||||||
|
)
|
||||||
, return n
|
, return n
|
||||||
)
|
)
|
||||||
, return n
|
|
||||||
)
|
|
||||||
|
|
||||||
dropl n = checkdrop n Nothing $ \numcopies ->
|
dropl n = checkdrop n Nothing $ \numcopies ->
|
||||||
Command.Drop.startLocal f numcopies key knownpresentremote
|
Command.Drop.startLocal f numcopies key knownpresentremote
|
||||||
|
|
|
@ -115,12 +115,12 @@ expensiveScan rs = unless onlyweb $ do
|
||||||
{- The syncable remotes may have changed since this
|
{- The syncable remotes may have changed since this
|
||||||
- scan began. -}
|
- scan began. -}
|
||||||
syncrs <- syncDataRemotes <$> getDaemonStatus
|
syncrs <- syncDataRemotes <$> getDaemonStatus
|
||||||
|
locs <- liftAnnex $ loggedLocations key
|
||||||
|
present <- liftAnnex $ inAnnex key
|
||||||
|
handleDropsFrom locs syncrs
|
||||||
|
"expensive scan found too many copies of object"
|
||||||
|
present key (Just f) Nothing
|
||||||
liftAnnex $ do
|
liftAnnex $ do
|
||||||
locs <- loggedLocations key
|
|
||||||
present <- inAnnex key
|
|
||||||
|
|
||||||
handleDropsFrom locs syncrs present key (Just f) Nothing
|
|
||||||
|
|
||||||
let slocs = S.fromList locs
|
let slocs = S.fromList locs
|
||||||
let use a = return $ catMaybes $ map (a key slocs) syncrs
|
let use a = return $ catMaybes $ map (a key slocs) syncrs
|
||||||
if present
|
if present
|
||||||
|
|
|
@ -115,10 +115,14 @@ finishedTransfer :: Transfer -> Maybe TransferInfo -> Assistant ()
|
||||||
finishedTransfer t (Just info)
|
finishedTransfer t (Just info)
|
||||||
| transferDirection t == Download =
|
| transferDirection t == Download =
|
||||||
whenM (liftAnnex $ inAnnex $ transferKey t) $ do
|
whenM (liftAnnex $ inAnnex $ transferKey t) $ do
|
||||||
handleDrops False (transferKey t) (associatedFile info) Nothing
|
dodrops False
|
||||||
queueTransfersMatching (/= transferUUID t)
|
queueTransfersMatching (/= transferUUID t)
|
||||||
"newly received object"
|
"newly received object"
|
||||||
Later (transferKey t) (associatedFile info) Upload
|
Later (transferKey t) (associatedFile info) Upload
|
||||||
| otherwise = handleDrops True (transferKey t) (associatedFile info) Nothing
|
| otherwise = dodrops True
|
||||||
|
where
|
||||||
|
dodrops fromhere = handleDrops
|
||||||
|
("drop wanted after " ++ describeTransfer t info)
|
||||||
|
fromhere (transferKey t) (associatedFile info) Nothing
|
||||||
finishedTransfer _ _ = noop
|
finishedTransfer _ _ = noop
|
||||||
|
|
||||||
|
|
|
@ -76,7 +76,9 @@ startTransfer program t info = case (transferRemote info, associatedFile info) o
|
||||||
void $ addAlert $ makeAlertFiller True $
|
void $ addAlert $ makeAlertFiller True $
|
||||||
transferFileAlert direction True file
|
transferFileAlert direction True file
|
||||||
unless isdownload $
|
unless isdownload $
|
||||||
handleDrops True (transferKey t)
|
handleDrops
|
||||||
|
("object uploaded to " ++ show remote)
|
||||||
|
True (transferKey t)
|
||||||
(associatedFile info)
|
(associatedFile info)
|
||||||
(Just remote)
|
(Just remote)
|
||||||
recordCommit
|
recordCommit
|
||||||
|
|
|
@ -254,7 +254,7 @@ onAddSymlink file filestatus = go =<< liftAnnex (Backend.lookupFile file)
|
||||||
if present
|
if present
|
||||||
then queueTransfers "new file created" Next key (Just file) Upload
|
then queueTransfers "new file created" Next key (Just file) Upload
|
||||||
else queueTransfers "new or renamed file wanted" Next key (Just file) Download
|
else queueTransfers "new or renamed file wanted" Next key (Just file) Download
|
||||||
handleDrops present key (Just file) Nothing
|
handleDrops "file renamed" present key (Just file) Nothing
|
||||||
| otherwise = noop
|
| otherwise = noop
|
||||||
|
|
||||||
onDel :: Handler
|
onDel :: Handler
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue