]> gitweb.michael.orlitzky.com - dead/htsn.git/blob - src/Main.hs
e1cb91abdd0a704a05157622bf47806baa8bd24c
[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 FeedHosts (FeedHosts(..))
40 import qualified OptionalConfiguration as OC (
41 OptionalConfiguration(..),
42 from_rc )
43 import Terminal (hPutRedLn, putGreenLn)
44 import TSN.Xml (parse_xmlfid, xml_prologue)
45
46
47 report_error :: String -> IO ()
48 report_error = hPutRedLn stderr
49
50
51 recv_line :: Handle -> IO String
52 recv_line h = do
53 line <- hGetLine h
54 putStrLn line
55 return line
56
57
58 save_document :: Configuration -> String -> IO ()
59 save_document cfg doc =
60 case maybe_path of
61 Nothing ->
62 report_error "ERROR: document missing XML_File_ID element."
63 Just path -> do
64 already_exists <- doesFileExist path
65 when already_exists $ do
66 let msg = "WARNING: file " ++ path ++ " already exists. Overwriting."
67 report_error msg
68 writeFile path doc
69 where
70 xmlfid = fmap show (parse_xmlfid doc)
71 filename = fmap (++ ".xml") xmlfid
72 maybe_path = fmap ((output_directory cfg) </>) filename
73
74 -- | Loop forever, writing the buffer to file whenever a new XML
75 -- prologue is seen.
76 loop :: Configuration -> Handle -> [String] -> IO ()
77 loop !cfg !h !buffer = do
78 line <- recv_line h
79
80 if (xml_prologue `isPrefixOf` line && not (null buffer))
81 then do
82 -- This is the beginning of a new document, and we have an "old"
83 -- one to save. The buffer is in reverse (newest first) order,
84 -- though, so we have to reverse it first. We then concatenate all
85 -- of its lines into one big string.
86 let document = concat $ reverse buffer
87 save_document cfg document
88 loop cfg h [line] -- empty the buffer before looping again
89 else
90 loop cfg h (line : buffer) -- append line to the head of the buffer and loop
91
92
93 log_in :: Configuration -> Handle -> IO ()
94 log_in cfg h = do
95 prompt1 <- recv_prompt h
96
97 if prompt1 /= username_prompt then
98 report_error "ERROR: didn't receive username prompt."
99 else do
100 send_line h (username cfg)
101 prompt2 <- recv_prompt h
102
103 if prompt2 /= password_prompt then
104 report_error "ERROR: didn't receive password prompt."
105 else do
106 send_line h (password cfg)
107 _ <- recv_line h -- "The Sports Network"
108 return ()
109 where
110 username_prompt = "Username: "
111 password_prompt = "Password: "
112
113 send_line :: Handle -> String -> IO ()
114 send_line h' s = do
115 hPutStr h' (s ++ "\r\n")
116 putGreenLn s
117
118 recv_chars :: Int -> Handle -> IO String
119 recv_chars n h' = do
120 s <- sequence [ hGetChar h' | _ <- [1..n] ]
121 putStr s
122 return s
123
124 recv_prompt :: Handle -> IO String
125 recv_prompt = recv_chars 10
126
127 connect_and_loop :: Configuration -> String -> IO ()
128 connect_and_loop cfg host = do
129 putStrLn $ "Connecting to " ++ host ++ "..."
130 bracket acquire_handle release_handle action
131 return ()
132 where
133 five_seconds :: Int
134 five_seconds = 5000000
135
136 acquire_handle = connectTo host (PortNumber 4500)
137 release_handle = hClose
138 action h = do
139 -- No buffering anywhere.
140 hSetBuffering h NoBuffering
141
142 -- The feed is often unresponsive after we send out username. It
143 -- happens in a telnet session, too (albeit less frequently?),
144 -- so there might be a bug on their end.
145 --
146 -- If we dump the packets with tcpdump, it looks like their
147 -- software is getting confused: they send us some XML in
148 -- the middle of the log-in procedure. In any case, the easiest
149 -- fix is to disconnect and try again.
150 --
151 login_worked <- timeout five_seconds $ log_in cfg h
152 case login_worked of
153 Nothing -> putStrLn "Login timed out (5s)."
154 Just _ -> loop cfg h []
155
156
157 -- | A wrapper around threadDelay which takes seconds instead of
158 -- microseconds as its argument.
159 thread_sleep :: Int -> IO ()
160 thread_sleep seconds = do
161 let microseconds = seconds * (10 ^ (6 :: Int))
162 threadDelay microseconds
163
164
165 main :: IO ()
166 main = do
167 rc_cfg <- OC.from_rc
168 cmd_cfg <- get_args
169
170 -- Merge the config file options with the command-line ones,
171 -- prefering the command-line ones.
172 let opt_config = rc_cfg <> cmd_cfg
173
174 -- This is necessary because if the user specifies an empty list of
175 -- hostnames in e.g. the config file, we want to bail rather than
176 -- fall back on the default list (which gets merged from a
177 -- Configuration below).
178 when (null $ get_feed_hosts (OC.feed_hosts opt_config)) $ do
179 report_error "ERROR: no feed hosts supplied."
180 exitWith (ExitFailure exit_no_feed_hosts)
181
182 when (isNothing (OC.password opt_config)) $ do
183 report_error "ERROR: no password supplied."
184 exitWith (ExitFailure exit_no_password)
185
186 when (isNothing (OC.username opt_config)) $ do
187 report_error "ERROR: no username supplied."
188 exitWith (ExitFailure exit_no_username)
189
190 -- Finally, update a default config with any options that have been
191 -- set in either the config file or on the command-line.
192 let cfg = (def :: Configuration) `merge_optional` opt_config
193
194 hSetBuffering stderr NoBuffering
195 hSetBuffering stdout NoBuffering
196
197 round_robin cfg 0
198
199 where
200 round_robin :: Configuration -> Int -> IO ()
201 round_robin cfg feed_host_idx = do
202 let hosts = get_feed_hosts $ feed_hosts cfg
203 let host = hosts !! feed_host_idx
204 catchIOError (connect_and_loop cfg host) (report_error . show)
205 thread_sleep 10 -- Wait 10s before attempting to reconnect.
206 round_robin cfg $ (feed_host_idx + 1) `mod` (length hosts)