]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blobdiff - src/Main.hs
Add code to main to delete successfully imported files.
[dead/htsn-import.git] / src / Main.hs
index e94d21b4fa7e264d39469daec8ad730a8838895f..9a9532124e53273ad0b2b475acd8df51151ed6cf 100644 (file)
+{-# 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 ( 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.Directory ( removeFile )
 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 (Maybe Int) -- ^ Return the number of records inserted.
-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 -> do
-        let msg = "Could not unpickle document in import_generic."
-        liftIO $ report_error msg
-        return Nothing
-      Just elt  -> do
-        ids <- mapM (\l -> insert l) (g elt)
-        return $ Just (length ids)
-
--- | Import TSN.Injuries from an 'XmlTree'.
-import_injuries :: XmlTree -> IO (Maybe Int)
-import_injuries =
-  import_generic
-    (undefined :: Injuries.Listing)
-    Injuries.listings
-
--- | Import TSN.InjuriesDetail from an 'XmlTree'.
-import_injuries_detail :: XmlTree -> IO (Maybe Int)
-import_injuries_detail =
-  import_generic
-    (undefined :: InjuriesDetail.PlayerListing)
-    ( (concatMap InjuriesDetail.player_listings) . InjuriesDetail.listings)
-
-import_file :: FilePath -> IO ()
-import_file 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 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 )
+
+
 
+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
@@ -151,19 +93,39 @@ import_file path = do
     --   big one outside of the list.
     parse_and_import :: IO [Maybe Int]
     parse_and_import =
-      (runX $ readA >>> (doctypeA &&& returnA) >>> (arr import_with_dtd))
+      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)
-      | dtd == "injuriesxml.dtd" = import_injuries xml
-      | dtd == "Injuries_Detail_XML.dtd" = import_injuries_detail xml
-      | otherwise = do
-          report_info $ "Unrecognized DTD in " ++ path ++ ": " ++ dtd ++ "."
-          return Nothing
+    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 ()
 main = do
@@ -186,13 +148,35 @@ 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)
-
   -- We don't do this in parallel (for now?) to keep the error
   -- messages nice and linear.
-  mapM_ import_file (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 ++ "."