Improve bash completion, so it completes names of remotes and backends in appropriate places.

Not necessarily everywhere, but a lot of the most often used places.

Re the use of .Internal, see
https://github.com/pcapriotti/optparse-applicative/issues/155
This commit is contained in:
Joey Hess 2015-09-14 13:19:04 -04:00
parent ffa8221517
commit 3f47d1b351
5 changed files with 32 additions and 2 deletions

View file

@ -8,9 +8,11 @@
module CmdLine.GitAnnex.Options where module CmdLine.GitAnnex.Options where
import Options.Applicative import Options.Applicative
import Options.Applicative.Builder.Internal
import Common.Annex import Common.Annex
import qualified Git.Config import qualified Git.Config
import qualified Git.Construct
import Git.Types import Git.Types
import Types.TrustLevel import Types.TrustLevel
import Types.NumCopies import Types.NumCopies
@ -26,6 +28,8 @@ import qualified Limit.Wanted
import CmdLine.Option import CmdLine.Option
import CmdLine.Usage import CmdLine.Usage
import CmdLine.GlobalSetter import CmdLine.GlobalSetter
import qualified Backend
import qualified Types.Backend as Backend
-- Global options that are accepted by all git-annex sub-commands, -- Global options that are accepted by all git-annex sub-commands,
-- although not always used. -- although not always used.
@ -40,16 +44,19 @@ gitAnnexGlobalOptions = commonGlobalOptions ++
( long "trust" <> metavar paramRemote ( long "trust" <> metavar paramRemote
<> help "override trust setting" <> help "override trust setting"
<> hidden <> hidden
<> completeRemotes
) )
, globalSetter (Remote.forceTrust SemiTrusted) $ strOption , globalSetter (Remote.forceTrust SemiTrusted) $ strOption
( long "semitrust" <> metavar paramRemote ( long "semitrust" <> metavar paramRemote
<> help "override trust setting back to default" <> help "override trust setting back to default"
<> hidden <> hidden
<> completeRemotes
) )
, globalSetter (Remote.forceTrust UnTrusted) $ strOption , globalSetter (Remote.forceTrust UnTrusted) $ strOption
( long "untrust" <> metavar paramRemote ( long "untrust" <> metavar paramRemote
<> help "override trust setting to untrusted" <> help "override trust setting to untrusted"
<> hidden <> hidden
<> completeRemotes
) )
, globalSetter setgitconfig $ strOption , globalSetter setgitconfig $ strOption
( long "config" <> short 'c' <> metavar "NAME=VALUE" ( long "config" <> short 'c' <> metavar "NAME=VALUE"
@ -98,7 +105,9 @@ parseAutoOption = switch
) )
parseRemoteOption :: Parser RemoteName -> Parser (DeferredParse Remote) parseRemoteOption :: Parser RemoteName -> Parser (DeferredParse Remote)
parseRemoteOption p = DeferredParse . (fromJust <$$> Remote.byNameWithUUID) . Just <$> p parseRemoteOption p = DeferredParse
. (fromJust <$$> Remote.byNameWithUUID)
. Just <$> p
data FromToOptions data FromToOptions
= FromRemote (DeferredParse Remote) = FromRemote (DeferredParse Remote)
@ -117,12 +126,14 @@ parseFromOption :: Parser (DeferredParse Remote)
parseFromOption = parseRemoteOption $ strOption parseFromOption = parseRemoteOption $ strOption
( long "from" <> short 'f' <> metavar paramRemote ( long "from" <> short 'f' <> metavar paramRemote
<> help "source remote" <> help "source remote"
<> completeRemotes
) )
parseToOption :: Parser (DeferredParse Remote) parseToOption :: Parser (DeferredParse Remote)
parseToOption = parseRemoteOption $ strOption parseToOption = parseRemoteOption $ strOption
( long "to" <> short 't' <> metavar paramRemote ( long "to" <> short 't' <> metavar paramRemote
<> help "destination remote" <> help "destination remote"
<> completeRemotes
) )
-- Options for acting on keys, rather than work tree files. -- Options for acting on keys, rather than work tree files.
@ -179,6 +190,7 @@ nonWorkTreeMatchingOptions' =
( long "in" <> short 'i' <> metavar paramRemote ( long "in" <> short 'i' <> metavar paramRemote
<> help "match files present in a remote" <> help "match files present in a remote"
<> hidden <> hidden
<> completeRemotes
) )
, globalSetter Limit.addCopies $ strOption , globalSetter Limit.addCopies $ strOption
( long "copies" <> short 'C' <> metavar paramRemote ( long "copies" <> short 'C' <> metavar paramRemote
@ -199,6 +211,7 @@ nonWorkTreeMatchingOptions' =
( long "inbackend" <> short 'B' <> metavar paramName ( long "inbackend" <> short 'B' <> metavar paramName
<> help "match files using a key-value backend" <> help "match files using a key-value backend"
<> hidden <> hidden
<> completeBackends
) )
, globalSetter Limit.addInAllGroup $ strOption , globalSetter Limit.addInAllGroup $ strOption
( long "inallgroup" <> metavar paramGroup ( long "inallgroup" <> metavar paramGroup
@ -299,3 +312,13 @@ parseDaemonOptions = DaemonOptions
( long "stop" ( long "stop"
<> help "stop daemon" <> help "stop daemon"
) )
completeRemotes :: HasCompleter f => Mod f a
completeRemotes = completer $ mkCompleter $ \input -> do
r <- maybe (pure Nothing) (Just <$$> Git.Config.read)
=<< Git.Construct.fromCwd
return $ filter (input `isPrefixOf`)
(maybe [] (mapMaybe remoteName . remotes) r)
completeBackends :: HasCompleter f => Mod f a
completeBackends = completeWith (map Backend.name Backend.list)

View file

@ -46,6 +46,7 @@ parseDropFromOption :: Parser (DeferredParse Remote)
parseDropFromOption = parseRemoteOption $ strOption parseDropFromOption = parseRemoteOption $ strOption
( long "from" <> short 'f' <> metavar paramRemote ( long "from" <> short 'f' <> metavar paramRemote
<> help "drop content from a remote" <> help "drop content from a remote"
<> completeRemotes
) )
seek :: DropOptions -> CommandSeek seek :: DropOptions -> CommandSeek

View file

@ -67,6 +67,7 @@ optParser desc = FsckOptions
<*> optional (parseRemoteOption $ strOption <*> optional (parseRemoteOption $ strOption
( long "from" <> short 'f' <> metavar paramRemote ( long "from" <> short 'f' <> metavar paramRemote
<> help "check remote" <> help "check remote"
<> completeRemotes
)) ))
<*> optional parseincremental <*> optional parseincremental
<*> optional (parseKeyOptions False) <*> optional (parseKeyOptions False)

View file

@ -70,7 +70,10 @@ data SyncOptions = SyncOptions
optParser :: CmdParamsDesc -> Parser SyncOptions optParser :: CmdParamsDesc -> Parser SyncOptions
optParser desc = SyncOptions optParser desc = SyncOptions
<$> cmdParams desc <$> (many $ argument str
( metavar desc
<> completeRemotes
))
<*> invertableSwitch "commit" True <*> invertableSwitch "commit" True
( help "avoid git commit" ( help "avoid git commit"
) )

2
debian/changelog vendored
View file

@ -22,6 +22,8 @@ git-annex (5.20150825) UNRELEASED; urgency=medium
--no-content options to specify the (current) default behavior. --no-content options to specify the (current) default behavior.
* annex.hardlink extended to also try to use hard links when copying from * annex.hardlink extended to also try to use hard links when copying from
the repository to a remote. the repository to a remote.
* Improve bash completion, so it completes names of remotes and backends
in appropriate places.
-- Joey Hess <id@joeyh.name> Tue, 01 Sep 2015 14:46:18 -0700 -- Joey Hess <id@joeyh.name> Tue, 01 Sep 2015 14:46:18 -0700