Commit 0c6fc867 authored by Yiannis Tsiouris's avatar Yiannis Tsiouris

Add parallel and distributed tests

Add '-rtsopts' to compilation flags. The tests should be run with:
  ./OrbitTests +RTS -Ksize -RTS
where 'size' is something like 256m.
parent 006a680d
...@@ -4,7 +4,7 @@ orbit: FORCE ...@@ -4,7 +4,7 @@ orbit: FORCE
ghc -Wall --make Bench.hs -main-is Bench -o orbit ghc -Wall --make Bench.hs -main-is Bench -o orbit
tests: orbit tests: orbit
ghc -Wall -threaded Tests.hs -o OrbitTests ghc -Wall -rtsopts -threaded Tests.hs -o OrbitTests
clean: clean:
$(RM) *.swp *~ *.hi *.o $(RM) *.swp *~ *.hi *.o
......
module Main where
import Control.Concurrent.MVar (MVar, putMVar, import Control.Concurrent.MVar (MVar, putMVar,
newEmptyMVar, takeMVar) newEmptyMVar, takeMVar)
import Control.Distributed.Process import Control.Distributed.Process
...@@ -11,7 +13,8 @@ import Test.Framework.Providers.HUnit (testCase) ...@@ -11,7 +13,8 @@ import Test.Framework.Providers.HUnit (testCase)
import Test.HUnit (Assertion) import Test.HUnit (Assertion)
import Test.HUnit.Base (assertBool) import Test.HUnit.Base (assertBool)
import Bench (seq) import Bench (seq, par, par_seq,
dist, dist_seq)
import MasterWorker (__remoteTable) import MasterWorker (__remoteTable)
import Utils import Utils
...@@ -32,10 +35,74 @@ testSeqLong result = do ...@@ -32,10 +35,74 @@ testSeqLong result = do
x <- seq gg1245 157 x <- seq gg1245 157
stash result x stash result x
-- Parallel Tests
testParShort :: TestResult String -> Process ()
testParShort result = do
x <- par gg13 11 2
stash result x
testParIntermediate :: TestResult String -> Process ()
testParIntermediate result = do
x <- par gg124 157 2
stash result x
testParLong :: TestResult String -> Process ()
testParLong result = do
x <- par gg1245 157 2
stash result x
testParSeqShort :: TestResult String -> Process ()
testParSeqShort result = do
x <- par_seq gg13 11 2
stash result x
testParSeqIntermediate :: TestResult String -> Process ()
testParSeqIntermediate result = do
x <- par_seq gg124 157 2
stash result x
testParSeqLong :: TestResult String -> Process ()
testParSeqLong result = do
x <- par_seq gg1245 157 2
stash result x
-- Distributed Tests
testDistShort :: [NodeId] -> TestResult String -> Process ()
testDistShort nodes result = do
x <- dist gg13 11 2 nodes
stash result x
testDistIntermediate :: [NodeId] -> TestResult String -> Process ()
testDistIntermediate nodes result = do
x <- dist gg124 157 2 nodes
stash result x
testDistLong :: [NodeId] -> TestResult String -> Process ()
testDistLong nodes result = do
x <- dist gg1245 157 2 nodes
stash result x
testDistSeqShort :: [NodeId] -> TestResult String -> Process ()
testDistSeqShort nodes result = do
x <- dist_seq gg13 11 2 nodes
stash result x
testDistSeqIntermediate :: [NodeId] -> TestResult String -> Process ()
testDistSeqIntermediate nodes result = do
x <- dist_seq gg124 157 2 nodes
stash result x
testDistSeqLong :: [NodeId] -> TestResult String -> Process ()
testDistSeqLong nodes result = do
x <- dist_seq gg1245 157 2 nodes
stash result x
-- Batch the tests -- Batch the tests
tests :: LocalNode -> [Test] tests :: [LocalNode] -> [Test]
tests localNode = [ tests (localNode : localNodes) = [
testGroup "Sequential Tests" [ testGroup "Sequential Tests" [
testCase "testSeqShort" testCase "testSeqShort"
(delayedAssertion "short" localNode "{size,10}" testSeqShort) (delayedAssertion "short" localNode "{size,10}" testSeqShort)
...@@ -44,6 +111,40 @@ tests localNode = [ ...@@ -44,6 +111,40 @@ tests localNode = [
, testCase "testSeqLong" , testCase "testSeqLong"
(delayedAssertion "long" localNode "{size,134}" testSeqLong) (delayedAssertion "long" localNode "{size,134}" testSeqLong)
] ]
, testGroup "Parallel Tests" [
testCase "testParSeqShort"
(delayedAssertion "short" localNode "{size,10}" testParSeqShort)
, testCase "testParSeqIntermediate"
(delayedAssertion "intermediate" localNode "{size,133}" testParSeqIntermediate)
, testCase "testParSeqLong"
(delayedAssertion "long" localNode "{size,134}" testParSeqLong)
, testCase "testParShort"
(delayedAssertion "short" localNode "{size,10}" testParShort)
, testCase "testParIntermediate"
(delayedAssertion "intermediate" localNode "{size,133}" testParIntermediate)
, testCase "testParLong"
(delayedAssertion "long" localNode "{size,134}" testParLong)
]
, testGroup "Distributed Tests" [
testCase "testDistSeqShort"
(delayedAssertion "short" localNode "{size,10}" $
testDistSeqShort (map localNodeId localNodes))
, testCase "testDistSeqIntermediate"
(delayedAssertion "intermediate" localNode "{size,133}" $
testDistSeqIntermediate (map localNodeId localNodes))
, testCase "testDistSeqLong"
(delayedAssertion "long" localNode "{size,134}" $
testDistSeqLong (map localNodeId localNodes))
, testCase "testDistShort"
(delayedAssertion "short" localNode "{size,10}" $
testDistShort (map localNodeId localNodes))
, testCase "testDistIntermediate"
(delayedAssertion "intermediate" localNode "{size,133}" $
testDistIntermediate (map localNodeId localNodes))
, testCase "testDistLong"
(delayedAssertion "long" localNode "{size,134}" $
testDistLong (map localNodeId localNodes))
]
] ]
-- Run the tests -- Run the tests
...@@ -51,7 +152,9 @@ tests localNode = [ ...@@ -51,7 +152,9 @@ tests localNode = [
orbitTests :: NT.Transport -> IO [Test] orbitTests :: NT.Transport -> IO [Test]
orbitTests transport = do orbitTests transport = do
localNode <- newLocalNode transport rtable localNode <- newLocalNode transport rtable
let testData = tests localNode localNode2 <- newLocalNode transport rtable
localNode3 <- newLocalNode transport rtable
let testData = tests [localNode, localNode2, localNode3]
return testData return testData
where rtable :: RemoteTable where rtable :: RemoteTable
rtable = MasterWorker.__remoteTable initRemoteTable rtable = MasterWorker.__remoteTable initRemoteTable
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment