]> 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 2ca3a83816843db631ed6a5eef56366384b4c242..9a9532124e53273ad0b2b475acd8df51151ed6cf 100644 (file)
-{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE OverloadedStrings #-}
-
+{-# LANGUAGE NoMonomorphismRestriction #-}
+{-# LANGUAGE DoAndIfThenElse #-}
 module Main
 where
 
---import Control.Monad.IO.Class  ( liftIO )
-import Data.Maybe ( listToMaybe )
---import Database.Groundhog.TH
---import Database.Groundhog.Sqlite
-import Text.Show.Pretty ( ppShow )
+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 )
+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.Directory ( removeFile )
+import System.Exit ( exitWith, ExitCode (ExitFailure) )
+import System.IO.Error ( catchIOError )
 import Text.XML.HXT.Core (
-  SysConfigList,
-  XmlPickler,
-  no,
-  runX,
-  withPreserveComment,
-  withRemoveWS,
-  withValidate,
-  xpickle,
-  xunpickleDocument,
-  yes )
-
-import qualified TSN.Injuries as Injuries ( Message )
-import qualified TSN.InjuriesDetail as InjuriesDetail ( Message )
-
-parse_opts :: SysConfigList
-parse_opts =
-  [ withPreserveComment no,
-    withRemoveWS yes,
-    withValidate no ]
-
-parse_file :: XmlPickler a => FilePath -> IO (Maybe a)
-parse_file path =
-  fmap listToMaybe $
-    runX ( xunpickleDocument xpickle parse_opts path )
-
--- main_sql :: IO ()
--- main_sql =
---   withSqliteConn "foo.sqlite3" $ runDbConn $ do
---   runMigration defaultMigrationLogger $ do
---     migrate (undefined :: Injuries.Message)
---     migrate (undefined :: Injuries.Listing)
-
---   msg :: Maybe Injuries.Message <- liftIO $ parse_file
---                                                "test/xml/injuriesxml.xml"
---   case msg of
---     Nothing -> return ()
---     Just m  -> do
---       msg_id <- insert m
---       return ()
+  ArrowXml,
+  IOStateArrow,
+  XmlTree,
+  (>>>),
+  (/>),
+  getAttrl,
+  getText,
+  hasName,
+  readDocument,
+  runX )
+
+import Backend ( Backend(..) )
+import CommandLine ( get_args )
+import Configuration ( Configuration(..), merge_optional )
+import ConnectionString ( ConnectionString(..) )
+import ExitCodes ( exit_no_xml_files )
+import qualified OptionalConfiguration as OC (
+  OptionalConfiguration ( xml_files ),
+  from_rc )
+import Network.Services.TSN.Report (
+  report_info,
+  report_error )
+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."
+    []    -> do
+      report_error $ "Unable to determine DTD for file " ++ path ++ "."
+      return False
+    (r:_) ->
+      case r of
+        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
+
+    -- | An arrow which parses the doctype "SYSTEM" of an 'XmlTree'.
+    --   We use these to determine the parser to use.
+    doctypeA :: ArrowXml a => a XmlTree String
+    doctypeA = getAttrl >>> hasName "doctype-SYSTEM" /> getText
+
+    -- | Combine the arrows above as well as the function below
+    --   (arrowized with 'arr') into an IO action that does everything
+    --   (parses and then runs the import on what was parsed).
+    --
+    --   The result of runX has type IO [IO (Maybe Int)]. We thus use
+    --   bind (>>=) and sequence to combine all of the IOs into one
+    --   big one outside of the list.
+    parse_and_import :: IO [Maybe Int]
+    parse_and_import =
+      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) =
+      -- 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
-  msg1 :: Maybe Injuries.Message <- parse_file "test/xml/injuriesxml.xml"
-  putStr $ ppShow msg1
+  rc_cfg <- OC.from_rc
+  cmd_cfg <- get_args
+
+  -- Merge the config file options with the command-line ones,
+  -- prefering the command-line ones.
+  let opt_config = rc_cfg <> cmd_cfg
+
+  -- Update a default config with any options that have been set in
+  -- either the config file or on the command-line.  We initialize
+  -- logging before the missing parameter checks below so that we can
+  -- log the errors.
+  let cfg = (def :: Configuration) `merge_optional` opt_config
+  init_logging (log_file cfg) (log_level cfg) (syslog cfg)
+
+  -- Check the optional config for missing required options.
+  when (null $ OC.xml_files opt_config) $ do
+    report_error "No XML files given."
+    exitWith (ExitFailure exit_no_xml_files)
+
+  -- We don't do this in parallel (for now?) to keep the error
+  -- messages nice and linear.
+  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
 
-  msg2 :: Maybe InjuriesDetail.Message <- parse_file
-                                            "test/xml/Injuries_Detail_XML.xml"
-  putStr $ ppShow msg2
+        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 ++ "."