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