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