checkpresentkey: Allow to be run without an explicit remote and add --batch

* checkpresentkey: Allow to be run without an explicit remote.
* checkpresentkey: Added --batch.
This commit is contained in:
Joey Hess 2016-02-12 16:43:51 -04:00
parent 84d657312e
commit cc4d3e3d45
Failed to extract signature
5 changed files with 90 additions and 23 deletions

View file

@ -1,6 +1,6 @@
{- git-annex command
-
- Copyright 2015 Joey Hess <id@joeyh.name>
- Copyright 2015-2016 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU GPL version 3 or higher.
-}
@ -9,29 +9,71 @@ module Command.CheckPresentKey where
import Command
import qualified Remote
import Annex
import Types.Messages
cmd :: Command
cmd = noCommit $
cmd = noCommit $ noMessages $
command "checkpresentkey" SectionPlumbing
"check if key is present in remote"
(paramPair paramKey paramRemote)
(withParams seek)
(paramPair paramKey (paramOptional paramRemote))
(seek <$$> optParser)
seek :: CmdParams -> CommandSeek
seek = withWords start
data CheckPresentKeyOptions = CheckPresentKeyOptions
{ params :: CmdParams
, batchOption :: BatchMode
}
start :: [String] -> CommandStart
start (ks:rn:[]) = do
setOutput QuietOutput
maybe (error "Unknown remote") (go <=< flip Remote.hasKey k)
=<< Remote.byNameWithUUID (Just rn)
optParser :: CmdParamsDesc -> Parser CheckPresentKeyOptions
optParser desc = CheckPresentKeyOptions
<$> cmdParams desc
<*> parseBatchOption
seek :: CheckPresentKeyOptions -> CommandSeek
seek o = case batchOption o of
NoBatch -> case params o of
(ks:rn:[]) -> toRemote rn >>= (check ks . Just) >>= exitResult
(ks:[]) -> check ks Nothing >>= exitResult
_ -> wrongnumparams
Batch -> do
checker <- case params o of
(rn:[]) -> toRemote rn >>= \r -> return (flip check (Just r))
[] -> return (flip check Nothing)
_ -> wrongnumparams
batchInput Right $ checker >=> batchResult
where
k = fromMaybe (error "bad key") (file2key ks)
go (Right True) = liftIO exitSuccess
go (Right False) = liftIO exitFailure
go (Left e) = liftIO $ do
hPutStrLn stderr e
exitWith $ ExitFailure 100
start _ = error "Wrong number of parameters"
wrongnumparams = error "Wrong number of parameters"
data Result = Present | NotPresent | CheckFailure String
check :: String -> Maybe Remote -> Annex Result
check ks mr = case mr of
Nothing -> go Nothing =<< Remote.keyPossibilities k
Just r -> go Nothing [r]
where
k = toKey ks
go Nothing [] = return NotPresent
go (Just e) [] = return $ CheckFailure e
go olderr (r:rs) = do
v <- Remote.hasKey r k
case v of
Right True -> return Present
Right False -> go olderr rs
Left e -> go (Just e) rs
exitResult :: Result -> Annex a
exitResult Present = liftIO exitSuccess
exitResult NotPresent = liftIO exitFailure
exitResult (CheckFailure msg) = liftIO $ do
hPutStrLn stderr msg
exitWith $ ExitFailure 100
batchResult :: Result -> Annex ()
batchResult Present = liftIO $ putStrLn "1"
batchResult NotPresent = liftIO $ putStrLn "0"
batchResult failure = exitResult failure
toKey :: String -> Key
toKey = fromMaybe (error "Bad key") . file2key
toRemote :: String -> Annex Remote
toRemote rn = maybe (error "Unknown remote") return
=<< Remote.byNameWithUUID (Just rn)

2
debian/changelog vendored
View file

@ -1,6 +1,8 @@
git-annex (6.20160212) UNRELEASED; urgency=medium
* Support getting files from read-only repositories.
* checkpresentkey: Allow to be run without an explicit remote.
* checkpresentkey: Added --batch.
-- Joey Hess <id@joeyh.name> Fri, 12 Feb 2016 14:03:46 -0400

View file

@ -4,16 +4,28 @@ git-annex checkpresentkey - check if key is present in remote
# SYNOPSIS
git annex checkpresentkey `key remote`
git annex checkpresentkey `key` `[remote]`
# DESCRIPTION
This plumbing-level command verifies if the specified key's content
is present in the specified remote.
When no remote is specified, it verifies if the key's content is present
somewhere, checking accessible remotes until it finds the content.
Exits 0 if the content is verified present, or 1 if it is verified to not
be present. If there is a problem checking the remote, the special
exit code 100 is used, and an error message is output to stderr.
be present. If there is a problem, the special exit code 100 is used,
and an error message is output to stderr.
# OPTIONS
* `--batch`
Enables batch mode. In this mode, the `key` is not specified at the
command line, but the `remote` may still be. Lines containing keys are
read from stdin, and a line is output with "1" if the key is verified to
be present, and "0" otherwise.
# SEE ALSO

View file

@ -1,3 +1,5 @@
While being asked to check if file is available from "[datalad-archives]" remote I need to check if the archive's key available. Ideally I wish I could ask through the ongoing interaction protocol, but if not, I could use smth like 'git annex checkpresentkey' but that one demands specification also of a remote which to check. In my case I just want to know if that key is available from any remote, so I could confirm that the file is still present in our archives remote, i.e. that it could be retrieved later on
[[!meta author=yoh]]
> [[done]]] --[[Joey]]

View file

@ -0,0 +1,9 @@
[[!comment format=mdwn
username="joey"
subject="""comment 1"""
date="2016-02-12T20:07:30Z"
content="""
Makes sense, and also I will add a --batch mode to it.
Done.
"""]]