initremote: Support --json and --json-error-messages

Including special --whatelse handling.

Otherwise, it seems unlikely to be too useful, but who knows.

Refactored code to call starting before displaying error messages.
This makes the error messages be captured by --json-error-messages

Sponsored-By: the NIH-funded NICEMAN (ReproNim TR&D3) project
This commit is contained in:
Joey Hess 2023-05-10 14:01:46 -04:00
parent 9812d9aaec
commit b3cc8dbacb
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
6 changed files with 96 additions and 41 deletions

View file

@ -39,8 +39,8 @@ git-annex (10.20230408) UNRELEASED; urgency=medium
broken.
* Support --json and --json-error-messages in more commands
(addunused, dead, describe, dropunused, expire, fix, importfeed, init,
log, merge, migrate, reinit, reinject, rekey, renameremote, rmurl,
semitrust, setpresentkey, trust, unannex, undo, untrust, unused,
initremote, log, merge, migrate, reinit, reinject, rekey, renameremote,
rmurl, semitrust, setpresentkey, trust, unannex, undo, untrust, unused,
upgrade)
* log: When --raw-date is used, display only seconds from the epoch, as
documented, omitting a trailing "s" that was included in the output

View file

@ -1,6 +1,6 @@
{- git-annex command
-
- Copyright 2011-2021 Joey Hess <id@joeyh.name>
- Copyright 2011-2023 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
@ -9,8 +9,6 @@
module Command.InitRemote where
import qualified Data.Map as M
import Command
import Annex.SpecialRemote
import qualified Remote
@ -23,12 +21,17 @@ import Types.GitConfig
import Types.ProposedAccepted
import Config
import Git.Config
import Utility.Aeson
import qualified Data.Map as M
import qualified Data.Text as T
cmd :: Command
cmd = command "initremote" SectionSetup
"creates a special (non-git) remote"
(paramPair paramName $ paramOptional $ paramRepeating paramParamValue)
(seek <$$> optParser)
cmd = withAnnexOptions [jsonOptions] $
command "initremote" SectionSetup
"creates a special (non-git) remote"
(paramPair paramName $ paramOptional $ paramRepeating paramParamValue)
(seek <$$> optParser)
data InitRemoteOptions = InitRemoteOptions
{ cmdparams :: CmdParams
@ -64,29 +67,35 @@ seek o = withWords (commandAction . (start o)) (cmdparams o)
start :: InitRemoteOptions -> [String] -> CommandStart
start _ [] = giveup "Specify a name for the remote."
start o (name:ws) = ifM (not . null <$> findExisting name)
( giveup $ "There is already a special remote named \"" ++ name ++
"\". (Use enableremote to enable an existing special remote.)"
, ifM (isJust <$> Remote.byNameOnly name)
( giveup $ "There is already a remote named \"" ++ name ++ "\""
, do
sameasuuid <- maybe
(pure Nothing)
(Just . Sameas <$$> getParsed)
(sameas o)
c <- newConfig name sameasuuid
(Logs.Remote.keyValToConfig Proposed ws)
<$> remoteConfigMap
t <- either giveup return (findType c)
if whatElse o
then startingCustomOutput (ActionItemOther Nothing) $
describeOtherParamsFor c t
else starting "initremote" (ActionItemOther (Just (UnquotedString name))) si $
perform t name c o
)
)
start o (name:ws) = do
if whatElse o
then ifM jsonOutputEnabled
( starting "initremote" ai si $ prep $ \c t ->
describeOtherParamsFor c t
, startingCustomOutput (ActionItemOther Nothing) $ prep $ \c t ->
describeOtherParamsFor c t
)
else starting "initremote" ai si $ prep $ \c t ->
perform t name c o
where
si = SeekInput [name]
prep a = do
whenM (not . null <$> findExisting name) $
giveup $ "There is already a special remote named \"" ++ name ++
"\". (Use enableremote to enable an existing special remote.)"
whenM (isJust <$> Remote.byNameOnly name) $
giveup $ "There is already a remote named \"" ++ name ++ "\""
sameasuuid <- maybe
(pure Nothing)
(Just . Sameas <$$> getParsed)
(sameas o)
c <- newConfig name sameasuuid
(Logs.Remote.keyValToConfig Proposed ws)
<$> remoteConfigMap
t <- either giveup return (findType c)
a c t
si = SeekInput (name:ws)
ai = ActionItemOther (Just (UnquotedString name))
perform :: RemoteType -> String -> R.RemoteConfig -> InitRemoteOptions -> CommandPerform
perform t name c o = do
@ -126,18 +135,36 @@ describeOtherParamsFor c t = do
cp <- R.configParser t c
let l = map mk (filter notinconfig $ remoteConfigFieldParsers cp)
++ map mk' (maybe [] snd (remoteConfigRestPassthrough cp))
liftIO $ forM_ l $ \(p, fd, vd) -> case fd of
HiddenField -> return ()
FieldDesc d -> do
putStrLn p
putStrLn ("\t" ++ d)
case vd of
Nothing -> return ()
Just (ValueDesc d') ->
putStrLn $ "\t(" ++ d' ++ ")"
ifM jsonOutputEnabled
( maybeAddJSONField "whatelse" $ M.fromList $ mkjson l
, liftIO $ forM_ l $ \(p, fd, vd) -> case fd of
HiddenField -> return ()
FieldDesc d -> do
putStrLn p
putStrLn ("\t" ++ d)
case vd of
Nothing -> return ()
Just (ValueDesc d') ->
putStrLn $ "\t(" ++ d' ++ ")"
)
next $ return True
where
mkjson = mapMaybe $ \(p, fd, vd) ->
case fd of
HiddenField -> Nothing
FieldDesc d -> Just
( T.pack p
, M.fromList
[ ("description" :: T.Text, d)
, ("valuedescription", case vd of
Nothing -> ""
Just (ValueDesc d') -> d')
]
)
notinconfig fp = not (M.member (parserForField fp) c)
mk fp = ( fromProposedAccepted (parserForField fp)
, fieldDesc fp
, valueDesc fp

View file

@ -47,6 +47,8 @@ want to use `git annex renameremote`.
git annex initremote mys3 type=S3 --whatelse
For a machine-readable list of the parameters, use this with --json.
* `--fast`
When initializing a remote that uses encryption, a cryptographic key is
@ -80,6 +82,16 @@ want to use `git annex renameremote`.
branch. The special remote will only be usable from the repository where
it was created.
* `--json`
Enable JSON output. This is intended to be parsed by programs that use
git-annex.
* `--json-error-messages`
Messages that would normally be output to standard error are included in
the JSON instead.
* Also the [[git-annex-common-options]](1) can be used.
# COMMON CONFIGURATION PARAMETERS

View file

@ -39,12 +39,12 @@ These commands have been updated to support --json:
* git-annex-importfeed
* git-annex-merge
* git-annex-upgrade
* git-annex-initremote
Provisional list of commands that don't support --json and maybe should:
* git-annex-configremote
* git-annex-enableremote
* git-annex-initremote
These commands could support json, but I punted:

View file

@ -57,3 +57,5 @@ Looking at the [protocol](https://git-annex.branchable.com/design/external_speci
[[!meta author=yoh]]
[[!tag projects/datalad]]
> [[done]] --[[Joey]]

View file

@ -0,0 +1,14 @@
[[!comment format=mdwn
username="joey"
subject="""comment 2"""
date="2023-05-10T16:56:37Z"
content="""
I'm still not seeing much of an application for this, but since I've been
adding --json support to most git-annex commands anyway recently, and got
to initremote, I did go ahead and make --whatelse --json work.
Currently only the field name and description, and a description of the
allowed values are in there. It might be possible to add more information
like type or required or not, but I'd want to work with someone who was
consuming that information to do that.
"""]]