]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blobdiff - src/Main.hs
Minimal undocumented implementation of TSN.XML.Weather.
[dead/htsn-import.git] / src / Main.hs
index ed28f919b7e349e782b8e62e4cacc7f2ecfa120c..663c51ce0ea206b649ad1565659eeca180b521c2 100644 (file)
@@ -3,6 +3,7 @@
 module Main
 where
 
+-- System imports.
 import Control.Arrow ( (&&&), (>>^), arr, returnA )
 import Control.Concurrent ( threadDelay )
 import Control.Exception ( SomeException, catch )
@@ -28,8 +29,10 @@ import Text.XML.HXT.Core (
   getText,
   hasName,
   readDocument,
-  runX )
+  runX,
+  unpickleDoc )
 
+-- Local imports.
 import Backend ( Backend(..) )
 import CommandLine ( get_args )
 import Configuration ( Configuration(..), merge_optional )
@@ -43,57 +46,56 @@ import Network.Services.TSN.Report (
   report_error )
 import TSN.DbImport ( DbImport(..), ImportResult(..) )
 import qualified TSN.XML.Heartbeat as Heartbeat ( verify )
-import qualified TSN.XML.Injuries as Injuries ( Listing )
-import qualified TSN.XML.InjuriesDetail as InjuriesDetail ( PlayerListing )
-import qualified TSN.XML.News as News ( News )
-import qualified TSN.XML.Odds as Odds ( Odds )
+import qualified TSN.XML.Injuries as Injuries ( pickle_message )
+import qualified TSN.XML.InjuriesDetail as InjuriesDetail ( pickle_message )
+import qualified TSN.XML.News as News ( pickle_message )
+import qualified TSN.XML.Odds as Odds ( pickle_message )
+import qualified TSN.XML.Weather as Weather ( pickle_message )
 import Xml ( DtdName(..), parse_opts )
 
 
 -- | This is where most of the work happens. This function is called
 --   on every file that we would like to import. It determines which
---   importer to use based on the DTD, processes the file, and then
---   returns whether or not any records were imported. If the file was
---   processed, the number of records imported is returned (wrapped in
---   a Just). Otherwise, if the file was not processed, 'Nothing' is
+--   importer to use based on the DTD, attempts to process the file,
+--   and then returns whether or not it was successful. If the file
+--   was processed, 'True' is returned. Otherwise, 'False' is
 --   returned.
 --
---   Since we are already in arrow world with HXT, the
---   'import_with_dtd' function is lifted to an 'Arrow' as well with
---   'arr'. This prevents us from having to do a bunch of unwrapping
---   and rewrapping with the associated error checking.
+--   The implementation is straightforward with one exception: since
+--   we are already in arrow world with HXT, the @import_with_dtd@
+--   function is lifted to an 'Arrow' as well with 'arr'. This
+--   prevents us from having to do a bunch of unwrapping and
+--   rewrapping with the associated error checking.
 --
 import_file :: Configuration -- ^ A configuration object needed for the
                              --   'backend' and 'connection_string'.
 
             -> FilePath -- ^ The path of the XML file to import.
 
-            -> IO (Maybe Int) -- ^ If we processed the file, Just the number
-                              --   of records imported. Otherwise, Nothing.
+            -> IO Bool -- ^ True if we processed the file, False otherwise.
 import_file cfg path = do
   results <- parse_and_import `catch` exception_handler
   case results of
     []    -> do
       -- One of the arrows returned "nothing."
       report_error $ "Unable to determine DTD for file " ++ path ++ "."
-      return Nothing
+      return False
     (ImportFailed errmsg:_) -> do
       report_error errmsg
-      return Nothing
+      return False
     (ImportSkipped infomsg:_) -> do
       -- We processed the message but didn't import anything. Return
       -- "success" so that the XML file is deleted.
       report_info infomsg
-      return $ Just 0
-    (ImportSucceeded count:_) -> do
-      report_info $ "Successfully imported " ++ (show count) ++
-                    " records from " ++ path ++ "."
-      return $ Just count
+      return True
+    (ImportSucceeded:_) -> do
+      report_info $ "Successfully imported " ++ path ++ "."
+      return True
     (ImportUnsupported infomsg:_) -> do
       -- For now we return "success" for these too, since we know we don't
       -- support a bunch of DTDs and we want them to get deleted.
       report_info infomsg
