]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blob - src/Main.hs
Rename the ImportResult constructors.
[dead/htsn-import.git] / src / Main.hs
1 {-# LANGUAGE DoAndIfThenElse #-}
2 {-# LANGUAGE NoMonomorphismRestriction #-}
3 module Main
4 where
5
6 import Control.Arrow ( (&&&), (>>^), arr, returnA )
7 import Control.Concurrent ( threadDelay )
8 import Control.Exception ( SomeException, catch )
9 import Control.Monad ( when )
10 import Database.Groundhog.Generic ( runDbConn )
11 import Database.Groundhog.Sqlite (
12 withSqliteConn )
13 import Database.Groundhog.Postgresql (
14 withPostgresqlConn )
15 import Data.Monoid ( (<>) )
16 import Network.Services.TSN.Logging ( init_logging )
17 import System.Console.CmdArgs ( def )
18 import System.Directory ( removeFile )
19 import System.Exit ( exitWith, ExitCode (ExitFailure) )
20 import System.IO.Error ( catchIOError )
21 import Text.XML.HXT.Core (
22 ArrowXml,
23 IOStateArrow,
24 XmlTree,
25 (>>>),
26 (/>),
27 getAttrl,
28 getText,
29 hasName,
30 readDocument,
31 runX )
32
33 import Backend ( Backend(..) )
34 import CommandLine ( get_args )
35 import Configuration ( Configuration(..), merge_optional )
36 import ConnectionString ( ConnectionString(..) )
37 import ExitCodes ( exit_no_xml_files )
38 import qualified OptionalConfiguration as OC (
39 OptionalConfiguration ( xml_files ),
40 from_rc )
41 import Network.Services.TSN.Report (
42 report_info,
43 report_error )
44 import TSN.DbImport ( DbImport(..), ImportResult(..) )
45 import qualified TSN.XML.Heartbeat as Heartbeat ( verify )
46 import qualified TSN.XML.Injuries as Injuries ( Listing )
47 import qualified TSN.XML.InjuriesDetail as InjuriesDetail ( PlayerListing )
48 import qualified TSN.XML.News as News ( Message )
49 import Xml ( DtdName(..), parse_opts )
50
51
52 -- | This is where most of the work happens. This function is called
53 -- on every file that we would like to import. It determines which
54 -- importer to use based on the DTD, processes the file, and then
55 -- returns whether or not any records were imported. If the file was
56 -- processed, the number of records imported is returned (wrapped in
57 -- a Just). Otherwise, if the file was not processed, 'Nothing' is
58 -- returned.
59 --
60 -- Since we are already in arrow world with HXT, the
61 -- 'import_with_dtd' function is lifted to an 'Arrow' as well with
62 -- 'arr'. This prevents us from having to do a bunch of unwrapping
63 -- and rewrapping with the associated error checking.
64 --
65 import_file :: Configuration -- ^ A configuration object needed for the
66 -- 'backend' and 'connection_string'.
67
68 -> FilePath -- ^ The path of the XML file to import.
69
70 -> IO (Maybe Int) -- ^ If we processed the file, Just the number
71 -- of records imported. Otherwise, Nothing.
72 import_file cfg path = do
73 results <- parse_and_import `catch` exception_handler
74 case results of
75 [] -> do
76 -- One of the arrows returned "nothing."
77 report_error $ "Unable to determine DTD for file " ++ path ++ "."
78 return Nothing
79 (ImportFailed errmsg:_) -> do
80 report_error errmsg
81 return Nothing
82 (ImportSkipped infomsg:_) -> do
83 -- We processed the message but didn't import anything. Return
84 -- "success" so that the XML file is deleted.
85 report_info infomsg
86 return $ Just 0
87 (ImportSucceeded count:_) -> do
88 report_info $ "Successfully imported " ++ (show count) ++
89 " records from " ++ path ++ "."
90 return $ Just count
91 (ImportUnsupported infomsg:_) -> do
92 -- For now we return "success" for these too, since we know we don't
93 -- support a bunch of DTDs and we want them to get deleted.
94 report_info infomsg
95 return $ Just 0
96 where
97 -- | This will catch *any* exception, even the ones thrown by
98 -- Haskell's 'error' (which should never occur under normal
99 -- circumstances).
100 exception_handler :: SomeException -> IO [ImportResult]
101 exception_handler e = do
102 report_error (show e)
103 let errdesc = "Failed to import file " ++ path ++ "."
104 -- Return a nonempty list so we don't claim incorrectly that
105 -- we couldn't parse the DTD.
106 return [ImportFailed errdesc]
107
108 -- | An arrow that reads a document into an 'XmlTree'.
109 readA :: IOStateArrow s a XmlTree
110 readA = readDocument parse_opts path
111
112 -- | An arrow which parses the doctype "SYSTEM" of an 'XmlTree'.
113 -- We use these to determine the parser to use.
114 doctypeA :: ArrowXml a => a XmlTree DtdName
115 doctypeA = getAttrl >>> hasName "doctype-SYSTEM" /> getText >>^ DtdName
116
117 -- | Combine the arrows above as well as the function below
118 -- (arrowized with 'arr') into an IO action that does everything
119 -- (parses and then runs the import on what was parsed).
120 --
121 -- The result of runX has type IO [IO ImportResult]. We thus use
122 -- bind (>>=) and sequence to combine all of the IOs into one
123 -- big one outside of the list.
124 parse_and_import :: IO [ImportResult]
125 parse_and_import =
126 runX (readA >>> (doctypeA &&& returnA) >>> (arr import_with_dtd))
127 >>=
128 sequence
129
130 -- | Takes a ('DtdName', 'XmlTree') pair and uses the 'DtdName'
131 -- to determine which function to call on the 'XmlTree'.
132 import_with_dtd :: (DtdName, XmlTree) -> IO ImportResult
133 import_with_dtd (DtdName dtd,xml)
134 -- We special-case the heartbeat so it doesn't have to run in
135 -- the database monad.
136 | dtd == "Heartbeat.dtd" = Heartbeat.verify xml
137 | otherwise =
138 -- We need NoMonomorphismRestriction here.
139 if backend cfg == Postgres
140 then withPostgresqlConn cs $ runDbConn $ importer xml
141 else withSqliteConn cs $ runDbConn $ importer xml
142 where
143 -- | Pull the real connection String out of the configuration.
144 cs :: String
145 cs = get_connection_string $ connection_string cfg
146
147 importer
148 | dtd == "injuriesxml.dtd" =
149 dbimport (undefined :: Injuries.Listing)
150
151 | dtd == "Injuries_Detail_XML.dtd" =
152 dbimport (undefined :: InjuriesDetail.PlayerListing)
153
154 | dtd == "newsxml.dtd" =
155 dbimport (undefined :: News.Message)
156
157 | otherwise = \_ -> do -- Dummy arg simplifies the other cases.
158 let infomsg =
159 "Unrecognized DTD in " ++ path ++ ": " ++ dtd ++ "."
160 return $ ImportUnsupported infomsg
161
162
163 -- | Entry point of the program. It twiddles some knobs for
164 -- configuration options and then calls 'import_file' on each XML file
165 -- given on the command-line.
166 --
167 -- Any file successfully processed is then removed, and we're done.
168 --
169 main :: IO ()
170 main = do
171 rc_cfg <- OC.from_rc
172 cmd_cfg <- get_args
173
174 -- Merge the config file options with the command-line ones,
175 -- prefering the command-line ones.
176 let opt_config = rc_cfg <> cmd_cfg
177
178 -- Update a default config with any options that have been set in
179 -- either the config file or on the command-line. We initialize
180 -- logging before the missing parameter checks below so that we can
181 -- log the errors.
182 let cfg = (def :: Configuration) `merge_optional` opt_config
183 init_logging (log_file cfg) (log_level cfg) (syslog cfg)
184
185 -- Check the optional config for missing required options.
186 when (null $ OC.xml_files opt_config) $ do
187 report_error "No XML files given."
188 exitWith (ExitFailure exit_no_xml_files)
189
190 -- We don't do this in parallel (for now?) to keep the error
191 -- messages nice and linear.
192 results <- mapM (import_file cfg) (OC.xml_files opt_config)
193
194 -- Zip the results with the files list to find out which ones can be
195 -- deleted.
196 let result_pairs = zip (OC.xml_files opt_config) results
197 let victims = [ (p,c) | (p, Just c) <- result_pairs ]
198 let imported_count = sum $ map snd victims
199 report_info $ "Imported " ++ (show imported_count) ++ " records total."
200 mapM_ ((kill True) . fst) victims
201
202 where
203 -- | Wrap these two actions into one function so that we don't
204 -- report that the file was removed if the exception handler is
205 -- run.
206 remove_and_report path = do
207 removeFile path
208 report_info $ "Removed processed file " ++ path ++ "."
209
210 -- | Try to remove @path@ and potentially try again.
211 kill try_again path = do
212 (remove_and_report path) `catchIOError` exception_handler
213 where
214 -- | A wrapper around threadDelay which takes seconds instead of
215 -- microseconds as its argument.
216 thread_sleep :: Int -> IO ()
217 thread_sleep seconds = do
218 let microseconds = seconds * (10 ^ (6 :: Int))
219 threadDelay microseconds
220
221 -- | If we can't remove the file, report that, and try once
222 -- more after waiting a few seconds.
223 exception_handler :: IOError -> IO ()
224 exception_handler e = do
225 report_error (show e)
226 report_error $ "Failed to remove imported file " ++ path ++ "."
227 if try_again then do
228 report_info $ "Waiting 5 seconds to attempt removal again..."
229 thread_sleep 5
230 kill False path
231 else
232 report_info $ "Giving up on " ++ path ++ "."