-- | A newtype around a list of Strings which represent the feed
-- hosts. This is all to avoid an orphan instance of Configured for
--- [String] if we had defined one in e.g. OptionalConfiguration.
+-- [String] if we had defined one in e.g. 'OptionalConfiguration'.
--
--- This was placed under the "TSN" namespace because its Default
+-- This was placed under the \"TSN\" namespace because its Default
-- instance is specific to TSN, even though otherwise it's just a
-- list of strings.
--
deriving (Data, Show, Typeable)
+-- | The default list of feed hosts. These were found by checking
+-- PTR records in the neighborhood of the IP address in use. There
+-- is a feed4.sportsnetwork.com, but it was not operational when
+-- this was written.
instance Default FeedHosts where
- -- | The default list of feed hosts. These were found by checking
- -- PTR records in the neighborhood of the IP address in use. There
- -- is a feed4.sportsnetwork.com, but it was not operational when
- -- this was written.
def = FeedHosts ["feed1.sportsnetwork.com",
"feed2.sportsnetwork.com",
"feed3.sportsnetwork.com"]
module Main
where
+-- System imports.
import Control.Concurrent ( threadDelay )
import Control.Exception ( bracket, throw )
import Control.Monad ( when )
import Network (
connectTo,
PortID (PortNumber) )
+import Network.Services.TSN.Logging ( init_logging )
+import Network.Services.TSN.Report (
+ report_debug,
+ report_info,
+ report_warning,
+ report_error )
+import Network.Services.TSN.Terminal ( display_sent )
import System.Console.CmdArgs ( def )
import System.Directory ( doesFileExist )
import System.Exit ( ExitCode(..), exitWith )
import System.IO.Error ( catchIOError )
import System.Timeout ( timeout )
+-- Local imports.
import CommandLine ( get_args )
import Configuration ( Configuration(..), merge_optional )
import ExitCodes (
exit_no_username,
exit_pidfile_exists )
import FeedHosts ( FeedHosts(..) )
-import Network.Services.TSN.Logging ( init_logging )
import qualified OptionalConfiguration as OC (
OptionalConfiguration(..),
from_rc )
-import Network.Services.TSN.Report (
- report_debug,
- report_info,
- report_warning,
- report_error )
-import Network.Services.TSN.Terminal ( display_sent )
import Xml ( parse_xmlfid )
import Unix ( full_daemonize )
--- | Receive a single line of text from a Handle, and send it to the
--- debug log.
+-- | Receive a single line of text from a 'Handle', and record it for
+-- debugging purposes.
--
recv_line :: Handle -> IO String
recv_line h = do
return line
--- | Takes a Configuration, and an XML document (as a String). The XML
--- document is written to the output directory, as specified by the
--- Configuration.
+-- | Takes a 'Configuration', and an XML document (as a 'String'). The
+-- XML document is written to the output directory, as specified by
+-- the 'Configuration'.
--
-- This can fail, but we don't purposefully throw any exceptions. If
-- something goes wrong, we would rather log it and keep going.
--
-save_document :: Configuration -> String -> IO ()
+save_document :: Configuration
+ -> String -- ^ String representation of an XML document
+ -> IO ()
save_document cfg doc =
case either_path of
Left err -> report_error err
either_path = fmap ((output_directory cfg) </>) filename
--- | 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.
+-- | 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
-- for a given document. We therefore rely on this to simplify
-- processing.
--
-loop :: Configuration -> Handle -> [String] -> IO ()
+-- The bang pattern at least on @buffer@ is necessary for
+-- performance reasons.
+--
+loop :: Configuration
+ -> Handle -- ^ Handle to the feed (network connection)
+ -> [String] -- ^ Current XML document buffer, line-by-line, in reverse
+ -> IO ()
loop !cfg !h !buffer = do
line <- recv_line h
let new_buffer = line : buffer
-- (apparently) successfully guessed it.
--
-- The first thing TSN sends once we've connected is the string
--- "Username: ", containing 10 ASCII characters. We then send a
+-- \"Username: \", containing 10 ASCII characters. We then send a
-- username, followed by a newline. If TSN likes the username, the
--- second they'll send is the string "Password: ", also containing
+-- second they'll send is the string \"Password: \", also containing
-- 10 ASCII characters, to which we reply in kind.
--
-- Assuming the above will always hold, it is implemented as follows:
--
-- 4. Send password if we got the password prompt
--
--- If TSN likes the password as well, they send the string "The
--- Sports Network" before finally beginning to stream the feed.
+-- If TSN likes the password as well, they send the string \"The
+-- Sports Network\" before finally beginning to stream the feed.
--
log_in :: Configuration -> Handle -> IO ()
log_in cfg h = do
--
-- Steps:
--
--- 1. Connect to the host on the XML port
+-- 1. Connect to @host@ on the XML feed port.
--
--- 2. Log in
+-- 2. Log in.
--
-- 3. Go into the eternal read/save loop.
--
-connect_and_parse :: Configuration -> String -> IO ()
+connect_and_parse :: Configuration
+ -> String -- ^ Hostname to connect to
+ -> IO ()
connect_and_parse cfg host = do
report_info $ "Connecting to " ++ host ++ "."
bracket acquire_handle release_handle action
-- | A wrapper around threadDelay which takes seconds instead of
-- microseconds as its argument.
--
-thread_sleep :: Int -> IO ()
+thread_sleep :: Int -- ^ Number of seconds for which to sleep.
+ -> IO ()
thread_sleep seconds = do
let microseconds = seconds * (10 ^ (6 :: Int))
threadDelay microseconds
else run_program
where
- -- | This is the top-level "loop forever" function. If an
+ -- | This is the top-level \"loop forever\" function. If an
-- exception is thrown, it will propagate up to this point, where
-- it will be logged and ignored in style.
--
--
module Xml (
parse_xmlfid,
+ -- * Tests
xml_tests )
where
xreadDoc )
--- | A tiny parser written in HXT to extract the "XML_File_ID" element
--- from a document. If we fail to parse an XML_File_ID, we return
--- the reason wrapped in a 'Left' constructor. The reason should be
--- one of two things:
+-- | A tiny parser written in HXT to extract the \"XML_File_ID\"
+-- element from a document. If we fail to parse an XML_File_ID, we
+-- return the reason wrapped in a 'Left' constructor. The reason
+-- should be one of two things:
--
-- 1. No XML_File_ID elements were found.
--
--
-- We use an Either rather than a Maybe because we do expect some
-- non-integer XML_File_IDs. In the examples, you will see
--- NHL_DepthChart_XML.XML with an XML_File_ID of "49618.61" and
--- CFL_Boxscore_XML1.xml with an XML_File_ID of "R28916". According
--- to Brijesh Patel of TSN, these are special category files and not
--- part of the usual feed.
+-- NHL_DepthChart_XML.XML with an XML_File_ID of \"49618.61\" and
+-- CFL_Boxscore_XML1.xml with an XML_File_ID of
+-- \"R28916\". According to Brijesh Patel of TSN, these are special
+-- category files and not part of the usual feed.
--
--- We want to report them differently, "just in case."
+-- We want to report them differently, \"just in case.\"
--
parse_xmlfid :: String -- ^ The XML Document
-> Either String Integer
parse_results = map read_either_integer elements
--- * Tasty Tests
+--
+-- Tasty Tests
+--
+
+-- | A list of all tests for this module.
+--
xml_tests :: TestTree
xml_tests =
testGroup
[ xml_file_id_tests ]
+-- | Ensure that we parse the correct XML_File_ID out of some known
+-- examples.
+--
xml_file_id_tests :: TestTree
xml_file_id_tests =
testCase "XML_File_ID is parsed correctly" $ do