-      return $ Just 0
+      return True
   where
     -- | This will catch *any* exception, even the ones thrown by
     --   Haskell's 'error' (which should never occur under normal
@@ -138,36 +140,55 @@ import_file cfg path = do
       | otherwise =
         -- We need NoMonomorphismRestriction here.
         if backend cfg == Postgres
-        then withPostgresqlConn cs $ runDbConn $ importer xml
-        else withSqliteConn cs $ runDbConn $ importer xml
+        then withPostgresqlConn cs $ runDbConn importer
+        else withSqliteConn cs $ runDbConn importer
         where
           -- | Pull the real connection String out  of the configuration.
           cs :: String
           cs = get_connection_string $ connection_string cfg
 
+          -- | Convenience; we use this everywhere below in 'importer'.
+          migrate_and_import m = dbmigrate m >> dbimport m
+
           importer
-            | dtd == "injuriesxml.dtd" =
-                dbimport (undefined :: Injuries.Listing)
+            | dtd == "injuriesxml.dtd" = do
+               let m = unpickleDoc Injuries.pickle_message xml
+               let errmsg = "Could not unpickle injuriesxml."
+               maybe (return $ ImportFailed errmsg) migrate_and_import m
+
+            | dtd == "Injuries_Detail_XML.dtd" = do
+                let m = unpickleDoc InjuriesDetail.pickle_message xml
+                let errmsg = "Could not unpickle Injuries_Detail_XML."
+                maybe (return $ ImportFailed errmsg) migrate_and_import m
+
 
-            | dtd == "Injuries_Detail_XML.dtd" =
-                dbimport (undefined :: InjuriesDetail.PlayerListing)
+            | dtd == "newsxml.dtd" = do
+                let m = unpickleDoc News.pickle_message xml
+                let errmsg = "Could not unpickle newsxml."
+                maybe (return $ ImportFailed errmsg) migrate_and_import m
 
-            | dtd == "newsxml.dtd" =
-                dbimport (undefined :: News.News)
+            | dtd == "Odds_XML.dtd" = do
+                let m = unpickleDoc Odds.pickle_message xml
+                let errmsg = "Could not unpickle Odds_XML."
+                maybe (return $ ImportFailed errmsg) migrate_and_import m
 
-            | dtd == "Odds_XML.dtd" = undefined
+            | dtd == "weatherxml.dtd" = do
+                let m = unpickleDoc Weather.pickle_message xml
+                let errmsg = "Could not unpickle weatherxml."
+                maybe (return $ ImportFailed errmsg) migrate_and_import m
 
-            | otherwise = \_ -> do -- Dummy arg simplifies the other cases.
+            | otherwise = do
               let infomsg =
                     "Unrecognized DTD in " ++ path ++ ": " ++ dtd ++ "."
               return $ ImportUnsupported infomsg
 
 
 -- | Entry point of the program. It twiddles some knobs for
---   configuration options and then calls 'import_file' on each XML file
---   given on the command-line.
+--   configuration options and then calls 'import_file' on each XML
+--   file given on the command-line.
 --
---   Any file successfully processed is then removed, and we're done.
+--   Any file successfully processed is then optionally removed, and
+--   we're done.
 --
 main :: IO ()
 main = do
@@ -197,10 +218,10 @@ main = do
   -- 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 = [ (p,c) | (p, Just c) <- result_pairs ]
-  let imported_count = sum $ map snd victims
-  report_info $ "Imported " ++ (show imported_count) ++ " records total."
-  mapM_ ((kill True) . fst) victims
+  let victims = [ p | (p, True) <- result_pairs ]
+  let imported_count = length victims
+  report_info $ "Imported " ++ (show imported_count) ++ " document(s) total."
+  when (remove cfg) $ mapM_ (kill True) victims
 
   where
     -- | Wrap these two actions into one function so that we don't