{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} -- | GameInfo represents a collection of DTDs that we don't really -- handle but want to make available. The raw XML gets stored in the -- database along with the XML_File_ID, but we don't parse any of it. -- -- See also: TSN.XML.SportInfo -- module TSN.XML.GameInfo ( dtds, game_info_tests, parse_xml, -- * WARNING: these are private but exported to silence warnings GameInfoConstructor(..) ) where -- System imports. import Data.Either ( rights ) import Data.String.Utils ( replace ) import Data.Time.Clock ( UTCTime ) import Database.Groundhog ( countAll, insert_, migrate ) import Database.Groundhog.Generic ( runDbConn, runMigrationSilent ) import Database.Groundhog.Sqlite ( withSqliteConn ) import Database.Groundhog.TH ( defaultCodegenConfig, groundhog, mkPersist ) import Test.Tasty ( TestTree, testGroup ) import Test.Tasty.HUnit ( (@?=), testCase ) import Text.XML.HXT.Core ( XmlTree ) import Text.XML.HXT.DOM.ShowXml ( xshow ) -- Local imports. import TSN.DbImport ( DbImport(..), ImportResult(..), run_dbmigrate ) import TSN.Parse ( ParseError, parse_game_id, parse_message, parse_schedule_id, parse_xmlfid, parse_xml_time_stamp ) import Xml ( unsafe_read_document ) -- | The DTDs for everything that we consider \"Game Info.\" -- -- TODO: This is the list from the old implementation. We need to -- make sure that we are really receiving XML for these DTDs -- (i.e. the names are correct). -- dtds :: [String] dtds = [ "CBASK_Lineup_XML.dtd", "cbaskpreviewxml.dtd", "cflpreviewxml.dtd", "Matchup_NBA_NHL_XML.dtd", "mlbpreviewxml.dtd", "MLB_Gaming_Matchup_XML.dtd", "MLB_Lineup_XML.dtd", "MLB_Matchup_XML.dtd", "MLS_Preview_XML.dtd", "NBA_Gaming_Matchup_XML.dtd", "NBA_Playoff_Matchup_XML.dtd", "NBALineupXML.dtd", "nbapreviewxml.dtd", "NCAA_FB_Preview_XML.dtd", "nflpreviewxml.dtd", "NFL_NCAA_FB_Matchup_XML.dtd", "nhlpreviewxml.dtd", "recapxml.dtd", "WorldBaseballPreviewXML.dtd" ] -- | This serves as both the database and XML representation of a -- GameInfo \. -- -- The 'game_id' and 'schedule_id' fields are foreign keys, but they -- key into multiple tables and key on records which may not exist -- when we import the GameInfo document. We therefore don't declare -- them as foreign keys; i.e. we don't require them to point -- anywhere in particular. But if they do, that's nice. -- data GameInfo = GameInfo { dtd :: String, xml_file_id :: Int, game_id :: Maybe Int, -- ^ These are optional because they are missing -- from at least the MLB_Matchup_XML.dtd documents. -- They provide foreign keys into any tables storing -- games with their IDs. schedule_id :: Maybe Int, -- ^ Optional key into any table storing a -- schedule along with its ID. We've noticed -- them missing in e.g. recapxml.dtd documents. time_stamp :: UTCTime, xml :: String } deriving (Eq, Show) -- | Attempt to parse a 'GameInfo' from an 'XmlTree'. If we cannot, -- we fail with an error message. -- parse_xml :: String -> XmlTree -> Either ParseError GameInfo parse_xml dtdname xmltree = do xmlfid <- parse_xmlfid xmltree game_id <- parse_game_id xmltree schedule_id <- parse_schedule_id xmltree timestamp <- parse_xml_time_stamp xmltree message <- parse_message xmltree return $ GameInfo dtdname xmlfid game_id schedule_id timestamp (xshow [message]) -- -- * Database code -- instance DbImport GameInfo where dbmigrate _ = run_dbmigrate $ migrate (undefined :: GameInfo) -- | We import a 'GameInfo' by inserting the whole thing at -- once. Nothing fancy going on here. dbimport msg = do insert_ msg return ImportSucceeded -- | The database schema for GameInfo is trivial; all we need is for -- the XML_File_ID to be unique. -- mkPersist defaultCodegenConfig [groundhog| - entity: GameInfo dbName: game_info constructors: - name: GameInfo uniques: - name: unique_game_info type: constraint # Prevent multiple imports of the same message. fields: [xml_file_id] |] -- -- Tasty Tests -- -- | A list of all tests for this module. -- game_info_tests :: TestTree game_info_tests = testGroup "GameInfo tests" [ test_accessors, test_parse_xml_succeeds, test_dbimport_succeeds ] -- | Make sure the accessors work and that we can parse one file. Ok, -- so the real point of this is to make the unused fields (dtd, xml, -- ...) warning go away without having to mangle the groundhog code. -- test_accessors :: TestTree test_accessors = testCase "we can access a parsed game_info" $ do xmltree <- unsafe_read_document "test/xml/gameinfo/recapxml.xml" let Right t = parse_xml "recapxml.dtd" xmltree let a1 = dtd t let ex1 = "recapxml.dtd" let a2 = xml_file_id t let ex2 = 21201550 let a3 = show $ time_stamp t let ex3 = "2014-05-31 15:13:00 UTC" let a4 = game_id t let ex4 = Just 39978 let a5 = schedule_id t let ex5 = Just 39978 let a6 = take 9 (xml t) let ex6 = "" let actual = (a1,a2,a3,a4,a5,a6) let expected = (ex1,ex2,ex3,ex4,ex5,ex6) actual @?= expected -- | Sample XML documents for GameInfo types. -- game_info_test_files :: [FilePath] game_info_test_files = map (change_suffix . add_path) dtds where add_path = ("test/xml/gameinfo/" ++ ) change_suffix = replace ".dtd" ".xml" -- | Make sure we can parse every element of 'game_info_test_files'. -- test_parse_xml_succeeds :: TestTree test_parse_xml_succeeds = testGroup "parse_xml" $ map check game_info_test_files where check t = testCase t $ do x <- unsafe_read_document t let result = parse_xml "dummy" x let actual = case result of -- isRight appears in base-4.7 Left _ -> False Right _ -> True let expected = True actual @?= expected -- | Ensure that each element of 'game_info_test_files' can be imported -- by counting the total number of database records (after -- importing) and comparing it against the length of -- 'game_info_test_files'. -- test_dbimport_succeeds :: TestTree test_dbimport_succeeds = testCase "dbimport succeeds" $ do xmltrees <- mapM unsafe_read_document game_info_test_files let msgs = rights $ map (parse_xml "dummy") xmltrees actual <- withSqliteConn ":memory:" $ runDbConn $ do runMigrationSilent $ migrate (undefined :: GameInfo) mapM_ dbimport msgs countAll (undefined :: GameInfo) actual @?= expected where expected = length game_info_test_files