X-Git-Url: http://gitweb.michael.orlitzky.com/?a=blobdiff_plain;f=src%2FTSN%2FXML%2FOdds.hs;h=95aecbed22767a28fb03a071e94790ff2e7003b7;hb=f0425854304197ab5ad47293b27b2e0b188cb844;hp=c4f00266b6fbfa398442056d2d47249da77cf3ce;hpb=b0a87f9323223a0af538184940b35a081f5763af;p=dead%2Fhtsn-import.git diff --git a/src/TSN/XML/Odds.hs b/src/TSN/XML/Odds.hs index c4f0026..95aecbe 100644 --- a/src/TSN/XML/Odds.hs +++ b/src/TSN/XML/Odds.hs @@ -1,6 +1,8 @@ +{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} +{-# LANGUAGE PatternGuards #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE TemplateHaskell #-} @@ -18,15 +20,16 @@ module TSN.XML.Odds ( -- * WARNING: these are private but exported to silence warnings OddsCasinoConstructor(..), OddsConstructor(..), - OddsGame_TeamConstructor(..), 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 ( (=.), (==.), @@ -34,15 +37,14 @@ import Database.Groundhog ( deleteAll, insert_, migrate, - runMigration, - silentMigrationLogger, update ) import Database.Groundhog.Core ( DefaultKey ) -import Database.Groundhog.Generic ( runDbConn ) +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 ) @@ -61,16 +63,19 @@ import Text.XML.HXT.Core ( xpWrap ) -- Local imports. -import TSN.Codegen ( - tsn_codegen_config ) +import TSN.Codegen ( tsn_codegen_config ) +import TSN.Database ( insert_or_select ) import TSN.DbImport ( DbImport(..), ImportResult(..), run_dbmigrate ) -import TSN.Picklers ( xp_date_padded, xp_time, xp_time_stamp ) -import TSN.Team ( Team(..) ) -import TSN.XmlImport ( XmlImport(..), XmlImportFk(..) ) +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(..), - FromXmlFk(..), ToDb(..), pickle_unpickle, unpickleable, @@ -109,12 +114,25 @@ data OddsCasino = -- 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 :: Int, - xml_casino_name :: String, + xml_casino_client_id :: Maybe Int, + xml_casino_name :: Maybe String, xml_casino_line :: Maybe String } - deriving (Eq, Show) + 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 @@ -127,127 +145,97 @@ home_away_line = join . (fmap readMaybe) . xml_casino_line instance ToDb OddsGameCasinoXml where -- | The database representation of an 'OddsGameCasinoXml' is an - -- 'OddsCasino'. + -- '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 = OddsCasino + type Db OddsGameCasinoXml = Maybe OddsCasino instance FromXml OddsGameCasinoXml where - -- | We convert from XML to the database by dropping the line field. + -- | 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{..} = - OddsCasino { - casino_client_id = xml_casino_client_id, - casino_name = xml_casino_name } - - --- | This allows us to insert the XML representation 'OddsGameCasinoXml' --- directly. --- -instance XmlImport OddsGameCasinoXml - - --- * OddsGameHomeTeamXml / OddsGameAwayTeamXml - --- | The XML representation of a \, as found in \s. --- This is basically the same as 'OddsGameAwayTeamXml', but the two --- types have different picklers. --- --- The starter id/name could perhaps be combined into an embedded --- type, but can you make an entire embedded type optional with --- Maybe? I doubt it works. --- -data OddsGameHomeTeamXml = - OddsGameHomeTeamXml { - xml_home_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_home_team_rotation_number :: Int, - xml_home_team_abbr :: String, - xml_home_team_name :: String, - xml_home_team_starter :: Maybe (Int, String), -- ^ (id, name) - xml_home_team_casinos :: [OddsGameCasinoXml] } - deriving (Eq, Show) + from_xml (OddsGameCasinoXml Nothing _ _) = Nothing + from_xml (OddsGameCasinoXml _ Nothing _) = Nothing -instance ToDb OddsGameHomeTeamXml where - -- | The database representation of an 'OddsGameHomeTeamXml' is an - -- 'OddsGameTeam'. - -- - type Db OddsGameHomeTeamXml = Team + from_xml (OddsGameCasinoXml (Just c) (Just n) _) = + Just OddsCasino { casino_client_id = c, casino_name = n } -instance FromXml OddsGameHomeTeamXml 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 OddsGameHomeTeamXml{..} = - Team { - team_id = xml_home_team_id, - abbreviation = Just xml_home_team_abbr, - name = Just xml_home_team_name } --- | This allows us to insert the XML representation --- 'OddsGameHomeTeamXml' directly. + +-- * 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). -- -instance XmlImport OddsGameHomeTeamXml where +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 \, as found in \s. --- This is basically the same as 'OddsGameHomeTeamXml', but the two --- types have different picklers. +-- | 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 OddsGameAwayTeamXml = - OddsGameAwayTeamXml { - xml_away_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_away_team_rotation_number :: Int, - xml_away_team_abbr :: String, - xml_away_team_name :: String, - xml_away_team_starter :: Maybe (Int, String), -- ^ (id, name) - xml_away_team_casinos :: [OddsGameCasinoXml] } - deriving (Eq, Show) +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 OddsGameAwayTeamXml where - -- | The database representation of an 'OddsGameAwayTeamXml' is a - -- 'Team'. +instance ToDb OddsGameTeamXml where + -- | The database representation of an 'OddsGameTeamXml' is an + -- 'OddsGameTeam'. -- - type Db OddsGameAwayTeamXml = Team + type Db OddsGameTeamXml = Team -instance FromXml OddsGameAwayTeamXml where +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 OddsGameAwayTeamXml{..} = Team - xml_away_team_id - (Just xml_away_team_abbr) - (Just xml_away_team_name) + 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 --- 'OddsGameAwayTeamXml' directly. +-- 'OddsGameTeamXml' directly. -- -instance XmlImport OddsGameAwayTeamXml where +instance XmlImport OddsGameTeamXml where --- * OddsGame_OddsGameTeam - --- | Database mapping between games and their home/away teams. --- -data OddsGame_Team = - OddsGame_Team { - ogt_odds_games_id :: DefaultKey OddsGame, - ogt_away_team_id :: DefaultKey Team, - ogt_home_team_id :: DefaultKey Team } -- * OddsGameOverUnderXml @@ -291,10 +279,12 @@ data OddsGameLine = 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 :: UTCTime, -- ^ Contains both the date and time. - db_away_team_rotation_number :: Int, - db_home_team_rotation_number :: 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, @@ -307,11 +297,17 @@ data OddsGameXml = OddsGameXml { xml_game_id :: Int, xml_game_date :: UTCTime, -- ^ Contains only the date - xml_game_time :: UTCTime, -- ^ Contains only the time - xml_away_team :: OddsGameAwayTeamXml, - xml_home_team :: OddsGameHomeTeamXml, + xml_game_time :: Maybe UTCTime, -- ^ Contains only the time + xml_away_team :: OddsGameTeamXml, + xml_home_team :: OddsGameTeamXml, xml_over_under :: OddsGameOverUnderXml } - deriving (Eq, Show) + 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. @@ -334,42 +330,57 @@ instance Child OddsGameXml where type Parent OddsGameXml = Odds -instance FromXmlFk OddsGameXml where +instance FromXmlFkTeams OddsGameXml where -- | To convert from the XML representation to the database one, we - -- drop the home/away teams and the casino lines, but retain the - -- home/away rotation numbers and the starters. + -- 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 fk OddsGameXml{..} = + from_xml_fk_teams fk fk_away fk_home OddsGameXml{..} = OddsGame { - db_odds_id = fk, + 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 = UTCTime - (utctDay xml_game_date) -- Take the day part from one, - (utctDayTime xml_game_time), -- the time from the other. + db_game_time = make_game_time xml_game_date xml_game_time, db_away_team_rotation_number = - (xml_away_team_rotation_number xml_away_team), + (xml_team_rotation_number xml_away_team), db_home_team_rotation_number = - (xml_home_team_rotation_number xml_home_team), + (xml_team_rotation_number xml_home_team), db_away_team_starter_id = - (fmap fst $ xml_away_team_starter xml_away_team), + (xml_starter_id <$> xml_team_starter xml_away_team), - db_away_team_starter_name = - (fmap snd $ xml_away_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 = - (fmap fst $ xml_home_team_starter xml_home_team), - - db_home_team_starter_name = - (fmap snd $ xml_home_team_starter xml_home_team) } + (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 XmlImportFk OddsGameXml +instance XmlImportFkTeams OddsGameXml -- * OddsGameWithNotes @@ -431,7 +442,12 @@ data Message = xml_line_time :: String, xml_games_with_notes :: [OddsGameWithNotes], xml_time_stamp :: UTCTime } - deriving (Eq, Show) + 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'. @@ -483,7 +499,7 @@ mkPersist tsn_codegen_config [groundhog| constructors: - name: OddsCasino uniques: - - name: unique_odds_casino + - name: unique_odds_casinos type: constraint fields: [casino_client_id] @@ -495,6 +511,12 @@ mkPersist tsn_codegen_config [groundhog| - 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 @@ -508,20 +530,6 @@ mkPersist tsn_codegen_config [groundhog| reference: onDelete: cascade -- entity: OddsGame_Team - dbName: odds_games__teams - constructors: - - name: OddsGame_Team - fields: - - name: ogt_odds_games_id - reference: - onDelete: cascade - - name: ogt_away_team_id - reference: - onDelete: cascade - - name: ogt_home_team_id - reference: - onDelete: cascade |] instance DbImport Message where @@ -531,72 +539,93 @@ instance DbImport Message where migrate (undefined :: Odds) migrate (undefined :: OddsCasino) migrate (undefined :: OddsGame) - migrate (undefined :: OddsGame_Team) 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) $ \g -> do - -- First insert the game, keyed to the "odds", - game_id <- insert_xml_fk odds_id g - - -- Next, we insert the home and away teams. - away_team_id <- insert_xml_or_select (xml_away_team g) - home_team_id <- insert_xml_or_select (xml_home_team g) + 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) - -- Insert a record into odds_games__teams mapping the - -- home/away teams to this game. Use the full record syntax - -- because the types would let us mix up the home/away teams. - insert_ OddsGame_Team { - ogt_odds_games_id = game_id, - ogt_away_team_id = away_team_id, - ogt_home_team_id = home_team_id } + -- 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 - -- Finaly, we insert the lines. The over/under entries for this + -- 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: - forM_ (xml_over_under_casinos g) $ \c -> do - -- Start by inderting the casino. - ou_casino_id <- insert_xml_or_select c - - -- 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 + -- 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. - forM_ (xml_away_team_casinos $ xml_away_team g) $ \c -> do - -- insert, or more likely retrieve the existing, casino - a_casino_id <- insert_xml_or_select c + let away_casinos = filter nonempty_casino $ + xml_team_casinos (xml_away_team game) - -- Get a Maybe Double instead of the Maybe String that's in there. - let away_line = home_away_line c + 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 - -- Unconditionally update that casino's away team line with ours. - update [Ogl_Away_Line =. away_line] $ -- WHERE - Ogl_Odds_Casinos_Id ==. a_casino_id + -- 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. - forM_ (xml_home_team_casinos $ xml_home_team g) $ \c ->do - h_casino_id <- insert_xml_or_select c - let home_line = home_away_line c - update [Ogl_Home_Line =. home_line] $ -- WHERE - Ogl_Odds_Casinos_Id ==. h_casino_id + 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 @@ -621,70 +650,72 @@ pickle_game_with_notes = pickle_casino :: PU OddsGameCasinoXml pickle_casino = xpElem "Casino" $ - xpWrap (from_tuple, to_tuple) $ + xpWrap (from_tuple, H.convert) $ xpTriple - (xpAttr "ClientID" xpInt) - (xpAttr "Name" xpText) + (xpAttr "ClientID" $ xp_attr_option) + (xpAttr "Name" $ xpOption xpText) (xpOption xpText) where from_tuple = uncurryN OddsGameCasinoXml - -- Use record wildcards to avoid unused field warnings. - to_tuple OddsGameCasinoXml{..} = (xml_casino_client_id, - xml_casino_name, - xml_casino_line) --- | Pickler for an 'OddsGameHomeTeamXml'. +-- | Pickler for an 'OddsGameTeamXml'. -- -pickle_home_team :: PU OddsGameHomeTeamXml +pickle_home_team :: PU OddsGameTeamXml pickle_home_team = xpElem "HomeTeam" $ - xpWrap (from_tuple, to_tuple) $ + xpWrap (from_tuple, H.convert) $ xp6Tuple (xpElem "HomeTeamID" xpText) - (xpElem "HomeRotationNumber" xpInt) + (xpElem "HomeRotationNumber" (xpOption xpInt)) (xpElem "HomeAbbr" xpText) (xpElem "HomeTeamName" xpText) - (-- This is an ugly way to get both the HStarter ID attribute - -- and contents. - xpOption (xpElem "HStarter" $ xpPair (xpAttr "ID" xpInt) xpText)) + (xpOption pickle_home_starter) (xpList pickle_casino) where - from_tuple = uncurryN OddsGameHomeTeamXml + 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 - -- Use record wildcards to avoid unused field warnings. - to_tuple OddsGameHomeTeamXml{..} = (xml_home_team_id, - xml_home_team_rotation_number, - xml_home_team_abbr, - xml_home_team_name, - xml_home_team_starter, - xml_home_team_casinos) --- | Pickler for an 'OddsGameAwayTeamXml'. +-- | Pickler for an away team 'OddsGameTeamStarterXml' -- -pickle_away_team :: PU OddsGameAwayTeamXml +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, to_tuple) $ + xpWrap (from_tuple, H.convert) $ xp6Tuple (xpElem "AwayTeamID" xpText) - (xpElem "AwayRotationNumber" xpInt) + (xpElem "AwayRotationNumber" (xpOption xpInt)) (xpElem "AwayAbbr" xpText) (xpElem "AwayTeamName" xpText) - (-- This is an ugly way to get both the AStarter ID attribute - -- and contents. - xpOption (xpElem "AStarter" $ xpPair (xpAttr "ID" xpInt) xpText)) + (xpOption pickle_away_starter) (xpList pickle_casino) where - from_tuple = uncurryN OddsGameAwayTeamXml - - -- Use record wildcards to avoid unused field warnings. - to_tuple OddsGameAwayTeamXml{..} = (xml_away_team_id, - xml_away_team_rotation_number, - xml_away_team_abbr, - xml_away_team_name, - xml_away_team_starter, - xml_away_team_casinos) + from_tuple = uncurryN OddsGameTeamXml @@ -705,23 +736,16 @@ pickle_over_under = pickle_game :: PU OddsGameXml pickle_game = xpElem "Game" $ - xpWrap (from_tuple, to_tuple) $ + xpWrap (from_tuple, H.convert) $ xp6Tuple (xpElem "GameID" xpInt) (xpElem "Game_Date" xp_date_padded) - (xpElem "Game_Time" xp_time) + (xpElem "Game_Time" xp_tba_time) pickle_away_team pickle_home_team pickle_over_under where from_tuple = uncurryN OddsGameXml - -- Use record wildcards to avoid unused field warnings. - to_tuple OddsGameXml{..} = (xml_game_id, - xml_game_date, - xml_game_time, - xml_away_team, - xml_home_team, - xml_over_under) -- | Pickler for the top-level 'Message'. @@ -729,7 +753,7 @@ pickle_game = pickle_message :: PU Message pickle_message = xpElem "message" $ - xpWrap (from_tuple, to_tuple) $ + xpWrap (from_tuple, H.convert) $ xp8Tuple (xpElem "XML_File_ID" xpInt) (xpElem "heading" xpText) (xpElem "category" xpText) @@ -740,14 +764,6 @@ pickle_message = (xpElem "time_stamp" xp_time_stamp) where from_tuple = uncurryN Message - to_tuple m = (xml_xml_file_id m, - xml_heading m, - xml_category m, - xml_sport m, - xml_title m, - xml_line_time m, - xml_games_with_notes m, - xml_time_stamp m) -- @@ -784,7 +800,16 @@ test_pickle_of_unpickle_is_identity = testGroup "pickle-unpickle tests" "test/xml/Odds_XML-largefile.xml", check "pickle composed with unpickle is the identity (league name)" - "test/xml/Odds_XML-league-name.xml" ] + "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" ] where check desc path = testCase desc $ do (expected, actual) <- pickle_unpickle pickle_message path @@ -808,7 +833,16 @@ test_unpickle_succeeds = testGroup "unpickle tests" "test/xml/Odds_XML-largefile.xml", check "unpickling succeeds (league name)" - "test/xml/Odds_XML-league-name.xml" ] + "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" ] where check desc path = testCase desc $ do actual <- unpickleable path pickle_message @@ -843,6 +877,18 @@ test_on_delete_cascade = testGroup "cascading delete tests" 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 ] where check desc path expected = testCase desc $ do @@ -851,16 +897,14 @@ test_on_delete_cascade = testGroup "cascading delete tests" let b = undefined :: Odds let c = undefined :: OddsCasino let d = undefined :: OddsGame - let e = undefined :: OddsGame_Team - let f = undefined :: OddsGameLine + let e = undefined :: OddsGameLine actual <- withSqliteConn ":memory:" $ runDbConn $ do - runMigration silentMigrationLogger $ do + runMigrationSilent $ do migrate a migrate b migrate c migrate d migrate e - migrate f _ <- dbimport odds deleteAll b count_a <- countAll a @@ -868,7 +912,6 @@ test_on_delete_cascade = testGroup "cascading delete tests" count_c <- countAll c count_d <- countAll d count_e <- countAll e - count_f <- countAll f return $ sum [count_a, count_b, count_c, - count_d, count_e, count_f ] + count_d, count_e ] actual @?= expected