X-Git-Url: http://gitweb.michael.orlitzky.com/?a=blobdiff_plain;f=src%2FMain.hs;h=568f0fe99f55c48b105ab31e04fd5e99d12dd08b;hb=f8a623928407ceaaa8c28b60316e9123a4f3821b;hp=9151a8ef06112a1b966b30938a34ca82aa22dd63;hpb=9d278c8b8eeff1a1317f2c3b0f7fdf5fb759ffb3;p=dead%2Fhtsn-import.git diff --git a/src/Main.hs b/src/Main.hs index 9151a8e..568f0fe 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -1,120 +1,71 @@ +{-# LANGUAGE NoMonomorphismRestriction #-} module Main where import Control.Arrow ( (&&&), arr, returnA ) import Control.Monad ( when ) -import Control.Monad.IO.Class ( liftIO ) -import Database.Groundhog.Core ( PersistEntity ) +import Control.Monad.IO.Class ( MonadIO, liftIO ) +import Database.Groundhog.Generic ( runDbConn ) import Database.Groundhog.Sqlite ( - defaultMigrationLogger, - insert, - migrate, - runDbConn, - runMigration, withSqliteConn ) -import Data.Maybe ( isNothing ) +import Database.Groundhog.Postgresql ( + withPostgresqlConn ) import Data.Monoid ( (<>) ) +import Network.Services.TSN.Logging ( init_logging ) import System.Console.CmdArgs ( def ) import System.Exit ( exitWith, ExitCode (ExitFailure) ) +import System.IO.Error ( catchIOError ) import Text.XML.HXT.Core ( ArrowXml, IOStateArrow, - SysConfigList, - XmlPickler, XmlTree, (>>>), (/>), getAttrl, getText, hasName, - no, readDocument, - runX, - unpickleDoc, - withPreserveComment, - withRemoveWS, - withSubstDTDEntities, - withValidate, - xpickle, - yes ) + runX ) +import Backend ( Backend(..) ) 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 ConnectionString ( ConnectionString(..) ) +import ExitCodes ( exit_no_xml_files ) import qualified OptionalConfiguration as OC ( - OptionalConfiguration ( connection_string, xml_files ), + 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 ) - - - --- | 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) +import TSN.DbImport +import qualified TSN.Injuries as Injuries ( Listing ) +import qualified TSN.InjuriesDetail as InjuriesDetail ( PlayerListing ) +import qualified TSN.News as News ( Message ) +import Xml ( parse_opts ) + + + +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:_) -> r -- Need to do something with the result or it gets GCed? - -- We do only expect one result fortunately. + (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 @@ -125,14 +76,47 @@ import_file path = do 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 () - 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 ++ "." + 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 + where + -- | Pull the real connection String out of the configuration. + cs :: String + cs = get_connection_string $ connection_string cfg + + importer + | 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 + return Nothing + main :: IO () @@ -156,12 +140,6 @@ main = 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 () + -- 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)