]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blob - src/Main.hs
Add code to main to delete successfully imported files.
[dead/htsn-import.git] / src / Main.hs
1 {-# LANGUAGE NoMonomorphismRestriction #-}
2 {-# LANGUAGE DoAndIfThenElse #-}
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 Control.Monad.IO.Class ( MonadIO, liftIO )
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
34 import Backend ( Backend(..) )
35 import CommandLine ( get_args )
36 import Configuration ( Configuration(..), merge_optional )
37 import ConnectionString ( ConnectionString(..) )
38 import ExitCodes ( exit_no_xml_files )
39 import qualified OptionalConfiguration as OC (
40 OptionalConfiguration ( xml_files ),
41 from_rc )
42 import Network.Services.TSN.Report (
43 report_info,
44 report_error )
45 import TSN.DbImport
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 ( parse_opts )
50
51
52
53 import_file :: Configuration -> FilePath -> IO Bool
54 import_file cfg path = do
55 results <- parse_and_import `catch` exception_handler
56 case results of
57 -- If results' is empty, one of the arrows return "nothing."
58 [] -> do
59 report_error $ "Unable to determine DTD for file " ++ path ++ "."
60 return False
61 (r:_) ->
62 case r of
63 Nothing -> return False
64 Just cnt -> do
65 report_info $ "Successfully imported " ++
66 (show cnt) ++
67 " records from " ++ path ++ "."
68 return True
69 where
70 exception_handler :: SomeException -> IO [Maybe Int]
71 exception_handler e = do
72 report_error (show e)
73 report_error $ "Failed to import file " ++ path ++ "."
74 -- Return a nonempty list so we don't claim incorrectly that
75 -- we couldn't parse the DTD.
76 return [Nothing]
77
78 -- | An arrow that reads a document into an 'XmlTree'.
79 readA :: IOStateArrow s a XmlTree
80 readA = readDocument parse_opts path
81
82 -- | An arrow which parses the doctype "SYSTEM" of an 'XmlTree'.
83 -- We use these to determine the parser to use.
84 doctypeA :: ArrowXml a => a XmlTree String
85 doctypeA = getAttrl >>> hasName "doctype-SYSTEM" /> getText
86
87 -- | Combine the arrows above as well as the function below
88 -- (arrowized with 'arr') into an IO action that does everything
89 -- (parses and then runs the import on what was parsed).
90 --
91 -- The result of runX has type IO [IO (Maybe Int)]. We thus use
92 -- bind (>>=) and sequence to combine all of the IOs into one
93 -- big one outside of the list.
94 parse_and_import :: IO [Maybe Int]
95 parse_and_import =
96 runX (readA >>> (doctypeA &&& returnA) >>> (arr import_with_dtd))
97 >>=
98 sequence
99
100 -- | Takes a 'Doctype', 'XmlTree' pair and uses the 'Doctype' to
101 -- determine which function to call on the 'XmlTree'.
102 import_with_dtd :: (String, XmlTree) -> IO (Maybe Int)
103 import_with_dtd (dtd,xml) =
104 -- We need NoMonomorphismRestriction here.
105 if backend cfg == Postgres
106 then withPostgresqlConn cs $ runDbConn $ importer xml
107 else withSqliteConn cs $ runDbConn $ importer xml
108 where
109 -- | Pull the real connection String out of the configuration.
110 cs :: String
111 cs = get_connection_string $ connection_string cfg
112
113 importer
114 | dtd == "injuriesxml.dtd" =
115 dbimport (undefined :: Injuries.Listing)
116
117 | dtd == "Injuries_Detail_XML.dtd" =
118 dbimport (undefined :: InjuriesDetail.PlayerListing)
119
120 | dtd == "newsxml.dtd" =
121 dbimport (undefined :: News.Message)
122
123 | otherwise = \_ -> do -- Dummy arg simplifies the other cases.
124 let errmsg = "Unrecognized DTD in " ++ path ++ ": " ++ dtd ++ "."
125 liftIO $ report_info errmsg
126 return Nothing
127
128
129
130 main :: IO ()
131 main = do
132 rc_cfg <- OC.from_rc
133 cmd_cfg <- get_args
134
135 -- Merge the config file options with the command-line ones,
136 -- prefering the command-line ones.
137 let opt_config = rc_cfg <> cmd_cfg
138
139 -- Update a default config with any options that have been set in
140 -- either the config file or on the command-line. We initialize
141 -- logging before the missing parameter checks below so that we can
142 -- log the errors.
143 let cfg = (def :: Configuration) `merge_optional` opt_config
144 init_logging (log_file cfg) (log_level cfg) (syslog cfg)
145
146 -- Check the optional config for missing required options.
147 when (null $ OC.xml_files opt_config) $ do
148 report_error "No XML files given."
149 exitWith (ExitFailure exit_no_xml_files)
150
151 -- We don't do this in parallel (for now?) to keep the error
152 -- messages nice and linear.
153 results <- mapM (import_file cfg) (OC.xml_files opt_config)
154
155 -- Zip the results with the files list to find out which ones can be
156 -- deleted.
157 let result_pairs = zip (OC.xml_files opt_config) results
158 let victims = filter (\(_,result) -> result) result_pairs
159 mapM_ ((kill True) . fst) victims
160
161 where
162 kill try_again path = do
163 removeFile path `catchIOError` exception_handler
164 report_info $ "Removed imported file " ++ path ++ "."
165 where
166 -- | A wrapper around threadDelay which takes seconds instead of
167 -- microseconds as its argument.
168 thread_sleep :: Int -> IO ()
169 thread_sleep seconds = do
170 let microseconds = seconds * (10 ^ (6 :: Int))
171 threadDelay microseconds
172
173 exception_handler :: IOError -> IO ()
174 exception_handler e = do
175 report_error (show e)
176 report_error $ "Failed to remove imported file " ++ path ++ "."
177 if try_again then do
178 report_info $ "Waiting 5 seconds to attempt removal again..."
179 thread_sleep 5
180 kill False path
181 else
182 report_info $ "Giving up on " ++ path ++ "."