module Control.Distributed.Process.Tests.Internal.Utils
( TestResult
, Ping(Ping)
, ping
, shouldBe
, shouldMatch
, shouldContain
, shouldNotContain
, expectThat
, synchronisedAssertion
, TestProcessControl
, startTestProcess
, runTestProcess
, testProcessGo
, testProcessStop
, testProcessReport
, delayedAssertion
, assertComplete
, Logger()
, newLogger
, putLogMsg
, stopLogger
, tryRunProcess
, tryForkProcess
, noop
, stash
) where
#if ! MIN_VERSION_base(4,6,0)
import Prelude hiding (catch)
#endif
import Control.Concurrent
( ThreadId
, myThreadId
, forkIO
)
import Control.Concurrent.STM
( TQueue
, newTQueueIO
, readTQueue
, writeTQueue
)
import Control.Concurrent.MVar
( MVar
, newEmptyMVar
, takeMVar
)
import Control.Concurrent
( throwTo
)
import Control.Concurrent.MVar
( putMVar
)
import Control.Distributed.Process
import Control.Distributed.Process.Node
import Control.Distributed.Process.Serializable()
import Control.Exception (AsyncException(ThreadKilled), SomeException)
import Control.Monad (forever)
import Control.Monad.STM (atomically)
import Control.Rematch hiding (match)
import Control.Rematch.Run
import Data.Binary
import Data.Typeable (Typeable)
import Test.HUnit (Assertion, assertFailure)
import Test.HUnit.Base (assertBool)
import GHC.Generics
type TestResult a = MVar a
data Ping = Ping
deriving (Typeable, Generic, Eq, Show)
instance Binary Ping where
ping :: ProcessId -> Process ()
ping pid = send pid Ping
data TestProcessControl = Stop | Go | Report ProcessId
deriving (Typeable, Generic)
instance Binary TestProcessControl where
noop :: Process ()
noop = return ()
synchronisedAssertion :: Eq a
=> String
-> LocalNode
-> a
-> (TestResult a -> Process ())
-> MVar ()
-> Assertion
synchronisedAssertion note localNode expected testProc lock = do
result <- newEmptyMVar
_ <- forkProcess localNode $ do
acquire lock
finally (testProc result)
(release lock)
assertComplete note result expected
where acquire lock' = liftIO $ takeMVar lock'
release lock' = liftIO $ putMVar lock' ()
stash :: TestResult a -> a -> Process ()
stash mvar x = liftIO $ putMVar mvar x
expectThat :: a -> Matcher a -> Process ()
expectThat a matcher = case res of
MatchSuccess -> return ()
(MatchFailure msg) -> liftIO $ assertFailure msg
where res = runMatch matcher a
shouldBe :: a -> Matcher a -> Process ()
shouldBe = expectThat
shouldContain :: (Show a, Eq a) => [a] -> a -> Process ()
shouldContain xs x = expectThat xs $ hasItem (equalTo x)
shouldNotContain :: (Show a, Eq a) => [a] -> a -> Process ()
shouldNotContain xs x = expectThat xs $ isNot (hasItem (equalTo x))
shouldMatch :: a -> Matcher a -> Process ()
shouldMatch = expectThat
delayedAssertion :: (Eq a) => String -> LocalNode -> a ->
(TestResult a -> Process ()) -> Assertion
delayedAssertion note localNode expected testProc = do
result <- newEmptyMVar
_ <- forkProcess localNode $ testProc result
assertComplete note result expected
assertComplete :: (Eq a) => String -> MVar a -> a -> IO ()
assertComplete msg mv a = do
b <- takeMVar mv
assertBool msg (a == b)
data Logger = Logger { _tid :: ThreadId, msgs :: TQueue String }
newLogger :: IO Logger
newLogger = do
tid <- liftIO $ myThreadId
q <- liftIO $ newTQueueIO
_ <- forkIO $ logger q
return $ Logger tid q
where logger q' = forever $ do
msg <- atomically $ readTQueue q'
putStrLn msg
putLogMsg :: Logger -> String -> Process ()
putLogMsg logger msg = liftIO $ atomically $ writeTQueue (msgs logger) msg
stopLogger :: Logger -> IO ()
stopLogger = (flip throwTo) ThreadKilled . _tid
startTestProcess :: Process () -> Process ProcessId
startTestProcess proc =
spawnLocal $ do
getSelfPid >>= register "test-process"
runTestProcess proc
runTestProcess :: Process () -> Process ()
runTestProcess proc = do
ctl <- expect
case ctl of
Stop -> return ()
Go -> proc >> runTestProcess proc
Report p -> receiveWait [matchAny (\m -> forward m p)] >> runTestProcess proc
testProcessGo :: ProcessId -> Process ()
testProcessGo pid = send pid Go
testProcessStop :: ProcessId -> Process ()
testProcessStop pid = send pid Stop
testProcessReport :: ProcessId -> Process ()
testProcessReport pid = do
self <- getSelfPid
send pid $ Report self
tryRunProcess :: LocalNode -> Process () -> IO ()
tryRunProcess node p = do
tid <- liftIO myThreadId
runProcess node $ catch p (\e -> liftIO $ throwTo tid (e::SomeException))
tryForkProcess :: LocalNode -> Process () -> IO ProcessId
tryForkProcess node p = do
tid <- liftIO myThreadId
forkProcess node $ catch p (\e -> liftIO $ throwTo tid (e::SomeException))