aboutsummaryrefslogtreecommitdiff
path: root/Command/DropUnused.hs
diff options
context:
space:
mode:
Diffstat (limited to 'Command/DropUnused.hs')
-rw-r--r--Command/DropUnused.hs48
1 files changed, 6 insertions, 42 deletions
diff --git a/Command/DropUnused.hs b/Command/DropUnused.hs
index 0b2a60216..a94c2873d 100644
--- a/Command/DropUnused.hs
+++ b/Command/DropUnused.hs
@@ -1,14 +1,13 @@
{- git-annex command
-
- - Copyright 2010 Joey Hess <joey@kitenet.net>
+ - Copyright 2010,2012 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Command.DropUnused where
-import qualified Data.Map as M
-
+import Logs.Unused
import Common.Annex
import Command
import qualified Annex
@@ -16,40 +15,17 @@ import qualified Command.Drop
import qualified Remote
import qualified Git
import qualified Option
-import Types.Key
-
-type UnusedMap = M.Map String Key
def :: [Command]
def = [withOptions [Command.Drop.fromOption] $
- command "dropunused" (paramRepeating paramNumber)
+ command "dropunused" (paramRepeating paramNumRange)
seek "drop unused file content"]
seek :: [CommandSeek]
-seek = [withUnusedMaps]
-
-{- Read unused logs once, and pass the maps to each start action. -}
-withUnusedMaps :: CommandSeek
-withUnusedMaps params = do
- unused <- readUnusedLog ""
- unusedbad <- readUnusedLog "bad"
- unusedtmp <- readUnusedLog "tmp"
- return $ map (start (unused, unusedbad, unusedtmp)) params
+seek = [withUnusedMaps start]
-start :: (UnusedMap, UnusedMap, UnusedMap) -> FilePath -> CommandStart
-start (unused, unusedbad, unusedtmp) s = search
- [ (unused, perform)
- , (unusedbad, performOther gitAnnexBadLocation)
- , (unusedtmp, performOther gitAnnexTmpLocation)
- ]
- where
- search [] = stop
- search ((m, a):rest) =
- case M.lookup s m of
- Nothing -> search rest
- Just key -> do
- showStart "dropunused" s
- next $ a key
+start :: UnusedMaps -> Int -> CommandStart
+start = startUnused "dropunused" perform (performOther gitAnnexBadLocation) (performOther gitAnnexTmpLocation)
perform :: Key -> CommandPerform
perform key = maybe droplocal dropremote =<< Remote.byName =<< from
@@ -66,15 +42,3 @@ performOther filespec key = do
f <- fromRepo $ filespec key
liftIO $ whenM (doesFileExist f) $ removeFile f
next $ return True
-
-readUnusedLog :: FilePath -> Annex UnusedMap
-readUnusedLog prefix = do
- f <- fromRepo $ gitAnnexUnusedLog prefix
- e <- liftIO $ doesFileExist f
- if e
- then M.fromList . map parse . lines <$> liftIO (readFile f)
- else return M.empty
- where
- parse line = (num, fromJust $ readKey rest)
- where
- (num, rest) = separate (== ' ') line