summaryrefslogtreecommitdiff
path: root/Command
diff options
context:
space:
mode:
Diffstat (limited to 'Command')
-rw-r--r--Command/AddUnused.hs34
-rw-r--r--Command/DropUnused.hs60
-rw-r--r--Command/Unused.hs10
3 files changed, 41 insertions, 63 deletions
diff --git a/Command/AddUnused.hs b/Command/AddUnused.hs
new file mode 100644
index 000000000..c498216dc
--- /dev/null
+++ b/Command/AddUnused.hs
@@ -0,0 +1,34 @@
+{- git-annex command
+ -
+ - Copyright 2012 Joey Hess <joey@kitenet.net>
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+module Command.AddUnused where
+
+import Common.Annex
+import Logs.Unused
+import Command
+import qualified Command.Add
+
+def :: [Command]
+def = [command "addunused" (paramRepeating paramNumRange)
+ seek "add back unused files"]
+
+seek :: [CommandSeek]
+seek = [withUnusedMaps start]
+
+start :: UnusedMaps -> Int -> CommandStart
+start = startUnused "addunused" perform (performOther "bad") (performOther "tmp")
+
+perform :: Key -> CommandPerform
+perform key = next $ Command.Add.cleanup file key True
+ where
+ file = "unused." ++ show key
+
+{- The content is not in the annex, but in another directory, and
+ - it seems better to error out, rather than moving bad/tmp content into
+ - the annex. -}
+performOther :: String -> Key -> CommandPerform
+performOther other _ = error $ "cannot addunused " ++ otherĀ ++ "content"
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
diff --git a/Command/Unused.hs b/Command/Unused.hs
index 5bdadcf44..6b319ee72 100644
--- a/Command/Unused.hs
+++ b/Command/Unused.hs
@@ -19,9 +19,9 @@ import Control.Monad.ST
import Common.Annex
import Command
+import Logs.Unused
import Annex.Content
import Utility.FileMode
-import Utility.TempFile
import Logs.Location
import Config
import qualified Annex
@@ -91,19 +91,13 @@ check file msg a c = do
l <- a
let unusedlist = number c l
unless (null l) $ showLongNote $ msg unusedlist
- writeUnusedFile file unusedlist
+ writeUnusedLog file unusedlist
return $ c + length l
number :: Int -> [a] -> [(Int, a)]
number _ [] = []
number n (x:xs) = (n+1, x) : number (n+1) xs
-writeUnusedFile :: FilePath -> [(Int, Key)] -> Annex ()
-writeUnusedFile prefix l = do
- logfile <- fromRepo $ gitAnnexUnusedLog prefix
- liftIO $ viaTmp writeFile logfile $
- unlines $ map (\(n, k) -> show n ++ " " ++ show k) l
-
table :: [(Int, Key)] -> [String]
table l = " NUMBER KEY" : map cols l
where