]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blobdiff - src/Main.hs
Create a stub for TSN.XML.AutoRacingDriverList.
[dead/htsn-import.git] / src / Main.hs
index 6a0380091a65d60f342b86bdb65190e4d024bce5..e7f9e9c6213ae8df2b65214d4ff46b69e9b294f5 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 )
@@ -29,9 +30,9 @@ import Text.XML.HXT.Core (
   hasName,
   readDocument,
   runX,
-  unpickleDoc,
-  xpickle)
+  unpickleDoc )
 
+-- Local imports.
 import Backend ( Backend(..) )
 import CommandLine ( get_args )
 import Configuration ( Configuration(..), merge_optional )
@@ -44,26 +45,59 @@ import Network.Services.TSN.Report (
   report_info,
   report_error )
 import TSN.DbImport ( DbImport(..), ImportResult(..) )
-import qualified TSN.XML.Heartbeat as Heartbeat ( verify )
-import qualified TSN.XML.Injuries as Injuries ( Message )
-import qualified TSN.XML.InjuriesDetail as InjuriesDetail ( Message )
-import qualified TSN.XML.News as News ( Message )
---import qualified TSN.XML.Odds as Odds ( Odds )
+import TSN.Parse ( format_parse_error )
+import qualified TSN.XML.AutoRacingDriverList as AutoRacingDriverList (
+  dtd,
+  pickle_message )
+import qualified TSN.XML.AutoRacingResults as AutoRacingResults (
+  dtd,
+  pickle_message )
+import qualified TSN.XML.AutoRacingSchedule as AutoRacingSchedule (
+  dtd,
+  pickle_message )
+import qualified TSN.XML.EarlyLine as EarlyLine (
+  dtd,
+  pickle_message )
+import qualified TSN.XML.GameInfo as GameInfo ( dtds, parse_xml )
+import qualified TSN.XML.Heartbeat as Heartbeat ( dtd, verify )
+import qualified TSN.XML.Injuries as Injuries ( dtd, pickle_message )
+import qualified TSN.XML.InjuriesDetail as InjuriesDetail (
+  dtd,
+  pickle_message )
+import qualified TSN.XML.MLBEarlyLine as MLBEarlyLine (
+  dtd,
+  pickle_message )
+import qualified TSN.XML.JFile as JFile ( dtd, pickle_message )
+import qualified TSN.XML.News as News (
+  dtd,
+  has_only_single_sms,
+  pickle_message )
+import qualified TSN.XML.Odds as Odds ( dtd, pickle_message )
+import qualified TSN.XML.ScheduleChanges as ScheduleChanges (
+  dtd,
+  pickle_message )
+import qualified TSN.XML.Scores as Scores ( dtd, pickle_message )
+import qualified TSN.XML.SportInfo as SportInfo ( dtds, parse_xml )
+import qualified TSN.XML.Weather as Weather (
+  dtd,
+  is_type1,
+  pickle_message,
+  teams_are_normal )
 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'.
@@ -79,7 +113,7 @@ import_file cfg path = do
       report_error $ "Unable to determine DTD for file " ++ path ++ "."
       return False
     (ImportFailed errmsg:_) -> do
-      report_error errmsg
+      report_error $ errmsg ++ " (" ++ path ++ ")"
       return False
     (ImportSkipped infomsg:_) -> do
       -- We processed the message but didn't import anything. Return
@@ -134,38 +168,105 @@ import_file cfg path = do
     import_with_dtd (DtdName dtd,xml)
         -- We special-case the heartbeat so it doesn't have to run in
         -- the database monad.
-      | dtd == "Heartbeat.dtd" = Heartbeat.verify xml
-      | otherwise = do
+      | dtd == Heartbeat.dtd = Heartbeat.verify xml
+      | otherwise =
         -- We need NoMonomorphismRestriction here.
         if backend cfg == Postgres
-        then withPostgresqlConn cs $ runDbConn importer
-        else withSqliteConn cs $ runDbConn importer
+        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
 
+          -- | The error message we return if unpickling fails.
+          --
+          errmsg = "Could not unpickle " ++ dtd ++ "."
+
+          -- | Try to migrate and import using the given pickler @f@;
+          --   if it works, return the result. Otherwise, return an
+          --   'ImportFailed' along with our error message.
+          --
+          go f = maybe
+                   (return $ ImportFailed errmsg)
+                   migrate_and_import
+                   (unpickleDoc f xml)
+
           importer
