make sync --no-content be accepted
It's the default, but this is a step toward changing that default later..
This commit is contained in:
parent
3435403089
commit
7be58b5e11
2 changed files with 48 additions and 3 deletions
|
@ -47,6 +47,7 @@ import Annex.AutoMerge
|
||||||
import Annex.Ssh
|
import Annex.Ssh
|
||||||
import Annex.BloomFilter
|
import Annex.BloomFilter
|
||||||
import Utility.Bloom
|
import Utility.Bloom
|
||||||
|
import Utility.OptParse
|
||||||
|
|
||||||
import Control.Concurrent.MVar
|
import Control.Concurrent.MVar
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
|
@ -67,9 +68,8 @@ data SyncOptions = SyncOptions
|
||||||
optParser :: CmdParamsDesc -> Parser SyncOptions
|
optParser :: CmdParamsDesc -> Parser SyncOptions
|
||||||
optParser desc = SyncOptions
|
optParser desc = SyncOptions
|
||||||
<$> cmdParams desc
|
<$> cmdParams desc
|
||||||
<*> switch
|
<*> invertableSwitch "content" False
|
||||||
( long "content"
|
( help "also transfer file contents"
|
||||||
<> help "also transfer file contents"
|
|
||||||
)
|
)
|
||||||
<*> optional (strOption
|
<*> optional (strOption
|
||||||
( long "message" <> short 'm' <> metavar "MSG"
|
( long "message" <> short 'm' <> metavar "MSG"
|
||||||
|
|
45
Utility/OptParse.hs
Normal file
45
Utility/OptParse.hs
Normal file
|
@ -0,0 +1,45 @@
|
||||||
|
{- optparse-applicative additions
|
||||||
|
-
|
||||||
|
- Copyright 2015 Joey Hess <id@joeyh.name>
|
||||||
|
-
|
||||||
|
- License: BSD-2-clause
|
||||||
|
-}
|
||||||
|
|
||||||
|
module Utility.OptParse where
|
||||||
|
|
||||||
|
import Options.Applicative
|
||||||
|
import Data.Monoid
|
||||||
|
|
||||||
|
-- | A switch that can be enabled using --foo and disabled using --no-foo.
|
||||||
|
--
|
||||||
|
-- The option modifier is applied to only the option that is *not* enabled
|
||||||
|
-- by default. For example:
|
||||||
|
--
|
||||||
|
-- > invertableSwitch "recursive" True (help "do not recurse into directories")
|
||||||
|
--
|
||||||
|
-- This example makes --recursive enabled by default, so
|
||||||
|
-- the help is shown only for --no-recursive.
|
||||||
|
invertableSwitch
|
||||||
|
:: String -- ^ long option
|
||||||
|
-> Bool -- ^ is switch enabled by default?
|
||||||
|
-> Mod FlagFields Bool -- ^ option modifier
|
||||||
|
-> Parser Bool
|
||||||
|
invertableSwitch longopt defv optmod = invertableSwitch' longopt defv
|
||||||
|
(if defv then mempty else optmod)
|
||||||
|
(if defv then optmod else mempty)
|
||||||
|
|
||||||
|
-- | Allows providing option modifiers for both --foo and --no-foo.
|
||||||
|
invertableSwitch'
|
||||||
|
:: String -- ^ long option (eg "foo")
|
||||||
|
-> Bool -- ^ is switch enabled by default?
|
||||||
|
-> Mod FlagFields Bool -- ^ option modifier for --foo
|
||||||
|
-> Mod FlagFields Bool -- ^ option modifier for --no-foo
|
||||||
|
-> Parser Bool
|
||||||
|
invertableSwitch' longopt defv enmod dismod = collapse <$> many
|
||||||
|
( flag' True (enmod <> long longopt)
|
||||||
|
<|> flag' False (dismod <> long nolongopt)
|
||||||
|
)
|
||||||
|
where
|
||||||
|
nolongopt = "no-" ++ longopt
|
||||||
|
collapse [] = defv
|
||||||
|
collapse l = last l
|
Loading…
Add table
Reference in a new issue