git-annex/Command/Map.hs

263 lines
8 KiB
Haskell
Raw Normal View History

{- git-annex command
-
- Copyright 2010 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Command.Map where
import qualified Data.Map as M
import Command
import qualified Git
2011-12-14 19:30:14 +00:00
import qualified Git.Url
import qualified Git.Config
import qualified Git.Construct
import qualified Remote
import qualified Annex
import Annex.UUID
2011-10-15 20:21:08 +00:00
import Logs.UUID
import Logs.Trust
import Types.TrustLevel
import qualified Remote.Helper.Ssh as Ssh
2011-07-06 00:36:43 +00:00
import qualified Utility.Dot as Dot
-- a link from the first repository to the second (its remote)
data Link = Link Git.Repo Git.Repo
cmd :: Command
cmd = dontCheck repoExists $
command "map" SectionQuery
"generate map of repositories"
paramNothing (withParams seek)
seek :: CmdParams -> CommandSeek
seek = withNothing start
start :: CommandStart
start = do
rs <- combineSame <$> (spider =<< gitRepo)
umap <- uuidMap
trustmap <- trustMapLoad
file <- (</>) <$> fromRepo gitAnnexDir <*> pure "map.dot"
liftIO $ writeFile file (drawMap rs trustmap umap)
next $ next $
ifM (Annex.getState Annex.fast)
2015-11-18 18:17:52 +00:00
( do
showLongNote $ "left map in " ++ file
return True
, do
showLongNote $ "running: dot -Tx11 " ++ file
showOutput
liftIO $ boolSystem "dot" [Param "-Tx11", File file]
)
{- Generates a graph for dot(1). Each repository, and any other uuids
- (except for dead ones), are displayed as a node, and each of its
- remotes is represented as an edge pointing at the node for the remote.
2011-02-04 04:13:47 +00:00
-
- The order nodes are added to the graph matters, since dot will draw
- the first ones near to the top and left. So it looks better to put
- the repositories first, followed by uuids that were not matched
- to a repository.
-}
drawMap :: [Git.Repo] -> TrustMap -> M.Map UUID String -> String
drawMap rs trustmap umap = Dot.graph $ repos ++ others
2012-11-12 05:05:04 +00:00
where
repos = map (node umap rs trustmap) rs
ruuids = map getUncachedUUID rs
others = map uuidnode $
filter (\u -> M.lookup u trustmap /= Just DeadTrusted) $
2012-11-12 05:05:04 +00:00
filter (`notElem` ruuids) (M.keys umap)
uuidnode u = trustDecorate trustmap u $
Dot.graphNode (fromUUID u) $ M.findWithDefault "" u umap
2011-02-04 03:23:16 +00:00
hostname :: Git.Repo -> String
hostname r
| Git.repoIsUrl r = fromMaybe (Git.repoLocation r) (Git.Url.host r)
2011-02-04 03:23:16 +00:00
| otherwise = "localhost"
2011-02-04 03:23:16 +00:00
basehostname :: Git.Repo -> String
basehostname r = fromMaybe "" $ headMaybe $ split "." $ hostname r
2011-02-04 03:23:16 +00:00
{- A name to display for a repo. Uses the name from uuid.log if available,
- or the remote name if not. -}
2011-07-15 16:47:14 +00:00
repoName :: M.Map UUID String -> Git.Repo -> String
repoName umap r
| repouuid == NoUUID = fallback
| otherwise = M.findWithDefault fallback repouuid umap
2012-11-12 05:05:04 +00:00
where
repouuid = getUncachedUUID r
fallback = fromMaybe "unknown" $ Git.remoteName r
2011-02-04 04:06:23 +00:00
{- A unique id for the node for a repo. Uses the annex.uuid if available. -}
2011-02-04 03:23:16 +00:00
nodeId :: Git.Repo -> String
nodeId r =
2011-07-15 16:47:14 +00:00
case getUncachedUUID r of
NoUUID -> Git.repoLocation r
UUID u -> u
2011-02-04 03:23:16 +00:00
{- A node representing a repo. -}
node :: M.Map UUID String -> [Git.Repo] -> TrustMap -> Git.Repo -> String
node umap fullinfo trustmap r = unlines $ n:edges
2012-11-12 05:05:04 +00:00
where
n = Dot.subGraph (hostname r) (basehostname r) "lightblue" $
trustDecorate trustmap (getUncachedUUID r) $
Dot.graphNode (nodeId r) (repoName umap r)
2012-11-12 05:05:04 +00:00
edges = map (edge umap fullinfo r) (Git.remotes r)
2011-02-04 03:23:16 +00:00
{- An edge between two repos. The second repo is a remote of the first. -}
2011-07-15 16:47:14 +00:00
edge :: M.Map UUID String -> [Git.Repo] -> Git.Repo -> Git.Repo -> String
2011-02-04 03:23:16 +00:00
edge umap fullinfo from to =
Dot.graphEdge (nodeId from) (nodeId fullto) edgename
2012-11-12 05:05:04 +00:00
where
-- get the full info for the remote, to get its UUID
fullto = findfullinfo to
findfullinfo n =
case filter (same n) fullinfo of
[] -> n
(n':_) -> n'
{- Only name an edge if the name is different than the name
- that will be used for the destination node, and is
- different from its hostname. (This reduces visual clutter.) -}
edgename = maybe Nothing calcname $ Git.remoteName to
calcname n
| n `elem` [repoName umap fullto, hostname fullto] = Nothing
| otherwise = Just n
2011-02-04 03:23:16 +00:00
trustDecorate :: TrustMap -> UUID -> String -> String
trustDecorate trustmap u s = case M.lookup u trustmap of
Just Trusted -> Dot.fillColor "green" s
Just UnTrusted -> Dot.fillColor "red" s
Just SemiTrusted -> Dot.fillColor "white" s
Just DeadTrusted -> Dot.fillColor "grey" s
Nothing -> Dot.fillColor "white" s
2011-02-04 04:06:23 +00:00
{- Recursively searches out remotes starting with the specified repo. -}
spider :: Git.Repo -> Annex [Git.Repo]
spider r = spider' [r] []
spider' :: [Git.Repo] -> [Git.Repo] -> Annex [Git.Repo]
spider' [] known = return known
spider' (r:rs) known
| any (same r) known = spider' rs known
| otherwise = do
r' <- scan r
2011-02-08 21:52:32 +00:00
-- The remotes will be relative to r', and need to be
-- made absolute for later use.
remotes <- mapM (absRepo r') (Git.remotes r')
2011-12-14 19:30:14 +00:00
let r'' = r' { Git.remotes = remotes }
2011-02-08 21:52:32 +00:00
spider' (rs ++ remotes) (r'':known)
{- Converts repos to a common absolute form. -}
absRepo :: Git.Repo -> Git.Repo -> Annex Git.Repo
absRepo reference r
| Git.repoIsUrl reference = return $ Git.Construct.localToUrl reference r
| Git.repoIsUrl r = return r
| otherwise = liftIO $ do
r' <- Git.Construct.fromAbsPath =<< absPath (Git.repoPath r)
r'' <- safely $ flip Annex.eval Annex.gitRepo =<< Annex.new r'
return (fromMaybe r' r'')
{- Checks if two repos are the same. -}
same :: Git.Repo -> Git.Repo -> Bool
same a b
| both Git.repoIsUrl = matching Git.Url.scheme && matching Git.Url.authority && matching Git.repoPath
| neither Git.repoIsUrl = matching Git.repoPath
| otherwise = False
2012-11-12 05:05:04 +00:00
where
matching t = t a == t b
both t = t a && t b
neither t = not (t a) && not (t b)
{- reads the config of a remote, with progress display -}
scan :: Git.Repo -> Annex Git.Repo
scan r = do
2011-02-04 03:23:16 +00:00
showStart "map" $ Git.repoDescribe r
v <- tryScan r
case v of
Just r' -> do
showEndOk
return r'
Nothing -> do
showOutput
showEndFail
return r
{- tries to read the config of a remote, returning it only if it can
- be accessed -}
tryScan :: Git.Repo -> Annex (Maybe Git.Repo)
tryScan r
| Git.repoIsSsh r = sshscan
| Git.repoIsUrl r = case Git.remoteName r of
-- Can't scan a non-ssh url, so use any cached uuid for it.
Just n -> Just <$> (either
(const (pure r))
(liftIO . setUUID r . Remote.uuid)
=<< Remote.byName' n)
Nothing -> return $ Just r
| otherwise = liftIO $ safely $ Git.Config.read r
2012-11-12 05:05:04 +00:00
where
2014-10-15 18:29:53 +00:00
pipedconfig pcmd params = liftIO $ safely $
2012-11-12 05:05:04 +00:00
withHandle StdoutHandle createProcessSuccess p $
Git.Config.hRead r
where
2014-10-15 18:29:53 +00:00
p = proc pcmd $ toCommand params
2012-11-12 05:05:04 +00:00
configlist = Ssh.onRemote r (pipedconfig, return Nothing) "configlist" [] []
2012-11-12 05:05:04 +00:00
manualconfiglist = do
2014-05-16 20:08:20 +00:00
gc <- Annex.getRemoteGitConfig r
sshparams <- Ssh.toRepo r gc [Param sshcmd]
2012-11-12 05:05:04 +00:00
liftIO $ pipedconfig "ssh" sshparams
where
sshcmd = "sh -c " ++ shellEscape
(cddir ++ " && " ++ "git config --null --list")
2012-11-12 05:05:04 +00:00
dir = Git.repoPath r
cddir
| "/~" `isPrefixOf` dir =
let (userhome, reldir) = span (/= '/') (drop 1 dir)
in "cd " ++ userhome ++ " && " ++ cdto (drop 1 reldir)
| otherwise = cdto dir
2014-10-13 20:06:35 +00:00
cdto p = "if ! cd " ++ shellEscape p ++ " 2>/dev/null; then cd " ++ shellEscape p ++ ".git; fi"
2012-11-12 05:05:04 +00:00
-- First, try sshing and running git config manually,
-- only fall back to git-annex-shell configlist if that
-- fails.
--
-- This is done for two reasons, first I'd like this
-- subcommand to be usable on non-git-annex repos.
-- Secondly, configlist doesn't include information about
-- the remote's remotes.
sshscan = do
sshnote
v <- manualconfiglist
case v of
Nothing -> do
sshnote
configlist
ok -> return ok
sshnote = do
showAction "sshing"
showOutput
{- Spidering can find multiple paths to the same repo, so this is used
- to combine (really remove) duplicate repos with the same UUID. -}
combineSame :: [Git.Repo] -> [Git.Repo]
combineSame = map snd . nubBy sameuuid . map pair
where
sameuuid (u1, _) (u2, _) = u1 == u2 && u1 /= NoUUID
pair r = (getUncachedUUID r, r)
safely :: IO Git.Repo -> IO (Maybe Git.Repo)
safely a = do
result <- tryNonAsync a
case result of
Left _ -> return Nothing
Right r' -> return $ Just r'