info: Added json output for "backend usage", "numcopies stats", "repositories containing these files", and "transfers in progress".

This commit is contained in:
Joey Hess 2015-06-16 13:50:28 -04:00
parent c96b333869
commit 67f7f1b1cb
5 changed files with 94 additions and 44 deletions

View file

@ -5,7 +5,7 @@
- Licensed under the GNU GPL version 3 or higher. - Licensed under the GNU GPL version 3 or higher.
-} -}
{-# LANGUAGE BangPatterns #-} {-# LANGUAGE BangPatterns, DeriveDataTypeable #-}
module Command.Info where module Command.Info where
@ -38,6 +38,7 @@ import Logs.Transfer
import Types.TrustLevel import Types.TrustLevel
import Types.FileMatcher import Types.FileMatcher
import qualified Limit import qualified Limit
import Messages.JSON (DualDisp(..))
-- 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, StatState String))
@ -59,8 +60,8 @@ newtype Variance = Variance Int
instance Show Variance where instance Show Variance where
show (Variance n) show (Variance n)
| n >= 0 = "numcopies +" ++ show n | n >= 0 = "+" ++ show n
| otherwise = "numcopies " ++ show n | otherwise = show n
-- cached info that multiple Stats use -- cached info that multiple Stats use
data StatInfo = StatInfo data StatInfo = StatInfo
@ -221,10 +222,10 @@ nostat :: Stat
nostat = return Nothing nostat = return Nothing
json :: JSON j => (j -> String) -> StatState j -> String -> StatState String json :: JSON j => (j -> String) -> StatState j -> String -> StatState String
json serialize a desc = do json fmt a desc = do
j <- a j <- a
lift $ maybeShowJSON [(desc, j)] lift $ maybeShowJSON [(desc, j)]
return $ serialize j return $ fmt j
nojson :: StatState String -> String -> StatState String nojson :: StatState String -> String -> StatState String
nojson a _ = a nojson a _ = a
@ -251,11 +252,16 @@ repo_list level = stat n $ nojson $ lift $ do
us <- filter (/= NoUUID) . M.keys us <- filter (/= NoUUID) . M.keys
<$> (M.union <$> uuidMap <*> remoteMap Remote.name) <$> (M.union <$> uuidMap <*> remoteMap Remote.name)
rs <- fst <$> trustPartition level us rs <- fst <$> trustPartition level us
s <- prettyPrintUUIDs n rs countRepoList (length rs)
return $ if null s then "0" else show (length rs) ++ "\n" ++ beginning s -- This also handles json display.
<$> prettyPrintUUIDs n rs
where where
n = showTrustLevel level ++ " repositories" n = showTrustLevel level ++ " repositories"
countRepoList :: Int -> String -> String
countRepoList _ [] = "0"
countRepoList n s = show n ++ "\n" ++ beginning s
dir_name :: FilePath -> Stat dir_name :: FilePath -> Stat
dir_name dir = simpleStat "directory" $ pure dir dir_name dir = simpleStat "directory" $ pure dir
@ -339,14 +345,16 @@ bloom_info = simpleStat "bloom filter size" $ do
return $ size ++ note return $ size ++ note
transfer_list :: Stat transfer_list :: Stat
transfer_list = stat "transfers in progress" $ nojson $ lift $ do transfer_list = stat desc $ nojson $ lift $ do
uuidmap <- Remote.remoteMap id uuidmap <- Remote.remoteMap id
ts <- getTransfers ts <- getTransfers
maybeShowJSON [(desc, map (uncurry jsonify) ts)]
return $ if null ts return $ if null ts
then "none" then "none"
else multiLine $ else multiLine $
map (uncurry $ line uuidmap) $ sort ts map (uncurry $ line uuidmap) $ sort ts
where where
desc = "transfers in progress"
line uuidmap t i = unwords line uuidmap t i = unwords
[ showLcDirection (transferDirection t) ++ "ing" [ showLcDirection (transferDirection t) ++ "ing"
, fromMaybe (key2file $ transferKey t) (associatedFile i) , fromMaybe (key2file $ transferKey t) (associatedFile i)
@ -354,6 +362,12 @@ transfer_list = stat "transfers in progress" $ nojson $ lift $ do
, maybe (fromUUID $ transferUUID t) Remote.name $ , maybe (fromUUID $ transferUUID t) Remote.name $
M.lookup (transferUUID t) uuidmap M.lookup (transferUUID t) uuidmap
] ]
jsonify t i = toJSObject
[ ("transfer", showLcDirection (transferDirection t))
, ("key", key2file (transferKey t))
, ("file", fromMaybe "" (associatedFile i))
, ("remote", fromUUID (transferUUID t))
]
disk_size :: Stat disk_size :: Stat
disk_size = simpleStat "available local disk space" $ lift $ disk_size = simpleStat "available local disk space" $ lift $
@ -374,42 +388,41 @@ disk_size = simpleStat "available local disk space" $ lift $
| otherwise = 0 | otherwise = 0
backend_usage :: Stat backend_usage :: Stat
backend_usage = stat "backend usage" $ nojson $ backend_usage = stat "backend usage" $ json fmt $
calc calc
<$> (backendsKeys <$> cachedReferencedData) <$> (backendsKeys <$> cachedReferencedData)
<*> (backendsKeys <$> cachedPresentData) <*> (backendsKeys <$> cachedPresentData)
where where
calc x y = multiLine $ calc x y = sort $ M.toList $ M.unionWith (+) x y
map (\(n, b) -> b ++ ": " ++ show n) $ fmt = multiLine . map (\(n, b) -> b ++ ": " ++ show n) . map swap
sortBy (flip compare) $ map swap $ M.toList $
M.unionWith (+) x y
numcopies_stats :: Stat numcopies_stats :: Stat
numcopies_stats = stat "numcopies stats" $ nojson $ numcopies_stats = stat "numcopies stats" $ json fmt $
calc <$> (maybe M.empty numCopiesVarianceMap <$> cachedNumCopiesStats) calc <$> (maybe M.empty numCopiesVarianceMap <$> cachedNumCopiesStats)
where where
calc = multiLine calc = map (\(variance, count) -> (show variance, count))
. map (\(variance, count) -> show variance ++ ": " ++ show count) . sortBy (flip (comparing snd))
. sortBy (flip (comparing snd)) . M.toList . M.toList
fmt = multiLine . map (\(variance, count) -> "numcopies " ++ variance ++ ": " ++ show count)
reposizes_stats :: Stat reposizes_stats :: Stat
reposizes_stats = stat "repositories containing these files" $ nojson $ reposizes_stats = stat desc $ nojson $ do
calc sizer <- lift mkSizer
<$> lift uuidDescriptions l <- map (\(u, kd) -> (u, sizer storageUnits True (sizeKeys kd)))
<*> lift mkSizer . sortBy (flip (comparing (sizeKeys . snd)))
<*> cachedRepoData . M.toList
<$> cachedRepoData
let maxlen = maximum (map (length . snd) l)
-- This also handles json display.
s <- lift $ prettyPrintUUIDsWith (Just "size") desc $
map (\(u, sz) -> (u, Just $ mkdisp sz maxlen)) l
return $ countRepoList (length l) s
where where
calc descm sizer = multiLine desc = "repositories containing these files"
. format mkdisp sz maxlen = DualDisp
. map (\(u, d) -> line descm sizer u d) { dispNormal = lpad maxlen sz
. sortBy (flip (comparing (sizeKeys . snd))) . M.toList , dispJson = sz
line descm sizer u d = (sz, fromUUID u ++ " -- " ++ desc) }
where
sz = sizer storageUnits True (sizeKeys d)
desc = fromMaybe "" (M.lookup u descm)
format l = map (\(c1, c2) -> lpad maxc1 c1 ++ ": " ++ c2 ) l
where
maxc1 = maximum (map (length . fst) l)
lpad n s = (replicate (n - length s) ' ') ++ s lpad n s = (replicate (n - length s) ' ') ++ s
cachedPresentData :: StatState KeyData cachedPresentData :: StatState KeyData

