tasty-rerun-1.1.17/src/0000755000000000000000000000000013604371472013062 5ustar0000000000000000tasty-rerun-1.1.17/src/Test/0000755000000000000000000000000013604371472014001 5ustar0000000000000000tasty-rerun-1.1.17/src/Test/Tasty/0000755000000000000000000000000013604371472015105 5ustar0000000000000000tasty-rerun-1.1.17/src/Test/Tasty/Ingredients/0000755000000000000000000000000013604371472017360 5ustar0000000000000000tasty-rerun-1.1.17/src/Test/Tasty/Ingredients/Rerun.hs0000644000000000000000000003075713604374307021023 0ustar0000000000000000-- | -- Module: Test.Tasty.Ingredients.Rerun -- Copyright: Oliver Charles (c) 2014, Andrew Lelechenko (c) 2019 -- Licence: BSD3 -- -- This ingredient -- for testing framework -- allows to filter a test tree depending -- on an outcome of the previous run. -- This may be useful in many scenarios, -- especially when a test suite grows large. -- -- The behaviour is controlled by command-line options: -- -- * @--rerun@ @ @ -- -- Rerun only tests, which failed during the last run. -- If the last run was successful, execute a full test -- suite afresh. A shortcut for @--rerun-update@ -- @--rerun-filter failures,exceptions@ -- @--rerun-all-on-success@. -- -- * @--rerun-update@ @ @ -- -- Update the log file to reflect latest test outcomes. -- -- * @--rerun-filter@ @CATEGORIES@ -- -- Read the log file and rerun only tests from a given -- comma-separated list of categories: @failures@, -- @exceptions@, @new@, @successful@. If this option is -- omitted or the log file is missing, rerun everything. -- -- * @--rerun-all-on-success@ @ @ -- -- If according to the log file and @--rerun-filter@ there -- is nothing left to rerun, run all tests. This comes -- especially handy in @stack test --file-watch@ or -- @ghcid@ scenarios. -- -- * @--rerun-log-file@ @FILE@ -- -- Location of the log file (default: @.tasty-rerun-log@). -- -- To add it to your test suite just replace -- 'Tasty.defaultMain' with -- 'defaultMainWithRerun' or wrap arguments -- of 'Tasty.defaultMainWithIngredients' -- into 'rerunningTests'. {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE FlexibleContexts #-} module Test.Tasty.Ingredients.Rerun ( defaultMainWithRerun , rerunningTests ) where import Prelude hiding (filter) import Control.Applicative import Control.Arrow ((>>>)) import Control.Monad (when) import Control.Monad.Trans.Class (lift) import Data.Char (isSpace, toLower) import Data.Foldable (asum) import Data.List (intercalate) import Data.List.Split (endBy) import Data.Maybe (fromMaybe) import Data.Monoid (Any(..), mempty) import Data.Proxy (Proxy(..)) import Data.Typeable (Typeable) import System.IO.Error (catchIOError, isDoesNotExistError) import qualified Control.Concurrent.STM as STM import qualified Control.Monad.State as State import qualified Data.Functor.Compose as Functor import qualified Data.IntMap as IntMap import qualified Data.Map.Strict as Map import qualified Data.Set as Set import qualified Options.Applicative as OptParse import qualified Test.Tasty.Options as Tasty import qualified Test.Tasty.Runners as Tasty -------------------------------------------------------------------------------- newtype RerunLogFile = RerunLogFile FilePath deriving (Typeable) instance Tasty.IsOption RerunLogFile where optionName = return "rerun-log-file" optionHelp = return "Location of the log file (default: .tasty-rerun-log)" defaultValue = RerunLogFile ".tasty-rerun-log" parseValue = Just . RerunLogFile optionCLParser = Tasty.mkOptionCLParser (OptParse.metavar "FILE") -------------------------------------------------------------------------------- newtype UpdateLog = UpdateLog Bool deriving (Typeable) instance Tasty.IsOption UpdateLog where optionName = return "rerun-update" optionHelp = return "Update the log file to reflect latest test outcomes" defaultValue = UpdateLog False parseValue = fmap UpdateLog . Tasty.safeReadBool optionCLParser = Tasty.mkFlagCLParser mempty (UpdateLog True) -------------------------------------------------------------------------------- data Filter = Failures | Exceptions | New | Successful deriving (Eq, Ord, Enum, Bounded, Show) parseFilter :: String -> Maybe Filter parseFilter s = lookup s (map (\x -> (map toLower (show x), x)) everything) -------------------------------------------------------------------------------- everything :: [Filter] everything = [minBound..maxBound] -------------------------------------------------------------------------------- newtype FilterOption = FilterOption (Set.Set Filter) deriving (Typeable) instance Tasty.IsOption FilterOption where optionName = return "rerun-filter" optionHelp = return $ "Read the log file and rerun only tests from a given comma-separated list of categories: " ++ map toLower (intercalate ", " (map show everything)) ++ ". If this option is omitted or the log file is missing, rerun everything." defaultValue = FilterOption (Set.fromList everything) parseValue = fmap (FilterOption . Set.fromList) . mapM (parseFilter . trim) . endBy "," where trim = reverse . dropWhile isSpace . reverse . dropWhile isSpace optionCLParser = Tasty.mkOptionCLParser (OptParse.metavar "CATEGORIES") -------------------------------------------------------------------------------- newtype AllOnSuccess = AllOnSuccess Bool deriving (Typeable) instance Tasty.IsOption AllOnSuccess where optionName = return "rerun-all-on-success" optionHelp = return "If according to the log file and --rerun-filter there is nothing left to rerun, run all tests. This comes especially handy in `stack test --file-watch` or `ghcid` scenarios." defaultValue = AllOnSuccess False parseValue = fmap AllOnSuccess . Tasty.safeReadBool optionCLParser = Tasty.mkFlagCLParser mempty (AllOnSuccess True) -------------------------------------------------------------------------------- newtype Rerun = Rerun { unRerun :: Bool } deriving (Typeable) instance Tasty.IsOption Rerun where optionName = return "rerun" optionHelp = return "Rerun only tests, which failed during the last run. If the last run was successful, execute a full test suite afresh. A shortcut for --rerun-update --rerun-filter failures,exceptions --rerun-all-on-success" defaultValue = Rerun False parseValue = fmap Rerun . Tasty.safeReadBool optionCLParser = Tasty.mkFlagCLParser mempty (Rerun True) rerunMeaning :: (UpdateLog, AllOnSuccess, FilterOption) rerunMeaning = (UpdateLog True, AllOnSuccess True, FilterOption (Set.fromList [Failures, Exceptions])) -------------------------------------------------------------------------------- data TestResult = Completed Bool | ThrewException deriving (Read, Show) -------------------------------------------------------------------------------- -- | Drop-in replacement for 'Tasty.defaultMain'. -- -- > import Test.Tasty -- > import Test.Tasty.Ingredients.Rerun -- > -- > main :: IO () -- > main = defaultMainWithRerun tests -- > -- > tests :: TestTree -- > tests = undefined defaultMainWithRerun :: Tasty.TestTree -> IO () defaultMainWithRerun = Tasty.defaultMainWithIngredients [ rerunningTests [ Tasty.listingTests, Tasty.consoleTestReporter ] ] -- | Ingredient transformer, to use with -- 'Tasty.defaultMainWithIngredients'. -- -- > import Test.Tasty -- > import Test.Tasty.Runners -- > import Test.Tasty.Ingredients.Rerun -- > -- > main :: IO () -- > main = -- > defaultMainWithIngredients -- > [ rerunningTests [ listingTests, consoleTestReporter ] ] -- > tests -- > -- > tests :: TestTree -- > tests = undefined rerunningTests :: [Tasty.Ingredient] -> Tasty.Ingredient rerunningTests ingredients = Tasty.TestManager (rerunOptions ++ Tasty.ingredientsOptions ingredients) $ \options testTree -> Just $ do let RerunLogFile stateFile = Tasty.lookupOption options (UpdateLog updateLog, AllOnSuccess allOnSuccess, FilterOption filter) | unRerun (Tasty.lookupOption options) = rerunMeaning | otherwise = (Tasty.lookupOption options, Tasty.lookupOption options, Tasty.lookupOption options) let nonEmptyFold = Tasty.trivialFold { Tasty.foldSingle = \_ _ _ -> Any True } nullTestTree = not . getAny . Tasty.foldTestTree nonEmptyFold options recoverFromEmpty t = if allOnSuccess && nullTestTree t then testTree else t filteredTestTree <- maybe testTree (recoverFromEmpty . filterTestTree testTree filter) <$> tryLoadStateFrom stateFile let tryAndRun (Tasty.TestReporter _ f) = do runner <- f options filteredTestTree return $ do (statusMap, outcome) <- Tasty.launchTestTree options filteredTestTree $ \sMap -> do f' <- runner sMap return (fmap (\a -> (sMap, a)) . f') let getTestResults = fmap getConst $ flip State.evalStateT 0 $ Functor.getCompose $ Tasty.getTraversal $ Tasty.foldTestTree (observeResults statusMap) options filteredTestTree when updateLog (saveStateTo stateFile getTestResults) return outcome tryAndRun (Tasty.TestManager _ f) = f options filteredTestTree case asum (map tryAndRun ingredients) of -- No Ingredients chose to run the tests, we should really return -- Nothing, but we've already committed to run by the act of -- filtering the TestTree. Nothing -> return False -- Otherwise, an Ingredient did choose to run the tests, so we -- simply run the above constructed IO action. Just e -> e where rerunOptions = [ Tasty.Option (Proxy :: Proxy Rerun) , Tasty.Option (Proxy :: Proxy UpdateLog) , Tasty.Option (Proxy :: Proxy FilterOption) , Tasty.Option (Proxy :: Proxy AllOnSuccess) , Tasty.Option (Proxy :: Proxy RerunLogFile) ] ------------------------------------------------------------------------------ filterTestTree :: Tasty.TestTree -> Set.Set Filter -> Map.Map [String] TestResult -> Tasty.TestTree filterTestTree testTree filter lastRecord = let go prefix (Tasty.SingleTest name t) = let requiredFilter = case Map.lookup (prefix ++ [name]) lastRecord of Just (Completed False) -> Failures Just ThrewException -> Exceptions Just (Completed True) -> Successful Nothing -> New in if (requiredFilter `Set.member` filter) then Tasty.SingleTest name t else Tasty.TestGroup "" [] go prefix (Tasty.TestGroup name tests) = Tasty.TestGroup name (go (prefix ++ [name]) <$> tests) go prefix (Tasty.PlusTestOptions f t) = Tasty.PlusTestOptions f (go prefix t) go prefix (Tasty.WithResource rSpec k) = Tasty.WithResource rSpec (go prefix <$> k) go prefix (Tasty.AskOptions k) = Tasty.AskOptions (go prefix <$> k) go prefix (Tasty.After a b c) = Tasty.After a b (go prefix c) in go [] testTree tryLoadStateFrom :: FilePath -> IO (Maybe (Map.Map [String] TestResult)) tryLoadStateFrom filePath = do fileContents <- (Just <$> readFile filePath) `catchIOError` (\e -> if isDoesNotExistError e then return Nothing else ioError e) return (read <$> fileContents) ------------------------------------------------------------------------------ saveStateTo :: FilePath -> IO (Map.Map [String] TestResult) -> IO () saveStateTo filePath getTestResults = getTestResults >>= (show >>> writeFile filePath) ------------------------------------------------------------------------------ observeResults :: IntMap.IntMap (STM.TVar Tasty.Status) -> Tasty.TreeFold (Tasty.Traversal (Functor.Compose (State.StateT Int IO) (Const (Map.Map [String] TestResult)))) observeResults statusMap = let foldSingle _ name _ = Tasty.Traversal $ Functor.Compose $ do i <- State.get status <- lift $ STM.atomically $ do status <- lookupStatus i case status of Tasty.Done result -> return $ case Tasty.resultOutcome result of Tasty.Failure (Tasty.TestThrewException _) -> ThrewException _ -> Completed (Tasty.resultSuccessful result) _ -> STM.retry Const (Map.singleton [name] status) <$ State.modify (+ 1) foldGroup name children = Tasty.Traversal $ Functor.Compose $ do Const soFar <- Functor.getCompose $ Tasty.getTraversal children pure $ Const (Map.mapKeys (name :) soFar) in Tasty.trivialFold { Tasty.foldSingle = foldSingle , Tasty.foldGroup = foldGroup } where lookupStatus i = STM.readTVar $ fromMaybe (error "Attempted to lookup test by index outside bounds") (IntMap.lookup i statusMap) tasty-rerun-1.1.17/LICENSE0000644000000000000000000000276613604371472013313 0ustar0000000000000000Copyright (c) 2014, Oliver Charles All rights reserved. Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: * Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. * Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. * Neither the name of Oliver Charles nor the names of other contributors may be used to endorse or promote products derived from this software without specific prior written permission. THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. tasty-rerun-1.1.17/Setup.hs0000644000000000000000000000005613604371472013730 0ustar0000000000000000import Distribution.Simple main = defaultMain tasty-rerun-1.1.17/tasty-rerun.cabal0000644000000000000000000000244213604375455015563 0ustar0000000000000000name: tasty-rerun version: 1.1.17 homepage: http://github.com/ocharles/tasty-rerun license: BSD3 license-file: LICENSE author: Oliver Charles maintainer: ollie@ocharles.org.uk copyright: Oliver Charles (c) 2014, Andrew Lelechenko (c) 2019 category: Testing build-type: Simple cabal-version: >=1.10 extra-source-files: Changelog.md README.md synopsis: Rerun only tests which failed in a previous test run description: This ingredient for testing framework allows to filter a test tree depending on an outcome of the previous run. This may be useful in many scenarios, especially when a test suite grows large. tested-with: GHC==8.8.1, GHC==8.6.5, GHC==8.4.4, GHC==8.2.2, GHC==8.0.2, GHC==7.10.3, GHC==7.8.4, GHC==7.6.3 library exposed-modules: Test.Tasty.Ingredients.Rerun build-depends: base >=4.6 && <4.14, containers >= 0.5.0.0, mtl >= 2.1.2, optparse-applicative >= 0.6, split >= 0.1 && < 0.3, stm >= 2.4.2, tagged >= 0.7 && <0.9, tasty >=1.2 && <1.3, transformers >= 0.3.0.0 hs-source-dirs: src default-language: Haskell2010 ghc-options: -Wall tasty-rerun-1.1.17/Changelog.md0000644000000000000000000000312013604374424014500 0ustar0000000000000000# 1.1.17 * Add `defaultMainWithRerun`, a drop-in replacement for `defaultMain`. # 1.1.16 * New command-line option `--rerun-all-on-success`. * New command-line shortcut `--rerun`. # 1.1.15 * Bump upper bound of base. * Restore missing -j command-line option. # 1.1.14 * Support tasty 1.2. # 1.1.13 * Bump upper bound of base. # 1.1.12 * Bump upper bound of tasty. # 1.1.11 * Bump upper bound of base. # 1.1.10 * Bump upper bound of tasty. # 1.1.9 * Bump upper bound of tasty. # 1.1.8 * Bump upper bound of tasty. # 1.1.7 * Allow base < 4.11. # 1.1.6 * Allow base 4.9 for building with GHC 8.0 # 1.1.5 * Supports tasty < 0.12. # 1.1.4 * Supports base <= 4.9, tagged <= 0.9 # 1.1.3 * Supports tasty =< 0.11 # 1.1.2 * Allow base 4.7 for building with GHC 7.8 # 1.1.1 * Update to work with tasty >= 0.8 # 1.1.0 * The `TestTree` is filtered using a custom traversal now, rather than a `TreeFold`. This gives better guarantees that the `TestTree` is only reduced and that nodes (such as `WithResources`) continue to work. The resulting filtered `TestTree` now has the same shape as the original tree, but filtered tests are transformed into `TestGroup`s with no tests. This is a fairly major change to how the filtering is performed, so this is a new major release, and previous versions are now considered deprecated. # 1.0.1 * Now supports filtering `TestTree`s that use resources. # 1.0.0 * Initial release. Supports the `--rerun-update`, `--rerun-log-file` and `--rerun-filter` options. Supported filters are `new`, `failures`, `exceptions` and `successful`. tasty-rerun-1.1.17/README.md0000644000000000000000000000423713604373323013555 0ustar0000000000000000# tasty-rerun This `Ingredient` for [`tasty`](https://hackage.haskell.org/package/tasty) testing framework allows to filter a test tree depending on an outcome of the previous run. This may be useful in many scenarios, especially when a test suite grows large. For example, `tasty-rerun` allows: * Rerun only tests, which failed during the last run (`--rerun`). Combined with live reloading (e. g., using `ghcid` or `stack test --file-watch`), it gives an ultimate power to focus on broken parts and put them back in shape, enjoying a tight feedback loop. * Rerun only tests, which have beed added since the last saved test run. This comes handy when writing a new module, which does not affect other parts of the system, or adding new test cases. * Rerun only tests, which passed during the last saved test run. Sometimes a part of the test suite is consistently failing (e. g., an external service is temporarily down), but you want be sure that you are not breaking anything else in course of your work. To add it to your test suite just replace `Test.Tasty.defaultMain` with `Test.Tasty.Ingredients.Rerun.defaultMainWithRerun`: ```haskell import Test.Tasty import Test.Tasty.Ingredients.Rerun main :: IO () main = defaultMainWithRerun tests tests :: TestTree tests = undefined ``` Use `--help` to list command-line options: * `--rerun` Rerun only tests, which failed during the last run. If the last run was successful, execute a full test suite afresh. A shortcut for `--rerun-update --rerun-filter failures,exceptions --rerun-all-on-success`. * `--rerun-update` Update the log file to reflect latest test outcomes. * `--rerun-filter CATEGORIES` Read the log file and rerun only tests from a given comma-separated list of categories: `failures`, `exceptions`, `new`, `successful`. If this option is omitted or the log file is missing, rerun everything. * `--rerun-all-on-success` If according to the log file and `--rerun-filter` there is nothing left to rerun, run all tests. This comes especially handy in `stack test --file-watch` or `ghcid` scenarios. * `--rerun-log-file FILE` Location of the log file (default: `.tasty-rerun-log`).