summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--bittorrent.cabal2
-rw-r--r--tests/Config.hs148
-rw-r--r--tests/Main.hs95
3 files changed, 217 insertions, 28 deletions
diff --git a/bittorrent.cabal b/bittorrent.cabal
index 0ccc5d97..e6a6db93 100644
--- a/bittorrent.cabal
+++ b/bittorrent.cabal
@@ -181,6 +181,8 @@ test-suite spec
181 hs-source-dirs: tests 181 hs-source-dirs: tests
182 main-is: Main.hs 182 main-is: Main.hs
183 other-modules: Spec 183 other-modules: Spec
184 Config
185
184 Data.Torrent.BitfieldSpec 186 Data.Torrent.BitfieldSpec
185 Data.Torrent.InfoHashSpec 187 Data.Torrent.InfoHashSpec
186 Data.Torrent.LayoutSpec 188 Data.Torrent.LayoutSpec
diff --git a/tests/Config.hs b/tests/Config.hs
new file mode 100644
index 00000000..3dc254a8
--- /dev/null
+++ b/tests/Config.hs
@@ -0,0 +1,148 @@
1{-# LANGUAGE RecordWildCards #-}
2module Config
3 ( -- * Types
4 ClientName
5 , ClientOpts (..)
6 , EnvOpts (..)
7
8 -- * For test suite driver
9 , getOpts
10
11 -- * For item specs
12 , getEnvOpts
13 , getThisOpts
14 , getRemoteOpts
15 , withRemote
16 ) where
17
18import Control.Monad
19import Network
20import Data.Default
21import Data.IORef
22import Data.List as L
23import Data.Maybe
24import Options.Applicative
25import System.Exit
26import System.Environment
27import System.IO.Unsafe
28import Test.Hspec
29
30type ClientName = String
31
32
33instance Read PortNumber where
34 readsPrec = undefined
35
36data ClientOpts = ClientOpts
37 { peerPort :: PortNumber -- tcp port
38 , nodePort :: PortNumber -- udp port
39 }
40
41instance Default ClientOpts where
42 def = ClientOpts
43 { peerPort = 6881
44 , nodePort = 6881
45 }
46
47defRemoteOpts :: ClientOpts
48defRemoteOpts = def
49
50defThisOpts :: ClientOpts
51defThisOpts = def
52 { peerPort = 6882
53 , nodePort = 6882
54 }
55
56clientOptsParser :: Parser ClientOpts
57clientOptsParser = ClientOpts
58 <$> option
59 ( long "peer-port" <> short 'p'
60 <> value 6881 <> showDefault
61 <> metavar "NUM"
62 <> help "port to bind the specified bittorrent client"
63 )
64 <*> option
65 ( long "node-port" <> short 'n'
66 <> value 6881 <> showDefault
67 <> metavar "NUM"
68 <> help "port to bind node of the specified client"
69 )
70
71data EnvOpts = EnvOpts
72 { testClient :: Maybe ClientName
73 , remoteOpts :: ClientOpts
74 , thisOpts :: ClientOpts
75 }
76
77instance Default EnvOpts where
78 def = EnvOpts
79 { testClient = Nothing
80 , remoteOpts = defRemoteOpts
81 , thisOpts = defThisOpts
82 }
83
84findConflicts :: EnvOpts -> [String]
85findConflicts EnvOpts {..}
86 | isNothing testClient = []
87 | peerPort remoteOpts == peerPort thisOpts = ["Peer port the same"]
88 | nodePort remoteOpts == nodePort thisOpts = ["Node port the same"]
89 | otherwise = []
90
91
92envOptsParser :: Parser EnvOpts
93envOptsParser = EnvOpts
94 <$> optional (strOption
95 ( long "bittorrent-client"
96 <> metavar "CLIENT"
97 <> help "torrent client to run"
98 ))
99 <*> clientOptsParser
100 <*> clientOptsParser
101
102envOptsInfo :: ParserInfo EnvOpts
103envOptsInfo = info (helper <*> envOptsParser)
104 ( fullDesc
105 <> progDesc "The bittorrent library testsuite"
106 <> header ""
107 )
108
109-- do not modify this while test suite is running because spec items
110-- can run in parallel
111envOptsRef :: IORef EnvOpts
112envOptsRef = unsafePerformIO (newIORef def)
113
114-- | Should be used from spec items.
115getEnvOpts :: IO EnvOpts
116getEnvOpts = readIORef envOptsRef
117
118getThisOpts :: IO ClientOpts
119getThisOpts = thisOpts <$> getEnvOpts
120
121-- | Return 'Nothing' if remote client is not running.
122getRemoteOpts :: IO (Maybe ClientOpts)
123getRemoteOpts = return Nothing
124
125withRemote :: (ClientOpts -> Expectation) -> Expectation
126withRemote action = do
127 mopts <- getRemoteOpts
128 case mopts of
129 Nothing -> pendingWith "Remote client isn't running"
130 Just opts -> action opts
131
132-- TODO fix EnvOpts parsing
133
134-- | Should be used by test suite driver.
135getOpts :: IO (EnvOpts, [String])
136getOpts = do
137 args <- getArgs
138-- case runParser SkipOpts envOptsParser args) (prefs idm) of
139 case (Right (def, args), ()) of
140 (Left err , _ctx) -> exitFailure
141 (Right (envOpts, hspecOpts), _ctx) -> do
142 let conflicts = findConflicts envOpts
143 unless (L.null conflicts) $ do
144 forM_ conflicts putStrLn
145 exitFailure
146
147 writeIORef envOptsRef envOpts
148 return (envOpts, hspecOpts) \ No newline at end of file
diff --git a/tests/Main.hs b/tests/Main.hs
index 63281cf3..6577e6f4 100644
--- a/tests/Main.hs
+++ b/tests/Main.hs
@@ -1,37 +1,76 @@
1{-# LANGUAGE RecordWildCards #-}
1module Main where 2module Main where
2 3import Control.Exception
3import Spec 4import Control.Monad
5import Data.Functor
6import Data.List
7import Data.Maybe
4import System.Exit 8import System.Exit
5import System.Environment 9import System.Environment
6import System.Process 10import System.Process
7import System.Directory 11import System.Directory
8import Control.Exception 12import Text.Printf
9import Data.List 13
10import Data.Maybe 14import Config
11import Data.Functor 15import Spec
16
17
18type Command = String
19type Descr = (ClientName, ClientOpts -> FilePath -> Command)
20
21torrents :: [FilePath]
22torrents =
23 [ "dapper-dvd-amd64-iso.torrent"
24 , "pkg.torrent"
25 , "testfile.torrent"
26 ]
27
28clients :: [Descr]
29clients =
30 [ ("rtorrent"
31 , \ ClientOpts {..} tfile -> printf
32 "rtorrent -p %i-%i -O dht=on -O dht_port=%i -O session=rtorrent-sessiondir %s"
33 (fromEnum peerPort) (fromEnum peerPort) (fromEnum nodePort) tfile
34 )
35 ]
36
37sessionName :: String -- screen session name
38sessionName = "bittorrent-testsuite"
39
40setupEnv :: EnvOpts -> IO (Maybe ())
41setupEnv EnvOpts {..}
42 | Just client <- testClient
43 , Just mkCmd <- lookup client clients = do
44 let runner = printf "screen -dm -S %s %s" sessionName
45 (mkCmd remoteOpts "testfile.torrent")
46 dir <- getCurrentDirectory
47 _ <- createProcess (shell runner) { cwd = Just (dir ++ "/res") }
48 return (Just ())
49
50 | Just client <- testClient = do
51 printf "Bad client `%s`, use one of %s" client (show (fst <$> clients))
52 return Nothing
53
54 | isNothing testClient = do
55 printf "Running without remote client"
56 return (Just ())
57
58terminateEnv :: IO ()
59terminateEnv = do
60 printf "closing screen session: %s" sessionName
61 _ <- system (printf "screen -S %s -X quit" sessionName)
62 return ()
12 63
13clients :: [(String, String)] 64runTestSuite :: [String] -> IO ExitCode
14clients = [ 65runTestSuite args = do
15 ("rtorrent","rtorrent -p 51234-51234 -O dht=on -O dht_port=6881 -O session=rtorrent-sessiondir testfile.torrent") ] 66 printf "running hspec test suite with args: %s\n" (show args)
67 catch (withArgs args hspecMain >> return ExitSuccess) return
16 68
17main :: IO () 69main :: IO ()
18main = do 70main = do
19 args <- getArgs 71 (envOpts, suiteArgs) <- getOpts
20 let cmd' = do 72 running <- setupEnv envOpts
21 cl <- listToMaybe $ reverse 73 code <- runTestSuite suiteArgs
22 $ map (tail . dropWhile (/='=')) 74 when (isJust running) $ do
23 $ filter (isPrefixOf "--bittorrent-client=") args 75 terminateEnv
24 cmd <- (++) "screen -dm -S bittorrent-testsuite " <$> lookup cl clients 76 exitWith code
25 return cmd
26 case cmd' of
27 Just cmd -> do _ <- system "screen -S bittorrent-testsuite -X quit"
28 dir <- getCurrentDirectory
29 _ <- createProcess (shell cmd) { cwd = Just (dir ++ "/res") }
30 return ()
31 Nothing -> return ()
32
33 let args' = (filter (not . isPrefixOf "--bittorrent-client=") args)
34 code <- catch (withArgs args' hspecMain >> return ExitSuccess) return
35
36 _ <- system "screen -S bittorrent-testsuite -X quit"
37 exitWith code >> return ()