{-# LANGUAGE NoMonomorphismRestriction #-} module Main where import Control.Arrow ( (&&&), arr, returnA ) 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 System.Console.CmdArgs ( def ) import System.Exit ( exitWith, ExitCode (ExitFailure) ) import System.IO.Error ( catchIOError ) import Text.XML.HXT.Core ( ArrowXml, IOStateArrow, XmlPickler, XmlTree, (>>>), (/>), getAttrl, getText, hasName, readDocument, runX, unpickleDoc, xpickle ) 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 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 ] ) case results of -- If results' is empty, one of the arrows return "nothing." [] -> report_error $ "Unable to determine DTD for file " ++ path ++ "." (r:_) -> case r of Nothing -> return () Just cnt -> report_info $ "Successfully imported " ++ (show cnt) ++ " records from " ++ path ++ "." where -- | An arrow that reads a document into an 'XmlTree'. readA :: IOStateArrow s a XmlTree readA = readDocument parse_opts path -- | An arrow which parses the doctype "SYSTEM" of an 'XmlTree'. -- We use these to determine the parser to use. doctypeA :: ArrowXml a => a XmlTree String doctypeA = getAttrl >>> hasName "doctype-SYSTEM" /> getText -- | Combine the arrows above as well as the function below -- (arrowized with 'arr') into an IO action that does everything -- (parses and then runs the import on what was parsed). -- -- The result of runX has type IO [IO (Maybe Int)]. We thus use -- bind (>>=) and sequence to combine all of the IOs into one -- big one outside of the list. parse_and_import :: IO [Maybe Int] parse_and_import = runX (readA >>> (doctypeA &&& returnA) >>> (arr import_with_dtd)) >>= sequence -- | Takes a 'Doctype', 'XmlTree' pair and uses the 'Doctype' to -- determine which function to call on the 'XmlTree'. import_with_dtd :: (String, XmlTree) -> IO (Maybe Int) import_with_dtd (dtd,xml) = if backend cfg == Postgres then withPostgresqlConn cs $ runDbConn $ importer xml else withSqliteConn cs $ runDbConn $ importer xml where -- | Pull the real connection String out of the configuration. cs :: String 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 | otherwise = \_ -> do -- Dummy arg simplifies the other cases. let errmsg = "Unrecognized DTD in " ++ path ++ ": " ++ dtd ++ "." liftIO $ report_info errmsg return Nothing main :: IO () main = do rc_cfg <- OC.from_rc cmd_cfg <- get_args -- Merge the config file options with the command-line ones, -- prefering the command-line ones. let opt_config = rc_cfg <> cmd_cfg -- Update a default config with any options that have been set in -- either the config file or on the command-line. We initialize -- logging before the missing parameter checks below so that we can -- log the errors. let cfg = (def :: Configuration) `merge_optional` opt_config init_logging (log_file cfg) (log_level cfg) (syslog cfg) -- Check the optional config for missing required options. when (null $ OC.xml_files opt_config) $ do report_error "No XML files given." exitWith (ExitFailure exit_no_xml_files) -- 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)