summaryrefslogtreecommitdiff
path: root/Command/DropUnused.hs
diff options
context:
space:
mode:
authorGravatar Joey Hess <joey@kitenet.net>2012-05-02 14:59:05 -0400
committerGravatar Joey Hess <joey@kitenet.net>2012-05-02 14:59:05 -0400
commit392931eca9191117ae5c9d479fabab1e8ecaf8df (patch)
treedcddce458b701d795c8b3ef7385ad955301c9ac0 /Command/DropUnused.hs
parent7d6b36dffbb11837a6fcfea3317b7d24ccbeeff7 (diff)
addunused: New command, the opposite of dropunused, it relinks unused content into the git repository.
Diffstat (limited to 'Command/DropUnused.hs')
-rw-r--r--Command/DropUnused.hs60
1 files changed, 5 insertions, 55 deletions
diff --git a/Command/DropUnused.hs b/Command/DropUnused.hs
index 9c9513ca9..a94c2873d 100644
--- a/Command/DropUnused.hs
+++ b/Command/DropUnused.hs
@@ -7,8 +7,7 @@
module Command.DropUnused where
-import qualified Data.Map as M
-
+import Logs.Unused
import Common.Annex
import Command
import qualified Annex
@@ -16,50 +15,17 @@ import qualified Command.Drop
import qualified Remote
import qualified Git
import qualified Option
-import Types.Key
-
-type UnusedMap = M.Map Integer 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)) $
- concatMap unusedSpec params
-
-unusedSpec :: String -> [Integer]
-unusedSpec spec
- | "-" `isInfixOf` spec = range $ separate (== '-') spec
- | otherwise = catMaybes [readish spec]
- where
- range (a, b) = case (readish a, readish b) of
- (Just x, Just y) -> [x..y]
- _ -> []
+seek = [withUnusedMaps start]
-start :: (UnusedMap, UnusedMap, UnusedMap) -> Integer -> CommandStart
-start (unused, unusedbad, unusedtmp) n = search
- [ (unused, perform)
- , (unusedbad, performOther gitAnnexBadLocation)
- , (unusedtmp, performOther gitAnnexTmpLocation)
- ]
- where
- search [] = stop
- search ((m, a):rest) =
- case M.lookup n m of
- Nothing -> search rest
- Just key -> do
- showStart "dropunused" (show n)
- 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
@@ -76,19 +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
- ifM (liftIO $ doesFileExist f)
- ( M.fromList . catMaybes . map parse . lines
- <$> liftIO (readFile f)
- , return M.empty
- )
- where
- parse line =
- case (readish tag, readKey rest) of
- (Just num, Just key) -> Just (num, key)
- _ -> Nothing
- where
- (tag, rest) = separate (== ' ') line