]> gitweb.michael.orlitzky.com - dead/htsn.git/blobdiff - src/Main.hs
Return an Either from parse_xmlfid instead of a Maybe for better error reporting.
[dead/htsn.git] / src / Main.hs
index 6b18c8646d311bdcaef94042561299f1a5836241..4ebada07e858fb53d2ca983503ced14201a1fd22 100644 (file)
@@ -4,19 +4,19 @@
 module Main
 where
 
-import Control.Concurrent (threadDelay)
-import Control.Exception.Base (bracket)
-import Control.Monad (when)
-import Data.List (isPrefixOf)
-import Data.Maybe (isNothing)
-import Data.Monoid ((<>))
+import Control.Concurrent ( threadDelay )
+import Control.Exception.Base ( bracket )
+import Control.Monad ( when )
+import Data.List ( isPrefixOf )
+import Data.Maybe ( isNothing )
+import Data.Monoid ( (<>) )
 import Network (
   connectTo,
   PortID (PortNumber) )
-import System.Console.CmdArgs (def)
-import System.Directory (doesFileExist)
-import System.Exit (ExitCode(..), exitWith)
-import System.FilePath ((</>))
+import System.Console.CmdArgs ( def )
+import System.Directory ( doesFileExist )
+import System.Exit ( ExitCode(..), exitWith )
+import System.FilePath ( (</>) )
 import System.IO (
   BufferMode (NoBuffering),
   Handle,
@@ -27,11 +27,11 @@ import System.IO (
   hSetBuffering,
   stderr,
   stdout )
-import System.IO.Error (catchIOError)
-import System.Timeout (timeout)
+import System.IO.Error ( catchIOError )
+import System.Timeout ( timeout )
 
-import CommandLine (get_args)
-import Configuration (Configuration(..), merge_optional)
+import CommandLine ( get_args )
+import Configuration ( Configuration(..), merge_optional )
 import ExitCodes (
   exit_no_feed_hosts,
   exit_no_password,
@@ -51,33 +51,49 @@ import Terminal (
   display_info,
   display_sent,
   display_warning )
-import TSN.FeedHosts (FeedHosts(..))
-import TSN.Xml (parse_xmlfid, xml_prologue)
+import TSN.FeedHosts ( FeedHosts(..) )
+import TSN.Xml ( parse_xmlfid )
 
 
--- | Warning! This does not automatically append a newline. The output
--- is displayed/logged as-is, for, you know, debug purposes.
+-- | Display and log debug information. WARNING! This does not
+--   automatically append a newline. The output is displayed/logged
+--   as-is, for, you know, debug purposes.
 report_debug :: String -> IO ()
 report_debug s = do
   display_debug s
   log_debug s
 
+
+-- | Display and log an error condition. This will prefix the error
+--   with "ERROR: " when displaying (but not logging) it so that it
+--   stands out.
+--
 report_error :: String -> IO ()
 report_error s = do
   display_error $ "ERROR: " ++ s
   log_error s
 
+
+-- | Display and log an informational (status) message.
 report_info :: String -> IO ()
 report_info s = do
   display_info s
   log_info s
 
--- | Warning! This does not automatically append a newline.
+
+-- | A special case of report_debug for reporting the two bits of data
+--   that we sent to TSN: the username and password.
+--
 report_sent :: String -> IO ()
 report_sent s = do
   display_sent s
   log_debug s
 
+
+-- | Display and log a warning. This will prefix the warning with
+--   "WARNING: " when displaying (but not logging) it so that it
+--   stands out.
+--
 report_warning :: String -> IO ()
 report_warning s = do
   display_warning $ "WARNING: " ++ s
@@ -103,10 +119,9 @@ recv_line h = do
 --
 save_document :: Configuration -> String -> IO ()
 save_document cfg doc =
-  case maybe_path of
-    Nothing ->
-      report_error "Document missing XML_File_ID element."
-    Just path -> do
+  case either_path of
+    Left err -> report_error err
+    Right path -> do
       already_exists <- doesFileExist path
       when already_exists $ do
         let msg = "File " ++ path ++ " already exists, overwriting."
@@ -114,31 +129,42 @@ save_document cfg doc =
       writeFile path doc
       report_info $ "Wrote file: " ++ path ++ "."
   where
+    -- All the fmaps are because we're working inside a Maybe.
     xmlfid = fmap show (parse_xmlfid doc)
     filename = fmap (++ ".xml") xmlfid
-    maybe_path = fmap ((output_directory cfg) </>) filename
+    either_path = fmap ((output_directory cfg) </>) filename
 
 
--- | Loop forever, writing the buffer to file whenever a new XML
---   prologue is seen. This is the low-level "loop forever" function
---   that we stay in as long as we are connected to one feed.
+-- | Loop forever, writing the buffer to file whenever a </message>
+--   tag is seen. This is the low-level "loop forever" function that
+--   we stay in as long as we are connected to one feed.
+--
+--   The documentation at
+--   <http://www.sportsnetworkdata.com/feeds/xml-levels.asp> states
+--   that \<message\> will always be the root element of the XML
+--   documents, and \</message\> will be the final line transmitted
+--   for a given document. We therefore rely on this to simplify
+--   processing.
 --
 loop :: Configuration -> Handle -> [String] -> IO ()
 loop !cfg !h !buffer = do
   line <- recv_line h
+  let new_buffer = line : buffer
 
-  if (xml_prologue `isPrefixOf` line && not (null buffer))
+  -- Use isPrefixOf to avoid line-ending issues. Hopefully they won't
+  -- send invalid junk (on the same line) after closing the root
+  -- element.
+  if "</message>" `isPrefixOf` line
   then do
-    -- This is the beginning of a new document, and we have an "old"
-    -- one to save. The buffer is in reverse (newest first) order,
-    -- though, so we have to reverse it first. We then concatenate all
-    -- of its lines into one big string.
-    let document = concat $ reverse buffer
+    -- The buffer is in reverse (newest first) order, though, so we
+    -- have to reverse it first. We then concatenate all of its lines
+    -- into one big string.
+    let document = concat $ reverse new_buffer
     save_document cfg document
-    loop cfg h [line] -- Empty the buffer before looping again.
+    loop cfg h [] -- Empty the buffer before looping again.
   else
     -- Append line to the head of the buffer and loop.
-    loop cfg h (line : buffer)
+    loop cfg h new_buffer
 
 
 log_in :: Configuration -> Handle -> IO ()
@@ -179,7 +205,7 @@ log_in cfg h = do
 
 connect_and_loop :: Configuration -> String -> IO ()
 connect_and_loop cfg host = do
-  report_info $ "Connecting to " ++ host ++ "..."
+  report_info $ "Connecting to " ++ host ++ "."
   bracket acquire_handle release_handle action
   return ()
   where
@@ -198,8 +224,14 @@ connect_and_loop cfg host = do
       --
       -- If we dump the packets with tcpdump, it looks like their
       -- software is getting confused: they send us some XML in
-      -- the middle of the log-in procedure. In any case, the easiest
-      -- fix is to disconnect and try again.
+      -- the middle of the log-in procedure.
+      --
+      -- On the other hand, the documentation at
+      -- <http://www.sportsnetworkdata.com/feeds/xml-levels.asp>
+      -- states that you can only make one connection per username to
+      -- a given host. So maybe they're simply rejecting the username
+      -- in an unfriendly fashion. In any case, the easiest fix is to
+      -- disconnect and try again.
       --
       login_worked <- timeout five_seconds $ log_in cfg h
       case login_worked of
@@ -231,7 +263,7 @@ main = do
   -- logging before the missing parameter checks below so that we can
   -- log the errors.
   let cfg = (def :: Configuration) `merge_optional` opt_config
-  init_logging (syslog cfg)
+  init_logging (log_file cfg) (log_level cfg) (syslog cfg)
 
   -- Check the optional config for missing required options. This is
   -- necessary because if the user specifies an empty list of
@@ -270,5 +302,5 @@ main = do
       let hosts = get_feed_hosts $ feed_hosts cfg
       let host = hosts !! feed_host_idx
       catchIOError (connect_and_loop cfg host) (report_error . show)
-      thread_sleep 10 -- Wait 10s before attempting to reconnect.
+      thread_sleep 5 -- Wait 5s before attempting to reconnect.
       round_robin cfg $ (feed_host_idx + 1) `mod` (length hosts)