]> gitweb.michael.orlitzky.com - dead/htsn-import.git/commitdiff
Add code to main to delete successfully imported files.
authorMichael Orlitzky <michael@orlitzky.com>
Wed, 1 Jan 2014 02:07:31 +0000 (21:07 -0500)
committerMichael Orlitzky <michael@orlitzky.com>
Wed, 1 Jan 2014 02:07:31 +0000 (21:07 -0500)
src/Main.hs
src/TSN/XML/News.hs

index 3ea260642286dc5cc44efa510152eb892c53e271..9a9532124e53273ad0b2b475acd8df51151ed6cf 100644 (file)
@@ -1,8 +1,11 @@
 {-# 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 ( MonadIO, liftIO )
 import Database.Groundhog.Generic ( runDbConn )
@@ -13,6 +16,7 @@ import Database.Groundhog.Postgresql (
 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 (
@@ -46,27 +50,31 @@ import Xml ( parse_opts )
 
 
 
-import_file :: Configuration -> FilePath -> IO ()
+import_file :: Configuration -> FilePath -> IO Bool
 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 ] )
-
+  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
@@ -142,4 +150,33 @@ main = do
 
   -- 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)
+  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 ++ "."
index 5782d2412e2f38820724de05195bf60986572cc7..550f26c44b77b52b61d36528b142d01fea02891e 100644 (file)
@@ -86,7 +86,7 @@ instance ToFromXml NewsTeam where
   -- used our named fields.
   to_xml (NewsTeam {..}) = NewsTeamXml db_team_name
   -- We can't create a DefaultKey Message...
-  from_xml = error "Called from_xml on a NewsTeam"
+  from_xml = error "Called from_xml on a NewsTeam."
   -- unless we're handed one.
   from_xml_fk key = (NewsTeam key) . xml_team_name
 
@@ -124,7 +124,7 @@ instance ToFromXml NewsLocation where
   -- used our named fields.
   to_xml (NewsLocation {..}) = NewsLocationXml db_city db_state db_country
   -- We can't create a DefaultKey Message...
-  from_xml = error "Called from_xml on a NewsLocation"
+  from_xml = error "Called from_xml on a NewsLocation."
   -- unless we're given one.
   from_xml_fk key (NewsLocationXml x y z) = NewsLocation key x y z