list --allrepos

This commit is contained in:
Joey Hess 2013-09-19 21:33:44 -04:00
parent 51d5c1d032
commit 55636bf92f
2 changed files with 36 additions and 13 deletions

View file

@ -9,30 +9,53 @@
module Command.List where module Command.List where
import qualified Data.Set as S import qualified Data.Set as S
import qualified Data.Map as M
import Data.Function
import Data.Tuple.Utils
import Data.Ord
import Common.Annex import Common.Annex
import Command import Command
import Remote import Remote
import Logs.Trust import Logs.Trust
import Logs.UUID
import Annex.UUID import Annex.UUID
import qualified Option
import qualified Annex
def :: [Command] def :: [Command]
def = [noCommit $ command "list" paramPaths seek def = [noCommit $ withOptions [allrepos] $ command "list" paramPaths seek
SectionQuery "show which remotes contain files"] SectionQuery "show which remotes contain files"]
allrepos :: Option
allrepos = Option.flag [] "allrepos" "show all repositories, not only remotes"
seek :: [CommandSeek] seek :: [CommandSeek]
seek = seek =
[ withValue getList $ \l -> withNothing $ startHeader l [ withValue getList $ withNothing . startHeader
, withValue getList $ \l -> withFilesInGit $ whenAnnexed $ start l , withValue getList $ withFilesInGit . whenAnnexed . start
] ]
getList :: Annex [(UUID, RemoteName, TrustLevel)] getList :: Annex [(UUID, RemoteName, TrustLevel)]
getList = do getList = ifM (Annex.getFlag $ Option.name allrepos)
rs <- remoteList ( nubBy ((==) `on` fst3) <$> ((++) <$> getRemotes <*> getAll)
ts <- mapM (lookupTrust . uuid) rs , getRemotes
hereu <- getUUID )
heretrust <- lookupTrust hereu where
return $ (hereu, "here", heretrust) : zip3 (map uuid rs) (map name rs) ts getRemotes = do
rs <- remoteList
ts <- mapM (lookupTrust . uuid) rs
hereu <- getUUID
heretrust <- lookupTrust hereu
return $ (hereu, "here", heretrust) : zip3 (map uuid rs) (map name rs) ts
getAll = do
rs <- M.toList <$> uuidMap
rs3 <- forM rs $ \(u, n) -> (,,)
<$> pure u
<*> pure n
<*> lookupTrust u
return $ sortBy (comparing snd3) $
filter (\t -> thd3 t /= DeadTrusted) rs3
startHeader :: [(UUID, RemoteName, TrustLevel)] -> CommandStart startHeader :: [(UUID, RemoteName, TrustLevel)] -> CommandStart
startHeader l = do startHeader l = do

View file

@ -549,14 +549,14 @@ subdirectories).
* `whereis [path ...]` * `whereis [path ...]`
Displays a list of repositories known to contain the contents of the Displays a information about where the contents of files are located.
specified file or files.
* `list [path ...]` * `list [path ...]`
Displays a table of remotes that contain the contents of the specified Displays a table of remotes that contain the contents of the specified
files. Unlike whereis, this only shows configured remotes, not other files. This is similar to whereis but a more compact display. Only
repositories. However it is a more compact display. configured remotes are shown by default; specify --allrepos to list
all repositories.
* `log [path ...]` * `log [path ...]`