summaryrefslogtreecommitdiff
path: root/Assistant/Drop.hs
diff options
context:
space:
mode:
authorGravatar Joey Hess <joey@kitenet.net>2012-10-18 15:22:28 -0400
committerGravatar Joey Hess <joey@kitenet.net>2012-10-18 15:22:28 -0400
commit3e369ace228e984224c417c6f3524f0b4f5900ac (patch)
tree01811ab6f0a1d49bd83a66ddbe556c0406fa81e8 /Assistant/Drop.hs
parentb9138b54db85610ce16d31ef1d1e74c18ee25b87 (diff)
split
Diffstat (limited to 'Assistant/Drop.hs')
-rw-r--r--Assistant/Drop.hs60
1 files changed, 60 insertions, 0 deletions
diff --git a/Assistant/Drop.hs b/Assistant/Drop.hs
new file mode 100644
index 000000000..b3dca3929
--- /dev/null
+++ b/Assistant/Drop.hs
@@ -0,0 +1,60 @@
+{- 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 Logs.Location
+import Logs.Trust
+import qualified Remote
+import qualified Command.Drop
+import Command
+import Annex.Wanted
+import Config
+
+{- Drop from local or remote when allowed by the preferred content and
+ - numcopies settings. -}
+handleDrops :: [Remote] -> Bool -> FilePath -> Key -> Annex ()
+handleDrops rs present f key = do
+ locs <- loggedLocations key
+ handleDrops' locs rs present f key
+
+handleDrops' :: [UUID] -> [Remote] -> Bool -> FilePath -> Key -> Annex ()
+handleDrops' locs rs present f key
+ | present = do
+ n <- getcopies
+ if checkcopies n
+ then go rs =<< dropl n
+ else go rs n
+ | otherwise = go rs =<< getcopies
+ where
+ getcopies = do
+ have <- length . snd <$> trustPartition UnTrusted locs
+ numcopies <- getNumCopies =<< numCopies f
+ return (have, numcopies)
+ checkcopies (have, numcopies) = have > numcopies
+ decrcopies (have, numcopies) = (have - 1, numcopies)
+
+ go [] _ = noop
+ go (r:rest) n
+ | checkcopies n = dropr r n >>= go rest
+ | otherwise = noop
+
+ checkdrop n@(_, numcopies) u a =
+ ifM (wantDrop u (Just f))
+ ( ifM (doCommand $ a (Just numcopies))
+ ( return $ decrcopies n
+ , return n
+ )
+ , return n
+ )
+
+ dropl n = checkdrop n Nothing $ \numcopies ->
+ Command.Drop.startLocal f numcopies key
+
+ dropr r n = checkdrop n (Just $ Remote.uuid r) $ \numcopies ->
+ Command.Drop.startRemote f numcopies key r