diff options
Diffstat (limited to 'tests/Config.hs')
-rw-r--r-- | tests/Config.hs | 148 |
1 files changed, 148 insertions, 0 deletions
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 #-} | ||
2 | module 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 | |||
18 | import Control.Monad | ||
19 | import Network | ||
20 | import Data.Default | ||
21 | import Data.IORef | ||
22 | import Data.List as L | ||
23 | import Data.Maybe | ||
24 | import Options.Applicative | ||
25 | import System.Exit | ||
26 | import System.Environment | ||
27 | import System.IO.Unsafe | ||
28 | import Test.Hspec | ||
29 | |||
30 | type ClientName = String | ||
31 | |||
32 | |||
33 | instance Read PortNumber where | ||
34 | readsPrec = undefined | ||
35 | |||
36 | data ClientOpts = ClientOpts | ||
37 | { peerPort :: PortNumber -- tcp port | ||
38 | , nodePort :: PortNumber -- udp port | ||
39 | } | ||
40 | |||
41 | instance Default ClientOpts where | ||
42 | def = ClientOpts | ||
43 | { peerPort = 6881 | ||
44 | , nodePort = 6881 | ||
45 | } | ||
46 | |||
47 | defRemoteOpts :: ClientOpts | ||
48 | defRemoteOpts = def | ||
49 | |||
50 | defThisOpts :: ClientOpts | ||
51 | defThisOpts = def | ||
52 | { peerPort = 6882 | ||
53 | , nodePort = 6882 | ||
54 | } | ||
55 | |||
56 | clientOptsParser :: Parser ClientOpts | ||
57 | clientOptsParser = 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 | |||
71 | data EnvOpts = EnvOpts | ||
72 | { testClient :: Maybe ClientName | ||
73 | , remoteOpts :: ClientOpts | ||
74 | , thisOpts :: ClientOpts | ||
75 | } | ||
76 | |||
77 | instance Default EnvOpts where | ||
78 | def = EnvOpts | ||
79 | { testClient = Nothing | ||
80 | , remoteOpts = defRemoteOpts | ||
81 | , thisOpts = defThisOpts | ||
82 | } | ||
83 | |||
84 | findConflicts :: EnvOpts -> [String] | ||
85 | findConflicts 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 | |||
92 | envOptsParser :: Parser EnvOpts | ||
93 | envOptsParser = EnvOpts | ||
94 | <$> optional (strOption | ||
95 | ( long "bittorrent-client" | ||
96 | <> metavar "CLIENT" | ||
97 | <> help "torrent client to run" | ||
98 | )) | ||
99 | <*> clientOptsParser | ||
100 | <*> clientOptsParser | ||
101 | |||
102 | envOptsInfo :: ParserInfo EnvOpts | ||
103 | envOptsInfo = 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 | ||
111 | envOptsRef :: IORef EnvOpts | ||
112 | envOptsRef = unsafePerformIO (newIORef def) | ||
113 | |||
114 | -- | Should be used from spec items. | ||
115 | getEnvOpts :: IO EnvOpts | ||
116 | getEnvOpts = readIORef envOptsRef | ||
117 | |||
118 | getThisOpts :: IO ClientOpts | ||
119 | getThisOpts = thisOpts <$> getEnvOpts | ||
120 | |||
121 | -- | Return 'Nothing' if remote client is not running. | ||
122 | getRemoteOpts :: IO (Maybe ClientOpts) | ||
123 | getRemoteOpts = return Nothing | ||
124 | |||
125 | withRemote :: (ClientOpts -> Expectation) -> Expectation | ||
126 | withRemote 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. | ||
135 | getOpts :: IO (EnvOpts, [String]) | ||
136 | getOpts = 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 | ||