summaryrefslogtreecommitdiff
path: root/bittorrent/tests/Main.hs
diff options
context:
space:
mode:
Diffstat (limited to 'bittorrent/tests/Main.hs')
-rw-r--r--bittorrent/tests/Main.hs97
1 files changed, 97 insertions, 0 deletions
diff --git a/bittorrent/tests/Main.hs b/bittorrent/tests/Main.hs
new file mode 100644
index 00000000..5ed953da
--- /dev/null
+++ b/bittorrent/tests/Main.hs
@@ -0,0 +1,97 @@
1{-# LANGUAGE RecordWildCards #-}
2module Main where
3import Control.Exception
4import Control.Monad
5import Data.Functor
6import Data.Maybe
7import System.Directory
8import System.Exit
9import System.Environment
10import System.FilePath
11import System.Process
12import Text.Printf
13import Test.Hspec
14
15import Config
16import qualified Spec as Generated
17
18
19type Command = String
20type Descr = (ClientName, ClientOpts -> FilePath -> Command)
21
22torrents :: [FilePath]
23torrents =
24 [ "dapper-dvd-amd64-iso.torrent"
25 , "pkg.torrent"
26 , "testfile.torrent"
27 ]
28
29rtorrentSessionDir :: String
30rtorrentSessionDir = "rtorrent-sessiondir"
31
32sessionName :: String -- screen session name
33sessionName = "bittorrent-testsuite"
34
35tmpDir :: FilePath
36tmpDir = "res"
37
38clients :: [Descr]
39clients =
40 [ ("rtorrent"
41 , \ ClientOpts {..} tfile -> printf
42 "rtorrent -p %i-%i -O dht=on -O dht_port=%i -O session=%s %s"
43 (fromEnum peerPort) (fromEnum peerPort) (fromEnum nodePort)
44 rtorrentSessionDir tfile
45 )
46 ]
47
48setupEnv :: EnvOpts -> IO (Maybe ())
49setupEnv EnvOpts {..}
50 | Just client <- testClient
51 , Just mkCmd <- lookup client clients = do
52 _ <- printf "Setting up %s\n" client
53
54 let torrentPath = "testfile.torrent"
55 let runner = printf "screen -dm -S %s %s" sessionName
56 (mkCmd remoteOpts torrentPath)
57
58 wd <- getCurrentDirectory
59 createDirectoryIfMissing True (wd </> tmpDir </> rtorrentSessionDir)
60 _ <- createProcess (shell runner) { cwd = Just (wd </> tmpDir) }
61
62 return (Just ())
63
64 | Just client <- testClient = do
65 _ <- printf "Bad client `%s`, use one of %s\n" client (show (fst <$> clients))
66 return Nothing
67
68 | otherwise = do
69 _ <- printf "Running without remote client\n"
70 return (Just ())
71
72terminateEnv :: IO ()
73terminateEnv = do
74 wd <- getCurrentDirectory
75 removeDirectoryRecursive (wd </> tmpDir </> rtorrentSessionDir)
76 _ <- printf "closing screen session: %s\n" sessionName
77 _ <- system (printf "screen -S %s -X quit" sessionName)
78 return ()
79
80runTestSuite :: [String] -> IO ExitCode
81runTestSuite args = do
82 _ <- printf "running hspec test suite with args: %s\n" (show args)
83 catch (withArgs args (hspec Generated.spec) >> return ExitSuccess) return
84
85withEnv :: EnvOpts -> IO a -> IO a
86withEnv opts action = bracket (setupEnv opts) terminate (const action)
87 where
88 terminate running = do
89 when (isJust running) $ do
90 terminateEnv
91
92main :: IO ()
93main = do
94 (envOpts, suiteArgs) <- getOpts
95 withEnv envOpts $ do
96 code <- runTestSuite suiteArgs
97 exitWith code