wired up global options

Note that I ran into a problem where parsing the global options looped
forever, eating memory. It was somehow caused by stacking
combineGlobalSetters inside a combineGlobalSetters. Maybe due to both
using "many"? Anyway, changed things to avoid that.
This commit is contained in:
Joey Hess 2015-07-10 02:03:03 -04:00
parent adb9fddfdd
commit b66a2d6c5b
5 changed files with 25 additions and 24 deletions

View file

@ -33,7 +33,7 @@ import Command
import Types.Messages import Types.Messages
{- Runs the passed command line. -} {- Runs the passed command line. -}
dispatch :: Bool -> CmdParams -> [Command] -> Parser GlobalSetter -> [(String, String)] -> IO Git.Repo -> String -> String -> IO () dispatch :: Bool -> CmdParams -> [Command] -> [Parser GlobalSetter] -> [(String, String)] -> IO Git.Repo -> String -> String -> IO ()
dispatch fuzzyok allargs allcmds globaloptions fields getgitrepo progname progdesc = do dispatch fuzzyok allargs allcmds globaloptions fields getgitrepo progname progdesc = do
setupConsole setupConsole
go =<< (E.try getgitrepo :: IO (Either E.SomeException Git.Repo)) go =<< (E.try getgitrepo :: IO (Either E.SomeException Git.Repo))
@ -43,30 +43,30 @@ dispatch fuzzyok allargs allcmds globaloptions fields getgitrepo progname progde
Annex.eval state $ do Annex.eval state $ do
checkEnvironment checkEnvironment
forM_ fields $ uncurry Annex.setField forM_ fields $ uncurry Annex.setField
(cmd, seek) <- parsewith cmdparser ((cmd, seek), globalconfig) <- parsewith cmdparser
(\a -> inRepo $ a . Just) (\a -> inRepo $ a . Just)
when (cmdnomessages cmd) $ when (cmdnomessages cmd) $
Annex.setOutput QuietOutput Annex.setOutput QuietOutput
-- TODO: propigate global options to annex state (how?) getParsed globalconfig
whenM (annexDebug <$> Annex.getGitConfig) $ whenM (annexDebug <$> Annex.getGitConfig) $
liftIO enableDebugOutput liftIO enableDebugOutput
startup startup
performCommandAction cmd seek $ performCommandAction cmd seek $
shutdown $ cmdnocommit cmd shutdown $ cmdnocommit cmd
go (Left norepo) = do go (Left norepo) = do
(_, a) <- parsewith ((_, a), _) <- parsewith
(fromMaybe (throw norepo) . cmdnorepo) (fromMaybe (throw norepo) . cmdnorepo)
(\a -> a =<< Git.Config.global) (\a -> a =<< Git.Config.global)
a a
parsewith getparser ingitrepo = parsewith getparser ingitrepo =
case parseCmd progname progdesc allargs allcmds getparser of case parseCmd progname progdesc globaloptions allargs allcmds getparser of
O.Failure _ -> do O.Failure _ -> do
-- parse failed, so fall back to -- parse failed, so fall back to
-- fuzzy matching, or to showing usage -- fuzzy matching, or to showing usage
when fuzzy $ when fuzzy $
ingitrepo autocorrect ingitrepo autocorrect
liftIO (O.handleParseResult (parseCmd progname progdesc correctedargs allcmds getparser)) liftIO (O.handleParseResult (parseCmd progname progdesc globaloptions correctedargs allcmds getparser))
res -> liftIO (O.handleParseResult res) res -> liftIO (O.handleParseResult res)
where where
autocorrect = Git.AutoCorrect.prepare (fromJust inputcmdname) cmdname cmds autocorrect = Git.AutoCorrect.prepare (fromJust inputcmdname) cmdname cmds
@ -81,10 +81,13 @@ dispatch fuzzyok allargs allcmds globaloptions fields getgitrepo progname progde
Just n -> n:args Just n -> n:args
{- Parses command line, selecting one of the commands from the list. -} {- Parses command line, selecting one of the commands from the list. -}
parseCmd :: String -> String -> CmdParams -> [Command] -> (Command -> O.Parser v) -> O.ParserResult (Command, v) parseCmd :: String -> String -> [Parser GlobalSetter] -> CmdParams -> [Command] -> (Command -> O.Parser v) -> O.ParserResult ((Command, v), GlobalSetter)
parseCmd progname progdesc allargs allcmds getparser = O.execParserPure (O.prefs O.idm) pinfo allargs parseCmd progname progdesc globaloptions allargs allcmds getparser =
O.execParserPure (O.prefs O.idm) pinfo allargs
where where
pinfo = O.info (O.helper <*> subcmds) (O.progDescDoc (Just intro)) pinfo = O.info
(O.helper <*> ((,) <$> subcmds <*> combineGlobalSetters globaloptions))
(O.progDescDoc (Just intro))
subcmds = O.hsubparser $ mconcat $ map mkcommand allcmds subcmds = O.hsubparser $ mconcat $ map mkcommand allcmds
mkcommand c = O.command (cmdname c) $ O.info (mkparser c) $ O.fullDesc mkcommand c = O.command (cmdname c) $ O.info (mkparser c) $ O.fullDesc
<> O.header (synopsis (progname ++ " " ++ cmdname c) (cmddesc c)) <> O.header (synopsis (progname ++ " " ++ cmdname c) (cmddesc c))

