whereis --json: Urls are now listed inside the remote that claims them, rather than all together at the end.

This commit is contained in:
Joey Hess 2016-01-15 14:16:48 -04:00
parent d9f9153c82
commit b26ce646e4
Failed to extract signature
6 changed files with 59 additions and 23 deletions

View file

@ -425,7 +425,7 @@ reposizes_stats = stat desc $ nojson $ do
let maxlen = maximum (map (length . snd) l) let maxlen = maximum (map (length . snd) l)
descm <- lift uuidDescriptions descm <- lift uuidDescriptions
-- This also handles json display. -- This also handles json display.
s <- lift $ prettyPrintUUIDsWith (Just "size") desc descm $ s <- lift $ prettyPrintUUIDsWith (Just "size") desc descm (Just . show) $
map (\(u, sz) -> (u, Just $ mkdisp sz maxlen)) l map (\(u, sz) -> (u, Just $ mkdisp sz maxlen)) l
return $ countRepoList (length l) s return $ countRepoList (length l) s
where where

View file

@ -13,6 +13,7 @@ import Remote
import Logs.Trust import Logs.Trust
import Logs.Web import Logs.Web
import Remote.Web (getWebUrls) import Remote.Web (getWebUrls)
import Annex.UUID
import qualified Data.Map as M import qualified Data.Map as M
@ -54,32 +55,39 @@ start' remotemap key afile = do
perform :: M.Map UUID Remote -> Key -> CommandPerform perform :: M.Map UUID Remote -> Key -> CommandPerform
perform remotemap key = do perform remotemap key = do
locations <- keyLocations key locations <- keyLocations key
urls <- getUUIDUrls key locations remotemap
(untrustedlocations, safelocations) <- trustPartition UnTrusted locations (untrustedlocations, safelocations) <- trustPartition UnTrusted locations
let num = length safelocations let num = length safelocations
showNote $ show num ++ " " ++ copiesplural num showNote $ show num ++ " " ++ copiesplural num
pp <- prettyPrintUUIDs "whereis" safelocations pp <- ppwhereis "whereis" safelocations urls
unless (null safelocations) $ showLongNote pp unless (null safelocations) $ showLongNote pp
pp' <- prettyPrintUUIDs "untrusted" untrustedlocations pp' <- ppwhereis "untrusted" untrustedlocations urls
unless (null untrustedlocations) $ showLongNote $ untrustedheader ++ pp' unless (null untrustedlocations) $ showLongNote $ untrustedheader ++ pp'
-- Since other remotes than the web remote can set urls mapM_ (showRemoteUrls remotemap) urls
-- where a key can be downloaded, get and show all such urls
-- as a special case.
showRemoteUrls "web" =<< getWebUrls key
forM_ (mapMaybe (`M.lookup` remotemap) locations) $
performRemoteUrls key
if null safelocations then stop else next $ return True if null safelocations then stop else next $ return True
where where
copiesplural 1 = "copy" copiesplural 1 = "copy"
copiesplural _ = "copies" copiesplural _ = "copies"
untrustedheader = "The following untrusted locations may also have copies:\n" untrustedheader = "The following untrusted locations may also have copies:\n"
ppwhereis h ls urls = do
descm <- uuidDescriptions
let urlvals = map (\(u, us) -> (u, Just us)) $
filter (\(u,_) -> u `elem` ls) urls
prettyPrintUUIDsWith (Just "urls") h descm (const Nothing) urlvals
performRemoteUrls :: Key -> Remote -> Annex () getUUIDUrls :: Key -> [UUID] -> M.Map UUID Remote -> Annex [(UUID, [URLString])]
performRemoteUrls key remote = do getUUIDUrls key uuids remotemap = forM uuids $ \uu -> (,)
ls <- (++) <$> pure uu
<*> maybe (pure []) (getRemoteUrls key) (M.lookup uu remotemap)
getRemoteUrls :: Key -> Remote -> Annex [URLString]
getRemoteUrls key remote
| uuid remote == webUUID = getWebUrls key
| otherwise = (++)
<$> askremote <$> askremote
<*> claimedurls <*> claimedurls
showRemoteUrls (name remote) ls
where where
askremote = maybe (pure []) (flip id key) (whereisKey remote) askremote = maybe (pure []) (flip id key) (whereisKey remote)
claimedurls = do claimedurls = do
@ -89,10 +97,11 @@ performRemoteUrls key remote = do
<$> getUrls key <$> getUrls key
filterM (\u -> (==) <$> pure remote <*> claimingUrl u) us filterM (\u -> (==) <$> pure remote <*> claimingUrl u) us
showRemoteUrls :: String -> [String] -> Annex () showRemoteUrls :: M.Map UUID Remote -> (UUID, [URLString]) -> Annex ()
showRemoteUrls nm us showRemoteUrls remotemap (uu, us)
| null us = return () | null us = noop
| otherwise = do | otherwise = case M.lookup uu remotemap of
let ls = unlines $ map (\u -> nm ++ ": " ++ u) us Just r -> do
outputMessage noop ('\n' : indent ls ++ "\n") let ls = unlines $ map (\u -> name r ++ ": " ++ u) us
maybeShowJSON [("urls", us)] outputMessage noop ('\n' : indent ls ++ "\n")
Nothing -> noop

