module Test.Tasty.Ingredients.ListTests
( ListTests(..)
, testsNames
, listingTests
) where
import Data.Typeable
import Data.Proxy
import Test.Tasty.Core
import Test.Tasty.Options
import Test.Tasty.Ingredients
newtype ListTests = ListTests Bool
deriving (Eq, Ord, Typeable)
instance IsOption ListTests where
defaultValue = ListTests False
parseValue = fmap ListTests . safeRead
optionName = return "list-tests"
optionHelp = return "Do not run the tests; just print their names"
optionCLParser = flagCLParser (Just 'l') (ListTests True)
testsNames :: OptionSet -> TestTree -> [TestName]
testsNames =
foldTestTree
trivialFold
{ foldSingle = \_opts name _test -> [name]
, foldGroup = \groupName names -> map ((groupName ++ "/") ++) names
}
listingTests :: Ingredient
listingTests = TestManager [Option (Proxy :: Proxy ListTests)] $
\opts tree ->
case lookupOption opts of
ListTests False -> Nothing
ListTests True -> Just $ do
mapM_ putStrLn $ testsNames opts tree
return True