]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blobdiff - src/Main.hs
Add a DbImport class implementing the import interface.
[dead/htsn-import.git] / src / Main.hs
index 9ca0df693b0a3700721fb315b7806baace0ac9bf..568f0fe99f55c48b105ab31e04fd5e99d12dd08b 100644 (file)
@@ -5,25 +5,19 @@ 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 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,
-  XmlPickler,
   XmlTree,
   (>>>),
   (/>),
@@ -31,84 +25,26 @@ 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 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 )
 
 
--- | 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
@@ -157,6 +93,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 +103,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