summaryrefslogtreecommitdiff
path: root/CmdLine/Option.hs
diff options
context:
space:
mode:
Diffstat (limited to 'CmdLine/Option.hs')
-rw-r--r--CmdLine/Option.hs96
1 files changed, 44 insertions, 52 deletions
diff --git a/CmdLine/Option.hs b/CmdLine/Option.hs
index 0cda34ba1..4e201cbd4 100644
--- a/CmdLine/Option.hs
+++ b/CmdLine/Option.hs
@@ -5,45 +5,55 @@
- Licensed under the GNU GPL version 3 or higher.
-}
-module CmdLine.Option (
- commonOptions,
- flagOption,
- fieldOption,
- optionName,
- optionParam,
- ArgDescr(..),
- OptDescr(..),
-) where
+module CmdLine.Option where
-import System.Console.GetOpt
+import Options.Applicative
import Common.Annex
+import CmdLine.Usage
+import CmdLine.GlobalSetter
import qualified Annex
import Types.Messages
-import Types.DesktopNotify
-import CmdLine.Usage
-
--- Options accepted by both git-annex and git-annex-shell sub-commands.
-commonOptions :: [Option]
-commonOptions =
- [ Option [] ["force"] (NoArg (setforce True))
- "allow actions that may lose annexed data"
- , Option ['F'] ["fast"] (NoArg (setfast True))
- "avoid slow operations"
- , Option ['q'] ["quiet"] (NoArg (Annex.setOutput QuietOutput))
- "avoid verbose output"
- , Option ['v'] ["verbose"] (NoArg (Annex.setOutput NormalOutput))
- "allow verbose output (default)"
- , Option ['d'] ["debug"] (NoArg setdebug)
- "show debug messages"
- , Option [] ["no-debug"] (NoArg unsetdebug)
- "don't show debug messages"
- , Option ['b'] ["backend"] (ReqArg setforcebackend paramName)
- "specify key-value backend to use"
- , Option [] ["notify-finish"] (NoArg (setdesktopnotify mkNotifyFinish))
- "show desktop notification after transfer finishes"
- , Option [] ["notify-start"] (NoArg (setdesktopnotify mkNotifyStart))
- "show desktop notification after transfer completes"
+import Types.DeferredParse
+
+-- Global options accepted by both git-annex and git-annex-shell sub-commands.
+commonGlobalOptions :: [GlobalOption]
+commonGlobalOptions =
+ [ globalFlag (setforce True)
+ ( long "force"
+ <> help "allow actions that may lose annexed data"
+ <> hidden
+ )
+ , globalFlag (setfast True)
+ ( long "fast" <> short 'F'
+ <> help "avoid slow operations"
+ <> hidden
+ )
+ , globalFlag (Annex.setOutput QuietOutput)
+ ( long "quiet" <> short 'q'
+ <> help "avoid verbose output"
+ <> hidden
+ )
+ , globalFlag (Annex.setOutput NormalOutput)
+ ( long "verbose" <> short 'v'
+ <> help "allow verbose output (default)"
+ <> hidden
+ )
+ , globalFlag setdebug
+ ( long "debug" <> short 'd'
+ <> help "show debug messages"
+ <> hidden
+ )
+ , globalFlag unsetdebug
+ ( long "no-debug"
+ <> help "don't show debug messages"
+ <> hidden
+ )
+ , globalSetter setforcebackend $ strOption
+ ( long "backend" <> short 'b' <> metavar paramName
+ <> help "specify key-value backend to use"
+ <> hidden
+ )
]
where
setforce v = Annex.changeState $ \s -> s { Annex.force = v }
@@ -51,21 +61,3 @@ commonOptions =
setforcebackend v = Annex.changeState $ \s -> s { Annex.forcebackend = Just v }
setdebug = Annex.changeGitConfig $ \c -> c { annexDebug = True }
unsetdebug = Annex.changeGitConfig $ \c -> c { annexDebug = False }
- setdesktopnotify v = Annex.changeState $ \s -> s { Annex.desktopnotify = Annex.desktopnotify s <> v }
-
-{- An option that sets a flag. -}
-flagOption :: String -> String -> String -> Option
-flagOption short opt description =
- Option short [opt] (NoArg (Annex.setFlag opt)) description
-
-{- An option that sets a field. -}
-fieldOption :: String -> String -> String -> String -> Option
-fieldOption short opt paramdesc description =
- Option short [opt] (ReqArg (Annex.setField opt) paramdesc) description
-
-{- The flag or field name used for an option. -}
-optionName :: Option -> String
-optionName (Option _ o _ _) = Prelude.head o
-
-optionParam :: Option -> String
-optionParam o = "--" ++ optionName o