{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE PatternGuards #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} -- | Parse TSN XML for the DTD \"Odds_XML.dtd\". Each document -- contains a root element \ that contains a bunch of -- other... disorganized... information. -- module TSN.XML.Odds ( dtd, pickle_message, -- * Tests odds_tests, -- * WARNING: these are private but exported to silence warnings OddsCasinoConstructor(..), OddsConstructor(..), OddsGameConstructor(..), OddsGameLineConstructor(..) ) where -- System imports. import Control.Applicative ( (<$>) ) import Control.Monad ( forM_, join ) import Data.Time ( UTCTime(..) ) import Data.Tuple.Curry ( uncurryN ) import qualified Data.Vector.HFixed as H ( HVector, convert ) import Database.Groundhog ( (=.), (==.), countAll, deleteAll, insert_, migrate, update ) import Database.Groundhog.Core ( DefaultKey ) import Database.Groundhog.Generic ( runDbConn, runMigrationSilent ) import Database.Groundhog.Sqlite ( withSqliteConn ) import Database.Groundhog.TH ( groundhog, mkPersist ) import qualified GHC.Generics as GHC ( Generic ) import Test.Tasty ( TestTree, testGroup ) import Test.Tasty.HUnit ( (@?=), testCase ) import Text.Read ( readMaybe ) import Text.XML.HXT.Core ( PU, xp6Tuple, xp8Tuple, xpAttr, xpElem, xpInt, xpList, xpOption, xpPair, xpText, xpTriple, xpWrap ) -- Local imports. import TSN.Codegen ( tsn_codegen_config ) import TSN.Database ( insert_or_select ) import TSN.DbImport ( DbImport(..), ImportResult(..), run_dbmigrate ) import TSN.Picklers ( xp_attr_option, xp_date_padded, xp_tba_time, xp_time_stamp ) import TSN.Team ( FromXmlFkTeams(..), Team(..) ) import TSN.XmlImport ( XmlImport(..), XmlImportFkTeams(..) ) import Xml ( Child(..), FromXml(..), ToDb(..), pickle_unpickle, unpickleable, unsafe_unpickle ) -- | The DTD to which this module corresponds. Used to invoke dbimport. -- dtd :: String dtd = "Odds_XML.dtd" -- -- DB/XML data types -- -- * OddsGameCasino/OddsGameCasinoXml -- | The casinos should have their own table, but the lines don't -- belong in that table (there is a separate table for -- 'OddsGameLine' which associates the two). -- -- We drop the \"Game\" prefix because the casinos really aren't -- children of the games; the XML just makes it seem that way. -- data OddsCasino = OddsCasino { casino_client_id :: Int, casino_name :: String } deriving (Eq, Show) -- | The home/away lines are 'Double's, but the over/under lines are -- textual. If we want to use one data type for both, we have to go -- with a 'String' and then attempt to 'read' a 'Double' later when we -- go to insert the thing. -- -- The client_id and name shouldn't really be optional, but TSN has -- started to send us empty casinos: -- -- \\ -- -- We need to parse these, but we'll silently drop them during the -- database import. -- data OddsGameCasinoXml = OddsGameCasinoXml { xml_casino_client_id :: Maybe Int, xml_casino_name :: Maybe String, xml_casino_line :: Maybe String } deriving (Eq, GHC.Generic, Show) -- | For 'H.convert'. -- instance H.HVector OddsGameCasinoXml -- | Try to get a 'Double' out of the 'xml_casino_line' which is a -- priori textual (because it might be an over/under line). -- home_away_line :: OddsGameCasinoXml -> Maybe Double home_away_line = join . (fmap readMaybe) . xml_casino_line instance ToDb OddsGameCasinoXml where -- | The database representation of an 'OddsGameCasinoXml' is an -- 'OddsCasino'. When our XML representation is missing a -- client_id or a name, we want to ignore it. So in that case, -- when we convert to the database type, we want 'Nothing'. -- type Db OddsGameCasinoXml = Maybe OddsCasino instance FromXml OddsGameCasinoXml where -- | We convert from XML to the database by dropping the -- 'xml_casino_line' field. If either the 'xml_casino_client_id' -- or 'xml_casino_name' is missing ('Nothing'), we'll return -- 'Nothing'. -- from_xml (OddsGameCasinoXml Nothing _ _) = Nothing from_xml (OddsGameCasinoXml _ Nothing _) = Nothing from_xml (OddsGameCasinoXml (Just c) (Just n) _) = Just OddsCasino { casino_client_id = c, casino_name = n } -- * OddsGameTeamXml / OddsGameTeamStarterXml -- | The XML representation of a \"starter\". It contains both an ID -- and a name. The ID does not appear to be optional, but the name -- can be absent. When the name is absent, the ID has always been -- set to \"0\". This occurs even though the entire starter element -- is optional (see 'OddsGameTeamXml' below). -- data OddsGameTeamStarterXml = OddsGameTeamStarterXml { xml_starter_id :: Int, xml_starter_name :: Maybe String } deriving (Eq, GHC.Generic, Show) -- | For 'H.convert'. -- instance H.HVector OddsGameTeamStarterXml -- | The XML representation of a \ or \, as -- found in \s. We can't use the 'Team' representation -- directly because there are some other fields we need to parse. -- data OddsGameTeamXml = OddsGameTeamXml { xml_team_id :: String, -- ^ The home/away team IDs -- are three characters but -- Postgres imposes no -- performance penalty on -- lengthless text fields, -- so we ignore the probable -- upper bound of three -- characters. xml_team_rotation_number :: Maybe Int, xml_team_abbr :: String, xml_team_name :: String, xml_team_starter :: Maybe OddsGameTeamStarterXml, xml_team_casinos :: [OddsGameCasinoXml] } deriving (Eq, GHC.Generic, Show) -- | For 'H.convert'. -- instance H.HVector OddsGameTeamXml instance ToDb OddsGameTeamXml where -- | The database representation of an 'OddsGameTeamXml' is an -- 'OddsGameTeam'. -- type Db OddsGameTeamXml = Team instance FromXml OddsGameTeamXml where -- | We convert from XML to the database by dropping the lines and -- rotation number (which are specific to the games, not the teams -- themselves). -- from_xml OddsGameTeamXml{..} = Team { team_id = xml_team_id, abbreviation = Just xml_team_abbr, name = Just xml_team_name } -- | This allows us to insert the XML representation -- 'OddsGameTeamXml' directly. -- instance XmlImport OddsGameTeamXml where -- * OddsGameOverUnderXml -- | XML representation of the over/under. A wrapper around a bunch of -- casino elements. -- newtype OddsGameOverUnderXml = OddsGameOverUnderXml { xml_casinos :: [OddsGameCasinoXml] } deriving (Eq, Show) -- * OddsGameLine -- | This database representation of the casino lines can't be -- constructed from the one in the XML. The casinos within -- Game-\>HomeTeam, Game-\>AwayTeam, and Game-\>Over_Under are all more or -- less the same. We don't need a bajillion different tables to -- store that, just one tying the casino/game pair to the three -- lines. -- -- The one small difference between the over/under casinos and the -- home/away ones is that the home/away lines are all 'Double's, but -- the over/under lines appear to be textual. -- data OddsGameLine = OddsGameLine { ogl_odds_games_id :: DefaultKey OddsGame, ogl_odds_casinos_id :: DefaultKey OddsCasino, ogl_over_under :: Maybe String, ogl_away_line :: Maybe Double, ogl_home_line :: Maybe Double } -- * OddsGame/OddsGameXml -- | Database representation of a game. We retain the rotation number -- of the home/away teams, since those are specific to the game and -- not the teams. -- data OddsGame = OddsGame { db_odds_id :: DefaultKey Odds, db_away_team_id :: DefaultKey Team, db_home_team_id :: DefaultKey Team, db_game_id :: Int, db_game_time :: Maybe UTCTime, -- ^ Contains both the date and time. db_away_team_rotation_number :: Maybe Int, db_home_team_rotation_number :: Maybe Int, db_away_team_starter_id :: Maybe Int, db_away_team_starter_name :: Maybe String, db_home_team_starter_id :: Maybe Int, db_home_team_starter_name :: Maybe String } -- | XML representation of an 'OddsGame'. -- data OddsGameXml = OddsGameXml { xml_game_id :: Int, xml_game_date :: UTCTime, -- ^ Contains only the date xml_game_time :: Maybe UTCTime, -- ^ Contains only the time xml_away_team :: OddsGameTeamXml, xml_home_team :: OddsGameTeamXml, xml_over_under :: OddsGameOverUnderXml } deriving (Eq, GHC.Generic, Show) -- | For 'H.convert'. -- instance H.HVector OddsGameXml -- | Pseudo-field that lets us get the 'OddsGameCasinoXml's out of -- xml_over_under. -- xml_over_under_casinos :: OddsGameXml -> [OddsGameCasinoXml] xml_over_under_casinos = xml_casinos . xml_over_under instance ToDb OddsGameXml where -- | The database representation of an 'OddsGameXml' is an -- 'OddsGame'. -- type Db OddsGameXml = OddsGame instance Child OddsGameXml where -- | Each 'OddsGameXml' is contained in an 'Odds'. In other words -- the foreign key for 'OddsGame' points to an 'Odds'. -- type Parent OddsGameXml = Odds instance FromXmlFkTeams OddsGameXml where -- | To convert from the XML representation to the database one, we -- drop the casino lines, but retain the home/away rotation -- numbers and the starters. The foreign keys to 'Odds' and the -- home/away teams are passed in. -- from_xml_fk_teams fk fk_away fk_home OddsGameXml{..} = OddsGame { db_odds_id = fk, db_away_team_id = fk_away, db_home_team_id = fk_home, db_game_id = xml_game_id, db_game_time = make_game_time xml_game_date xml_game_time, db_away_team_rotation_number = (xml_team_rotation_number xml_away_team), db_home_team_rotation_number = (xml_team_rotation_number xml_home_team), db_away_team_starter_id = (xml_starter_id <$> xml_team_starter xml_away_team), -- Sometimes the starter element is present but the name isn't, -- so we combine the two maybes with join. db_away_team_starter_name = join (xml_starter_name <$> xml_team_starter xml_away_team), db_home_team_starter_id = (xml_starter_id <$> xml_team_starter xml_home_team), -- Sometimes the starter element is present but the name isn't, -- so we combine the two maybes with join. db_home_team_starter_name = join (xml_starter_name <$> xml_team_starter xml_home_team) } where -- | Construct the database game time from the XML \ -- and \ elements. The \ elements -- sometimes have a value of \"TBA\"; in that case, we don't -- want to pretend that we know the time by setting it to -- e.g. midnight, so instead we make the entire date/time -- Nothing. make_game_time :: UTCTime -> Maybe UTCTime -> Maybe UTCTime make_game_time _ Nothing = Nothing make_game_time d (Just t) = Just $ UTCTime (utctDay d) (utctDayTime t) -- | This lets us insert the XML representation 'OddsGameXml' directly. -- instance XmlImportFkTeams OddsGameXml -- * OddsGameWithNotes -- | This is our best guess at what occurs in the Odds_XML -- documents. It looks like each consecutive set of games can -- optionally have some notes appear before it. Each \"note\" comes -- as its own \...\ element. -- -- The notes are ignored completely in the database; we only bother -- with them to ensure that we're (un)pickling correctly. -- -- We can't group the notes with a \"set\" of 'OddsGame's, because -- that leads to ambiguity in parsing. Since we're going to ignore -- the notes anyway, we just stick them with an arbitrary -- game. C'est la vie. -- -- We have to take the same approach with the league. The -- \ elements are sitting outside of the games, and -- are presumably supposed to be interpreted in \"chronological\" -- order; i.e. the current league stays the same until we see -- another \ element. Unfortunately, that's not how -- XML works. So we're forced to ignore the league in the database -- and pull the same trick, pairing them with games. -- data OddsGameWithNotes = OddsGameWithNotes { league :: Maybe String, notes :: [String], game :: OddsGameXml } deriving (Eq, Show) -- * Odds/Message -- | Database representation of a 'Message'. -- data Odds = Odds { db_xml_file_id :: Int, db_sport :: String, db_title :: String, db_line_time :: String, -- ^ We don't parse these as a 'UTCTime' -- because their timezones are ambiguous -- (and the date is less than useful when -- it might be off by an hour). db_time_stamp :: UTCTime } -- | The XML representation of 'Odds'. -- data Message = Message { xml_xml_file_id :: Int, xml_heading :: String, xml_category :: String, xml_sport :: String, xml_title :: String, xml_line_time :: String, xml_games_with_notes :: [OddsGameWithNotes], xml_time_stamp :: UTCTime } deriving (Eq, GHC.Generic, Show) -- | For 'H.convert'. -- instance H.HVector Message -- | Pseudo-field that lets us get the 'OddsGame's out of -- 'xml_games_with_notes'. -- xml_games :: Message -> [OddsGameXml] xml_games m = map game (xml_games_with_notes m) instance ToDb Message where -- | The database representation of a 'Message' is 'Odds'. -- type Db Message = Odds instance FromXml Message where -- | To convert from the XML representation to the database one, we -- just drop a bunch of fields. -- from_xml Message{..} = Odds { db_xml_file_id = xml_xml_file_id, db_sport = xml_sport, db_title = xml_title, db_line_time = xml_line_time, db_time_stamp = xml_time_stamp } -- | This lets us insert the XML representation 'Message' directly. -- instance XmlImport Message -- -- Database code -- -- Groundhog database schema. This must come before the DbImport -- instance definition. Don't know why. mkPersist tsn_codegen_config [groundhog| - entity: Odds constructors: - name: Odds uniques: - name: unique_odds type: constraint # Prevent multiple imports of the same message. fields: [db_xml_file_id] - entity: OddsCasino dbName: odds_casinos constructors: - name: OddsCasino uniques: - name: unique_odds_casinos type: constraint fields: [casino_client_id] - entity: OddsGame dbName: odds_games constructors: - name: OddsGame fields: - name: db_odds_id reference: onDelete: cascade - name: db_away_team_id reference: onDelete: cascade - name: db_home_team_id reference: onDelete: cascade - entity: OddsGameLine dbName: odds_games_lines constructors: - name: OddsGameLine fields: - name: ogl_odds_games_id reference: onDelete: cascade - name: ogl_odds_casinos_id reference: onDelete: cascade |] instance DbImport Message where dbmigrate _= run_dbmigrate $ do migrate (undefined :: Team) migrate (undefined :: Odds) migrate (undefined :: OddsCasino) migrate (undefined :: OddsGame) migrate (undefined :: OddsGameLine) dbimport m = do -- Insert the root "odds" element and acquire its primary key (id). odds_id <- insert_xml m forM_ (xml_games m) $ \game -> do -- First we insert the home and away teams. away_team_id <- insert_xml_or_select (xml_away_team game) home_team_id <- insert_xml_or_select (xml_home_team game) -- Now insert the game, keyed to the "odds" and its teams. game_id <- insert_xml_fk_teams odds_id away_team_id home_team_id game -- Finally, we insert the lines. The over/under entries for this -- game and the lines for the casinos all wind up in the same -- table, odds_games_lines. We can insert the over/under entries -- freely with empty away/home lines. -- -- Before we continue, we drop all casinos that are missing -- either a client_id or name field. -- let ou_casinos = filter nonempty_casino $ xml_over_under_casinos game forM_ ou_casinos $ \c -> -- Since we already filtered out the casinos without a -- client_id or a name, the database conversion should always -- return (Just something). case (from_xml c) of Nothing -> return () -- Should never happen, we filtered them out. Just casino -> do -- Start by inserting the casino. ou_casino_id <- insert_or_select casino -- Now add the over/under entry with the casino's id. let ogl = OddsGameLine { ogl_odds_games_id = game_id, ogl_odds_casinos_id = ou_casino_id, ogl_over_under = (xml_casino_line c), ogl_away_line = Nothing, ogl_home_line = Nothing } insert_ ogl -- ...but then when we insert the home/away team lines, we -- prefer to update the existing entry rather than overwrite it -- or add a new record. let away_casinos = filter nonempty_casino $ xml_team_casinos (xml_away_team game) forM_ away_casinos $ \c -> case (from_xml c) of Nothing -> return () -- Should never happen, we filtered them out. Just casino -> do -- insert, or more likely retrieve the existing, casino a_casino_id <- insert_or_select casino -- Get a Maybe Double instead of the Maybe String that's in there. let away_line = home_away_line c -- Unconditionally update that casino's away team line with ours. update [Ogl_Away_Line =. away_line] $ -- WHERE Ogl_Odds_Casinos_Id ==. a_casino_id -- Repeat all that for the home team. let home_casinos = filter nonempty_casino $ xml_team_casinos (xml_home_team game) forM_ home_casinos $ \c -> case (from_xml c) of Nothing -> return () -- Should never happen, we filtered them out. Just casino -> do h_casino_id <- insert_or_select casino let home_line = home_away_line c update [Ogl_Home_Line =. home_line] $ -- WHERE Ogl_Odds_Casinos_Id ==. h_casino_id return game_id return ImportSucceeded where nonempty_casino :: OddsGameCasinoXml -> Bool nonempty_casino OddsGameCasinoXml{..} | Nothing <- xml_casino_client_id = False | Nothing <- xml_casino_name = False | otherwise = True -- -- Pickling -- -- | Pickler for an 'OddsGame' optionally preceded by some notes. -- pickle_game_with_notes :: PU OddsGameWithNotes pickle_game_with_notes = xpWrap (from_pair, to_pair) $ xpTriple (xpOption $ xpElem "League_Name" xpText) (xpList $ xpElem "Notes" xpText) pickle_game where from_pair = uncurryN OddsGameWithNotes to_pair OddsGameWithNotes{..} = (league, notes, game) -- | Pickler for an 'OddsGameCasinoXml'. -- pickle_casino :: PU OddsGameCasinoXml pickle_casino = xpElem "Casino" $ xpWrap (from_tuple, H.convert) $ xpTriple (xpAttr "ClientID" xp_attr_option) (xpAttr "Name" $ xpOption xpText) (xpOption xpText) where from_tuple = uncurryN OddsGameCasinoXml -- | Pickler for an 'OddsGameTeamXml'. -- pickle_home_team :: PU OddsGameTeamXml pickle_home_team = xpElem "HomeTeam" $ xpWrap (from_tuple, H.convert) $ xp6Tuple (xpElem "HomeTeamID" xpText) (xpElem "HomeRotationNumber" (xpOption xpInt)) (xpElem "HomeAbbr" xpText) (xpElem "HomeTeamName" xpText) (xpOption pickle_home_starter) (xpList pickle_casino) where from_tuple = uncurryN OddsGameTeamXml -- | Portion of the 'OddsGameTeamStarterXml' pickler that is not -- specific to the home/away teams. -- pickle_starter :: PU OddsGameTeamStarterXml pickle_starter = xpWrap (from_tuple, H.convert) $ xpPair (xpAttr "ID" xpInt) (xpOption xpText) where from_tuple = uncurry OddsGameTeamStarterXml -- | Pickler for an home team 'OddsGameTeamStarterXml' -- pickle_home_starter :: PU OddsGameTeamStarterXml pickle_home_starter = xpElem "HStarter" pickle_starter -- | Pickler for an away team 'OddsGameTeamStarterXml' -- pickle_away_starter :: PU OddsGameTeamStarterXml pickle_away_starter = xpElem "AStarter" pickle_starter -- | Pickler for an 'OddsGameTeamXml'. -- pickle_away_team :: PU OddsGameTeamXml pickle_away_team = xpElem "AwayTeam" $ xpWrap (from_tuple, H.convert) $ xp6Tuple (xpElem "AwayTeamID" xpText) (xpElem "AwayRotationNumber" (xpOption xpInt)) (xpElem "AwayAbbr" xpText) (xpElem "AwayTeamName" xpText) (xpOption pickle_away_starter) (xpList pickle_casino) where from_tuple = uncurryN OddsGameTeamXml -- | Pickler for an 'OddsGameOverUnderXml'. -- pickle_over_under :: PU OddsGameOverUnderXml pickle_over_under = xpElem "Over_Under" $ xpWrap (to_newtype, from_newtype) $ xpList pickle_casino where from_newtype (OddsGameOverUnderXml cs) = cs to_newtype = OddsGameOverUnderXml -- | Pickler for an 'OddsGameXml'. -- pickle_game :: PU OddsGameXml pickle_game = xpElem "Game" $ xpWrap (from_tuple, H.convert) $ xp6Tuple (xpElem "GameID" xpInt) (xpElem "Game_Date" xp_date_padded) (xpElem "Game_Time" xp_tba_time) pickle_away_team pickle_home_team pickle_over_under where from_tuple = uncurryN OddsGameXml -- | Pickler for the top-level 'Message'. -- pickle_message :: PU Message pickle_message = xpElem "message" $ xpWrap (from_tuple, H.convert) $ xp8Tuple (xpElem "XML_File_ID" xpInt) (xpElem "heading" xpText) (xpElem "category" xpText) (xpElem "sport" xpText) (xpElem "Title" xpText) (xpElem "Line_Time" xpText) (xpList pickle_game_with_notes) (xpElem "time_stamp" xp_time_stamp) where from_tuple = uncurryN Message -- -- Tasty Tests -- -- | A list of all tests for this module. -- odds_tests :: TestTree odds_tests = testGroup "Odds tests" [ test_on_delete_cascade, test_pickle_of_unpickle_is_identity, test_unpickle_succeeds ] -- | If we unpickle something and then pickle it, we should wind up -- with the same thing we started with. WARNING: success of this -- test does not mean that unpickling succeeded. -- test_pickle_of_unpickle_is_identity :: TestTree test_pickle_of_unpickle_is_identity = testGroup "pickle-unpickle tests" [ check "pickle composed with unpickle is the identity" "test/xml/Odds_XML.xml", check "pickle composed with unpickle is the identity (non-int team_id)" "test/xml/Odds_XML-noninteger-team-id.xml", check "pickle composed with unpickle is the identity (positive(+) line)" "test/xml/Odds_XML-positive-line.xml", check "pickle composed with unpickle is the identity (large file)" "test/xml/Odds_XML-largefile.xml", check "pickle composed with unpickle is the identity (league name)" "test/xml/Odds_XML-league-name.xml", check "pickle composed with unpickle is the identity (missing starters)" "test/xml/Odds_XML-missing-starters.xml", check "pickle composed with unpickle is the identity (TBA game time)" "test/xml/Odds_XML-tba-game-time.xml", check "pickle composed with unpickle is the identity (empty casino)" "test/xml/Odds_XML-empty-casino.xml", check "pickle composed with unpickle is the identity (long import)" "test/xml/Odds_XML-long-import.xml" ] where check desc path = testCase desc $ do (expected, actual) <- pickle_unpickle pickle_message path actual @?= expected -- | Make sure we can actually unpickle these things. -- test_unpickle_succeeds :: TestTree test_unpickle_succeeds = testGroup "unpickle tests" [ check "unpickling succeeds" "test/xml/Odds_XML.xml", check "unpickling succeeds (non-int team_id)" "test/xml/Odds_XML-noninteger-team-id.xml", check "unpickling succeeds (positive(+) line)" "test/xml/Odds_XML-positive-line.xml", check "unpickling succeeds (large file)" "test/xml/Odds_XML-largefile.xml", check "unpickling succeeds (league name)" "test/xml/Odds_XML-league-name.xml", check "unpickling succeeds (missing starters)" "test/xml/Odds_XML-missing-starters.xml", check "unpickling succeeds (TBA game time)" "test/xml/Odds_XML-tba-game-time.xml", check "unpickling succeeds (empty casino)" "test/xml/Odds_XML-empty-casino.xml", check "unpickling succeeds (long-import)" "test/xml/Odds_XML-long-import.xml" ] where check desc path = testCase desc $ do actual <- unpickleable path pickle_message let expected = True actual @?= expected -- | Make sure everything gets deleted when we delete the top-level -- record. The casinos and teams should be left behind. -- test_on_delete_cascade :: TestTree test_on_delete_cascade = testGroup "cascading delete tests" [ check "deleting odds deletes its children" "test/xml/Odds_XML.xml" 13 -- 5 casinos, 8 teams , check "deleting odds deletes its children (non-int team_id)" "test/xml/Odds_XML-noninteger-team-id.xml" 51 -- 5 casinos, 46 teams , check "deleting odds deleted its children (positive(+) line)" "test/xml/Odds_XML-positive-line.xml" 17 -- 5 casinos, 12 teams , check "deleting odds deleted its children (large file)" "test/xml/Odds_XML-largefile.xml" 189 -- 5 casinos, 184 teams , check "deleting odds deleted its children (league name)" "test/xml/Odds_XML-league-name.xml" 35 -- 5 casinos, 30 teams , check "deleting odds deleted its children (missing starters)" "test/xml/Odds_XML-missing-starters.xml" 7 -- 5 casinos, 2 teams , check "deleting odds deleted its children (TBA game time)" "test/xml/Odds_XML-tba-game-time.xml" 119 -- 5 casinos, 114 teams , check "deleting odds deleted its children (empty casino)" "test/xml/Odds_XML-empty-casino.xml" 11 -- 5 casinos, 6 teams , check "deleting odds deleted its children (long import)" "test/xml/Odds_XML-long-import.xml" 219 -- 5 casinos, 214 teams ] where check desc path expected = testCase desc $ do odds <- unsafe_unpickle path pickle_message let a = undefined :: Team let b = undefined :: Odds let c = undefined :: OddsCasino let d = undefined :: OddsGame let e = undefined :: OddsGameLine actual <- withSqliteConn ":memory:" $ runDbConn $ do runMigrationSilent $ do migrate a migrate b migrate c migrate d migrate e _ <- dbimport odds deleteAll b count_a <- countAll a count_b <- countAll b count_c <- countAll c count_d <- countAll d count_e <- countAll e return $ sum [count_a, count_b, count_c, count_d, count_e ] actual @?= expected