X-Git-Url: http://gitweb.michael.orlitzky.com/?a=blobdiff_plain;f=src%2FMain.hs;h=9a9532124e53273ad0b2b475acd8df51151ed6cf;hb=0e37f70a58d512858b38e1458c6d83bc1727269c;hp=9ca0df693b0a3700721fb315b7806baace0ac9bf;hpb=9cf45320c04c72472be8148819753e41d6535f65;p=dead%2Fhtsn-import.git diff --git a/src/Main.hs b/src/Main.hs index 9ca0df6..9a95321 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -1,29 +1,27 @@ {-# LANGUAGE NoMonomorphismRestriction #-} +{-# LANGUAGE DoAndIfThenElse #-} module Main where import Control.Arrow ( (&&&), arr, returnA ) +import Control.Concurrent ( threadDelay ) +import Control.Exception ( SomeException, catch ) import Control.Monad ( when ) import Control.Monad.IO.Class ( MonadIO, liftIO ) -import Database.Groundhog ( - defaultMigrationLogger, - insert, - migrate, - runMigration ) -import Database.Groundhog.Core ( PersistBackend, PersistEntity ) import Database.Groundhog.Generic ( runDbConn ) import Database.Groundhog.Sqlite ( withSqliteConn ) import Database.Groundhog.Postgresql ( withPostgresqlConn ) import Data.Monoid ( (<>) ) +import Network.Services.TSN.Logging ( init_logging ) import System.Console.CmdArgs ( def ) +import System.Directory ( removeFile ) import System.Exit ( exitWith, ExitCode (ExitFailure) ) import System.IO.Error ( catchIOError ) import Text.XML.HXT.Core ( ArrowXml, IOStateArrow, - XmlPickler, XmlTree, (>>>), (/>), @@ -31,106 +29,52 @@ import Text.XML.HXT.Core ( getText, hasName, readDocument, - runX, - unpickleDoc, - xpickle ) + runX ) import Backend ( Backend(..) ) import CommandLine ( get_args ) import Configuration ( Configuration(..), merge_optional ) import ConnectionString ( ConnectionString(..) ) import ExitCodes ( exit_no_xml_files ) -import Network.Services.TSN.Logging ( init_logging ) import qualified OptionalConfiguration as OC ( OptionalConfiguration ( xml_files ), from_rc ) import Network.Services.TSN.Report ( report_info, report_error ) -import qualified TSN.Injuries as Injuries ( - Listing, - Message ( listings ) ) -import qualified TSN.InjuriesDetail as InjuriesDetail ( - Listing ( player_listings ), - Message ( listings ), - PlayerListing ) -import qualified TSN.News as News ( Message ) +import TSN.DbImport +import qualified TSN.XML.Injuries as Injuries ( Listing ) +import qualified TSN.XML.InjuriesDetail as InjuriesDetail ( PlayerListing ) +import qualified TSN.XML.News as News ( Message ) import Xml ( parse_opts ) --- | We put the 'Configuration' and 'XmlTree' arguments last so that --- it's easy to eta reduce all of the import_foo functions that call --- this. --- -import_generic :: (XmlPickler a, MonadIO m, PersistEntity b, PersistBackend m) - => b -- ^ Dummy Listing instance needed for 'migrate' - -> (a -> [b]) -- ^ listings getter - -> XmlTree - -> m (Maybe Int) -- ^ Return the number of records inserted. -import_generic dummy g xml = do - -- Needs NoMonomorphismRestriction to be allowed to return - -- different types in the two cases above. - runMigration defaultMigrationLogger $ migrate dummy - let root_element = unpickleDoc xpickle xml - case root_element of - Nothing -> do - let msg = "Could not unpickle document in import_generic." - liftIO $ report_error msg - return Nothing - Just elt -> do - ids <- mapM insert (g elt) - return $ Just (length ids) - - - --- | Import TSN.News from an 'XmlTree'. -import_news :: (MonadIO m, PersistBackend m) - => XmlTree - -> m (Maybe Int) -import_news = -- This implementation is wrroooonnnnngggg. - import_generic - (undefined :: News.Message) - (\m -> [m] :: [News.Message]) -- Turn a Message into a [Message] - --- | Import TSN.Injuries from an 'XmlTree'. -import_injuries :: (MonadIO m, PersistBackend m) - => XmlTree - -> m (Maybe Int) -import_injuries = - import_generic - (undefined :: Injuries.Listing) - Injuries.listings - --- | Import TSN.InjuriesDetail from an 'XmlTree'. -import_injuries_detail :: (MonadIO m, PersistBackend m) - => XmlTree - -> m (Maybe Int) -import_injuries_detail = - import_generic - (undefined :: InjuriesDetail.PlayerListing) - ( (concatMap InjuriesDetail.player_listings) . InjuriesDetail.listings) - -import_file :: Configuration -> FilePath -> IO () -import_file cfg path = do - results <- catchIOError - parse_and_import - (\e -> do - report_error (show e) - report_error $ "Failed to import file " ++ path ++ "." - -- Return a nonempty list so we don't claim incorrectly that - -- we couldn't parse the DTD. - return [ Nothing ] ) +import_file :: Configuration -> FilePath -> IO Bool +import_file cfg path = do + results <- parse_and_import `catch` exception_handler case results of -- If results' is empty, one of the arrows return "nothing." - [] -> report_error $ "Unable to determine DTD for file " ++ path ++ "." + [] -> do + report_error $ "Unable to determine DTD for file " ++ path ++ "." + return False (r:_) -> case r of - Nothing -> return () - Just cnt -> report_info $ "Successfully imported " ++ - (show cnt) ++ - " records from " ++ path ++ "." + Nothing -> return False + Just cnt -> do + report_info $ "Successfully imported " ++ + (show cnt) ++ + " records from " ++ path ++ "." + return True where + exception_handler :: SomeException -> IO [Maybe Int] + exception_handler e = do + report_error (show e) + report_error $ "Failed to import file " ++ path ++ "." + -- Return a nonempty list so we don't claim incorrectly that + -- we couldn't parse the DTD. + return [Nothing] + -- | An arrow that reads a document into an 'XmlTree'. readA :: IOStateArrow s a XmlTree readA = readDocument parse_opts path @@ -157,6 +101,7 @@ import_file cfg path = do -- determine which function to call on the 'XmlTree'. import_with_dtd :: (String, XmlTree) -> IO (Maybe Int) import_with_dtd (dtd,xml) = + -- We need NoMonomorphismRestriction here. if backend cfg == Postgres then withPostgresqlConn cs $ runDbConn $ importer xml else withSqliteConn cs $ runDbConn $ importer xml @@ -166,9 +111,15 @@ import_file cfg path = do cs = get_connection_string $ connection_string cfg importer - | dtd == "injuriesxml.dtd" = import_injuries - | dtd == "Injuries_Detail_XML.dtd" = import_injuries_detail - | dtd == "newsxml.dtd" = import_news + | dtd == "injuriesxml.dtd" = + dbimport (undefined :: Injuries.Listing) + + | dtd == "Injuries_Detail_XML.dtd" = + dbimport (undefined :: InjuriesDetail.PlayerListing) + + | dtd == "newsxml.dtd" = + dbimport (undefined :: News.Message) + | otherwise = \_ -> do -- Dummy arg simplifies the other cases. let errmsg = "Unrecognized DTD in " ++ path ++ ": " ++ dtd ++ "." liftIO $ report_info errmsg @@ -199,4 +150,33 @@ main = do -- We don't do this in parallel (for now?) to keep the error -- messages nice and linear. - mapM_ (import_file cfg) (OC.xml_files opt_config) + results <- mapM (import_file cfg) (OC.xml_files opt_config) + + -- Zip the results with the files list to find out which ones can be + -- deleted. + let result_pairs = zip (OC.xml_files opt_config) results + let victims = filter (\(_,result) -> result) result_pairs + mapM_ ((kill True) . fst) victims + + where + kill try_again path = do + removeFile path `catchIOError` exception_handler + report_info $ "Removed imported file " ++ path ++ "." + where + -- | A wrapper around threadDelay which takes seconds instead of + -- microseconds as its argument. + thread_sleep :: Int -> IO () + thread_sleep seconds = do + let microseconds = seconds * (10 ^ (6 :: Int)) + threadDelay microseconds + + exception_handler :: IOError -> IO () + exception_handler e = do + report_error (show e) + report_error $ "Failed to remove imported file " ++ path ++ "." + if try_again then do + report_info $ "Waiting 5 seconds to attempt removal again..." + thread_sleep 5 + kill False path + else + report_info $ "Giving up on " ++ path ++ "."