]> gitweb.michael.orlitzky.com - dead/htsn.git/blob - src/Main.hs
4ebada07e858fb53d2ca983503ced14201a1fd22
[dead/htsn.git] / src / Main.hs
1 {-# LANGUAGE BangPatterns #-}
2 {-# LANGUAGE DoAndIfThenElse #-}
3
4 module Main
5 where
6
7 import Control.Concurrent ( threadDelay )
8 import Control.Exception.Base ( bracket )
9 import Control.Monad ( when )
10 import Data.List ( isPrefixOf )
11 import Data.Maybe ( isNothing )
12 import Data.Monoid ( (<>) )
13 import Network (
14 connectTo,
15 PortID (PortNumber) )
16 import System.Console.CmdArgs ( def )
17 import System.Directory ( doesFileExist )
18 import System.Exit ( ExitCode(..), exitWith )
19 import System.FilePath ( (</>) )
20 import System.IO (
21 BufferMode (NoBuffering),
22 Handle,
23 hClose,
24 hGetChar,
25 hGetLine,
26 hPutStr,
27 hSetBuffering,
28 stderr,
29 stdout )
30 import System.IO.Error ( catchIOError )
31 import System.Timeout ( timeout )
32
33 import CommandLine ( get_args )
34 import Configuration ( Configuration(..), merge_optional )
35 import ExitCodes (
36 exit_no_feed_hosts,
37 exit_no_password,
38 exit_no_username )
39 import Logging (
40 init_logging,
41 log_debug,
42 log_error,
43 log_info,
44 log_warning )
45 import qualified OptionalConfiguration as OC (
46 OptionalConfiguration(..),
47 from_rc )
48 import Terminal (
49 display_debug,
50 display_error,
51 display_info,
52 display_sent,
53 display_warning )
54 import TSN.FeedHosts ( FeedHosts(..) )
55 import TSN.Xml ( parse_xmlfid )
56
57
58 -- | Display and log debug information. WARNING! This does not
59 -- automatically append a newline. The output is displayed/logged
60 -- as-is, for, you know, debug purposes.
61 report_debug :: String -> IO ()
62 report_debug s = do
63 display_debug s
64 log_debug s
65
66
67 -- | Display and log an error condition. This will prefix the error
68 -- with "ERROR: " when displaying (but not logging) it so that it
69 -- stands out.
70 --
71 report_error :: String -> IO ()
72 report_error s = do
73 display_error $ "ERROR: " ++ s
74 log_error s
75
76
77 -- | Display and log an informational (status) message.
78 report_info :: String -> IO ()
79 report_info s = do
80 display_info s
81 log_info s
82
83
84 -- | A special case of report_debug for reporting the two bits of data
85 -- that we sent to TSN: the username and password.
86 --
87 report_sent :: String -> IO ()
88 report_sent s = do
89 display_sent s
90 log_debug s
91
92
93 -- | Display and log a warning. This will prefix the warning with
94 -- "WARNING: " when displaying (but not logging) it so that it
95 -- stands out.
96 --
97 report_warning :: String -> IO ()
98 report_warning s = do
99 display_warning $ "WARNING: " ++ s
100 log_warning s
101
102
103 -- | Receive a single line of text from a Handle, and send it to the
104 -- debug log.
105 --
106 recv_line :: Handle -> IO String
107 recv_line h = do
108 line <- hGetLine h
109 report_debug (line ++ "\n")
110 return line
111
112
113 -- | Takes a Configuration, and an XML document (as a String). The XML
114 -- document is written to the output directory, as specified by the
115 -- Configuration.
116 --
117 -- This can fail, but we don't purposefully throw any exceptions. If
118 -- something goes wrong, we would rather log it and keep going.
119 --
120 save_document :: Configuration -> String -> IO ()
121 save_document cfg doc =
122 case either_path of
123 Left err -> report_error err
124 Right path -> do
125 already_exists <- doesFileExist path
126 when already_exists $ do
127 let msg = "File " ++ path ++ " already exists, overwriting."
128 report_warning msg
129 writeFile path doc
130 report_info $ "Wrote file: " ++ path ++ "."
131 where
132 -- All the fmaps are because we're working inside a Maybe.
133 xmlfid = fmap show (parse_xmlfid doc)
134 filename = fmap (++ ".xml") xmlfid
135 either_path = fmap ((output_directory cfg) </>) filename
136
137
138 -- | Loop forever, writing the buffer to file whenever a </message>
139 -- tag is seen. This is the low-level "loop forever" function that
140 -- we stay in as long as we are connected to one feed.
141 --
142 -- The documentation at
143 -- <http://www.sportsnetworkdata.com/feeds/xml-levels.asp> states
144 -- that \<message\> will always be the root element of the XML
145 -- documents, and \</message\> will be the final line transmitted
146 -- for a given document. We therefore rely on this to simplify
147 -- processing.
148 --
149 loop :: Configuration -> Handle -> [String] -> IO ()
150 loop !cfg !h !buffer = do
151 line <- recv_line h
152 let new_buffer = line : buffer
153
154 -- Use isPrefixOf to avoid line-ending issues. Hopefully they won't
155 -- send invalid junk (on the same line) after closing the root
156 -- element.
157 if "</message>" `isPrefixOf` line
158 then do
159 -- The buffer is in reverse (newest first) order, though, so we
160 -- have to reverse it first. We then concatenate all of its lines
161 -- into one big string.
162 let document = concat $ reverse new_buffer
163 save_document cfg document
164 loop cfg h [] -- Empty the buffer before looping again.
165 else
166 -- Append line to the head of the buffer and loop.
167 loop cfg h new_buffer
168
169
170 log_in :: Configuration -> Handle -> IO ()
171 log_in cfg h = do
172 prompt1 <- recv_prompt h
173
174 if prompt1 /= username_prompt then
175 report_error "Didn't receive username prompt."
176 else do
177 send_line h (username cfg)
178 prompt2 <- recv_prompt h
179
180 if prompt2 /= password_prompt then
181 report_error "Didn't receive password prompt."
182 else do
183 send_line h (password cfg)
184 _ <- recv_line h -- "The Sports Network"
185 return ()
186 where
187 username_prompt = "Username: "
188 password_prompt = "Password: "
189
190 send_line :: Handle -> String -> IO ()
191 send_line h' s = do
192 let line = s ++ "\r\n"
193 hPutStr h' line
194 display_sent line
195
196 recv_chars :: Int -> Handle -> IO String
197 recv_chars n h' = do
198 s <- sequence [ hGetChar h' | _ <- [1..n] ]
199 report_debug s
200 return s
201
202 recv_prompt :: Handle -> IO String
203 recv_prompt = recv_chars 10
204
205
206 connect_and_loop :: Configuration -> String -> IO ()
207 connect_and_loop cfg host = do
208 report_info $ "Connecting to " ++ host ++ "."
209 bracket acquire_handle release_handle action
210 return ()
211 where
212 five_seconds :: Int
213 five_seconds = 5000000
214
215 acquire_handle = connectTo host (PortNumber 4500)
216 release_handle = hClose
217 action h = do
218 -- No buffering anywhere.
219 hSetBuffering h NoBuffering
220
221 -- The feed is often unresponsive after we send out username. It
222 -- happens in a telnet session, too (albeit less frequently?),
223 -- so there might be a bug on their end.
224 --
225 -- If we dump the packets with tcpdump, it looks like their
226 -- software is getting confused: they send us some XML in
227 -- the middle of the log-in procedure.
228 --
229 -- On the other hand, the documentation at
230 -- <http://www.sportsnetworkdata.com/feeds/xml-levels.asp>
231 -- states that you can only make one connection per username to
232 -- a given host. So maybe they're simply rejecting the username
233 -- in an unfriendly fashion. In any case, the easiest fix is to
234 -- disconnect and try again.
235 --
236 login_worked <- timeout five_seconds $ log_in cfg h
237 case login_worked of
238 Nothing -> report_info "Login timed out (5s)."
239 Just _ -> loop cfg h []
240
241
242 -- | A wrapper around threadDelay which takes seconds instead of
243 -- microseconds as its argument.
244 --
245 thread_sleep :: Int -> IO ()
246 thread_sleep seconds = do
247 let microseconds = seconds * (10 ^ (6 :: Int))
248 threadDelay microseconds
249
250
251 -- | The entry point of the program.
252 main :: IO ()
253 main = do
254 rc_cfg <- OC.from_rc
255 cmd_cfg <- get_args
256
257 -- Merge the config file options with the command-line ones,
258 -- prefering the command-line ones.
259 let opt_config = rc_cfg <> cmd_cfg
260
261 -- Update a default config with any options that have been set in
262 -- either the config file or on the command-line. We initialize
263 -- logging before the missing parameter checks below so that we can
264 -- log the errors.
265 let cfg = (def :: Configuration) `merge_optional` opt_config
266 init_logging (log_file cfg) (log_level cfg) (syslog cfg)
267
268 -- Check the optional config for missing required options. This is
269 -- necessary because if the user specifies an empty list of
270 -- hostnames in e.g. the config file, we want to bail rather than
271 -- fall back on the default list (which was merged from a default
272 -- Configuration above).
273 when (null $ get_feed_hosts (OC.feed_hosts opt_config)) $ do
274 report_error "No feed hosts supplied."
275 exitWith (ExitFailure exit_no_feed_hosts)
276
277 when (isNothing (OC.password opt_config)) $ do
278 report_error "No password supplied."
279 exitWith (ExitFailure exit_no_password)
280
281 when (isNothing (OC.username opt_config)) $ do
282 report_error "No username supplied."
283 exitWith (ExitFailure exit_no_username)
284
285 -- This may be superstition (and I believe stderr is unbuffered),
286 -- but it can't hurt.
287 hSetBuffering stderr NoBuffering
288 hSetBuffering stdout NoBuffering
289
290 -- Begin connecting to our feed hosts, starting with the first one.
291 round_robin cfg 0
292
293 where
294 -- | This is the top-level "loop forever" function. If an
295 -- exception is thrown, it will propagate up to this point, where
296 -- it will be logged and ignored in style.
297 --
298 -- Afterwards, we recurse (call ourself) again to loop more forevers.
299 --
300 round_robin :: Configuration -> Int -> IO ()
301 round_robin cfg feed_host_idx = do
302 let hosts = get_feed_hosts $ feed_hosts cfg
303 let host = hosts !! feed_host_idx
304 catchIOError (connect_and_loop cfg host) (report_error . show)
305 thread_sleep 5 -- Wait 5s before attempting to reconnect.
306 round_robin cfg $ (feed_host_idx + 1) `mod` (length hosts)