X-Git-Url: http://gitweb.michael.orlitzky.com/?p=dead%2Fhtsn-import.git;a=blobdiff_plain;f=src%2FTSN%2FXML%2FOdds.hs;h=95aecbed22767a28fb03a071e94790ff2e7003b7;hp=2bc52216148e6c173bec6bfb7f953de764c30d1d;hb=f0425854304197ab5ad47293b27b2e0b188cb844;hpb=c6d0a578213ecfadd1359ea0af2a59da189654b1 diff --git a/src/TSN/XML/Odds.hs b/src/TSN/XML/Odds.hs index 2bc5221..95aecbe 100644 --- a/src/TSN/XML/Odds.hs +++ b/src/TSN/XML/Odds.hs @@ -1,44 +1,55 @@ +{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} +{-# LANGUAGE PatternGuards #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE RecordWildCards #-} -{-# LANGUAGE ScopedTypeVariables #-} -{-# LANGUAGE StandaloneDeriving #-} {-# 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 ( - Odds, - Message, - odds_tests ) + dtd, + pickle_message, + -- * Tests + odds_tests, + -- * WARNING: these are private but exported to silence warnings + OddsCasinoConstructor(..), + OddsConstructor(..), + OddsGameConstructor(..), + OddsGameLineConstructor(..) ) where - --- | Parse TSN XML for the DTD "Odds_XML.dtd". Each document contains --- a root element \ that contains a bunch of other --- unorganized crap. --- - -import Control.Monad ( forM_ ) +-- 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_, - insertByAll, 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, - XmlPickler(..), - xp5Tuple, xp6Tuple, xp8Tuple, xpAttr, @@ -47,32 +58,48 @@ import Text.XML.HXT.Core ( xpList, xpOption, xpPair, - xpPrim, xpText, xpTriple, xpWrap ) -import TSN.Codegen ( - tsn_codegen_config ) +-- Local imports. +import TSN.Codegen ( tsn_codegen_config ) +import TSN.Database ( insert_or_select ) import TSN.DbImport ( DbImport(..), ImportResult(..), run_dbmigrate ) -import TSN.XmlImport ( XmlImport(..) ) -import Xml ( FromXml(..), pickle_unpickle, unpickleable ) +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 +-- -data OddsGameCasinoXml = - OddsGameCasinoXml { - xml_casino_client_id :: Int, - xml_casino_name :: String, - xml_casino_line :: Maybe Double } - deriving (Eq, Show) +-- * OddsGameCasino/OddsGameCasinoXml -- | The casinos should have their own table, but the lines don't --- belong in that table. (There should be another table joining the --- casinos and the thing the lines are for together.) +-- 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 +-- 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 = @@ -81,160 +108,330 @@ data OddsCasino = 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 - type Db OddsGameCasinoXml = OddsCasino + -- | 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 - -- We don't need the key argument (from_xml_fk) since the XML type - -- contains more information in this case. - from_xml OddsGameCasinoXml{..} = OddsCasino - xml_casino_client_id - xml_casino_name + from_xml (OddsGameCasinoXml (Just c) (Just n) _) = + Just OddsCasino { casino_client_id = c, casino_name = n } -instance XmlImport OddsGameCasinoXml -data OddsGameHomeTeamXml = - OddsGameHomeTeamXml { - xml_home_team_id :: Int, - xml_home_rotation_number :: Int, - xml_home_abbr :: String, - xml_home_team_name :: String, - xml_home_casinos :: [OddsGameCasinoXml] } - deriving (Eq, Show) +-- * OddsGameTeamXml / OddsGameTeamStarterXml -instance FromXml OddsGameHomeTeamXml where - type Db OddsGameHomeTeamXml = OddsGameTeam - from_xml OddsGameHomeTeamXml{..} = OddsGameTeam - xml_home_team_id - xml_home_abbr - xml_home_team_name +-- | 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) -instance XmlImport OddsGameHomeTeamXml where +-- | For 'H.convert'. +-- +instance H.HVector OddsGameTeamStarterXml -data OddsGameTeam = - OddsGameTeam { - db_team_id :: Int, - db_abbr :: String, - db_team_name :: String } - deriving (Eq, Show) + +-- | 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 --- | Database mapping between games and their home/away teams. -data OddsGame_OddsGameTeam = - OddsGame_OddsGameTeam { - ogogt_odds_games_id :: DefaultKey OddsGame, - ogogt_away_team_id :: DefaultKey OddsGameTeam, - ogogt_home_team_id :: DefaultKey OddsGameTeam } - -data OddsGameAwayTeamXml = - OddsGameAwayTeamXml { - xml_away_team_id :: Int, - xml_away_rotation_number :: Int, - xml_away_abbr :: String, - xml_away_team_name :: String, - xml_away_casinos :: [OddsGameCasinoXml] } - deriving (Eq, Show) -instance FromXml OddsGameAwayTeamXml where - type Db OddsGameAwayTeamXml = OddsGameTeam - from_xml OddsGameAwayTeamXml{..} = OddsGameTeam - xml_away_team_id - xml_away_abbr - xml_away_team_name -instance XmlImport OddsGameAwayTeamXml where +-- * OddsGameOverUnderXml --- | Can't use a newtype with Groundhog. +-- | 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 the --- same. We don't need a bajillion different tables to store that -- --- just one tying the casino/game pair to the three lines. +-- 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 Double, + 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_date :: String, -- TODO - db_game_time :: String, -- TODO - db_game_away_team_rotation_number :: Int, - db_game_home_team_rotation_number :: Int } -deriving instance Eq OddsGame -deriving instance Show OddsGame + 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 :: String, -- TODO - xml_game_time :: String, -- TODO - xml_game_away_team :: OddsGameAwayTeamXml, - xml_game_home_team :: OddsGameHomeTeamXml, - xml_game_over_under :: OddsGameOverUnderXml } - deriving (Eq, Show) + 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) --- | Pseudo-field that lets us get the 'OddsCasino's out of --- xml_game_over_under. -xml_game_over_under_casinos :: OddsGameXml -> [OddsGameCasinoXml] -xml_game_over_under_casinos = xml_casinos . xml_game_over_under +-- | For 'H.convert'. +-- +instance H.HVector OddsGameXml -instance FromXml OddsGameXml where - type Db OddsGameXml = OddsGame - from_xml OddsGameXml{..} = OddsGame - xml_game_id - xml_game_date - xml_game_time - (xml_away_rotation_number xml_game_away_team) - (xml_home_rotation_number xml_game_home_team) -instance XmlImport 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 -data Odds = - Odds { - db_sport :: String, - db_title :: String, - db_line_time :: String } + +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 --- | Map 'Odds' to their children 'OddsGame's. -data Odds_OddsGame = - Odds_OddsGame { - oog_odds_id :: DefaultKey Odds, - oog_odds_games_id :: DefaultKey OddsGame } +-- * 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. +-- 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 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) --- | The XML representation of Odds. + +-- * 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, @@ -244,220 +441,286 @@ data Message = xml_title :: String, xml_line_time :: String, xml_games_with_notes :: [OddsGameWithNotes], - xml_time_stamp :: String } - deriving (Eq, Show) + 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 FromXml Message where +instance ToDb Message where + -- | The database representation of a 'Message' is 'Odds'. + -- type Db Message = Odds - -- We don't need the key argument (from_xml_fk) since the XML type - -- contains more information in this case. - from_xml (Message _ _ _ d e f _ _) = - Odds d e f - +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 - --- * Groundhog database schema. --- | This must come before the dbimport code. -- +-- 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_casino + - name: unique_odds_casinos type: constraint fields: [casino_client_id] -- entity: OddsGameTeam - dbName: odds_games_teams - constructors: - - name: OddsGameTeam - uniques: - - name: unique_odds_games_team - type: constraint - fields: [db_team_id] - - - entity: OddsGame dbName: odds_games constructors: - name: OddsGame - uniques: - - name: unique_odds_game - type: constraint - fields: [db_game_id] + 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 -- entity: Odds_OddsGame - dbName: odds__odds_games - -- entity: OddsGame_OddsGameTeam - dbName: odds_games__odds_games_teams |] instance DbImport Message where dbmigrate _= run_dbmigrate $ do + migrate (undefined :: Team) migrate (undefined :: Odds) migrate (undefined :: OddsCasino) - migrate (undefined :: OddsGameTeam) migrate (undefined :: OddsGame) - migrate (undefined :: Odds_OddsGame) - migrate (undefined :: OddsGame_OddsGameTeam) migrate (undefined :: OddsGameLine) dbimport m = do -- Insert the root "odds" element and acquire its primary key (id). odds_id <- insert_xml m - -- Next, we insert the home and away teams. We do this before - -- inserting the game itself because the game has two foreign keys - -- pointing to odds_games_teams. - forM_ (xml_games m) $ \g -> do - game_id <- insert_xml_or_select g - -- Insert a record into odds__odds_game mapping this game - -- to its parent in the odds table. - insert_ (Odds_OddsGame odds_id game_id) - - -- Next to insert the home and away teams. - away_team_id <- insert_xml_or_select (xml_game_away_team g) - home_team_id <- insert_xml_or_select (xml_game_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__odds_games_teams - -- mapping the home/away teams to this game. - insert_ (OddsGame_OddsGameTeam game_id away_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_game_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 - game_id - ou_casino_id - (xml_casino_line c) - Nothing - Nothing - - insertByAll 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_casinos $ xml_game_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) - -- Unconditionally update that casino's away team line with ours. - update [Ogl_Away_Line =. (xml_casino_line c)] $ -- WHERE - Ogl_Odds_Casinos_Id ==. a_casino_id + 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. - forM_ (xml_home_casinos $ xml_game_home_team g) $ \c ->do - h_casino_id <- insert_xml_or_select c - update [Ogl_Home_Line =. (xml_casino_line c)] $ -- 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 +-- + +-- | Pickler for an 'OddsGame' optionally preceded by some notes. +-- pickle_game_with_notes :: PU OddsGameWithNotes pickle_game_with_notes = xpWrap (from_pair, to_pair) $ - xpPair + xpTriple + (xpOption $ xpElem "League_Name" xpText) (xpList $ xpElem "Notes" xpText) pickle_game where - from_pair = uncurry OddsGameWithNotes - to_pair OddsGameWithNotes{..} = (notes, game) - + 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, to_tuple) $ + xpWrap (from_tuple, H.convert) $ xpTriple - (xpAttr "ClientID" xpInt) - (xpAttr "Name" xpText) - (xpOption xpPrim) -- Double + (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) - -instance XmlPickler OddsGameCasinoXml where - xpickle = pickle_casino -pickle_home_team :: PU OddsGameHomeTeamXml +-- | Pickler for an 'OddsGameTeamXml'. +-- +pickle_home_team :: PU OddsGameTeamXml pickle_home_team = xpElem "HomeTeam" $ - xpWrap (from_tuple, to_tuple) $ - xp5Tuple - (xpElem "HomeTeamID" xpInt) - (xpElem "HomeRotationNumber" xpInt) + 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 OddsGameHomeTeamXml - -- Use record wildcards to avoid unused field warnings. - to_tuple OddsGameHomeTeamXml{..} = (xml_home_team_id, - xml_home_rotation_number, - xml_home_abbr, - xml_home_team_name, - xml_home_casinos) + 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 -instance XmlPickler OddsGameHomeTeamXml where - xpickle = pickle_home_team -pickle_away_team :: PU OddsGameAwayTeamXml +-- | Pickler for an 'OddsGameTeamXml'. +-- +pickle_away_team :: PU OddsGameTeamXml pickle_away_team = xpElem "AwayTeam" $ - xpWrap (from_tuple, to_tuple) $ - xp5Tuple - (xpElem "AwayTeamID" xpInt) - (xpElem "AwayRotationNumber" xpInt) + 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 OddsGameAwayTeamXml - -- Use record wildcards to avoid unused field warnings. - to_tuple OddsGameAwayTeamXml{..} = (xml_away_team_id, - xml_away_rotation_number, - xml_away_abbr, - xml_away_team_name, - xml_away_casinos) - + from_tuple = uncurryN OddsGameTeamXml -instance XmlPickler OddsGameAwayTeamXml where - xpickle = pickle_away_team +-- | Pickler for an 'OddsGameOverUnderXml'. +-- pickle_over_under :: PU OddsGameOverUnderXml pickle_over_under = xpElem "Over_Under" $ @@ -467,39 +730,30 @@ pickle_over_under = from_newtype (OddsGameOverUnderXml cs) = cs to_newtype = OddsGameOverUnderXml -instance XmlPickler OddsGameOverUnderXml where - xpickle = pickle_over_under - +-- | Pickler for an 'OddsGameXml'. +-- 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" xpText) - (xpElem "Game_Time" xpText) + (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 - -- Use record wildcards to avoid unused field warnings. - to_tuple OddsGameXml{..} = (xml_game_id, - xml_game_date, - xml_game_time, - xml_game_away_team, - xml_game_home_team, - xml_game_over_under) - -instance XmlPickler OddsGameXml where - xpickle = pickle_game +-- | Pickler for the top-level 'Message'. +-- 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) @@ -507,48 +761,157 @@ pickle_message = (xpElem "Title" xpText) (xpElem "Line_Time" xpText) (xpList pickle_game_with_notes) - (xpElem "time_stamp" xpText) + (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) - - -instance XmlPickler Message where - xpickle = pickle_message - +-- +-- Tasty Tests +-- --- * Tasty Tests +-- | A list of all tests for this module. +-- odds_tests :: TestTree odds_tests = testGroup "Odds tests" - [ test_pickle_of_unpickle_is_identity, + [ test_on_delete_cascade, + test_pickle_of_unpickle_is_identity, test_unpickle_succeeds ] --- | Warning, succeess of this test does not mean that unpickling --- succeeded. +-- | 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 = - testCase "pickle composed with unpickle is the identity" $ do - let path = "test/xml/Odds_XML.xml" - (expected :: [Message], actual) <- pickle_unpickle "message" path - actual @?= expected +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" ] + 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 = - testCase "unpickling succeeds" $ do - let path = "test/xml/Odds_XML.xml" - actual <- unpickleable path pickle_message - let expected = True - actual @?= expected +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" ] + 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 + ] + 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