Make --help work when not in a git repository. Closes: #758592
Note that this means getopt parsing is done even when not in a git repository, even though currently cmdnorepo is not passed the results of it. I'd like to move to cmdnorepo not doing its own ad-hoc option parsing, so this is really a good thing. (But as long as eg, getOptionFlag needs an Annex monad, it cannot be used in cmdnorepo handling.) There is a potential for problems if any cmdnorepo branch of a command handles options that are not in its regular getopt, but that would be a bug anyway.
This commit is contained in:
parent
4b3f03ef38
commit
37293dc28f
2 changed files with 30 additions and 21 deletions
45
CmdLine.hs
45
CmdLine.hs
|
@ -6,6 +6,7 @@
|
||||||
-}
|
-}
|
||||||
|
|
||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
|
{-# LANGUAGE BangPatterns #-}
|
||||||
|
|
||||||
module CmdLine (
|
module CmdLine (
|
||||||
dispatch,
|
dispatch,
|
||||||
|
@ -34,28 +35,30 @@ import Types.Messages
|
||||||
dispatch :: Bool -> CmdParams -> [Command] -> [Option] -> [(String, String)] -> String -> IO Git.Repo -> IO ()
|
dispatch :: Bool -> CmdParams -> [Command] -> [Option] -> [(String, String)] -> String -> IO Git.Repo -> IO ()
|
||||||
dispatch fuzzyok allargs allcmds commonoptions fields header getgitrepo = do
|
dispatch fuzzyok allargs allcmds commonoptions fields header getgitrepo = do
|
||||||
setupConsole
|
setupConsole
|
||||||
r <- E.try getgitrepo :: IO (Either E.SomeException Git.Repo)
|
case getOptCmd args cmd commonoptions of
|
||||||
case r of
|
Right (flags, params) -> go flags params
|
||||||
Left e -> maybe (throw e) (\a -> a params) (cmdnorepo cmd)
|
=<< (E.try getgitrepo :: IO (Either E.SomeException Git.Repo))
|
||||||
Right g -> do
|
Left parseerr -> error parseerr
|
||||||
state <- Annex.new g
|
|
||||||
Annex.eval state $ do
|
|
||||||
checkEnvironment
|
|
||||||
checkfuzzy
|
|
||||||
forM_ fields $ uncurry Annex.setField
|
|
||||||
when (cmdnomessages cmd) $
|
|
||||||
Annex.setOutput QuietOutput
|
|
||||||
sequence_ flags
|
|
||||||
whenM (annexDebug <$> Annex.getGitConfig) $
|
|
||||||
liftIO enableDebugOutput
|
|
||||||
startup
|
|
||||||
performCommandAction cmd params
|
|
||||||
shutdown $ cmdnocommit cmd
|
|
||||||
where
|
where
|
||||||
|
go flags params (Right g) = do
|
||||||
|
state <- Annex.new g
|
||||||
|
Annex.eval state $ do
|
||||||
|
checkEnvironment
|
||||||
|
checkfuzzy
|
||||||
|
forM_ fields $ uncurry Annex.setField
|
||||||
|
when (cmdnomessages cmd) $
|
||||||
|
Annex.setOutput QuietOutput
|
||||||
|
sequence_ flags
|
||||||
|
whenM (annexDebug <$> Annex.getGitConfig) $
|
||||||
|
liftIO enableDebugOutput
|
||||||
|
startup
|
||||||
|
performCommandAction cmd params
|
||||||
|
shutdown $ cmdnocommit cmd
|
||||||
|
go _flags params (Left e) =
|
||||||
|
maybe (throw e) (\a -> a params) (cmdnorepo cmd)
|
||||||
err msg = msg ++ "\n\n" ++ usage header allcmds
|
err msg = msg ++ "\n\n" ++ usage header allcmds
|
||||||
cmd = Prelude.head cmds
|
cmd = Prelude.head cmds
|
||||||
(fuzzy, cmds, name, args) = findCmd fuzzyok allargs allcmds err
|
(fuzzy, cmds, name, args) = findCmd fuzzyok allargs allcmds err
|
||||||
(flags, params) = getOptCmd args cmd commonoptions
|
|
||||||
checkfuzzy = when fuzzy $
|
checkfuzzy = when fuzzy $
|
||||||
inRepo $ Git.AutoCorrect.prepare name cmdname cmds
|
inRepo $ Git.AutoCorrect.prepare name cmdname cmds
|
||||||
|
|
||||||
|
@ -81,12 +84,12 @@ findCmd fuzzyok argv cmds err
|
||||||
|
|
||||||
{- Parses command line options, and returns actions to run to configure flags
|
{- Parses command line options, and returns actions to run to configure flags
|
||||||
- and the remaining parameters for the command. -}
|
- and the remaining parameters for the command. -}
|
||||||
getOptCmd :: CmdParams -> Command -> [Option] -> ([Annex ()], CmdParams)
|
getOptCmd :: CmdParams -> Command -> [Option] -> Either String ([Annex ()], CmdParams)
|
||||||
getOptCmd argv cmd commonoptions = check $
|
getOptCmd argv cmd commonoptions = check $
|
||||||
getOpt Permute (commonoptions ++ cmdoptions cmd) argv
|
getOpt Permute (commonoptions ++ cmdoptions cmd) argv
|
||||||
where
|
where
|
||||||
check (flags, rest, []) = (flags, rest)
|
check (flags, rest, []) = Right (flags, rest)
|
||||||
check (_, _, errs) = error $ unlines
|
check (_, _, errs) = Left $ unlines
|
||||||
[ concat errs
|
[ concat errs
|
||||||
, commandUsage cmd
|
, commandUsage cmd
|
||||||
]
|
]
|
||||||
|
|
6
debian/changelog
vendored
6
debian/changelog
vendored
|
@ -1,3 +1,9 @@
|
||||||
|
git-annex (5.20140818) UNRELEASED; urgency=medium
|
||||||
|
|
||||||
|
* Make --help work when not in a git repository. Closes: #758592
|
||||||
|
|
||||||
|
-- Joey Hess <joeyh@debian.org> Tue, 19 Aug 2014 12:52:41 -0400
|
||||||
|
|
||||||
git-annex (5.20140817) unstable; urgency=medium
|
git-annex (5.20140817) unstable; urgency=medium
|
||||||
|
|
||||||
* New chunk= option to chunk files stored in special remotes.
|
* New chunk= option to chunk files stored in special remotes.
|
||||||
|
|
Loading…
Reference in a new issue