-{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE OverloadedStrings #-}
-
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 Database.Groundhog.Core ( PersistEntity )
+import Database.Groundhog.Sqlite (
+ defaultMigrationLogger,
+ insert,
+ migrate,
+ runDbConn,
+ runMigration,
+ withSqliteConn )
import Text.XML.HXT.Core (
+ ArrowXml,
+ IOStateArrow,
SysConfigList,
XmlPickler,
+ XmlTree,
+ (>>>),
+ (/>),
+ getAttrl,
+ getText,
+ hasName,
no,
+ readDocument,
runX,
+ unpickleDoc,
withPreserveComment,
withRemoveWS,
+ withSubstDTDEntities,
withValidate,
xpickle,
- xunpickleDocument,
yes )
+import System.Environment ( getArgs )
+import qualified TSN.Injuries as Injuries (
+ Listing,
+ Message ( listings ) )
+import qualified TSN.InjuriesDetail as InjuriesDetail (
+ Listing ( player_listings ),
+ Message ( listings ),
+ PlayerListing )
-import qualified TSN.Injuries as Injuries ( Message )
-import qualified TSN.InjuriesDetail as InjuriesDetail ( Message )
+-- | 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 ]
-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 ()
+
+-- | 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 ()
+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)
+
+-- | Import TSN.Injuries from an 'XmlTree'.
+import_injuries :: XmlTree -> IO ()
+import_injuries =
+ import_generic
+ (undefined :: Injuries.Listing)
+ Injuries.listings
+
+-- | Import TSN.InjuriesDetail from an 'XmlTree'.
+import_injuries_detail :: XmlTree -> IO ()
+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)
+ 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.
+ 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
+
+ -- | 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."
+
main :: IO ()
main = do
- msg1 :: Maybe Injuries.Message <- parse_file "test/xml/injuriesxml.xml"
- putStr $ ppShow msg1
-
- msg2 :: Maybe InjuriesDetail.Message <- parse_file
- "test/xml/Injuries_Detail_XML.xml"
- putStr $ ppShow msg2
+ args <- getArgs
+ import_file (args !! 0)