View file

@ -183,6 +183,7 @@ prettyPrintUUIDs header uuids = do
prettyPrintUUIDsDescs :: String -> M.Map UUID RemoteName -> [UUID] -> Annex String prettyPrintUUIDsDescs :: String -> M.Map UUID RemoteName -> [UUID] -> Annex String
prettyPrintUUIDsDescs header descm uuids = prettyPrintUUIDsDescs header descm uuids =
prettyPrintUUIDsWith Nothing header descm prettyPrintUUIDsWith Nothing header descm
(const Nothing)
(zip uuids (repeat (Nothing :: Maybe String))) (zip uuids (repeat (Nothing :: Maybe String)))
{- An optional field can be included in the list of UUIDs. -} {- An optional field can be included in the list of UUIDs. -}
@ -191,9 +192,10 @@ prettyPrintUUIDsWith
=> Maybe String => Maybe String
-> String -> String
-> M.Map UUID RemoteName -> M.Map UUID RemoteName
-> (v -> Maybe String)
-> [(UUID, Maybe v)] -> [(UUID, Maybe v)]
-> Annex String -> Annex String
prettyPrintUUIDsWith optfield header descm uuidvals = do prettyPrintUUIDsWith optfield header descm showval uuidvals = do
hereu <- getUUID hereu <- getUUID
maybeShowJSON [(header, map (jsonify hereu) uuidvals)] maybeShowJSON [(header, map (jsonify hereu) uuidvals)]
return $ unwords $ map (\u -> "\t" ++ prettify hereu u ++ "\n") uuidvals return $ unwords $ map (\u -> "\t" ++ prettify hereu u ++ "\n") uuidvals
@ -209,9 +211,9 @@ prettyPrintUUIDsWith optfield header descm uuidvals = do
| null n && ishere = "here" | null n && ishere = "here"
| ishere = addName n "here" | ishere = addName n "here"
| otherwise = n | otherwise = n
addoptval s = case optval of addoptval s = case showval =<< optval of
Nothing -> s Nothing -> s
Just val -> show val ++ ": " ++ s Just val -> val ++ ": " ++ s
jsonify hereu (u, optval) = toJSObject $ catMaybes jsonify hereu (u, optval) = toJSObject $ catMaybes
[ Just ("uuid", toJSON $ fromUUID u) [ Just ("uuid", toJSON $ fromUUID u)
, Just ("description", toJSON $ finddescription u) , Just ("description", toJSON $ finddescription u)

7
debian/changelog vendored
View file

@ -1,3 +1,10 @@
git-annex (6.20160115) UNRELEASED; urgency=medium
* whereis --json: Urls are now listed inside the remote that claims them,
rather than all together at the end.
-- Joey Hess <id@joeyh.name> Fri, 15 Jan 2016 14:05:01 -0400
git-annex (6.20160114) unstable; urgency=medium git-annex (6.20160114) unstable; urgency=medium
"hexapodia as the key insight" "hexapodia as the key insight"

View file

@ -89,3 +89,5 @@ as you can see -- only --json format is missing on web remote URLs. I guess, id
what is the purpose of note in current output anyways since it just duplicates information in 'whereis' field? what is the purpose of note in current output anyways since it just duplicates information in 'whereis' field?
[[!meta author=yoh]] [[!meta author=yoh]]
> [[fixed|done]] --[[Joey]]

View file

@ -0,0 +1,16 @@
[[!comment format=mdwn
username="joey"
subject="""comment 1"""
date="2016-01-15T18:10:26Z"
content="""
The web urls were included in the json output, but it seems some json
parsers, including the one you're using, only show the last value of an
attribute when multiple values are repeated, as happened when there were
both web and other remotes with urls.
Anyway, I've updated the json output to include the url list inside the
remote's record.
(The "note" just collects any output that is not explicitly formatted as
json.)
"""]]