]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blobdiff - src/Main.hs
Reorganize the import_foo functions so that the database choice comes sooner and...
[dead/htsn-import.git] / src / Main.hs
index 11cbfae1305c7d446eca0b00168a0c3cc14431f3..9ca0df693b0a3700721fb315b7806baace0ac9bf 100644 (file)
@@ -1,19 +1,28 @@
+{-# LANGUAGE NoMonomorphismRestriction #-}
 module Main
 where
 
 import Control.Arrow ( (&&&), arr, returnA )
-import Database.Groundhog.Core ( PersistEntity )
-import Database.Groundhog.Sqlite (
+import Control.Monad ( when )
+import Control.Monad.IO.Class ( MonadIO, liftIO )
+import Database.Groundhog (
   defaultMigrationLogger,
   insert,
   migrate,
-  runDbConn,
-  runMigration,
+  runMigration )
+import Database.Groundhog.Core ( PersistBackend, PersistEntity )
+import Database.Groundhog.Generic ( runDbConn )
+import Database.Groundhog.Sqlite (
   withSqliteConn )
+import Database.Groundhog.Postgresql (
+  withPostgresqlConn )
+import Data.Monoid ( (<>) )
+import System.Console.CmdArgs ( def )
+import System.Exit ( exitWith, ExitCode (ExitFailure) )
+import System.IO.Error ( catchIOError )
 import Text.XML.HXT.Core (
   ArrowXml,
   IOStateArrow,
-  SysConfigList,
   XmlPickler,
   XmlTree,
   (>>>),
@@ -21,17 +30,23 @@ import Text.XML.HXT.Core (
   getAttrl,
   getText,
   hasName,
-  no,
   readDocument,
   runX,
   unpickleDoc,
-  withPreserveComment,
-  withRemoveWS,
-  withSubstDTDEntities,
-  withValidate,
-  xpickle,
-  yes )
-import System.Environment ( getArgs )
+  xpickle )
+
+import Backend ( Backend(..) )
+import CommandLine ( get_args )
+import Configuration ( Configuration(..), merge_optional )
+import ConnectionString ( ConnectionString(..) )
+import ExitCodes ( exit_no_xml_files )
+import Network.Services.TSN.Logging ( init_logging )
+import qualified OptionalConfiguration as OC (
+  OptionalConfiguration ( xml_files ),
+  from_rc )
+import Network.Services.TSN.Report (
+  report_info,
+  report_error )
 import qualified TSN.Injuries as Injuries (
   Listing,
   Message ( listings ) )
@@ -39,61 +54,82 @@ import qualified TSN.InjuriesDetail as InjuriesDetail (
   Listing ( player_listings ),
   Message ( listings ),
   PlayerListing )
+import qualified TSN.News as News ( Message )
+import Xml ( parse_opts )
 
 
--- | 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.
+-- | We put the 'Configuration' and 'XmlTree' arguments last so that
+-- it's easy to eta reduce all of the import_foo functions that call
+-- this.
 --
-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)
+import_generic :: (XmlPickler a, MonadIO m, PersistEntity b, PersistBackend m)
                => b          -- ^ Dummy Listing instance needed for 'migrate'
                -> (a -> [b]) -- ^ listings getter
                -> XmlTree
-               -> IO ()
-import_generic dummy g xml =
-  withSqliteConn "foo.sqlite3" $ runDbConn $ do
-    runMigration defaultMigrationLogger $ do
-      migrate dummy
-    let msg = unpickleDoc xpickle xml
-    case msg of
-      Nothing -> error "Should unpickle!"
-      Just m  -> mapM_ (\l -> insert l) (g m)
+               -> m (Maybe Int) -- ^ Return the number of records inserted.
+import_generic dummy g xml = do
+  -- Needs NoMonomorphismRestriction to be allowed to return
+  -- different types in the two cases above.
+  runMigration defaultMigrationLogger $ 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 insert (g elt)
+      return $ Just (length ids)
+
+
+
+-- | Import TSN.News from an 'XmlTree'.
+import_news :: (MonadIO m, PersistBackend m)
+            => XmlTree
+            -> m (Maybe Int)
+import_news = -- This implementation is wrroooonnnnngggg.
+  import_generic
+    (undefined :: News.Message)
+    (\m -> [m] :: [News.Message]) -- Turn a Message into a [Message]
 
 -- | Import TSN.Injuries from an 'XmlTree'.
-import_injuries :: XmlTree -> IO ()
+import_injuries :: (MonadIO m, PersistBackend m)
+                => XmlTree
+                -> m (Maybe Int)
 import_injuries =
   import_generic
     (undefined :: Injuries.Listing)
     Injuries.listings
 
 -- | Import TSN.InjuriesDetail from an 'XmlTree'.
-import_injuries_detail :: XmlTree -> IO ()
+import_injuries_detail :: (MonadIO m, PersistBackend m)
+                       => XmlTree
+                       -> m (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 <- runX $ readA >>> (doctypeA &&& returnA) >>> (arr import_with_dtd)
+import_file :: Configuration -> FilePath -> IO ()
+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 ] )
+
   case results of
-    []    -> error "ERROR: Unable to determine DOCTYPE."
-    (r:_) -> r -- Need to do something with the result or it gets GCed?
-               -- We do only expect one result fortunately.
+    -- If results' is empty, one of the arrows return "nothing."
+    []    -> report_error $ "Unable to determine DTD for file " ++ path ++ "."
+    (r:_) ->
+      case r of
+        Nothing -> return ()
+        Just cnt -> report_info $ "Successfully imported " ++
+                                  (show cnt) ++
+                                  " records from " ++ path ++ "."
   where
     -- | An arrow that reads a document into an 'XmlTree'.
     readA :: IOStateArrow s a XmlTree
@@ -104,16 +140,63 @@ import_file path = do
     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 ()
-    import_with_dtd (dtd,xml)
-      | dtd == "injuriesxml.dtd" = import_injuries xml
-      | dtd == "Injuries_Detail_XML.dtd" = import_injuries_detail xml
-      | otherwise = error "ERROR: Unrecognized DTD."
+    import_with_dtd :: (String, XmlTree) -> IO (Maybe Int)
+    import_with_dtd (dtd,xml) =
+      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" = import_injuries
+          | dtd == "Injuries_Detail_XML.dtd" = import_injuries_detail
+          | dtd == "newsxml.dtd" = import_news
+          | 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
-  args <- getArgs
-  import_file (args !! 0)
+  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.
+  mapM_ (import_file cfg) (OC.xml_files opt_config)