View file

@ -29,10 +29,9 @@ import CmdLine.Usage
-- 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.
gitAnnexGlobalOptions :: Parser GlobalSetter gitAnnexGlobalOptions :: [Parser GlobalSetter]
gitAnnexGlobalOptions = globalSetters gitAnnexGlobalOptions = commonGlobalOptions ++
[ commonGlobalOptions [ globalSetter setnumcopies $ option auto
, globalSetter setnumcopies $ option auto
( long "numcopies" <> short 'N' <> metavar paramNumber ( long "numcopies" <> short 'N' <> metavar paramNumber
<> help "override default number of copies" <> help "override default number of copies"
) )

View file

@ -53,14 +53,13 @@ cmds = map adddirparam $ cmds_readonly ++ cmds_notreadonly
where where
adddirparam c = c { cmdparamdesc = "DIRECTORY " ++ cmdparamdesc c } adddirparam c = c { cmdparamdesc = "DIRECTORY " ++ cmdparamdesc c }
options :: Parser GlobalSetter globalOptions :: [Parser GlobalSetter]
options = globalSetters globalOptions =
[ commonGlobalOptions globalSetter checkUUID (strOption
, globalSetter checkUUID $ strOption
( long "uuid" <> metavar paramUUID ( long "uuid" <> metavar paramUUID
<> help "local repository uuid" <> help "local repository uuid"
) ))
] : commonGlobalOptions
where where
checkUUID expected = getUUID >>= check checkUUID expected = getUUID >>= check
where where
@ -101,7 +100,7 @@ builtin cmd dir params = do
let (params', fieldparams, opts) = partitionParams params let (params', fieldparams, opts) = partitionParams params
rsyncopts = ("RsyncOptions", unwords opts) rsyncopts = ("RsyncOptions", unwords opts)
fields = rsyncopts : filter checkField (parseFields fieldparams) fields = rsyncopts : filter checkField (parseFields fieldparams)
dispatch False (cmd : params') cmds options fields mkrepo dispatch False (cmd : params') cmds globalOptions fields mkrepo
"git-annex-shell" "git-annex-shell"
"Restricted login shell for git-annex only SSH access" "Restricted login shell for git-annex only SSH access"
where where

View file

@ -25,8 +25,8 @@ import Types.Messages
import Types.DeferredParse import Types.DeferredParse
-- Global options accepted by both git-annex and git-annex-shell sub-commands. -- Global options accepted by both git-annex and git-annex-shell sub-commands.
commonGlobalOptions :: Parser GlobalSetter commonGlobalOptions :: [Parser GlobalSetter]
commonGlobalOptions = globalSetters commonGlobalOptions =
[ globalFlag (setforce True) [ globalFlag (setforce True)
( long "force" ( long "force"
<> help "allow actions that may lose annexed data" <> help "allow actions that may lose annexed data"

View file

@ -46,6 +46,6 @@ globalFlag setter = flag' (DeferredParse setter)
globalSetter :: (v -> Annex ()) -> Parser v -> Parser GlobalSetter globalSetter :: (v -> Annex ()) -> Parser v -> Parser GlobalSetter
globalSetter setter parser = DeferredParse . setter <$> parser globalSetter setter parser = DeferredParse . setter <$> parser
globalSetters :: [Parser GlobalSetter] -> Parser GlobalSetter combineGlobalSetters :: [Parser GlobalSetter] -> Parser GlobalSetter
globalSetters l = DeferredParse . sequence_ . map getParsed combineGlobalSetters l = DeferredParse . sequence_ . map getParsed
<$> many (foldl1 (<|>) l) <$> many (foldl1 (<|>) l)