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