git-annex/CmdLine.hs

139 lines
4.3 KiB
Haskell
Raw Normal View History

{- git-annex command line parsing and dispatch
-
- Copyright 2010-2012 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
2013-05-10 21:29:59 +00:00
{-# LANGUAGE CPP #-}
module CmdLine (
dispatch,
usage,
shutdown
) where
import qualified Control.Exception as E
import qualified Data.Map as M
import Control.Exception (throw)
import System.Console.GetOpt
#ifndef __WINDOWS__
import System.Posix.Signals
2013-05-10 21:29:59 +00:00
#endif
2011-10-05 20:02:51 +00:00
import Common.Annex
import qualified Annex
2011-10-04 04:40:47 +00:00
import qualified Annex.Queue
import qualified Git
import qualified Git.AutoCorrect
2011-10-04 04:40:47 +00:00
import Annex.Content
import Annex.Ssh
import Annex.Environment
import Command
import Types.Messages
2011-10-31 00:04:15 +00:00
type Params = [String]
type Flags = [Annex ()]
{- Runs the passed command line. -}
2012-07-02 04:53:00 +00:00
dispatch :: Bool -> Params -> [Command] -> [Option] -> [(String, String)] -> String -> IO Git.Repo -> IO ()
dispatch fuzzyok allargs allcmds commonoptions fields header getgitrepo = do
setupConsole
r <- E.try getgitrepo :: IO (Either E.SomeException Git.Repo)
case r of
2011-12-09 05:57:13 +00:00
Left e -> fromMaybe (throw e) (cmdnorepo cmd)
Right g -> do
state <- Annex.new g
(actions, state') <- Annex.run state $ do
checkEnvironment
checkfuzzy
2013-03-29 03:27:45 +00:00
forM_ fields $ uncurry Annex.setField
when (cmdnomessages cmd) $
Annex.setOutput QuietOutput
sequence_ flags
whenM (annexDebug <$> Annex.getGitConfig) $
liftIO enableDebugOutput
prepCommand cmd params
2012-09-16 00:46:38 +00:00
tryRun state' cmd $ [startup] ++ actions ++ [shutdown $ cmdnocommit cmd]
2012-11-11 04:51:07 +00:00
where
err msg = msg ++ "\n\n" ++ usage header allcmds
2012-11-11 04:51:07 +00:00
cmd = Prelude.head cmds
(fuzzy, cmds, name, args) = findCmd fuzzyok allargs allcmds err
2013-03-27 17:51:24 +00:00
(flags, params) = getOptCmd args cmd commonoptions
2012-11-11 04:51:07 +00:00
checkfuzzy = when fuzzy $
inRepo $ Git.AutoCorrect.prepare name cmdname cmds
2010-12-30 19:44:15 +00:00
{- Parses command line params far enough to find the Command to run, and
- returns the remaining params.
- Does fuzzy matching if necessary, which may result in multiple Commands. -}
findCmd :: Bool -> Params -> [Command] -> (String -> String) -> (Bool, [Command], String, Params)
findCmd fuzzyok argv cmds err
| isNothing name = error $ err "missing command"
| not (null exactcmds) = (False, exactcmds, fromJust name, args)
| fuzzyok && not (null inexactcmds) = (True, inexactcmds, fromJust name, args)
| otherwise = error $ err $ "unknown command " ++ fromJust name
2012-11-11 04:51:07 +00:00
where
(name, args) = findname argv []
findname [] c = (Nothing, reverse c)
findname (a:as) c
| "-" `isPrefixOf` a = findname as (a:c)
| otherwise = (Just a, reverse c ++ as)
exactcmds = filter (\c -> name == Just (cmdname c)) cmds
inexactcmds = case name of
Nothing -> []
Just n -> Git.AutoCorrect.fuzzymatches n cmdname cmds
{- Parses command line options, and returns actions to run to configure flags
- and the remaining parameters for the command. -}
2013-03-27 17:51:24 +00:00
getOptCmd :: Params -> Command -> [Option] -> (Flags, Params)
getOptCmd argv cmd commonoptions = check $
getOpt Permute (commonoptions ++ cmdoptions cmd) argv
2012-11-11 04:51:07 +00:00
where
check (flags, rest, []) = (flags, rest)
2013-03-27 17:51:24 +00:00
check (_, _, errs) = error $ unlines
[ concat errs
, commandUsage cmd
]
{- Runs a list of Annex actions. Catches IO errors and continues
- (but explicitly thrown errors terminate the whole command).
-}
2011-10-31 00:04:15 +00:00
tryRun :: Annex.AnnexState -> Command -> [CommandCleanup] -> IO ()
tryRun = tryRun' 0
2011-10-31 00:04:15 +00:00
tryRun' :: Integer -> Annex.AnnexState -> Command -> [CommandCleanup] -> IO ()
tryRun' errnum _ cmd []
| errnum > 0 = error $ cmdname cmd ++ ": " ++ show errnum ++ " failed"
2012-04-22 03:32:33 +00:00
| otherwise = noop
tryRun' errnum state cmd (a:as) = do
r <- run
handle $! r
2012-11-11 04:51:07 +00:00
where
run = tryIO $ Annex.run state $ do
Annex.Queue.flushWhenFull
a
handle (Left err) = showerr err >> cont False state
handle (Right (success, state')) = cont success state'
cont success s = do
let errnum' = if success then errnum else errnum + 1
(tryRun' $! errnum') s cmd as
showerr err = Annex.eval state $ do
showErr err
showEndFail
{- Actions to perform each time ran. -}
startup :: Annex Bool
startup = liftIO $ do
#ifndef __WINDOWS__
void $ installHandler sigINT Default Nothing
#endif
return True
{- Cleanup actions. -}
shutdown :: Bool -> Annex Bool
2012-09-16 00:46:38 +00:00
shutdown nocommit = do
saveState nocommit
sequence_ =<< M.elems <$> Annex.getState Annex.cleanup
liftIO reapZombies -- zombies from long-running git processes
sshCleanup -- ssh connection caching
2011-01-30 03:32:32 +00:00
return True