module Main where import Control.Arrow ( (&&&), arr, returnA ) import Control.Monad ( when ) import Control.Monad.IO.Class ( liftIO ) import Database.Groundhog.Core ( PersistEntity ) import Database.Groundhog.Sqlite ( defaultMigrationLogger, insert, migrate, runDbConn, runMigration, withSqliteConn ) import Data.Maybe ( isNothing ) import Data.Monoid ( (<>) ) import System.Console.CmdArgs ( def ) import System.Exit ( exitWith, ExitCode (ExitFailure) ) import Text.XML.HXT.Core ( ArrowXml, IOStateArrow, SysConfigList, XmlPickler, XmlTree, (>>>), (/>), getAttrl, getText, hasName, no, readDocument, runX, unpickleDoc, withPreserveComment, withRemoveWS, withSubstDTDEntities, withValidate, xpickle, yes ) import CommandLine ( get_args ) import Configuration ( Configuration(..), merge_optional ) import ExitCodes ( exit_no_connection_string, exit_no_xml_files ) import Network.Services.TSN.Logging ( init_logging ) import qualified OptionalConfiguration as OC ( OptionalConfiguration ( connection_string, 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 ) -- | A list of options passed to 'readDocument' when we parse an XML -- document. We don't validate because the DTDs from TSN are -- wrong. As a result, we don't want to keep useless DTDs -- areound. Thus we disable 'withSubstDTDEntities' which, when -- combined with "withValidate no", prevents HXT from trying to read -- the DTD at all. -- parse_opts :: SysConfigList parse_opts = [ withPreserveComment no, withRemoveWS yes, withSubstDTDEntities no, withValidate no ] -- | We put the 'XmlTree' argument last so that it's easy to eta -- reduce all of the import_foo functions that call this. -- import_generic :: (XmlPickler a, PersistEntity b) => b -- ^ Dummy Listing instance needed for 'migrate' -> (a -> [b]) -- ^ listings getter -> XmlTree -> IO () import_generic dummy g xml = withSqliteConn "foo.sqlite3" $ runDbConn $ do runMigration defaultMigrationLogger $ do migrate dummy let root_element = unpickleDoc xpickle xml case root_element of Nothing -> let msg = "Could not unpickle document in import_generic." in liftIO $ report_error msg Just elt -> mapM_ (\l -> insert l) (g elt) -- | Import TSN.Injuries from an 'XmlTree'. import_injuries :: XmlTree -> IO () import_injuries = import_generic (undefined :: Injuries.Listing) Injuries.listings -- | Import TSN.InjuriesDetail from an 'XmlTree'. import_injuries_detail :: XmlTree -> IO () import_injuries_detail = import_generic (undefined :: InjuriesDetail.PlayerListing) ( (concatMap InjuriesDetail.player_listings) . InjuriesDetail.listings) import_file :: FilePath -> IO () import_file path = do report_info $ "Attempting to import " ++ path ++ "." results <- runX $ readA >>> (doctypeA &&& returnA) >>> (arr import_with_dtd) case results of [] -> report_error $ "Unable to determine DTD for file " ++ path ++ "." (r:_) -> r -- Need to do something with the result or it gets GCed? -- We do only expect one result fortunately. 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 -- | Takes a 'Doctype', 'XmlTree' pair and uses the 'Doctype' to -- determine which function to call on the 'XmlTree'. import_with_dtd :: (String, XmlTree) -> IO () import_with_dtd (dtd,xml) | dtd == "injuriesxml.dtd" = import_injuries xml | dtd == "Injuries_Detail_XML.dtd" = import_injuries_detail xml | otherwise = report_info $ "Unrecognized DTD in " ++ path ++ ": " ++ dtd ++ "." 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) -- There's a default connection string, namely the empty string, but -- it's not much use to us. So we make sure that we were given -- something explicitly. when (isNothing (OC.connection_string opt_config)) $ do report_error "No connection string supplied." exitWith (ExitFailure exit_no_connection_string) return ()