add describe subcommand

This commit is contained in:
Joey Hess 2011-03-03 17:21:00 -04:00
parent 1de12a2918
commit 657395b628
5 changed files with 55 additions and 4 deletions

View file

@ -209,6 +209,8 @@ paramRepeating :: String -> String
paramRepeating s = s ++ " ..." paramRepeating s = s ++ " ..."
paramOptional :: String -> String paramOptional :: String -> String
paramOptional s = "[" ++ s ++ "]" paramOptional s = "[" ++ s ++ "]"
paramPair :: String -> String -> String
paramPair a b = a ++ " " ++ b
paramPath :: String paramPath :: String
paramPath = "PATH" paramPath = "PATH"
paramKey :: String paramKey :: String

41
Command/Describe.hs Normal file
View file

@ -0,0 +1,41 @@
{- git-annex command
-
- Copyright 2011 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Command.Describe where
import Command
import qualified GitRepo as Git
import qualified Remotes
import UUID
import Messages
import qualified Command.Init
command :: [Command]
command = [Command "describe" (paramPair paramRemote paramDesc) seek
"change description of a repository"]
seek :: [CommandSeek]
seek = [withString start]
start :: CommandStartString
start params = notBareRepo $ do
let (name, description) =
case (words params) of
(n:d) -> (n,unwords d)
_ -> error "Specify a repository and a description."
showStart "describe" name
Remotes.readConfigs
r <- Remotes.byName name
return $ Just $ perform r description
perform :: Git.Repo -> String -> CommandPerform
perform repo description = do
u <- getUUID repo
describeUUID u description
return $ Just $ Command.Init.cleanup

View file

@ -62,7 +62,7 @@ cleanup = do
liftIO $ Git.run g "add" [File logfile] liftIO $ Git.run g "add" [File logfile]
liftIO $ Git.run g "commit" liftIO $ Git.run g "commit"
[ Params "-q -m" [ Params "-q -m"
, Param "git annex init" , Param "git annex repository description"
, File logfile , File logfile
] ]
return True return True

View file

@ -26,6 +26,7 @@ import qualified Command.DropKey
import qualified Command.SetKey import qualified Command.SetKey
import qualified Command.Fix import qualified Command.Fix
import qualified Command.Init import qualified Command.Init
import qualified Command.Describe
import qualified Command.Fsck import qualified Command.Fsck
import qualified Command.Unused import qualified Command.Unused
import qualified Command.DropUnused import qualified Command.DropUnused
@ -50,6 +51,7 @@ cmds = concat
, Command.Unlock.command , Command.Unlock.command
, Command.Lock.command , Command.Lock.command
, Command.Init.command , Command.Init.command
, Command.Describe.command
, Command.Unannex.command , Command.Unannex.command
, Command.Uninit.command , Command.Uninit.command
, Command.PreCommit.command , Command.PreCommit.command

View file

@ -211,17 +211,23 @@ repoNotIgnored r = do
same :: Git.Repo -> Git.Repo -> Bool same :: Git.Repo -> Git.Repo -> Bool
same a b = Git.repoRemoteName a == Git.repoRemoteName b same a b = Git.repoRemoteName a == Git.repoRemoteName b
{- Looks up a remote by name. -} {- Looks up a remote by name. (Or by UUID.) -}
byName :: String -> Annex Git.Repo byName :: String -> Annex Git.Repo
byName "." = Annex.gitRepo -- special case to refer to current repository byName "." = Annex.gitRepo -- special case to refer to current repository
byName name = do byName name = do
when (null name) $ error "no remote specified" when (null name) $ error "no remote specified"
g <- Annex.gitRepo g <- Annex.gitRepo
let match = filter (\r -> Just name == Git.repoRemoteName r) $ match <- filterM matching $ Git.remotes g
Git.remotes g
when (null match) $ error $ when (null match) $ error $
"there is no git remote named \"" ++ name ++ "\"" "there is no git remote named \"" ++ name ++ "\""
return $ head match return $ head match
where
matching r = do
if Just name == Git.repoRemoteName r
then return True
else do
u <- getUUID r
return $ (name == u)
{- Tries to copy a key's content from a remote's annex to a file. -} {- Tries to copy a key's content from a remote's annex to a file. -}
copyFromRemote :: Git.Repo -> Key -> FilePath -> Annex Bool copyFromRemote :: Git.Repo -> Key -> FilePath -> Annex Bool