]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blob - src/Main.hs
Allow "TBA" laps in TSN.XML.AutoRacingSchedule.
[dead/htsn-import.git] / src / Main.hs
1 {-# LANGUAGE DoAndIfThenElse #-}
2 {-# LANGUAGE NoMonomorphismRestriction #-}
3 module Main
4 where
5
6 -- System imports.
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 (
13 withSqliteConn )
14 import Database.Groundhog.Postgresql (
15 withPostgresqlConn )
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 (
23 ArrowXml,
24 IOStateArrow,
25 SysConfigList,
26 XmlTree,
27 (>>>),
28 (/>),
29 getAttrl,
30 getText,
31 hasName,
32 readDocument,
33 runX,
34 unpickleDoc )
35
36 -- Local imports.
37 import Backend ( Backend(..) )
38 import CommandLine ( get_args )
39 import Configuration ( Configuration(..), merge_optional )
40 import ConnectionString ( ConnectionString(..) )
41 import ExitCodes ( exit_no_xml_files )
42 import qualified OptionalConfiguration as OC (
43 OptionalConfiguration ( xml_files ),
44 from_rc )
45 import Network.Services.TSN.Report (
46 report_info,
47 report_error )
48 import TSN.DbImport ( DbImport(..), ImportResult(..) )
49 import TSN.Parse ( format_parse_error )
50 import qualified TSN.XML.AutoRacingDriverList as AutoRacingDriverList (
51 dtd,
52 pickle_message )
53 import qualified TSN.XML.AutoRacingResults as AutoRacingResults (
54 dtd,
55 pickle_message )
56 import qualified TSN.XML.AutoRacingSchedule as AutoRacingSchedule (
57 dtd,
58 pickle_message )
59 import qualified TSN.XML.EarlyLine as EarlyLine (
60 dtd,
61 pickle_message )
62 import qualified TSN.XML.GameInfo as GameInfo ( dtds, parse_xml )
63 import qualified TSN.XML.Heartbeat as Heartbeat ( dtd, verify )
64 import qualified TSN.XML.Injuries as Injuries ( dtd, pickle_message )
65 import qualified TSN.XML.InjuriesDetail as InjuriesDetail (
66 dtd,
67 pickle_message )
68 import qualified TSN.XML.MLBEarlyLine as MLBEarlyLine (
69 dtd,
70 pickle_message )
71 import qualified TSN.XML.JFile as JFile ( dtd, pickle_message )
72 import qualified TSN.XML.News as News (
73 dtd,
74 has_only_single_sms,
75 pickle_message )
76 import qualified TSN.XML.Odds as Odds ( dtd, pickle_message )
77 import qualified TSN.XML.ScheduleChanges as ScheduleChanges (
78 dtd,
79 pickle_message )
80 import qualified TSN.XML.Scores as Scores ( dtd, pickle_message )
81 import qualified TSN.XML.SportInfo as SportInfo ( dtds, parse_xml )
82 import qualified TSN.XML.Weather as Weather (
83 dtd,
84 is_type1,
85 pickle_message,
86 teams_are_normal )
87 import Xml ( DtdName(..), parse_opts, parse_opts_novalidate )
88
89
90 -- | This is where most of the work happens. This function is called
91 -- on every file that we would like to import. It determines which
92 -- importer to use based on the DTD, attempts to process the file,
93 -- and then returns whether or not it was successful. If the file
94 -- was processed, 'True' is returned. Otherwise, 'False' is
95 -- returned.
96 --
97 -- The implementation is straightforward with one exception: since
98 -- we are already in arrow world with HXT, the @import_with_dtd@
99 -- function is lifted to an 'Arrow' as well with 'arr'. This
100 -- prevents us from having to do a bunch of unwrapping and
101 -- rewrapping with the associated error checking.
102 --
103 import_file :: Configuration -- ^ A configuration object needed for the
104 -- 'backend' and 'connection_string'.
105
106 -> FilePath -- ^ The path of the XML file to import.
107
108 -> IO Bool -- ^ True if we processed the file, False otherwise.
109 import_file cfg path = do
110 results <- parse_and_import `catch` exception_handler
111 case results of
112 [] -> do
113 -- One of the arrows returned "nothing." Now that we're
114 -- validating against the DTDs, this will almost always be
115 -- caused by a document whose DTD is not present (i.e. is
116 -- unsupported). So we return "success" to allow the XML file to
117 -- be deleted.
118 report_info $ "No DTD for file " ++ path ++ "."
119 return True
120 (ImportFailed errmsg:_) -> do
121 report_error $ errmsg ++ " (" ++ path ++ ")"
122 return False
123 (ImportSkipped infomsg:_) -> do
124 -- We processed the message but didn't import anything. Return
125 -- "success" so that the XML file is deleted.
126 report_info infomsg
127 return True
128 (ImportSucceeded:_) -> do
129 report_info $ "Successfully imported " ++ path ++ "."
130 return True
131 (ImportUnsupported infomsg:_) -> do
132 -- For now we return "success" for these too, since we know we don't
133 -- support a bunch of DTDs and we want them to get deleted.
134 report_info infomsg
135 return True
136 where
137 -- | This will catch *any* exception, even the ones thrown by
138 -- Haskell's 'error' (which should never occur under normal
139 -- circumstances).
140 exception_handler :: SomeException -> IO [ImportResult]
141 exception_handler e = do
142 report_error (show e)
143 let errdesc = "Failed to import file " ++ path ++ "."
144 -- Return a nonempty list so we don't claim incorrectly that
145 -- we couldn't parse the DTD.
146 return [ImportFailed errdesc]
147
148 -- | An arrow that reads a document into an 'XmlTree'. We take a
149 -- SysConfigList so our caller can decide whether or not to
150 -- e.g. validate the document against its DTD.
151 readA :: SysConfigList -> IOStateArrow s a XmlTree
152 readA scl = readDocument scl path
153
154 -- | An arrow which parses the doctype "SYSTEM" of an 'XmlTree'.
155 -- We use these to determine the parser to use.
156 dtdnameA :: ArrowXml a => a XmlTree DtdName
157 dtdnameA = getAttrl >>> hasName "doctype-SYSTEM" /> getText >>^ DtdName
158
159 -- | Combine the arrows above as well as the function below
160 -- (arrowized with 'arr') into an IO action that does everything
161 -- (parses and then runs the import on what was parsed).
162 --
163 -- The result of runX has type IO [IO ImportResult]. We thus use
164 -- bind (>>=) and sequence to combine all of the IOs into one
165 -- big one outside of the list.
166 --
167 -- Before we actually run the import, we check it against a list
168 -- of problem DTDs. These can produce weird errors, and we have
169 -- checks for them. But with DTD validation enabled, we can't
170 -- even look inside the document to see what's wrong -- parsing
171 -- will fail! So for those special document types, we proceed
172 -- using 'parse_opts_novalidate' instead of the default
173 -- 'parse_opts'.
174 --
175 parse_and_import :: IO [ImportResult]
176 parse_and_import = do
177 -- Get the DTD name without validating against it.
178 ((DtdName dtd) : _) <- runX $ (readA parse_opts_novalidate) >>> dtdnameA
179
180 let problem_dtds = [ News.dtd, Weather.dtd ]
181 let opts = if dtd `elem` problem_dtds
182 then parse_opts_novalidate
183 else parse_opts
184
185 runX ((readA opts) >>> (dtdnameA &&& returnA) >>> (arr import_with_dtd))
186 >>= sequence
187
188 -- | Takes a ('DtdName', 'XmlTree') pair and uses the 'DtdName'
189 -- to determine which function to call on the 'XmlTree'.
190 import_with_dtd :: (DtdName, XmlTree) -> IO ImportResult
191 import_with_dtd (DtdName dtd,xml)
192 -- We special-case the heartbeat so it doesn't have to run in
193 -- the database monad.
194 | dtd == Heartbeat.dtd = Heartbeat.verify xml
195 | otherwise =
196 -- We need NoMonomorphismRestriction here.
197 if backend cfg == Postgres
198 then withPostgresqlConn cs $ runDbConn importer
199 else withSqliteConn cs $ runDbConn importer
200 where
201 -- | Pull the real connection String out of the configuration.
202 --
203 cs :: String
204 cs = get_connection_string $ connection_string cfg
205
206 -- | Convenience; we use this everywhere below in 'importer'.
207 --
208 migrate_and_import m = dbmigrate m >> dbimport m
209
210 -- | The error message we return if unpickling fails.
211 --
212 errmsg = "Could not unpickle " ++ dtd ++ "."
213
214 -- | Try to migrate and import using the given pickler @f@;
215 -- if it works, return the result. Otherwise, return an
216 -- 'ImportFailed' along with our error message.
217 --
218 go f = maybe
219 (return $ ImportFailed errmsg)
220 migrate_and_import
221 (unpickleDoc f xml)
222
223 importer
224 | dtd == AutoRacingDriverList.dtd =
225 go AutoRacingDriverList.pickle_message
226
227 | dtd == AutoRacingResults.dtd =
228 go AutoRacingResults.pickle_message
229
230 | dtd == AutoRacingSchedule.dtd =
231 go AutoRacingSchedule.pickle_message
232
233 | dtd == EarlyLine.dtd =
234 go EarlyLine.pickle_message
235
236 -- GameInfo and SportInfo appear last in the guards
237 | dtd == Injuries.dtd = go Injuries.pickle_message
238
239 | dtd == InjuriesDetail.dtd = go InjuriesDetail.pickle_message
240
241 | dtd == JFile.dtd = go JFile.pickle_message
242
243 | dtd == MLBEarlyLine.dtd = go MLBEarlyLine.pickle_message
244
245 | dtd == News.dtd =
246 -- Some of the newsxml docs are busted in predictable ways.
247 -- We want them to "succeed" so that they're deleted.
248 -- We already know we can't parse them.
249 if News.has_only_single_sms xml
250 then go News.pickle_message
251 else do
252 let msg = "Unsupported newsxml.dtd with multiple SMS " ++
253 "(" ++ path ++ ")"
254 return $ ImportUnsupported msg
255 | dtd == Odds.dtd = go Odds.pickle_message
256
257 | dtd == ScheduleChanges.dtd = go ScheduleChanges.pickle_message
258
259 | dtd == Scores.dtd = go Scores.pickle_message
260
261 -- SportInfo and GameInfo appear last in the guards
262 | dtd == Weather.dtd =
263 -- Some of the weatherxml docs are busted in predictable ways.
264 -- We want them to "succeed" so that they're deleted.
265 -- We already know we can't parse them.
266 if Weather.is_type1 xml
267 then if Weather.teams_are_normal xml
268 then go Weather.pickle_message
269 else do
270 let msg = "Teams in reverse order in weatherxml.dtd" ++
271 " (" ++ path ++ ")"
272 return $ ImportUnsupported msg
273 else do
274 let msg = "Unsupported weatherxml.dtd type (" ++ path ++ ")"
275 return $ ImportUnsupported msg
276
277 | dtd `elem` GameInfo.dtds = do
278 let either_m = GameInfo.parse_xml dtd xml
279 case either_m of
280 -- This might give us a slightly better error
281 -- message than the default 'errmsg'.
282 Left err -> return $ ImportFailed (format_parse_error err)
283 Right m -> migrate_and_import m
284
285 | dtd `elem` SportInfo.dtds = do
286 let either_m = SportInfo.parse_xml dtd xml
287 case either_m of
288 -- This might give us a slightly better error
289 -- message than the default 'errmsg'.
290 Left err -> return $ ImportFailed (format_parse_error err)
291 Right m -> migrate_and_import m
292
293 | otherwise = do
294 let infomsg =
295 "Unrecognized DTD in " ++ path ++ ": " ++ dtd ++ "."
296 -- This should be an impossible case while DTD
297 -- validation is enabled. If we can parse the file at
298 -- all, then we have a DTD for it sitting around. And we
299 -- only have DTDs for supported types.
300 return $ ImportUnsupported infomsg
301
302
303
304 -- | Entry point of the program. It twiddles some knobs for
305 -- configuration options and then calls 'import_file' on each XML
306 -- file given on the command-line.
307 --
308 -- Any file successfully processed is then optionally removed, and
309 -- we're done.
310 --
311 main :: IO ()
312 main = do
313 rc_cfg <- OC.from_rc
314 cmd_cfg <- get_args
315
316 -- Merge the config file options with the command-line ones,
317 -- prefering the command-line ones.
318 let opt_config = rc_cfg <> cmd_cfg
319
320 -- Update a default config with any options that have been set in
321 -- either the config file or on the command-line. We initialize
322 -- logging before the missing parameter checks below so that we can
323 -- log the errors.
324 let cfg = (def :: Configuration) `merge_optional` opt_config
325 init_logging (log_level cfg) (log_file cfg) (syslog cfg)
326
327 -- Check the optional config for missing required options.
328 when (null $ OC.xml_files opt_config) $ do
329 report_error "No XML files given."
330 exitWith (ExitFailure exit_no_xml_files)
331
332 -- We don't do this in parallel (for now?) to keep the error
333 -- messages nice and linear.
334 results <- mapM (import_file cfg) (OC.xml_files opt_config)
335
336 -- Zip the results with the files list to find out which ones can be
337 -- deleted.
338 let result_pairs = zip (OC.xml_files opt_config) results
339 let victims = [ p | (p, True) <- result_pairs ]
340 let processed_count = length victims
341 report_info $ "Processed " ++ (show processed_count) ++ " document(s) total."
342 when (remove cfg) $ mapM_ (kill True) victims
343
344 where
345 -- | Wrap these two actions into one function so that we don't
346 -- report that the file was removed if the exception handler is
347 -- run.
348 remove_and_report path = do
349 removeFile path
350 report_info $ "Removed processed file " ++ path ++ "."
351
352 -- | Try to remove @path@ and potentially try again.
353 kill try_again path =
354 (remove_and_report path) `catchIOError` exception_handler
355 where
356 -- | A wrapper around threadDelay which takes seconds instead of
357 -- microseconds as its argument.
358 thread_sleep :: Int -> IO ()
359 thread_sleep seconds = do
360 let microseconds = seconds * (10 ^ (6 :: Int))
361 threadDelay microseconds
362
363 -- | If we can't remove the file, report that, and try once
364 -- more after waiting a few seconds.
365 exception_handler :: IOError -> IO ()
366 exception_handler e = do
367 report_error (show e)
368 report_error $ "Failed to remove imported file " ++ path ++ "."
369 if try_again then do
370 report_info "Waiting 5 seconds to attempt removal again..."
371 thread_sleep 5
372 kill False path
373 else
374 report_info $ "Giving up on " ++ path ++ "."