-            | dtd == "injuriesxml.dtd" = do
-               let m = unpickleDoc xpickle xml :: Maybe Injuries.Message
-               let errmsg = "Could not unpickle injuriesxml."
-               maybe (return $ ImportFailed errmsg) migrate_and_import m
+            | dtd == AutoRacingDriverList.dtd =
+                go AutoRacingDriverList.pickle_message
+
+            | dtd == AutoRacingResults.dtd =
+                go AutoRacingResults.pickle_message
+
+            | dtd == AutoRacingSchedule.dtd =
+                go AutoRacingSchedule.pickle_message
+
+            | dtd == EarlyLine.dtd =
+                go EarlyLine.pickle_message
+
+            -- GameInfo and SportInfo appear last in the guards
+            | dtd == Injuries.dtd = go Injuries.pickle_message
 
-            | dtd == "Injuries_Detail_XML.dtd" = do
-                let m = unpickleDoc xpickle xml :: Maybe InjuriesDetail.Message
-                let errmsg = "Could not unpickle Injuries_Detail_XML."
-                maybe (return $ ImportFailed errmsg) migrate_and_import m
+            | dtd == InjuriesDetail.dtd = go InjuriesDetail.pickle_message
 
+            | dtd == JFile.dtd = go JFile.pickle_message
 
-            | dtd == "newsxml.dtd" = do
-                let m = unpickleDoc xpickle xml :: Maybe News.Message
-                let errmsg = "Could not unpickle newsxml."
-                maybe (return $ ImportFailed errmsg) migrate_and_import m
+            | dtd == MLBEarlyLine.dtd =
+                go MLBEarlyLine.pickle_message
 
-            -- | dtd == "Odds_XML.dtd" = undefined
+            | dtd == News.dtd =
+                -- Some of the newsxml docs are busted in predictable ways.
+                -- We want them to "succeed" so that they're deleted.
+                -- We already know we can't parse them.
+                if News.has_only_single_sms xml
+                then go News.pickle_message
+                else do
+                  let msg = "Unsupported newsxml.dtd with multiple SMS " ++
+                            "(" ++ path ++ ")"
+                  return $ ImportUnsupported msg
+            | dtd == Odds.dtd = go Odds.pickle_message
+
+            | dtd == ScheduleChanges.dtd = go ScheduleChanges.pickle_message
+
+            | dtd == Scores.dtd = go Scores.pickle_message
+
+            -- SportInfo and GameInfo appear last in the guards
+            | dtd == Weather.dtd =
+                -- Some of the weatherxml docs are busted in predictable ways.
+                -- We want them to "succeed" so that they're deleted.
+                -- We already know we can't parse them.
+                if Weather.is_type1 xml
+                then if Weather.teams_are_normal xml
+                     then go Weather.pickle_message
+                     else do
+                       let msg = "Teams in reverse order in weatherxml.dtd" ++
+                                 " (" ++ path ++ ")"
+                       return $ ImportUnsupported msg
+                else do
+                  let msg = "Unsupported weatherxml.dtd type (" ++ path ++ ")"
+                  return $ ImportUnsupported msg
+
+            | dtd `elem` GameInfo.dtds = do
+                let either_m = GameInfo.parse_xml dtd xml
+                case either_m of
+                  -- This might give us a slightly better error
+                  -- message than the default 'errmsg'.
+                  Left err -> return $ ImportFailed (format_parse_error err)
+                  Right m     -> migrate_and_import m
+
+            | dtd `elem` SportInfo.dtds = do
+                let either_m = SportInfo.parse_xml dtd xml
+                case either_m of
+                  -- This might give us a slightly better error
+                  -- message than the default 'errmsg'.
+                  Left err -> return $ ImportFailed (format_parse_error err)
+                  Right m     -> migrate_and_import m
 
             | otherwise = do
               let infomsg =
@@ -173,11 +274,13 @@ import_file cfg path = do
               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
@@ -208,9 +311,9 @@ main = do
   -- deleted.
   let result_pairs = zip (OC.xml_files opt_config) results
   let victims = [ p | (p, True) <- result_pairs ]
-  let imported_count = length victims
-  report_info $ "Imported " ++ (show imported_count) ++ " document(s) total."
-  mapM_ (kill True) victims
+  let processed_count = length victims
+  report_info $ "Processed " ++ (show processed_count) ++ " document(s) total."
+  when (remove cfg) $ mapM_ (kill True) victims
 
   where
     -- | Wrap these two actions into one function so that we don't