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