git-annex/Command/Whereis.hs
Joey Hess 89e1a05a8f
Fix mangling of --json output of utf-8 characters when not running in a utf-8 locale
As long as all code imports Utility.Aeson rather than Data.Aeson,
and no Strings that may contain utf-8 characters are used for eg, object
keys via T.pack, this is guaranteed to fix the problem everywhere that
git-annex generates json.

It's kind of annoying to need to wrap ToJSON with a ToJSON', especially
since every data type that has a ToJSON instance has to be ported over.
However, that only took 50 lines of code, which is worth it to ensure full
coverage. I initially tried an alternative approach of a newtype FileEncoded,
which had to be used everywhere a String was fed into aeson, and chasing
down all the sites would have been far too hard. Did consider creating an
intentionally overlapping instance ToJSON String, and letting ghc fail
to build anything that passed in a String, but am not sure that wouldn't
pollute some library that git-annex depends on that happens to use ToJSON
String internally.

This commit was supported by the NSF-funded DataLad project.
2018-04-16 16:21:21 -04:00

111 lines
3.3 KiB
Haskell

{- git-annex command
-
- Copyright 2010-2016 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Command.Whereis where
import Command
import Remote
import Logs.Trust
import Logs.Web
import Remote.Web (getWebUrls)
import Annex.UUID
import qualified Data.Map as M
import qualified Data.Vector as V
cmd :: Command
cmd = noCommit $ withGlobalOptions [jsonOptions, annexedMatchingOptions] $
command "whereis" SectionQuery
"lists repositories that have file content"
paramPaths (seek <$$> optParser)
data WhereisOptions = WhereisOptions
{ whereisFiles :: CmdParams
, keyOptions :: Maybe KeyOptions
, batchOption :: BatchMode
}
optParser :: CmdParamsDesc -> Parser WhereisOptions
optParser desc = WhereisOptions
<$> cmdParams desc
<*> optional parseKeyOptions
<*> parseBatchOption
seek :: WhereisOptions -> CommandSeek
seek o = do
m <- remoteMap id
let go = whenAnnexed $ start m
case batchOption o of
Batch -> batchFiles go
NoBatch ->
withKeyOptions (keyOptions o) False
(startKeys m)
(withFilesInGit go)
=<< workTreeItems (whereisFiles o)
start :: M.Map UUID Remote -> FilePath -> Key -> CommandStart
start remotemap file key = startKeys remotemap key (mkActionItem afile)
where
afile = AssociatedFile (Just file)
startKeys :: M.Map UUID Remote -> Key -> ActionItem -> CommandStart
startKeys remotemap key ai = do
showStartKey "whereis" key ai
next $ perform remotemap key
perform :: M.Map UUID Remote -> Key -> CommandPerform
perform remotemap key = do
locations <- keyLocations key
urls <- getUUIDUrls key locations remotemap
(untrustedlocations, safelocations) <- trustPartition UnTrusted locations
let num = length safelocations
showNote $ show num ++ " " ++ copiesplural num
pp <- ppwhereis "whereis" safelocations urls
unless (null safelocations) $ showLongNote pp
pp' <- ppwhereis "untrusted" untrustedlocations urls
unless (null untrustedlocations) $ showLongNote $ untrustedheader ++ pp'
mapM_ (showRemoteUrls remotemap) urls
if null safelocations then stop else next $ return True
where
copiesplural 1 = "copy"
copiesplural _ = "copies"
untrustedheader = "The following untrusted locations may also have copies:\n"
ppwhereis h ls urls = do
descm <- uuidDescriptions
let urlvals = map (\(u, us) -> (u, Just (V.fromList us))) $
filter (\(u,_) -> u `elem` ls) urls
prettyPrintUUIDsWith (Just "urls") h descm (const Nothing) urlvals
getUUIDUrls :: Key -> [UUID] -> M.Map UUID Remote -> Annex [(UUID, [URLString])]
getUUIDUrls key uuids remotemap = forM uuids $ \uu -> (,)
<$> 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
<*> claimedurls
where
askremote = maybe (pure []) (flip id key) (whereisKey remote)
claimedurls = do
us <- map fst
. filter (\(_, d) -> d == OtherDownloader)
. map getDownloader
<$> getUrls key
filterM (\u -> (==) <$> pure remote <*> claimingUrl u) us
showRemoteUrls :: M.Map UUID Remote -> (UUID, [URLString]) -> Annex ()
showRemoteUrls remotemap (uu, us)
| null us = noop
| otherwise = case M.lookup uu remotemap of
Just r -> showLongNote $
unlines $ map (\u -> name r ++ ": " ++ u) us
Nothing -> noop