module Main where import System.Environment (getArgs) import System.Posix.Process import qualified Test.DMuCheck.Slave as Slave import qualified Test.DMuCheck.Master as Master import Control.Monad localHost, localPort :: String localHost = "127.0.0.1" localPort = "12345" help :: IO () help = do putStrLn "d-mucheck " putStrLn "E.g." putStrLn " d-mucheck 4 qsort Examples/QuickCheckTest.hs 'quickCheckResult revProp' 'quickCheckResult modelProp'" main :: IO () main = do args <- getArgs case args of ("-h":_) -> help (sslaves : fn : file : props) -> process sslaves fn file props _ -> putStrLn "use -h to get help." process :: String -> String -> String -> [String] -> IO () process sslaves fn file props = do let host = localHost nport = read localPort :: Int nslaves = read sslaves :: Int forM_ [show (i + nport) | i <- [1..nslaves]] $ \port_ -> forkProcess $ do Slave.process host port_ Master.process localHost localPort fn file props