View file

@ -10,7 +10,8 @@ module Messages.JSON (
end, end,
note, note,
add, add,
complete complete,
DualDisp(..),
) where ) where
import Text.JSON import Text.JSON
@ -35,3 +36,16 @@ add v = putStr $ Stream.add v
complete :: JSON a => [(String, a)] -> IO () complete :: JSON a => [(String, a)] -> IO ()
complete v = putStr $ Stream.start v ++ Stream.end complete v = putStr $ Stream.start v ++ Stream.end
-- A value that can be displayed either normally, or as JSON.
data DualDisp = DualDisp
{ dispNormal :: String
, dispJson :: String
}
instance JSON DualDisp where
showJSON = JSString . toJSString . dispJson
readJSON _ = Error "stub"
instance Show DualDisp where
show = dispNormal

View file

@ -31,6 +31,7 @@ module Remote (
byNameWithUUID, byNameWithUUID,
byCost, byCost,
prettyPrintUUIDs, prettyPrintUUIDs,
prettyPrintUUIDsWith,
prettyListUUIDs, prettyListUUIDs,
prettyUUID, prettyUUID,
remoteFromUUID, remoteFromUUID,
@ -168,19 +169,29 @@ nameToUUID' n = byName' n >>= go
{- Pretty-prints a list of UUIDs of remotes, for human display. {- Pretty-prints a list of UUIDs of remotes, for human display.
- -
- When JSON is enabled, also generates a machine-readable description - When JSON is enabled, also outputs a machine-readable description
- of the UUIDs. -} - of the UUIDs. -}
prettyPrintUUIDs :: String -> [UUID] -> Annex String prettyPrintUUIDs :: String -> [UUID] -> Annex String
prettyPrintUUIDs desc uuids = do prettyPrintUUIDs desc uuids = prettyPrintUUIDsWith Nothing desc $
zip uuids (repeat (Nothing :: Maybe String))
{- An optional field can be included in the list of UUIDs. -}
prettyPrintUUIDsWith
:: (JSON v, Show v)
=> Maybe String
-> String
-> [(UUID, Maybe v)]
-> Annex String
prettyPrintUUIDsWith optfield desc uuids = do
hereu <- getUUID hereu <- getUUID
m <- uuidDescriptions m <- uuidDescriptions
maybeShowJSON [(desc, map (jsonify m hereu) uuids)] maybeShowJSON [(desc, map (jsonify m hereu) uuids)]
return $ unwords $ map (\u -> "\t" ++ prettify m hereu u ++ "\n") uuids return $ unwords $ map (\u -> "\t" ++ prettify m hereu u ++ "\n") uuids
where where
finddescription m u = M.findWithDefault "" u m finddescription m u = M.findWithDefault "" u m
prettify m hereu u prettify m hereu (u, optval)
| not (null d) = fromUUID u ++ " -- " ++ d | not (null d) = addoptval $ fromUUID u ++ " -- " ++ d
| otherwise = fromUUID u | otherwise = addoptval $ fromUUID u
where where
ishere = hereu == u ishere = hereu == u
n = finddescription m u n = finddescription m u
@ -188,10 +199,16 @@ prettyPrintUUIDs desc uuids = do
| null n && ishere = "here" | null n && ishere = "here"
| ishere = addName n "here" | ishere = addName n "here"
| otherwise = n | otherwise = n
jsonify m hereu u = toJSObject addoptval s = case optval of
[ ("uuid", toJSON $ fromUUID u) Nothing -> s
, ("description", toJSON $ finddescription m u) Just val -> show val ++ ": " ++ s
, ("here", toJSON $ hereu == u) jsonify m hereu (u, optval) = toJSObject $ catMaybes
[ Just ("uuid", toJSON $ fromUUID u)
, Just ("description", toJSON $ finddescription m u)
, Just ("here", toJSON $ hereu == u)
, case (optfield, optval) of
(Just field, Just val) -> Just (field, showJSON val)
_ -> Nothing
] ]
{- List of remote names and/or descriptions, for human display. -} {- List of remote names and/or descriptions, for human display. -}

2
debian/changelog vendored
View file

@ -32,6 +32,8 @@ git-annex (5.20150529) UNRELEASED; urgency=medium
* Improve url parsing to handle some urls containing illegal [] * Improve url parsing to handle some urls containing illegal []
characters in their paths. characters in their paths.
* debian/cabal-wrapper: Removed this hack which should not be needed anymore. * debian/cabal-wrapper: Removed this hack which should not be needed anymore.
* info: Added json output for "backend usage", "numcopies stats",
"repositories containing these files", and "transfers in progress".
-- Joey Hess <id@joeyh.name> Sat, 30 May 2015 02:07:18 -0400 -- Joey Hess <id@joeyh.name> Sat, 30 May 2015 02:07:18 -0400

View file

@ -26,3 +26,7 @@ transfers in progress:
"""]] """]]
[[anarcat]] [[anarcat]]
> JSON output has to be implemented on a case by case basis for stat
> displays; I've now added it to this and more. [[done]]
> --[[Joey]]