status: In --fast mode, all status info is displayed now; but some of it is only approximate, and is marked as such.

This commit is contained in:
Joey Hess 2011-09-20 18:13:08 -04:00
parent b62123c378
commit cabbefd9d2
3 changed files with 36 additions and 28 deletions

View file

@ -23,13 +23,15 @@ import qualified Git
import Command import Command
import Types import Types
import Utility.DataUnits import Utility.DataUnits
import Utility.Conditional
import Content import Content
import Types.Key import Types.Key
import Locations import Locations
import Backend import Backend
import Messages
-- a named computation that produces a statistic -- a named computation that produces a statistic
type Stat = StatState (Maybe (String, StatState String)) type Stat = StatState (Maybe (String, Bool, StatState String))
-- cached info that multiple Stats may need -- cached info that multiple Stats may need
data StatInfo = StatInfo data StatInfo = StatInfo
@ -58,16 +60,13 @@ seek = [withNothing start]
{- Order is significant. Less expensive operations, and operations {- Order is significant. Less expensive operations, and operations
- that share data go together. - that share data go together.
-} -}
faststats :: [Stat] stats :: [Stat]
faststats = stats =
[ supported_backends [ supported_backends
, supported_remote_types , supported_remote_types
, tmp_size , tmp_size
, bad_data_size , bad_data_size
] , local_annex_keys
slowstats :: [Stat]
slowstats =
[ local_annex_keys
, local_annex_size , local_annex_size
, total_annex_keys , total_annex_keys
, total_annex_size , total_annex_size
@ -76,13 +75,16 @@ slowstats =
start :: CommandStart start :: CommandStart
start = do start = do
fast <- Annex.getState Annex.fast evalStateT (mapM_ showStat stats) (StatInfo Nothing Nothing)
let todo = if fast then faststats else faststats ++ slowstats fastmode_note
evalStateT (mapM_ showStat todo) (StatInfo Nothing Nothing)
stop stop
stat :: String -> StatState String -> Stat fastmode_note :: Annex ()
stat desc a = return $ Just (desc, a) fastmode_note = whenM (Annex.getState Annex.fast) $
showLongNote "(*) approximate due to fast mode"
stat :: String -> Bool -> StatState String -> Stat
stat desc approx a = return $ Just (desc, approx, a)
nostat :: Stat nostat :: Stat
nostat = return Nothing nostat = return Nothing
@ -90,33 +92,37 @@ nostat = return Nothing
showStat :: Stat -> StatState () showStat :: Stat -> StatState ()
showStat s = calc =<< s showStat s = calc =<< s
where where
calc (Just (desc, a)) = do calc (Just (desc, approx, a)) = do
liftIO $ putStr $ desc ++ ": " fast <- lift $ Annex.getState Annex.fast
let star = if fast && approx then "(*)" else ""
liftIO $ putStr $ desc ++ star ++ ": "
liftIO $ hFlush stdout liftIO $ hFlush stdout
liftIO . putStrLn =<< a liftIO . putStrLn =<< a
calc Nothing = return () calc Nothing = return ()
supported_backends :: Stat supported_backends :: Stat
supported_backends = stat "supported backends" $ supported_backends = stat "supported backends" False $
return $ unwords $ map B.name Backend.list return $ unwords $ map B.name Backend.list
supported_remote_types :: Stat supported_remote_types :: Stat
supported_remote_types = stat "supported remote types" $ supported_remote_types = stat "supported remote types" False $
return $ unwords $ map R.typename Remote.remoteTypes return $ unwords $ map R.typename Remote.remoteTypes
local_annex_size :: Stat local_annex_size :: Stat
local_annex_size = stat "local annex size" $ local_annex_size = stat "local annex size" False $
cachedKeysPresent >>= keySizeSum cachedKeysPresent >>= keySizeSum
total_annex_size :: Stat total_annex_size :: Stat
total_annex_size = stat "total annex size" $ total_annex_size = stat "total annex size" True $
cachedKeysReferenced >>= keySizeSum cachedKeysReferenced >>= keySizeSum
local_annex_keys :: Stat local_annex_keys :: Stat
local_annex_keys = stat "local annex keys" $ show . snd <$> cachedKeysPresent local_annex_keys = stat "local annex keys" False $
show . snd <$> cachedKeysPresent
total_annex_keys :: Stat total_annex_keys :: Stat
total_annex_keys = stat "total annex keys" $ show . snd <$> cachedKeysReferenced total_annex_keys = stat "total annex keys" True $
show . snd <$> cachedKeysReferenced
tmp_size :: Stat tmp_size :: Stat
tmp_size = staleSize "temporary directory size" gitAnnexTmpDir tmp_size = staleSize "temporary directory size" gitAnnexTmpDir
@ -125,7 +131,7 @@ bad_data_size :: Stat
bad_data_size = staleSize "bad keys size" gitAnnexBadDir bad_data_size = staleSize "bad keys size" gitAnnexBadDir
backend_usage :: Stat backend_usage :: Stat
backend_usage = stat "backend usage" $ usage <$> cachedKeysReferenced backend_usage = stat "backend usage" True $ usage <$> cachedKeysReferenced
where where
usage (ks, _) = pp "" $ sort $ map swap $ splits ks usage (ks, _) = pp "" $ sort $ map swap $ splits ks
splits :: [Key] -> [(String, Integer)] splits :: [Key] -> [(String, Integer)]
@ -135,7 +141,6 @@ backend_usage = stat "backend usage" $ usage <$> cachedKeysReferenced
pp c [] = c pp c [] = c
pp c ((n, b):xs) = "\n\t" ++ b ++ ": " ++ show n ++ pp c xs pp c ((n, b):xs) = "\n\t" ++ b ++ ": " ++ show n ++ pp c xs
cachedKeysPresent :: StatState (SizeList Key) cachedKeysPresent :: StatState (SizeList Key)
cachedKeysPresent = do cachedKeysPresent = do
s <- get s <- get
@ -153,10 +158,11 @@ cachedKeysReferenced = do
case keysReferencedCache s of case keysReferencedCache s of
Just v -> return v Just v -> return v
Nothing -> do Nothing -> do
-- A given key may be referenced repeatedly,
-- so nub is needed for accuracy, but is slow.
keys <- lift Command.Unused.getKeysReferenced keys <- lift Command.Unused.getKeysReferenced
-- A given key may be referenced repeatedly. fast <- lift $ Annex.getState Annex.fast
-- nub does not seem too slow (yet).. let v = sizeList $ if fast then keys else nub keys
let v = sizeList $ nub keys
put s { keysReferencedCache = Just v } put s { keysReferencedCache = Just v }
return v return v
@ -175,7 +181,7 @@ staleSize label dirspec = do
keys <- lift (Command.Unused.staleKeys dirspec) keys <- lift (Command.Unused.staleKeys dirspec)
if null keys if null keys
then nostat then nostat
else stat label $ do else stat label False $ do
s <- keySizeSum $ sizeList keys s <- keySizeSum $ sizeList keys
return $ s ++ aside "clean up with git-annex unused" return $ s ++ aside "clean up with git-annex unused"

2
debian/changelog vendored
View file

@ -12,6 +12,8 @@ git-annex (3.20110916) UNRELEASED; urgency=low
match the specified conditions. match the specified conditions.
* Note that this is a behavior change for git-annex find! Old behavior * Note that this is a behavior change for git-annex find! Old behavior
can be gotten by using: git-annex find --in . can be gotten by using: git-annex find --in .
* status: In --fast mode, all status info is displayed now; but some
of it is only approximate, and is marked as such.
-- Joey Hess <joeyh@debian.org> Sun, 18 Sep 2011 18:25:51 -0400 -- Joey Hess <joeyh@debian.org> Sun, 18 Sep 2011 18:25:51 -0400

View file

@ -240,8 +240,8 @@ subdirectories).
Some of the statistics can take a while to generate, and those Some of the statistics can take a while to generate, and those
come last. You can ctrl-c this command once it's displayed the come last. You can ctrl-c this command once it's displayed the
information you wanted to see. Or, use --fast to only display information you wanted to see. Or, use --fast to produce statistics
the first, fast(ish) statistics. more quickly, but possibly less accurately.
* map * map