dejafu/tasty-dejafu/Test/Tasty/DejaFu.hs

303 lines
9.8 KiB
Haskell
Raw Normal View History

{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeSynonymInstances #-}
2015-10-08 23:50:52 +03:00
2016-05-26 15:54:13 +03:00
#if __GLASGOW_HASKELL__ >= 800
-- Impredicative polymorphism checks got stronger in GHC 8, breaking
-- the use of 'unsafeCoerce' below.
{-# LANGUAGE ImpredicativeTypes #-}
#endif
2015-10-08 23:50:52 +03:00
-- | This module allows using Deja Fu predicates with Tasty to test
-- the behaviour of concurrent systems.
module Test.Tasty.DejaFu
( -- * Unit testing
-- | This is supported by the 'IsTest' instances for 'ConcST' and
-- 'ConcIO'. These instances try all executions, reporting as
-- failures the cases which return a 'Just' string.
--
-- @instance Typeable t => IsTest (ConcST t (Maybe String))@
-- @instance IsTest (ConcIO (Maybe String))@
-- @instance IsOption Bounds@
-- @instance IsOption MemType@
-- * Property testing
2015-10-08 23:50:52 +03:00
testAuto
, testDejafu
, testDejafus
, testAuto'
, testDejafu'
, testDejafus'
-- ** @IO@
2015-10-08 23:50:52 +03:00
, testAutoIO
, testDejafuIO
, testDejafusIO
, testAutoIO'
, testDejafuIO'
, testDejafusIO'
-- * Re-exports
, Bounds(..)
, MemType(..)
2015-10-08 23:50:52 +03:00
) where
import Data.Char (toUpper)
import Data.List (intercalate, intersperse)
import Data.Proxy (Proxy(..))
import Data.Tagged (Tagged(..))
2015-10-08 23:50:52 +03:00
import Data.Typeable (Typeable)
import Test.DejaFu
import Test.DejaFu.Deterministic (ConcST, ConcIO, Trace, ThreadId, ThreadAction, Lookahead, showFail, showTrace)
2015-11-19 16:57:14 +03:00
import Test.DejaFu.SCT (sctBound, sctBoundIO)
2015-10-08 23:50:52 +03:00
import Test.Tasty (TestName, TestTree, testGroup)
import Test.Tasty.Options (OptionDescription(..), IsOption(..), lookupOption)
2015-10-08 23:50:52 +03:00
import Test.Tasty.Providers (IsTest(..), singleTest, testPassed, testFailed)
-- Can't put the necessary forall in the @IsTest ConcST t@
-- instance :(
import Unsafe.Coerce (unsafeCoerce)
#if MIN_VERSION_dejafu(0,3,0)
type Trc = Trace ThreadId ThreadAction Lookahead
#else
type Trc = Trace
#endif
2015-10-08 23:50:52 +03:00
--------------------------------------------------------------------------------
-- Unit testing
instance Typeable t => IsTest (ConcST t (Maybe String)) where
testOptions = Tagged concOptions
run options conc callback = do
let memtype = lookupOption options :: MemType
let bounds = lookupOption options :: Bounds
let sctBound' :: ConcST t (Maybe String) -> [(Either Failure (Maybe String), Trc)]
sctBound' = unsafeCoerce $ sctBound memtype bounds
let traces = sctBound' conc
run options (ConcTest traces assertableP) callback
instance IsTest (ConcIO (Maybe String)) where
testOptions = Tagged concOptions
run options conc callback = do
let memtype = lookupOption options
let bounds = lookupOption options
let traces = sctBoundIO memtype bounds conc
run options (ConcIOTest traces assertableP) callback
concOptions :: [OptionDescription]
concOptions =
[ Option (Proxy :: Proxy Bounds)
, Option (Proxy :: Proxy MemType)
]
assertableP :: Predicate (Maybe String)
assertableP = alwaysTrue $ \r -> case r of
Right (Just _) -> False
_ -> True
instance IsOption Bounds where
defaultValue = defaultBounds
parseValue = const Nothing
optionName = Tagged "schedule-bounds"
optionHelp = Tagged "The schedule bounds to use. This cannot be set on the command line."
instance IsOption MemType where
defaultValue = defaultMemType
parseValue str = shortName (map toUpper str) where
shortName "SC" = Just SequentialConsistency
shortName "TSO" = Just TotalStoreOrder
shortName "PSO" = Just PartialStoreOrder
shortName _ = Nothing
optionName = Tagged "memory-model"
optionHelp = Tagged "The memory model to use. This should be one of \"SC\", \"TSO\", or \"PSO\"."
--------------------------------------------------------------------------------
-- Property testing
2015-10-08 23:50:52 +03:00
-- | Automatically test a computation. In particular, look for
-- deadlocks, uncaught exceptions, and multiple return values.
--
-- This uses the 'Conc' monad for testing, which is an instance of
-- 'MonadConc'. If you need to test something which also uses
-- 'MonadIO', use 'testAutoIO'.
testAuto :: (Eq a, Show a)
2015-11-07 21:07:10 +03:00
=> (forall t. ConcST t a)
2015-10-08 23:50:52 +03:00
-- ^ The computation to test
-> TestTree
testAuto = testAuto' defaultMemType
2015-10-08 23:50:52 +03:00
-- | Variant of 'testAuto' which tests a computation under a given
-- memory model.
testAuto' :: (Eq a, Show a)
=> MemType
-- ^ The memory model to use for non-synchronised @CRef@ operations.
2015-11-07 21:07:10 +03:00
-> (forall t. ConcST t a)
2015-10-08 23:50:52 +03:00
-- ^ The computation to test
-> TestTree
2015-11-19 16:57:14 +03:00
testAuto' memtype conc = testDejafus' memtype defaultBounds conc autocheckCases
2015-10-08 23:50:52 +03:00
-- | Variant of 'testAuto' for computations which do 'IO'.
testAutoIO :: (Eq a, Show a) => ConcIO a -> TestTree
testAutoIO = testAutoIO' defaultMemType
2015-10-08 23:50:52 +03:00
-- | Variant of 'testAuto'' for computations which do 'IO'.
testAutoIO' :: (Eq a, Show a) => MemType -> ConcIO a -> TestTree
2015-11-19 16:57:14 +03:00
testAutoIO' memtype concio = testDejafusIO' memtype defaultBounds concio autocheckCases
2015-10-08 23:50:52 +03:00
-- | Predicates for the various autocheck functions.
autocheckCases :: Eq a => [(TestName, Predicate a)]
autocheckCases =
[("Never Deadlocks", representative deadlocksNever)
, ("No Exceptions", representative exceptionsNever)
2015-10-08 23:50:52 +03:00
, ("Consistent Result", alwaysSame)
]
-- | Check that a predicate holds.
2015-10-25 20:05:40 +03:00
testDejafu :: Show a
2015-11-07 21:07:10 +03:00
=> (forall t. ConcST t a)
2015-10-08 23:50:52 +03:00
-- ^ The computation to test
-> TestName
-- ^ The name of the test.
-> Predicate a
-- ^ The predicate to check
-> TestTree
2015-11-19 16:57:14 +03:00
testDejafu = testDejafu' defaultMemType defaultBounds
2015-10-08 23:50:52 +03:00
-- | Variant of 'testDejafu' which takes a memory model and
-- pre-emption bound.
2015-10-25 20:05:40 +03:00
testDejafu' :: Show a
2015-10-08 23:50:52 +03:00
=> MemType
-- ^ The memory model to use for non-synchronised @CRef@ operations.
2015-11-19 16:57:14 +03:00
-> Bounds
-- ^ The schedule bounds.
2015-11-07 21:07:10 +03:00
-> (forall t. ConcST t a)
2015-10-08 23:50:52 +03:00
-- ^ The computation to test
-> TestName
-- ^ The name of the test.
-> Predicate a
-- ^ The predicate to check
-> TestTree
2015-11-19 16:57:14 +03:00
testDejafu' memtype cb conc name p = testDejafus' memtype cb conc [(name, p)]
2015-10-08 23:50:52 +03:00
-- | Variant of 'testDejafu' which takes a collection of predicates to
-- test. This will share work between the predicates, rather than
-- running the concurrent computation many times for each predicate.
2015-10-25 20:05:40 +03:00
testDejafus :: Show a
2015-11-07 21:07:10 +03:00
=> (forall t. ConcST t a)
2015-10-08 23:50:52 +03:00
-- ^ The computation to test
-> [(TestName, Predicate a)]
-- ^ The list of predicates (with names) to check
-> TestTree
2015-11-19 16:57:14 +03:00
testDejafus = testDejafus' defaultMemType defaultBounds
2015-10-08 23:50:52 +03:00
-- | Variant of 'testDejafus' which takes a memory model and pre-emption
-- bound.
2015-10-25 20:05:40 +03:00
testDejafus' :: Show a
2015-10-08 23:50:52 +03:00
=> MemType
-- ^ The memory model to use for non-synchronised @CRef@ operations.
2015-11-19 16:57:14 +03:00
-> Bounds
-- ^ The schedule bounds.
2015-11-07 21:07:10 +03:00
-> (forall t. ConcST t a)
2015-10-08 23:50:52 +03:00
-- ^ The computation to test
-> [(TestName, Predicate a)]
-- ^ The list of predicates (with names) to check
-> TestTree
testDejafus' = testst
2015-10-08 23:50:52 +03:00
-- | Variant of 'testDejafu' for computations which do 'IO'.
testDejafuIO :: Show a => ConcIO a -> TestName -> Predicate a -> TestTree
2015-11-19 16:57:14 +03:00
testDejafuIO = testDejafuIO' defaultMemType defaultBounds
2015-10-08 23:50:52 +03:00
-- | Variant of 'testDejafu'' for computations which do 'IO'.
2015-11-19 16:57:14 +03:00
testDejafuIO' :: Show a => MemType -> Bounds -> ConcIO a -> TestName -> Predicate a -> TestTree
testDejafuIO' memtype cb concio name p = testDejafusIO' memtype cb concio [(name, p)]
2015-10-08 23:50:52 +03:00
-- | Variant of 'testDejafus' for computations which do 'IO'.
testDejafusIO :: Show a => ConcIO a -> [(TestName, Predicate a)] -> TestTree
2015-11-19 16:57:14 +03:00
testDejafusIO = testDejafusIO' defaultMemType defaultBounds
2015-10-08 23:50:52 +03:00
-- | Variant of 'dejafus'' for computations which do 'IO'.
2015-11-19 16:57:14 +03:00
testDejafusIO' :: Show a => MemType -> Bounds -> ConcIO a -> [(TestName, Predicate a)] -> TestTree
2015-10-08 23:50:52 +03:00
testDejafusIO' = testio
--------------------------------------------------------------------------------
-- Tasty integration
data ConcTest where
ConcTest :: Show a => [(Either Failure a, Trc)] -> Predicate a -> ConcTest
2015-10-08 23:50:52 +03:00
deriving Typeable
data ConcIOTest where
ConcIOTest :: Show a => IO [(Either Failure a, Trc)] -> Predicate a -> ConcIOTest
2015-10-08 23:50:52 +03:00
deriving Typeable
instance IsTest ConcTest where
testOptions = return []
run _ (ConcTest traces p) _ =
let err = showErr $ p traces
in return $ if null err then testPassed "" else testFailed err
instance IsTest ConcIOTest where
testOptions = return []
run _ (ConcIOTest iotraces p) _ = do
traces <- iotraces
let err = showErr $ p traces
return $ if null err then testPassed "" else testFailed err
-- | Produce a Tasty 'TestTree' from a Deja Fu test.
testst :: Show a => MemType -> Bounds -> (forall t. ConcST t a) -> [(TestName, Predicate a)] -> TestTree
testst memtype cb conc tests = case map toTest tests of
2015-10-08 23:50:52 +03:00
[t] -> t
ts -> testGroup "Deja Fu Tests" ts
where
toTest (name, p) = singleTest name $ ConcTest traces p
2015-11-19 16:57:14 +03:00
traces = sctBound memtype cb conc
2015-10-08 23:50:52 +03:00
-- | Produce a Tasty 'Test' from an IO-using Deja Fu test.
2015-11-19 16:57:14 +03:00
testio :: Show a => MemType -> Bounds -> ConcIO a -> [(TestName, Predicate a)] -> TestTree
testio memtype cb concio tests = case map toTest tests of
2015-10-08 23:50:52 +03:00
[t] -> t
ts -> testGroup "Deja Fu Tests" ts
where
toTest (name, p) = singleTest name $ ConcIOTest traces p
-- As with HUnit, constructing a test is side-effect free, so
-- sharing of traces can't happen here.
2015-11-19 16:57:14 +03:00
traces = sctBoundIO memtype cb concio
2015-10-08 23:50:52 +03:00
-- | Convert a test result into an error message on failure (empty
-- string on success).
showErr :: Show a => Result a -> String
showErr res
| _pass res = ""
| otherwise = "Failed after " ++ show (_casesChecked res) ++ " cases:\n" ++ msg ++ unlines failures ++ rest where
msg = if null (_failureMsg res) then "" else _failureMsg res ++ "\n"
2015-10-08 23:50:52 +03:00
failures = intersperse "" . map (\(r, t) -> indent $ either showFail show r ++ " " ++ showTrace t) . take 5 $ _failures res
2015-10-08 23:50:52 +03:00
rest = if moreThan (_failures res) 5 then "\n\t..." else ""
-- | Check if a list has more than some number of elements.
moreThan :: [a] -> Int -> Bool
moreThan [] n = n < 0
moreThan _ 0 = True
moreThan (_:xs) n = moreThan xs (n-1)
-- | Indent every line of a string.
indent :: String -> String
indent = intercalate "\n" . map ('\t':) . lines