]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blobdiff - src/Main.hs
Make it really import the XML files from the command line.
[dead/htsn-import.git] / src / Main.hs
index d2e51727f9468b58417c0ecbb7ba71cdefeef324..e94d21b4fa7e264d39469daec8ad730a8838895f 100644 (file)
 module Main
 where
 
-import Text.Show.Pretty ( ppShow )
-import Text.XML.HXT.Core
+import Control.Arrow ( (&&&), arr, returnA )
+import Control.Monad ( when )
+import Control.Monad.IO.Class ( liftIO )
+import Database.Groundhog.Core ( PersistEntity )
+import Database.Groundhog.Sqlite (
+  defaultMigrationLogger,
+  insert,
+  migrate,
+  runDbConn,
+  runMigration,
+  withSqliteConn )
+import Data.Maybe ( isNothing )
+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,
+  (>>>),
+  (/>),
+  getAttrl,
+  getText,
+  hasName,
+  no,
+  readDocument,
+  runX,
+  unpickleDoc,
+  withPreserveComment,
+  withRemoveWS,
+  withSubstDTDEntities,
+  withValidate,
+  xpickle,
+  yes )
 
-import qualified TSN.Injuries as Injuries
+import CommandLine ( get_args )
+import Configuration ( Configuration(..), merge_optional )
+import ExitCodes (
+  exit_no_connection_string,
+  exit_no_xml_files )
+import Network.Services.TSN.Logging ( init_logging )
+import qualified OptionalConfiguration as OC (
+  OptionalConfiguration ( connection_string, xml_files ),
+  from_rc )
+import Network.Services.TSN.Report (
+  report_info,
+  report_error )
+import qualified TSN.Injuries as Injuries (
+  Listing,
+  Message ( listings ) )
+import qualified TSN.InjuriesDetail as InjuriesDetail (
+  Listing ( player_listings ),
+  Message ( listings ),
+  PlayerListing )
 
 
+
+-- | 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.
+--
+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)
+               => b          -- ^ Dummy Listing instance needed for 'migrate'
+               -> (a -> [b]) -- ^ listings getter
+               -> XmlTree
+               -> IO (Maybe Int) -- ^ Return the number of records inserted.
+import_generic dummy g xml =
+  withSqliteConn "foo.sqlite3" $ runDbConn $ do
+    runMigration defaultMigrationLogger $ do
+      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 (\l -> insert l) (g elt)
+        return $ Just (length ids)
+
+-- | Import TSN.Injuries from an 'XmlTree'.
+import_injuries :: XmlTree -> IO (Maybe Int)
+import_injuries =
+  import_generic
+    (undefined :: Injuries.Listing)
+    Injuries.listings
+
+-- | Import TSN.InjuriesDetail from an 'XmlTree'.
+import_injuries_detail :: XmlTree -> IO (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 <- 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
+    -- 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
+    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)
+      | dtd == "injuriesxml.dtd" = import_injuries xml
+      | dtd == "Injuries_Detail_XML.dtd" = import_injuries_detail xml
+      | otherwise = do
+          report_info $ "Unrecognized DTD in " ++ path ++ ": " ++ dtd ++ "."
+          return Nothing
+
 main :: IO ()
 main = do
-  res <- runX ( xunpickleDocument Injuries.pickle_message
-                       [ withValidate no
-                       , withTrace 1
-                       , withRemoveWS yes
-                       , withPreserveComment no
-                       ] "test/xml/injuriesxml.xml" )
-  putStr $ ppShow res
+  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)
+
+  -- There's a default connection string, namely the empty string, but
+  -- it's not much use to us. So we make sure that we were given
+  -- something explicitly.
+  when (isNothing (OC.connection_string opt_config)) $ do
+    report_error "No connection string supplied."
+    exitWith (ExitFailure exit_no_connection_string)
+
+  -- We don't do this in parallel (for now?) to keep the error
+  -- messages nice and linear.
+  mapM_ import_file (OC.xml_files opt_config)