This repository was archived by the owner on Sep 3, 2024. It is now read-only.
-
Notifications
You must be signed in to change notification settings - Fork 6
/
Copy pathTestUtils.hs
236 lines (200 loc) · 6.72 KB
/
TestUtils.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DeriveGeneric #-}
module TestUtils
( TestResult
-- ping !
, Ping(Ping)
, ping
, shouldBe
, shouldMatch
, shouldContain
, shouldNotContain
, shouldExitWith
, expectThat
-- test process utilities
, TestProcessControl
, startTestProcess
, runTestProcess
, testProcessGo
, testProcessStop
, testProcessReport
, delayedAssertion
, assertComplete
, waitForExit
-- logging
, Logger()
, newLogger
, putLogMsg
, stopLogger
-- runners
, mkNode
, tryRunProcess
, testMain
, 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
, putMVar
)
import Control.Distributed.Process hiding (catch, finally)
import Control.Distributed.Process.Node
import Control.Distributed.Process.Serializable()
import Control.Distributed.Process.Extras.Time
import Control.Distributed.Process.Extras.Timer
import Control.Distributed.Process.Extras.Internal.Types
import Control.Exception (SomeException)
import qualified Control.Exception as Exception
import Control.Monad (forever)
import Control.Monad.Catch (catch)
import Control.Monad.STM (atomically)
import Control.Rematch hiding (match)
import Control.Rematch.Run
import Test.HUnit (Assertion, assertFailure)
import Test.HUnit.Base (assertBool)
import Test.Framework (Test, defaultMain)
import Control.DeepSeq
import Network.Transport.TCP
import qualified Network.Transport as NT
import Data.Binary
import Data.Typeable
import GHC.Generics
--expect :: a -> Matcher a -> Process ()
--expect a m = liftIO $ Rematch.expect a m
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
shouldExitWith :: (Resolvable a) => a -> DiedReason -> Process ()
shouldExitWith a r = do
_ <- resolve a
d <- receiveWait [ match (\(ProcessMonitorNotification _ _ r') -> return r') ]
d `shouldBe` equalTo r
waitForExit :: MVar ExitReason
-> Process (Maybe ExitReason)
waitForExit exitReason = do
-- we *might* end up blocked here, so ensure the test doesn't jam up!
self <- getSelfPid
tref <- killAfter (within 10 Seconds) self "testcast timed out"
tr <- liftIO $ takeMVar exitReason
cancelTimer tref
case tr of
ExitNormal -> return Nothing
other -> return $ Just other
mkNode :: String -> IO LocalNode
mkNode port = do
Right (transport1, _) <-
createTransportExposeInternals "127.0.0.1" port ("127.0.0.1",) defaultTCPParameters
newLocalNode transport1 initRemoteTable
-- | Run the supplied @testProc@ using an @MVar@ to collect and assert
-- against its result. Uses the supplied @note@ if the assertion fails.
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
-- | Takes the value of @mv@ (using @takeMVar@) and asserts that it matches @a@
assertComplete :: (Eq a) => String -> MVar a -> a -> IO ()
assertComplete msg mv a = do
b <- takeMVar mv
assertBool msg (a == b)
-- synchronised logging
data Logger = Logger { _tid :: ThreadId, msgs :: TQueue String }
-- | Create a new Logger.
-- Logger uses a 'TQueue' to receive and process messages on a worker thread.
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
-- | Send a message to the Logger
putLogMsg :: Logger -> String -> Process ()
putLogMsg logger msg = liftIO $ atomically $ writeTQueue (msgs logger) msg
-- | Stop the worker thread for the given Logger
stopLogger :: Logger -> IO ()
stopLogger = (flip Exception.throwTo) Exception.ThreadKilled . _tid
-- | Given a @builder@ function, make and run a test suite on a single transport
testMain :: (NT.Transport -> IO [Test]) -> IO ()
testMain builder = do
Right (transport, _) <- createTransportExposeInternals
"127.0.0.1" "0" ("127.0.0.1",) defaultTCPParameters
testData <- builder transport
defaultMain testData
-- | Runs a /test process/ around the supplied @proc@, which is executed
-- whenever the outer process loop receives a 'Go' signal.
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
-- | Starts a test process on the local node.
startTestProcess :: Process () -> Process ProcessId
startTestProcess proc =
spawnLocal $ do
getSelfPid >>= register "test-process"
runTestProcess proc
-- | Control signals used to manage /test processes/
data TestProcessControl = Stop | Go | Report ProcessId
deriving (Typeable, Generic)
instance Binary TestProcessControl where
-- | A mutable cell containing a test result.
type TestResult a = MVar a
-- | Stashes a value in our 'TestResult' using @putMVar@
stash :: TestResult a -> a -> Process ()
stash mvar x = liftIO $ putMVar mvar x
-- | Tell a /test process/ to stop (i.e., 'terminate')
testProcessStop :: ProcessId -> Process ()
testProcessStop pid = send pid Stop
-- | Tell a /test process/ to continue executing
testProcessGo :: ProcessId -> Process ()
testProcessGo pid = send pid Go
-- | A simple @Ping@ signal
data Ping = Ping
deriving (Typeable, Generic, Eq, Show)
instance Binary Ping where
instance NFData Ping where
ping :: ProcessId -> Process ()
ping pid = send pid Ping
tryRunProcess :: LocalNode -> Process () -> IO ()
tryRunProcess node p = do
tid <- liftIO myThreadId
runProcess node $ catch p (\e -> liftIO $ Exception.throwTo tid (e::SomeException))
-- | Tell a /test process/ to send a report (message)
-- back to the calling process
testProcessReport :: ProcessId -> Process ()
testProcessReport pid = do
self <- getSelfPid
send pid $ Report self