2011-02-03 22:55:12 +00:00
|
|
|
{- git-annex command
|
|
|
|
-
|
2015-01-21 16:50:09 +00:00
|
|
|
- Copyright 2010 Joey Hess <id@joeyh.name>
|
2011-02-03 22:55:12 +00:00
|
|
|
-
|
2019-03-13 19:48:14 +00:00
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
2011-02-03 22:55:12 +00:00
|
|
|
-}
|
|
|
|
|
|
|
|
module Command.Map where
|
|
|
|
|
2011-02-04 02:20:55 +00:00
|
|
|
import qualified Data.Map as M
|
2011-02-03 22:55:12 +00:00
|
|
|
|
|
|
|
import Command
|
2011-06-30 17:16:57 +00:00
|
|
|
import qualified Git
|
2011-12-14 19:30:14 +00:00
|
|
|
import qualified Git.Url
|
2011-12-13 19:05:07 +00:00
|
|
|
import qualified Git.Config
|
|
|
|
import qualified Git.Construct
|
2015-11-18 19:08:55 +00:00
|
|
|
import qualified Remote
|
2011-12-20 20:31:59 +00:00
|
|
|
import qualified Annex
|
2017-02-15 19:08:46 +00:00
|
|
|
import Annex.Ssh
|
2011-10-15 21:47:03 +00:00
|
|
|
import Annex.UUID
|
2011-10-15 20:21:08 +00:00
|
|
|
import Logs.UUID
|
|
|
|
import Logs.Trust
|
2016-05-04 18:12:41 +00:00
|
|
|
import Types.TrustLevel
|
2013-09-24 17:37:41 +00:00
|
|
|
import qualified Remote.Helper.Ssh as Ssh
|
2011-07-06 00:36:43 +00:00
|
|
|
import qualified Utility.Dot as Dot
|
2011-02-03 22:55:12 +00:00
|
|
|
|
|
|
|
-- a link from the first repository to the second (its remote)
|
|
|
|
data Link = Link Git.Repo Git.Repo
|
|
|
|
|
2018-01-09 19:36:56 +00:00
|
|
|
-- a repo and its remotes
|
|
|
|
type RepoRemotes = (Git.Repo, [Git.Repo])
|
|
|
|
|
2015-07-08 16:33:27 +00:00
|
|
|
cmd :: Command
|
|
|
|
cmd = dontCheck repoExists $
|
2015-07-08 19:08:02 +00:00
|
|
|
command "map" SectionQuery
|
2015-07-08 16:33:27 +00:00
|
|
|
"generate map of repositories"
|
2015-07-08 19:08:02 +00:00
|
|
|
paramNothing (withParams seek)
|
2011-02-03 22:55:12 +00:00
|
|
|
|
2015-07-08 19:08:02 +00:00
|
|
|
seek :: CmdParams -> CommandSeek
|
2018-10-01 18:12:06 +00:00
|
|
|
seek = withNothing (commandAction start)
|
2011-02-03 22:55:12 +00:00
|
|
|
|
2011-09-15 20:50:49 +00:00
|
|
|
start :: CommandStart
|
2019-06-12 18:11:23 +00:00
|
|
|
start = startingNoMessage (ActionItemOther Nothing) $ do
|
2013-03-16 20:31:46 +00:00
|
|
|
rs <- combineSame <$> (spider =<< gitRepo)
|
2011-02-03 22:55:12 +00:00
|
|
|
|
2019-01-01 19:39:45 +00:00
|
|
|
umap <- uuidDescMap
|
2016-05-04 18:12:41 +00:00
|
|
|
trustmap <- trustMapLoad
|
2012-07-17 16:27:06 +00:00
|
|
|
|
|
|
|
file <- (</>) <$> fromRepo gitAnnexDir <*> pure "map.dot"
|
2011-02-04 02:20:55 +00:00
|
|
|
|
2016-05-04 18:12:41 +00:00
|
|
|
liftIO $ writeFile file (drawMap rs trustmap umap)
|
make CommandStart return a StartMessage
The goal is to be able to run CommandStart in the main thread when -J is
used, rather than unncessarily passing it off to a worker thread, which
incurs overhead that is signficant when the CommandStart is going to
quickly decide to stop.
To do that, the message it displays needs to be displayed in the worker
thread, after the CommandStart has run.
Also, the change will mean that CommandStart will no longer necessarily
run with the same Annex state as CommandPerform. While its docs already
said it should avoid modifying Annex state, I audited all the
CommandStart code as part of the conversion. (Note that CommandSeek
already sometimes runs with a different Annex state, and that has not been
a source of any problems, so I am not too worried that this change will
lead to breakage going forward.)
The only modification of Annex state I found was it calling
allowMessages in some Commands that default to noMessages. Dealt with
that by adding a startCustomOutput and a startingUsualMessages.
This lets a command start with noMessages and then select the output it
wants for each CommandStart.
One bit of breakage: onlyActionOn has been removed from commands that used it.
The plan is that, since a StartMessage contains an ActionItem,
when a Key can be extracted from that, the parallel job runner can
run onlyActionOn' automatically. Then commands won't need to worry about
this detail. Future work.
Otherwise, this was a fairly straightforward process of making each
CommandStart compile again. Hopefully other behavior changes were mostly
avoided.
In a few cases, a command had a CommandStart that called a CommandPerform
that then called showStart multiple times. I have collapsed those
down to a single start action. The main command to perhaps suffer from it
is Command.Direct, which used to show a start for each file, and no
longer does.
Another minor behavior change is that some commands used showStart
before, but had an associated file and a Key available, so were changed
to ShowStart with an ActionItemAssociatedFile. That will not change the
normal output or behavior, but --json output will now include the key.
This should not break it for anyone using a real json parser.
2019-06-06 19:42:30 +00:00
|
|
|
next $
|
2012-03-14 21:43:34 +00:00
|
|
|
ifM (Annex.getState Annex.fast)
|
2016-11-30 16:50:49 +00:00
|
|
|
( runViewer file []
|
|
|
|
, runViewer file
|
|
|
|
[ ("xdot", [File file])
|
|
|
|
, ("dot", [Param "-Tx11", File file])
|
|
|
|
]
|
2012-03-14 21:43:34 +00:00
|
|
|
)
|
2011-02-03 22:55:12 +00:00
|
|
|
|
2016-11-30 16:50:49 +00:00
|
|
|
runViewer :: FilePath -> [(String, [CommandParam])] -> Annex Bool
|
|
|
|
runViewer file [] = do
|
|
|
|
showLongNote $ "left map in " ++ file
|
|
|
|
return True
|
|
|
|
runViewer file ((c, ps):rest) = ifM (liftIO $ inPath c)
|
|
|
|
( do
|
|
|
|
showLongNote $ "running: " ++ c ++ unwords (toCommand ps)
|
|
|
|
showOutput
|
|
|
|
liftIO $ boolSystem c ps
|
|
|
|
, runViewer file rest
|
|
|
|
)
|
|
|
|
|
2016-05-04 18:12:41 +00:00
|
|
|
{- 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.
|
|
|
|
-}
|
2019-01-01 19:39:45 +00:00
|
|
|
drawMap :: [RepoRemotes] -> TrustMap -> UUIDDescMap -> String
|
2016-05-04 18:12:41 +00:00
|
|
|
drawMap rs trustmap umap = Dot.graph $ repos ++ others
|
2012-11-12 05:05:04 +00:00
|
|
|
where
|
2018-01-09 19:36:56 +00:00
|
|
|
repos = map (node umap (map fst rs) trustmap) rs
|
|
|
|
ruuids = map (getUncachedUUID . fst) rs
|
2016-05-04 18:12:41 +00:00
|
|
|
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)
|
2016-05-04 18:12:41 +00:00
|
|
|
uuidnode u = trustDecorate trustmap u $
|
2019-01-01 19:39:45 +00:00
|
|
|
Dot.graphNode
|
|
|
|
(fromUUID u)
|
|
|
|
(fromUUIDDesc $ M.findWithDefault mempty u umap)
|
2011-02-04 02:20:55 +00:00
|
|
|
|
2011-02-04 03:23:16 +00:00
|
|
|
hostname :: Git.Repo -> String
|
|
|
|
hostname r
|
2013-11-04 18:14:44 +00:00
|
|
|
| Git.repoIsUrl r = fromMaybe (Git.repoLocation r) (Git.Url.host r)
|
2011-02-04 03:23:16 +00:00
|
|
|
| otherwise = "localhost"
|
2011-02-04 02:20:55 +00:00
|
|
|
|
2011-02-04 03:23:16 +00:00
|
|
|
basehostname :: Git.Repo -> String
|
2017-01-31 22:40:42 +00:00
|
|
|
basehostname r = fromMaybe "" $ headMaybe $ splitc '.' $ hostname r
|
2011-02-04 02:20:55 +00:00
|
|
|
|
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. -}
|
2019-01-01 19:39:45 +00:00
|
|
|
repoName :: UUIDDescMap -> Git.Repo -> String
|
2011-02-04 02:20:55 +00:00
|
|
|
repoName umap r
|
2011-11-07 18:46:01 +00:00
|
|
|
| repouuid == NoUUID = fallback
|
2019-01-01 19:39:45 +00:00
|
|
|
| otherwise = maybe fallback fromUUIDDesc $ M.lookup repouuid umap
|
2012-11-12 05:05:04 +00:00
|
|
|
where
|
|
|
|
repouuid = getUncachedUUID r
|
|
|
|
fallback = fromMaybe "unknown" $ Git.remoteName r
|
2011-02-04 02:20:55 +00:00
|
|
|
|
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
|
2011-11-07 18:46:01 +00:00
|
|
|
NoUUID -> Git.repoLocation r
|
2019-01-01 17:49:19 +00:00
|
|
|
u@(UUID _) -> fromUUID u
|
2011-02-04 03:23:16 +00:00
|
|
|
|
|
|
|
{- A node representing a repo. -}
|
2019-01-01 19:39:45 +00:00
|
|
|
node :: UUIDDescMap -> [Git.Repo] -> TrustMap -> RepoRemotes -> String
|
2018-01-09 19:36:56 +00:00
|
|
|
node umap fullinfo trustmap (r, rs) = unlines $ n:edges
|
2012-11-12 05:05:04 +00:00
|
|
|
where
|
|
|
|
n = Dot.subGraph (hostname r) (basehostname r) "lightblue" $
|
2016-05-04 18:12:41 +00:00
|
|
|
trustDecorate trustmap (getUncachedUUID r) $
|
|
|
|
Dot.graphNode (nodeId r) (repoName umap r)
|
2018-01-09 19:36:56 +00:00
|
|
|
edges = map (edge umap fullinfo r) rs
|
2011-02-04 03:23:16 +00:00
|
|
|
|
|
|
|
{- An edge between two repos. The second repo is a remote of the first. -}
|
2019-01-01 19:39:45 +00:00
|
|
|
edge :: UUIDDescMap -> [Git.Repo] -> Git.Repo -> Git.Repo -> String
|
2011-02-04 03:23:16 +00:00
|
|
|
edge umap fullinfo from to =
|
2011-02-08 21:46:52 +00:00
|
|
|
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
|
|
|
|
2016-05-04 18:12:41 +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
|
|
|
|
2011-02-03 22:55:12 +00:00
|
|
|
{- Recursively searches out remotes starting with the specified repo. -}
|
2018-01-09 19:36:56 +00:00
|
|
|
spider :: Git.Repo -> Annex [RepoRemotes]
|
2011-02-03 22:55:12 +00:00
|
|
|
spider r = spider' [r] []
|
2018-01-09 19:36:56 +00:00
|
|
|
spider' :: [Git.Repo] -> [RepoRemotes] -> Annex [RepoRemotes]
|
2011-02-03 22:55:12 +00:00
|
|
|
spider' [] known = return known
|
|
|
|
spider' (r:rs) known
|
2018-01-09 19:36:56 +00:00
|
|
|
| any (same r) (map fst known) = spider' rs known
|
2011-02-03 22:55:12 +00:00
|
|
|
| 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.
|
2018-01-09 19:36:56 +00:00
|
|
|
remotes <- mapM (absRepo r')
|
|
|
|
=<< (liftIO $ Git.Construct.fromRemotes r')
|
|
|
|
|
|
|
|
spider' (rs ++ remotes) ((r', remotes):known)
|
2011-02-03 22:55:12 +00:00
|
|
|
|
2011-12-04 16:23:10 +00:00
|
|
|
{- Converts repos to a common absolute form. -}
|
|
|
|
absRepo :: Git.Repo -> Git.Repo -> Annex Git.Repo
|
2011-02-04 05:56:45 +00:00
|
|
|
absRepo reference r
|
2011-12-13 19:05:07 +00:00
|
|
|
| Git.repoIsUrl reference = return $ Git.Construct.localToUrl reference r
|
2012-01-08 20:05:57 +00:00
|
|
|
| Git.repoIsUrl r = return r
|
2014-01-13 19:36:02 +00:00
|
|
|
| otherwise = liftIO $ do
|
|
|
|
r' <- Git.Construct.fromAbsPath =<< absPath (Git.repoPath r)
|
2014-03-17 19:44:42 +00:00
|
|
|
r'' <- safely $ flip Annex.eval Annex.gitRepo =<< Annex.new r'
|
|
|
|
return (fromMaybe r' r'')
|
2011-02-03 22:55:12 +00:00
|
|
|
|
|
|
|
{- Checks if two repos are the same. -}
|
|
|
|
same :: Git.Repo -> Git.Repo -> Bool
|
|
|
|
same a b
|
2015-11-18 19:08:55 +00:00
|
|
|
| both Git.repoIsUrl = matching Git.Url.scheme && matching Git.Url.authority && matching Git.repoPath
|
|
|
|
| neither Git.repoIsUrl = matching Git.repoPath
|
2011-02-03 22:55:12 +00:00
|
|
|
| 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)
|
2011-02-03 22:55:12 +00:00
|
|
|
|
|
|
|
{- reads the config of a remote, with progress display -}
|
|
|
|
scan :: Git.Repo -> Annex Git.Repo
|
|
|
|
scan r = do
|
2017-11-28 18:40:26 +00:00
|
|
|
showStart' "map" (Just $ Git.repoDescribe r)
|
2011-02-03 22:55:12 +00:00
|
|
|
v <- tryScan r
|
|
|
|
case v of
|
|
|
|
Just r' -> do
|
|
|
|
showEndOk
|
|
|
|
return r'
|
|
|
|
Nothing -> do
|
2011-07-19 18:07:23 +00:00
|
|
|
showOutput
|
2011-02-03 22:55:12 +00:00
|
|
|
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
|
2015-11-18 19:08:55 +00:00
|
|
|
| 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
|
2014-03-17 19:44:42 +00:00
|
|
|
| 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
|
|
|
|
2017-02-15 19:08:46 +00:00
|
|
|
configlist = Ssh.onRemote NoConsumeStdin 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
|
2017-03-17 20:02:47 +00:00
|
|
|
(sshcmd, sshparams) <- Ssh.toRepo NoConsumeStdin r gc remotecmd
|
|
|
|
liftIO $ pipedconfig sshcmd sshparams
|
2012-11-12 05:05:04 +00:00
|
|
|
where
|
2017-03-17 20:02:47 +00:00
|
|
|
remotecmd = "sh -c " ++ shellEscape
|
2014-10-12 18:11:29 +00:00
|
|
|
(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)
|
2014-10-12 18:11:29 +00:00
|
|
|
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
|
2013-03-16 20:31:46 +00:00
|
|
|
|
|
|
|
{- Spidering can find multiple paths to the same repo, so this is used
|
|
|
|
- to combine (really remove) duplicate repos with the same UUID. -}
|
2018-01-09 19:36:56 +00:00
|
|
|
combineSame :: [RepoRemotes] -> [RepoRemotes]
|
2013-03-16 20:31:46 +00:00
|
|
|
combineSame = map snd . nubBy sameuuid . map pair
|
|
|
|
where
|
|
|
|
sameuuid (u1, _) (u2, _) = u1 == u2 && u1 /= NoUUID
|
2018-01-09 19:36:56 +00:00
|
|
|
pair (r, rs) = (getUncachedUUID r, (r, rs))
|
2014-03-17 19:44:42 +00:00
|
|
|
|
|
|
|
safely :: IO Git.Repo -> IO (Maybe Git.Repo)
|
|
|
|
safely a = do
|
unify exception handling into Utility.Exception
Removed old extensible-exceptions, only needed for very old ghc.
Made webdav use Utility.Exception, to work after some changes in DAV's
exception handling.
Removed Annex.Exception. Mostly this was trivial, but note that
tryAnnex is replaced with tryNonAsync and catchAnnex replaced with
catchNonAsync. In theory that could be a behavior change, since the former
caught all exceptions, and the latter don't catch async exceptions.
However, in practice, nothing in the Annex monad uses async exceptions.
Grepping for throwTo and killThread only find stuff in the assistant,
which does not seem related.
Command.Add.undo is changed to accept a SomeException, and things
that use it for rollback now catch non-async exceptions, rather than
only IOExceptions.
2014-08-08 01:55:44 +00:00
|
|
|
result <- tryNonAsync a
|
2014-03-17 19:44:42 +00:00
|
|
|
case result of
|
|
|
|
Left _ -> return Nothing
|
|
|
|
Right r' -> return $ Just r'
|