1 {-# LANGUAGE DoAndIfThenElse #-}
2 {-# LANGUAGE NoMonomorphismRestriction #-}
7 import Control.Arrow ( (&&&), (>>^), arr, returnA )
8 import Control.Concurrent ( threadDelay )
9 import Control.Exception ( SomeException, catch )
10 import Control.Monad ( when )
11 import Database.Groundhog.Generic ( runDbConn )
12 import Database.Groundhog.Sqlite (
14 import Database.Groundhog.Postgresql (
16 import Data.Monoid ( (<>) )
17 import Network.Services.TSN.Logging ( init_logging )
18 import System.Console.CmdArgs ( def )
19 import System.Directory ( removeFile )
20 import System.Exit ( exitWith, ExitCode (ExitFailure) )
21 import System.IO.Error ( catchIOError )
22 import Text.XML.HXT.Core (
36 import Backend ( Backend(..) )
37 import CommandLine ( get_args )
38 import Configuration ( Configuration(..), merge_optional )
39 import ConnectionString ( ConnectionString(..) )
40 import ExitCodes ( exit_no_xml_files )
41 import qualified OptionalConfiguration as OC (
42 OptionalConfiguration ( xml_files ),
44 import Network.Services.TSN.Report (
47 import TSN.DbImport ( DbImport(..), ImportResult(..) )
48 import qualified TSN.XML.AutoRacingResults as AutoRacingResults (
51 import qualified TSN.XML.AutoRacingSchedule as AutoRacingSchedule (
54 import qualified TSN.XML.GameInfo as GameInfo ( dtds, parse_xml )
55 import qualified TSN.XML.Heartbeat as Heartbeat ( dtd, verify )
56 import qualified TSN.XML.Injuries as Injuries ( dtd, pickle_message )
57 import qualified TSN.XML.InjuriesDetail as InjuriesDetail (
60 import qualified TSN.XML.News as News ( dtd, pickle_message )
61 import qualified TSN.XML.Odds as Odds ( dtd, pickle_message )
62 import qualified TSN.XML.Scores as Scores ( dtd, pickle_message )
63 import qualified TSN.XML.SportInfo as SportInfo ( dtds, parse_xml )
64 import qualified TSN.XML.Weather as Weather ( dtd, pickle_message )
65 import Xml ( DtdName(..), parse_opts )
68 -- | This is where most of the work happens. This function is called
69 -- on every file that we would like to import. It determines which
70 -- importer to use based on the DTD, attempts to process the file,
71 -- and then returns whether or not it was successful. If the file
72 -- was processed, 'True' is returned. Otherwise, 'False' is
75 -- The implementation is straightforward with one exception: since
76 -- we are already in arrow world with HXT, the @import_with_dtd@
77 -- function is lifted to an 'Arrow' as well with 'arr'. This
78 -- prevents us from having to do a bunch of unwrapping and
79 -- rewrapping with the associated error checking.
81 import_file :: Configuration -- ^ A configuration object needed for the
82 -- 'backend' and 'connection_string'.
84 -> FilePath -- ^ The path of the XML file to import.
86 -> IO Bool -- ^ True if we processed the file, False otherwise.
87 import_file cfg path = do
88 results <- parse_and_import `catch` exception_handler
91 -- One of the arrows returned "nothing."
92 report_error $ "Unable to determine DTD for file " ++ path ++ "."
94 (ImportFailed errmsg:_) -> do
97 (ImportSkipped infomsg:_) -> do
98 -- We processed the message but didn't import anything. Return
99 -- "success" so that the XML file is deleted.
102 (ImportSucceeded:_) -> do
103 report_info $ "Successfully imported " ++ path ++ "."
105 (ImportUnsupported infomsg:_) -> do
106 -- For now we return "success" for these too, since we know we don't
107 -- support a bunch of DTDs and we want them to get deleted.
111 -- | This will catch *any* exception, even the ones thrown by
112 -- Haskell's 'error' (which should never occur under normal
114 exception_handler :: SomeException -> IO [ImportResult]
115 exception_handler e = do
116 report_error (show e)
117 let errdesc = "Failed to import file " ++ path ++ "."
118 -- Return a nonempty list so we don't claim incorrectly that
119 -- we couldn't parse the DTD.
120 return [ImportFailed errdesc]
122 -- | An arrow that reads a document into an 'XmlTree'.
123 readA :: IOStateArrow s a XmlTree
124 readA = readDocument parse_opts path
126 -- | An arrow which parses the doctype "SYSTEM" of an 'XmlTree'.
127 -- We use these to determine the parser to use.
128 dtdnameA :: ArrowXml a => a XmlTree DtdName
129 dtdnameA = getAttrl >>> hasName "doctype-SYSTEM" /> getText >>^ DtdName
131 -- | Combine the arrows above as well as the function below
132 -- (arrowized with 'arr') into an IO action that does everything
133 -- (parses and then runs the import on what was parsed).
135 -- The result of runX has type IO [IO ImportResult]. We thus use
136 -- bind (>>=) and sequence to combine all of the IOs into one
137 -- big one outside of the list.
138 parse_and_import :: IO [ImportResult]
140 runX (readA >>> (dtdnameA &&& returnA) >>> (arr import_with_dtd))
144 -- | Takes a ('DtdName', 'XmlTree') pair and uses the 'DtdName'
145 -- to determine which function to call on the 'XmlTree'.
146 import_with_dtd :: (DtdName, XmlTree) -> IO ImportResult
147 import_with_dtd (DtdName dtd,xml)
148 -- We special-case the heartbeat so it doesn't have to run in
149 -- the database monad.
150 | dtd == Heartbeat.dtd = Heartbeat.verify xml
152 -- We need NoMonomorphismRestriction here.
153 if backend cfg == Postgres
154 then withPostgresqlConn cs $ runDbConn importer
155 else withSqliteConn cs $ runDbConn importer
157 -- | Pull the real connection String out of the configuration.
160 cs = get_connection_string $ connection_string cfg
162 -- | Convenience; we use this everywhere below in 'importer'.
164 migrate_and_import m = dbmigrate m >> dbimport m
167 | dtd == AutoRacingResults.dtd = do
168 let m = unpickleDoc AutoRacingResults.pickle_message xml
169 maybe (return $ ImportFailed errmsg) migrate_and_import m
171 | dtd == AutoRacingSchedule.dtd = do
172 let m = unpickleDoc AutoRacingSchedule.pickle_message xml
173 maybe (return $ ImportFailed errmsg) migrate_and_import m
175 -- GameInfo and SportInfo appear least in the guards
176 | dtd == Injuries.dtd = do
177 let m = unpickleDoc Injuries.pickle_message xml
178 maybe (return $ ImportFailed errmsg) migrate_and_import m
180 | dtd == InjuriesDetail.dtd = do
181 let m = unpickleDoc InjuriesDetail.pickle_message xml
182 maybe (return $ ImportFailed errmsg) migrate_and_import m
185 | dtd == News.dtd = do
186 let m = unpickleDoc News.pickle_message xml
187 maybe (return $ ImportFailed errmsg) migrate_and_import m
189 | dtd == Odds.dtd = do
190 let m = unpickleDoc Odds.pickle_message xml
191 maybe (return $ ImportFailed errmsg) migrate_and_import m
193 | dtd == Scores.dtd = do
194 let m = unpickleDoc Scores.pickle_message xml
195 maybe (return $ ImportFailed errmsg) migrate_and_import m
197 -- SportInfo and GameInfo appear least in the guards
198 | dtd == Weather.dtd = do
199 let m = unpickleDoc Weather.pickle_message xml
200 maybe (return $ ImportFailed errmsg) migrate_and_import m
202 | dtd `elem` GameInfo.dtds = do
203 let either_m = GameInfo.parse_xml dtd xml
205 -- This might give us a slightly better error
206 -- message than the default 'errmsg'.
207 Left err -> return $ ImportFailed err
208 Right m -> migrate_and_import m
210 | dtd `elem` SportInfo.dtds = do
211 let either_m = SportInfo.parse_xml dtd xml
213 -- This might give us a slightly better error
214 -- message than the default 'errmsg'.
215 Left err -> return $ ImportFailed err
216 Right m -> migrate_and_import m
220 "Unrecognized DTD in " ++ path ++ ": " ++ dtd ++ "."
221 return $ ImportUnsupported infomsg
224 errmsg = "Could not unpickle " ++ dtd ++ "."
227 -- | Entry point of the program. It twiddles some knobs for
228 -- configuration options and then calls 'import_file' on each XML
229 -- file given on the command-line.
231 -- Any file successfully processed is then optionally removed, and
239 -- Merge the config file options with the command-line ones,
240 -- prefering the command-line ones.
241 let opt_config = rc_cfg <> cmd_cfg
243 -- Update a default config with any options that have been set in
244 -- either the config file or on the command-line. We initialize
245 -- logging before the missing parameter checks below so that we can
247 let cfg = (def :: Configuration) `merge_optional` opt_config
248 init_logging (log_level cfg) (log_file cfg) (syslog cfg)
250 -- Check the optional config for missing required options.
251 when (null $ OC.xml_files opt_config) $ do
252 report_error "No XML files given."
253 exitWith (ExitFailure exit_no_xml_files)
255 -- We don't do this in parallel (for now?) to keep the error
256 -- messages nice and linear.
257 results <- mapM (import_file cfg) (OC.xml_files opt_config)
259 -- Zip the results with the files list to find out which ones can be
261 let result_pairs = zip (OC.xml_files opt_config) results
262 let victims = [ p | (p, True) <- result_pairs ]
263 let processed_count = length victims
264 report_info $ "Processed " ++ (show processed_count) ++ " document(s) total."
265 when (remove cfg) $ mapM_ (kill True) victims
268 -- | Wrap these two actions into one function so that we don't
269 -- report that the file was removed if the exception handler is
271 remove_and_report path = do
273 report_info $ "Removed processed file " ++ path ++ "."
275 -- | Try to remove @path@ and potentially try again.
276 kill try_again path =
277 (remove_and_report path) `catchIOError` exception_handler
279 -- | A wrapper around threadDelay which takes seconds instead of
280 -- microseconds as its argument.
281 thread_sleep :: Int -> IO ()
282 thread_sleep seconds = do
283 let microseconds = seconds * (10 ^ (6 :: Int))
284 threadDelay microseconds
286 -- | If we can't remove the file, report that, and try once
287 -- more after waiting a few seconds.
288 exception_handler :: IOError -> IO ()
289 exception_handler e = do
290 report_error (show e)
291 report_error $ "Failed to remove imported file " ++ path ++ "."
293 report_info "Waiting 5 seconds to attempt removal again..."
297 report_info $ "Giving up on " ++ path ++ "."