2010-11-15 20:35:06 +00:00
|
|
|
{- git-annex command
|
|
|
|
-
|
|
|
|
- Copyright 2010 Joey Hess <joey@kitenet.net>
|
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
|
|
|
module Command.Unused where
|
|
|
|
|
2011-04-29 17:59:00 +00:00
|
|
|
import Control.Monad (filterM, unless, forM_, when)
|
2010-11-15 22:04:19 +00:00
|
|
|
import Control.Monad.State (liftIO)
|
2011-01-30 05:41:15 +00:00
|
|
|
import qualified Data.Set as S
|
2011-01-16 20:05:05 +00:00
|
|
|
import Data.Maybe
|
2011-01-28 18:10:50 +00:00
|
|
|
import System.FilePath
|
|
|
|
import System.Directory
|
2010-11-15 20:35:06 +00:00
|
|
|
|
|
|
|
import Command
|
|
|
|
import Types
|
2011-01-16 20:05:05 +00:00
|
|
|
import Content
|
2010-11-15 20:35:06 +00:00
|
|
|
import Messages
|
2010-11-15 22:04:19 +00:00
|
|
|
import Locations
|
2011-01-28 16:35:51 +00:00
|
|
|
import Utility
|
2011-04-03 00:59:41 +00:00
|
|
|
import LocationLog
|
2010-11-15 22:04:19 +00:00
|
|
|
import qualified Annex
|
2011-01-16 20:05:05 +00:00
|
|
|
import qualified GitRepo as Git
|
|
|
|
import qualified Backend
|
2011-04-03 00:59:41 +00:00
|
|
|
import qualified Remote
|
2010-11-15 20:35:06 +00:00
|
|
|
|
2010-12-30 19:06:26 +00:00
|
|
|
command :: [Command]
|
2011-03-19 22:58:49 +00:00
|
|
|
command = [repoCommand "unused" paramNothing seek
|
|
|
|
"look for unused file content"]
|
2010-12-30 19:06:26 +00:00
|
|
|
|
2010-12-30 18:19:16 +00:00
|
|
|
seek :: [CommandSeek]
|
2010-11-15 20:35:06 +00:00
|
|
|
seek = [withNothing start]
|
|
|
|
|
|
|
|
{- Finds unused content in the annex. -}
|
2010-12-30 18:19:16 +00:00
|
|
|
start :: CommandStartNothing
|
2011-03-03 20:40:55 +00:00
|
|
|
start = notBareRepo $ do
|
2011-05-29 02:20:22 +00:00
|
|
|
from <- Annex.getState Annex.fromremote
|
2011-05-29 02:37:17 +00:00
|
|
|
let (name, action) = case from of
|
|
|
|
Nothing -> (".", checkUnused)
|
|
|
|
Just "." -> (".", checkUnused)
|
|
|
|
Just n -> (n, checkRemoteUnused n)
|
|
|
|
showStart "unused" name
|
|
|
|
next action
|
2010-11-15 20:35:06 +00:00
|
|
|
|
2011-05-29 02:20:22 +00:00
|
|
|
checkUnused :: CommandPerform
|
2010-11-15 20:35:06 +00:00
|
|
|
checkUnused = do
|
2011-04-29 17:59:00 +00:00
|
|
|
(unused, stalebad, staletmp) <- unusedKeys
|
2011-05-29 02:24:48 +00:00
|
|
|
_ <- list "" unusedMsg unused 0 >>=
|
|
|
|
list "bad" staleBadMsg stalebad >>=
|
|
|
|
list "tmp" staleTmpMsg staletmp
|
2011-05-29 02:20:22 +00:00
|
|
|
next $ return True
|
2011-04-29 17:59:00 +00:00
|
|
|
where
|
|
|
|
list file msg l c = do
|
|
|
|
let unusedlist = number c l
|
2011-06-23 16:23:25 +00:00
|
|
|
when (not $ null l) $ do
|
|
|
|
showLongNote $ msg unusedlist
|
|
|
|
showLongNote $ "\n"
|
2011-04-29 17:59:00 +00:00
|
|
|
writeUnusedFile file unusedlist
|
2011-05-29 02:28:14 +00:00
|
|
|
return $ c + length l
|
2011-01-28 18:10:50 +00:00
|
|
|
|
2011-05-29 02:20:22 +00:00
|
|
|
checkRemoteUnused :: String -> CommandPerform
|
|
|
|
checkRemoteUnused name = do
|
|
|
|
checkRemoteUnused' =<< Remote.byName name
|
|
|
|
next $ return True
|
2011-05-15 06:49:43 +00:00
|
|
|
|
|
|
|
checkRemoteUnused' :: Remote.Remote Annex -> Annex ()
|
|
|
|
checkRemoteUnused' r = do
|
2011-05-29 02:20:22 +00:00
|
|
|
showNote $ "checking for unused data..."
|
2011-04-03 00:59:41 +00:00
|
|
|
referenced <- getKeysReferenced
|
2011-06-23 03:24:14 +00:00
|
|
|
remotehas <- filterM isthere =<< loggedKeys
|
2011-04-03 00:59:41 +00:00
|
|
|
let remoteunused = remotehas `exclude` referenced
|
|
|
|
let list = number 0 remoteunused
|
2011-04-29 17:59:00 +00:00
|
|
|
writeUnusedFile "" list
|
2011-04-03 00:59:41 +00:00
|
|
|
unless (null remoteunused) $ do
|
|
|
|
showLongNote $ remoteUnusedMsg r list
|
|
|
|
showLongNote $ "\n"
|
|
|
|
where
|
|
|
|
isthere k = do
|
2011-06-22 20:13:43 +00:00
|
|
|
us <- keyLocations k
|
2011-04-03 00:59:41 +00:00
|
|
|
return $ uuid `elem` us
|
|
|
|
uuid = Remote.uuid r
|
|
|
|
|
2011-04-29 17:59:00 +00:00
|
|
|
writeUnusedFile :: FilePath -> [(Int, Key)] -> Annex ()
|
|
|
|
writeUnusedFile prefix l = do
|
2011-04-03 00:59:41 +00:00
|
|
|
g <- Annex.gitRepo
|
2011-04-29 17:59:00 +00:00
|
|
|
liftIO $ safeWriteFile (gitAnnexUnusedLog prefix g) $
|
2011-04-03 00:59:41 +00:00
|
|
|
unlines $ map (\(n, k) -> show n ++ " " ++ show k) l
|
|
|
|
|
|
|
|
table :: [(Int, Key)] -> [String]
|
|
|
|
table l = [" NUMBER KEY"] ++ map cols l
|
2010-11-15 20:35:06 +00:00
|
|
|
where
|
2011-03-12 19:30:17 +00:00
|
|
|
cols (n,k) = " " ++ pad 6 (show n) ++ " " ++ show k
|
2010-11-15 22:04:19 +00:00
|
|
|
pad n s = s ++ replicate (n - length s) ' '
|
|
|
|
|
2011-01-28 18:10:50 +00:00
|
|
|
number :: Int -> [a] -> [(Int, a)]
|
2010-11-15 22:04:19 +00:00
|
|
|
number _ [] = []
|
2011-01-28 18:10:50 +00:00
|
|
|
number n (x:xs) = (n+1, x):(number (n+1) xs)
|
2010-11-15 20:35:06 +00:00
|
|
|
|
2011-04-03 00:59:41 +00:00
|
|
|
staleTmpMsg :: [(Int, Key)] -> String
|
|
|
|
staleTmpMsg t = unlines $
|
|
|
|
["Some partially transferred data exists in temporary files:"]
|
|
|
|
++ table t ++ [dropMsg Nothing]
|
2011-04-29 17:59:00 +00:00
|
|
|
|
|
|
|
staleBadMsg :: [(Int, Key)] -> String
|
|
|
|
staleBadMsg t = unlines $
|
|
|
|
["Some corrupted files have been preserved by fsck, just in case:"]
|
|
|
|
++ table t ++ [dropMsg Nothing]
|
|
|
|
|
2011-04-03 00:59:41 +00:00
|
|
|
unusedMsg :: [(Int, Key)] -> String
|
|
|
|
unusedMsg u = unusedMsg' u
|
2011-06-23 16:23:25 +00:00
|
|
|
["Some annexed data is no longer used by any files in the current branch:"]
|
|
|
|
[dropMsg Nothing,
|
|
|
|
"Please be cautious -- are you sure that another branch, or another",
|
|
|
|
"repository does not still use this data?"]
|
2011-04-03 00:59:41 +00:00
|
|
|
|
|
|
|
remoteUnusedMsg :: Remote.Remote Annex -> [(Int, Key)] -> String
|
|
|
|
remoteUnusedMsg r u = unusedMsg' u
|
|
|
|
["Some annexed data on " ++ name ++
|
2011-06-23 16:23:25 +00:00
|
|
|
" is not used by any files in the current branch:"]
|
2011-04-03 00:59:41 +00:00
|
|
|
[dropMsg $ Just r,
|
2011-06-23 16:23:25 +00:00
|
|
|
"Please be cautious -- Are you sure that the remote repository",
|
|
|
|
"does not use this data? Or that it's not used by another branch?"]
|
2011-04-03 00:59:41 +00:00
|
|
|
where
|
|
|
|
name = Remote.name r
|
|
|
|
|
|
|
|
unusedMsg' :: [(Int, Key)] -> [String] -> [String] -> String
|
|
|
|
unusedMsg' u header trailer = unlines $
|
|
|
|
header ++
|
|
|
|
table u ++
|
|
|
|
["(To see where data was previously used, try: git log --stat -S'KEY')"] ++
|
|
|
|
trailer
|
|
|
|
|
|
|
|
dropMsg :: Maybe (Remote.Remote Annex) -> String
|
|
|
|
dropMsg Nothing = dropMsg' ""
|
|
|
|
dropMsg (Just r) = dropMsg' $ " --from " ++ Remote.name r
|
|
|
|
dropMsg' :: String -> String
|
2011-06-23 16:23:25 +00:00
|
|
|
dropMsg' s = "\nTo remove unwanted data: git-annex dropunused" ++ s ++ " NUMBER\n"
|
2011-04-03 00:59:41 +00:00
|
|
|
|
2010-11-15 20:35:06 +00:00
|
|
|
{- Finds keys whose content is present, but that do not seem to be used
|
2011-04-29 17:59:00 +00:00
|
|
|
- by any files in the git repo, or that are only present as bad or tmp
|
|
|
|
- files. -}
|
|
|
|
unusedKeys :: Annex ([Key], [Key], [Key])
|
2010-11-15 20:35:06 +00:00
|
|
|
unusedKeys = do
|
2011-03-22 21:41:06 +00:00
|
|
|
fast <- Annex.getState Annex.fast
|
|
|
|
if fast
|
|
|
|
then do
|
2011-04-29 17:59:00 +00:00
|
|
|
showNote "fast mode enabled; only finding stale files"
|
2011-05-17 01:18:34 +00:00
|
|
|
tmp <- staleKeys gitAnnexTmpDir
|
|
|
|
bad <- staleKeys gitAnnexBadDir
|
2011-04-29 17:59:00 +00:00
|
|
|
return ([], bad, tmp)
|
2011-03-22 21:41:06 +00:00
|
|
|
else do
|
|
|
|
showNote "checking for unused data..."
|
|
|
|
present <- getKeysPresent
|
|
|
|
referenced <- getKeysReferenced
|
2011-04-03 00:59:41 +00:00
|
|
|
let unused = present `exclude` referenced
|
2011-05-17 01:18:34 +00:00
|
|
|
staletmp <- staleKeysPrune gitAnnexTmpDir present
|
|
|
|
stalebad <- staleKeysPrune gitAnnexBadDir present
|
2011-04-29 17:59:00 +00:00
|
|
|
return (unused, stalebad, staletmp)
|
2011-01-28 18:10:50 +00:00
|
|
|
|
2011-04-03 00:59:41 +00:00
|
|
|
{- Finds items in the first, smaller list, that are not
|
|
|
|
- present in the second, larger list.
|
|
|
|
-
|
|
|
|
- Constructing a single set, of the list that tends to be
|
|
|
|
- smaller, appears more efficient in both memory and CPU
|
|
|
|
- than constructing and taking the S.difference of two sets. -}
|
|
|
|
exclude :: Ord a => [a] -> [a] -> [a]
|
|
|
|
exclude [] _ = [] -- optimisation
|
|
|
|
exclude smaller larger = S.toList $ remove larger $ S.fromList smaller
|
2010-11-15 20:35:06 +00:00
|
|
|
where
|
2011-01-30 05:41:15 +00:00
|
|
|
remove a b = foldl (flip S.delete) b a
|
2011-01-16 20:05:05 +00:00
|
|
|
|
|
|
|
{- List of keys referenced by symlinks in the git repo. -}
|
|
|
|
getKeysReferenced :: Annex [Key]
|
|
|
|
getKeysReferenced = do
|
|
|
|
g <- Annex.gitRepo
|
|
|
|
files <- liftIO $ Git.inRepo g [Git.workTree g]
|
|
|
|
keypairs <- mapM Backend.lookupFile files
|
|
|
|
return $ map fst $ catMaybes keypairs
|
2011-01-28 18:10:50 +00:00
|
|
|
|
2011-04-29 17:59:00 +00:00
|
|
|
{- Looks in the specified directory for bad/tmp keys, and returns a list
|
|
|
|
- of those that might still have value, or might be stale and removable.
|
|
|
|
-
|
|
|
|
- When a list of presently available keys is provided, stale keys
|
|
|
|
- that no longer have value are deleted.
|
|
|
|
-}
|
2011-05-17 01:18:34 +00:00
|
|
|
staleKeysPrune :: (Git.Repo -> FilePath) -> [Key] -> Annex [Key]
|
|
|
|
staleKeysPrune dirspec present = do
|
|
|
|
contents <- staleKeys dirspec
|
2011-04-29 17:59:00 +00:00
|
|
|
|
|
|
|
let stale = contents `exclude` present
|
|
|
|
let dup = contents `exclude` stale
|
|
|
|
|
|
|
|
g <- Annex.gitRepo
|
|
|
|
let dir = dirspec g
|
|
|
|
liftIO $ forM_ dup $ \t -> removeFile $ dir </> keyFile t
|
|
|
|
|
|
|
|
return stale
|
|
|
|
|
2011-05-17 01:18:34 +00:00
|
|
|
staleKeys :: (Git.Repo -> FilePath) -> Annex [Key]
|
|
|
|
staleKeys dirspec = do
|
2011-01-28 18:10:50 +00:00
|
|
|
g <- Annex.gitRepo
|
2011-04-29 17:59:00 +00:00
|
|
|
let dir = dirspec g
|
|
|
|
exists <- liftIO $ doesDirectoryExist dir
|
|
|
|
if not exists
|
2011-01-28 18:10:50 +00:00
|
|
|
then return []
|
|
|
|
else do
|
2011-04-29 17:59:00 +00:00
|
|
|
contents <- liftIO $ getDirectoryContents dir
|
2011-01-28 18:10:50 +00:00
|
|
|
files <- liftIO $ filterM doesFileExist $
|
2011-04-29 17:59:00 +00:00
|
|
|
map (dir </>) contents
|
2011-03-16 01:34:13 +00:00
|
|
|
return $ catMaybes $ map (fileKey . takeFileName) files
|