wire tasty's option parser into the main program option parser
This makes bash completion work for git-annex test, and is generally cleaner.
This commit is contained in:
parent
02d522a12e
commit
730cc3feb5
6 changed files with 82 additions and 82 deletions
|
@ -1,6 +1,6 @@
|
||||||
{- git-annex main program
|
{- git-annex main program
|
||||||
-
|
-
|
||||||
- Copyright 2010-2014 Joey Hess <id@joeyh.name>
|
- Copyright 2010-2015 Joey Hess <id@joeyh.name>
|
||||||
-
|
-
|
||||||
- Licensed under the GNU GPL version 3 or higher.
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
@ -14,6 +14,7 @@ import CmdLine
|
||||||
import Command
|
import Command
|
||||||
import Utility.Env
|
import Utility.Env
|
||||||
import Annex.Ssh
|
import Annex.Ssh
|
||||||
|
import Types.Test
|
||||||
|
|
||||||
import qualified Command.Help
|
import qualified Command.Help
|
||||||
import qualified Command.Add
|
import qualified Command.Add
|
||||||
|
@ -117,8 +118,8 @@ import qualified Command.TestRemote
|
||||||
import System.Remote.Monitoring
|
import System.Remote.Monitoring
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
cmds :: [Command]
|
cmds :: Parser TestOptions -> Maybe TestRunner -> [Command]
|
||||||
cmds =
|
cmds testoptparser testrunner =
|
||||||
[ Command.Help.cmd
|
[ Command.Help.cmd
|
||||||
, Command.Add.cmd
|
, Command.Add.cmd
|
||||||
, Command.Get.cmd
|
, Command.Get.cmd
|
||||||
|
@ -213,21 +214,23 @@ cmds =
|
||||||
#endif
|
#endif
|
||||||
, Command.RemoteDaemon.cmd
|
, Command.RemoteDaemon.cmd
|
||||||
#endif
|
#endif
|
||||||
, Command.Test.cmd
|
, Command.Test.cmd testoptparser testrunner
|
||||||
#ifdef WITH_TESTSUITE
|
#ifdef WITH_TESTSUITE
|
||||||
, Command.FuzzTest.cmd
|
, Command.FuzzTest.cmd
|
||||||
, Command.TestRemote.cmd
|
, Command.TestRemote.cmd
|
||||||
#endif
|
#endif
|
||||||
]
|
]
|
||||||
|
|
||||||
run :: [String] -> IO ()
|
run :: Parser TestOptions -> Maybe TestRunner -> [String] -> IO ()
|
||||||
run args = do
|
run testoptparser testrunner args = do
|
||||||
#ifdef WITH_EKG
|
#ifdef WITH_EKG
|
||||||
_ <- forkServer "localhost" 4242
|
_ <- forkServer "localhost" 4242
|
||||||
#endif
|
#endif
|
||||||
go envmodes
|
go envmodes
|
||||||
where
|
where
|
||||||
go [] = dispatch True args cmds gitAnnexGlobalOptions [] Git.CurrentRepo.get
|
go [] = dispatch True args
|
||||||
|
(cmds testoptparser testrunner)
|
||||||
|
gitAnnexGlobalOptions [] Git.CurrentRepo.get
|
||||||
"git-annex"
|
"git-annex"
|
||||||
"manage files with git, without checking their contents in"
|
"manage files with git, without checking their contents in"
|
||||||
go ((v, a):rest) = maybe (go rest) a =<< getEnv v
|
go ((v, a):rest) = maybe (go rest) a =<< getEnv v
|
||||||
|
|
|
@ -1,6 +1,6 @@
|
||||||
{- git-annex command
|
{- git-annex command
|
||||||
-
|
-
|
||||||
- Copyright 2013 Joey Hess <id@joeyh.name>
|
- Copyright 2013-2015 Joey Hess <id@joeyh.name>
|
||||||
-
|
-
|
||||||
- Licensed under the GNU GPL version 3 or higher.
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
@ -10,31 +10,23 @@ module Command.Test where
|
||||||
import Common
|
import Common
|
||||||
import Command
|
import Command
|
||||||
import Messages
|
import Messages
|
||||||
|
import Types.Test
|
||||||
|
|
||||||
cmd :: Command
|
cmd :: Parser TestOptions -> Maybe TestRunner -> Command
|
||||||
cmd = noRepo (parseparams startIO) $ dontCheck repoExists $
|
cmd optparser runner = noRepo (startIO runner <$$> const optparser) $
|
||||||
|
dontCheck repoExists $
|
||||||
command "test" SectionTesting
|
command "test" SectionTesting
|
||||||
"run built-in test suite"
|
"run built-in test suite"
|
||||||
paramNothing (parseparams seek)
|
paramNothing (seek runner <$$> const optparser)
|
||||||
where
|
|
||||||
parseparams = withParams
|
|
||||||
|
|
||||||
seek :: CmdParams -> CommandSeek
|
seek :: Maybe TestRunner -> TestOptions -> CommandSeek
|
||||||
seek = withWords start
|
seek runner o = commandAction $ start runner o
|
||||||
|
|
||||||
{- We don't actually run the test suite here because of a dependency loop.
|
start :: Maybe TestRunner -> TestOptions -> CommandStart
|
||||||
- The main program notices when the command is test and runs it; this
|
start runner o = do
|
||||||
- function is never run if that works.
|
liftIO $ startIO runner o
|
||||||
-
|
|
||||||
- However, if git-annex is built without the test suite, just print a
|
|
||||||
- warning, and do not exit nonzero. This is so git-annex test can be run
|
|
||||||
- in debian/rules despite some architectures not being able to build the
|
|
||||||
- test suite.
|
|
||||||
-}
|
|
||||||
start :: [String] -> CommandStart
|
|
||||||
start ps = do
|
|
||||||
liftIO $ startIO ps
|
|
||||||
stop
|
stop
|
||||||
|
|
||||||
startIO :: CmdParams -> IO ()
|
startIO :: Maybe TestRunner -> TestOptions -> IO ()
|
||||||
startIO _ = warningIO "git-annex was built without its test suite; not testing"
|
startIO Nothing _ = warningIO "git-annex was built without its test suite; not testing"
|
||||||
|
startIO (Just runner) o = runner o
|
||||||
|
|
31
Test.hs
31
Test.hs
|
@ -1,6 +1,6 @@
|
||||||
{- git-annex test suite
|
{- git-annex test suite
|
||||||
-
|
-
|
||||||
- Copyright 2010-2013 Joey Hess <id@joeyh.name>
|
- Copyright 2010-2015 Joey Hess <id@joeyh.name>
|
||||||
-
|
-
|
||||||
- Licensed under the GNU GPL version 3 or higher.
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
@ -9,7 +9,22 @@
|
||||||
|
|
||||||
module Test where
|
module Test where
|
||||||
|
|
||||||
|
import Options.Applicative.Types
|
||||||
|
|
||||||
|
#ifndef WITH_TESTSUITE
|
||||||
|
|
||||||
|
import Options.Applicative (pure)
|
||||||
|
|
||||||
|
optParser :: Parser ()
|
||||||
|
optParser = pure ()
|
||||||
|
|
||||||
|
runner :: Maybe (() -> IO ())
|
||||||
|
runner = Nothing
|
||||||
|
|
||||||
|
#else
|
||||||
|
|
||||||
import Test.Tasty
|
import Test.Tasty
|
||||||
|
import Test.Tasty.Options
|
||||||
import Test.Tasty.Runners
|
import Test.Tasty.Runners
|
||||||
import Test.Tasty.HUnit
|
import Test.Tasty.HUnit
|
||||||
import Test.Tasty.QuickCheck
|
import Test.Tasty.QuickCheck
|
||||||
|
@ -20,7 +35,6 @@ import qualified Text.JSON
|
||||||
|
|
||||||
import Common
|
import Common
|
||||||
|
|
||||||
import qualified Utility.SubTasty
|
|
||||||
import qualified Utility.SafeCommand
|
import qualified Utility.SafeCommand
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
import qualified Annex.UUID
|
import qualified Annex.UUID
|
||||||
|
@ -81,10 +95,11 @@ import qualified Types.Crypto
|
||||||
import qualified Utility.Gpg
|
import qualified Utility.Gpg
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
main :: [String] -> IO ()
|
optParser :: Parser OptionSet
|
||||||
main ps = do
|
optParser = suiteOptionParser ingredients tests
|
||||||
opts <- Utility.SubTasty.parseOpts "test" ingredients tests ("test":ps)
|
|
||||||
case tryIngredients ingredients opts tests of
|
runner :: Maybe (OptionSet -> IO ())
|
||||||
|
runner = Just $ \opts -> case tryIngredients ingredients opts tests of
|
||||||
Nothing -> error "No tests found!?"
|
Nothing -> error "No tests found!?"
|
||||||
Just act -> ifM act
|
Just act -> ifM act
|
||||||
( exitSuccess
|
( exitSuccess
|
||||||
|
@ -1424,7 +1439,7 @@ git_annex command params = do
|
||||||
Right _ -> return True
|
Right _ -> return True
|
||||||
Left _ -> return False
|
Left _ -> return False
|
||||||
where
|
where
|
||||||
run = GitAnnex.run (command:"-q":params)
|
run = GitAnnex.run optParser Nothing (command:"-q":params)
|
||||||
|
|
||||||
{- Runs git-annex and returns its output. -}
|
{- Runs git-annex and returns its output. -}
|
||||||
git_annex_output :: String -> [String] -> IO String
|
git_annex_output :: String -> [String] -> IO String
|
||||||
|
@ -1762,3 +1777,5 @@ backendWORM = backend_ "WORM"
|
||||||
|
|
||||||
backend_ :: String -> Types.Backend
|
backend_ :: String -> Types.Backend
|
||||||
backend_ = Backend.lookupBackendName
|
backend_ = Backend.lookupBackendName
|
||||||
|
|
||||||
|
#endif
|
||||||
|
|
22
Types/Test.hs
Normal file
22
Types/Test.hs
Normal file
|
@ -0,0 +1,22 @@
|
||||||
|
{- git-annex test data types.
|
||||||
|
-
|
||||||
|
- Copyright 2011-2015 Joey Hess <id@joeyh.name>
|
||||||
|
-
|
||||||
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
|
-}
|
||||||
|
|
||||||
|
{-# LANGUAGE CPP #-}
|
||||||
|
|
||||||
|
module Types.Test where
|
||||||
|
|
||||||
|
#ifdef WITH_TESTSUITE
|
||||||
|
import Test.Tasty.Options
|
||||||
|
#endif
|
||||||
|
|
||||||
|
#ifdef WITH_TESTSUITE
|
||||||
|
type TestOptions = OptionSet
|
||||||
|
#else
|
||||||
|
type TestOptions = ()
|
||||||
|
#endif
|
||||||
|
|
||||||
|
type TestRunner = TestOptions -> IO ()
|
|
@ -1,25 +0,0 @@
|
||||||
{- Running tasty as a subcommand.
|
|
||||||
-
|
|
||||||
- Copyright 2015 Joey Hess <id@joeyh.name>
|
|
||||||
-
|
|
||||||
- License: BSD-2-clause
|
|
||||||
-}
|
|
||||||
|
|
||||||
module Utility.SubTasty where
|
|
||||||
|
|
||||||
import Test.Tasty
|
|
||||||
import Test.Tasty.Options
|
|
||||||
import Test.Tasty.Runners
|
|
||||||
import Options.Applicative
|
|
||||||
|
|
||||||
-- Uses tasty's option parser, modified to expect a subcommand.
|
|
||||||
parseOpts :: String -> [Ingredient] -> TestTree -> [String] -> IO OptionSet
|
|
||||||
parseOpts subcommand is ts =
|
|
||||||
handleParseResult . execParserPure (prefs idm) pinfo
|
|
||||||
where
|
|
||||||
pinfo = info (helper <*> subpinfo) (fullDesc <> header desc)
|
|
||||||
subpinfo = subparser $ command subcommand $
|
|
||||||
suiteOptionParser is ts
|
|
||||||
`info`
|
|
||||||
progDesc desc
|
|
||||||
desc = "Builtin test suite"
|
|
11
git-annex.hs
11
git-annex.hs
|
@ -13,9 +13,7 @@ import Network.Socket (withSocketsDo)
|
||||||
|
|
||||||
import qualified CmdLine.GitAnnex
|
import qualified CmdLine.GitAnnex
|
||||||
import qualified CmdLine.GitAnnexShell
|
import qualified CmdLine.GitAnnexShell
|
||||||
#ifdef WITH_TESTSUITE
|
|
||||||
import qualified Test
|
import qualified Test
|
||||||
#endif
|
|
||||||
|
|
||||||
#ifdef mingw32_HOST_OS
|
#ifdef mingw32_HOST_OS
|
||||||
import Utility.UserInfo
|
import Utility.UserInfo
|
||||||
|
@ -37,14 +35,7 @@ main = withSocketsDo $ do
|
||||||
#else
|
#else
|
||||||
gitannex ps
|
gitannex ps
|
||||||
#endif
|
#endif
|
||||||
gitannex ps =
|
gitannex = CmdLine.GitAnnex.run Test.optParser Test.runner
|
||||||
#ifdef WITH_TESTSUITE
|
|
||||||
case ps of
|
|
||||||
("test":ps') -> Test.main ps'
|
|
||||||
_ -> CmdLine.GitAnnex.run ps
|
|
||||||
#else
|
|
||||||
CmdLine.GitAnnex.run ps
|
|
||||||
#endif
|
|
||||||
isshell n = takeFileName n == "git-annex-shell"
|
isshell n = takeFileName n == "git-annex-shell"
|
||||||
|
|
||||||
#ifdef mingw32_HOST_OS
|
#ifdef mingw32_HOST_OS
|
||||||
|
|
Loading…
Reference in a new issue