-- unorganized crap.
--
-import Data.Data ( Data, constrFields, dataTypeConstrs, dataTypeOf )
-import Data.List.Utils ( join, split )
+import Control.Monad ( forM_ )
import Data.Tuple.Curry ( uncurryN )
-import Data.Typeable ( Typeable )
import Database.Groundhog (
- defaultMigrationLogger,
- insert,
+ (=.),
+ (==.),
+ insert_,
+ insertByAll,
migrate,
- runMigration )
+ update )
import Database.Groundhog.Core ( DefaultKey )
import Database.Groundhog.TH (
groundhog,
mkPersist )
-import System.Console.CmdArgs.Default ( Default(..) )
import Test.Tasty ( TestTree, testGroup )
import Test.Tasty.HUnit ( (@?=), testCase )
import Text.XML.HXT.Core (
PU,
XmlPickler(..),
- unpickleDoc,
xp5Tuple,
xp6Tuple,
xp8Tuple,
xpPair,
xpPrim,
xpText,
- xpText0,
xpTriple,
xpWrap )
import TSN.Codegen (
- tsn_codegen_config,
- tsn_db_field_namer )
-import TSN.DbImport ( DbImport(..), ImportResult(..) )
+ tsn_codegen_config )
+import TSN.DbImport ( DbImport(..), ImportResult(..), run_dbmigrate )
import TSN.XmlImport ( XmlImport(..) )
import Xml ( FromXml(..), pickle_unpickle, unpickleable )
-data OddsCasinoXml =
- OddsCasinoXml {
+data OddsGameCasinoXml =
+ OddsGameCasinoXml {
xml_casino_client_id :: Int,
xml_casino_name :: String,
- xml_casino_line :: Maybe Float }
+ xml_casino_line :: Maybe Double }
deriving (Eq, Show)
-- | 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.)
+--
+-- 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)
-instance FromXml OddsCasinoXml where
- type Db OddsCasinoXml = OddsCasino
+instance FromXml OddsGameCasinoXml where
+ type Db OddsGameCasinoXml = OddsCasino
-- We don't need the key argument (from_xml_fk) since the XML type
-- contains more information in this case.
- from_xml OddsCasinoXml{..} = OddsCasino
- xml_casino_client_id
- xml_casino_name
+ from_xml OddsGameCasinoXml{..} = OddsCasino
+ xml_casino_client_id
+ xml_casino_name
-instance XmlImport OddsCasinoXml
+instance XmlImport OddsGameCasinoXml
-data OddsHomeTeamXml =
- OddsHomeTeamXml {
+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 :: [OddsCasinoXml] }
+ xml_home_casinos :: [OddsGameCasinoXml] }
deriving (Eq, Show)
-instance FromXml OddsHomeTeamXml where
- type Db OddsHomeTeamXml = OddsTeam
- from_xml OddsHomeTeamXml{..} = OddsTeam
- xml_home_team_id
- xml_home_abbr
- xml_home_team_name
+instance FromXml OddsGameHomeTeamXml where
+ type Db OddsGameHomeTeamXml = OddsGameTeam
+ from_xml OddsGameHomeTeamXml{..} = OddsGameTeam
+ xml_home_team_id
+ xml_home_abbr
+ xml_home_team_name
-instance XmlImport OddsHomeTeamXml where
+instance XmlImport OddsGameHomeTeamXml where
-data OddsTeam =
- OddsTeam {
+data OddsGameTeam =
+ OddsGameTeam {
db_team_id :: Int,
db_abbr :: String,
db_team_name :: String }
deriving (Eq, Show)
-data OddsAwayTeamXml =
- OddsAwayTeamXml {
+
+-- | 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 :: [OddsCasinoXml] }
+ xml_away_casinos :: [OddsGameCasinoXml] }
deriving (Eq, Show)
-instance FromXml OddsAwayTeamXml where
- type Db OddsAwayTeamXml = OddsTeam
- from_xml OddsAwayTeamXml{..} = OddsTeam
- xml_away_team_id
- xml_away_abbr
- xml_away_team_name
+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 OddsAwayTeamXml where
+instance XmlImport OddsGameAwayTeamXml where
-- | Can't use a newtype with Groundhog.
-data OddsOverUnder =
- OddsOverUnder [OddsCasinoXml]
+newtype OddsGameOverUnderXml =
+ OddsGameOverUnderXml { xml_casinos :: [OddsGameCasinoXml] }
deriving (Eq, Show)
+-- | 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.
+data OddsGameLine =
+ OddsGameLine {
+ ogl_odds_games_id :: DefaultKey OddsGame,
+ ogl_odds_casinos_id :: DefaultKey OddsCasino,
+ ogl_over_under :: Maybe Double,
+ ogl_away_line :: Maybe Double,
+ ogl_home_line :: Maybe Double }
+
data OddsGame =
OddsGame {
db_game_id :: Int,
db_game_date :: String, -- TODO
db_game_time :: String, -- TODO
- db_game_away_team_id :: DefaultKey OddsTeam,
db_game_away_team_rotation_number :: Int,
- db_game_home_team_id :: DefaultKey OddsTeam,
db_game_home_team_rotation_number :: Int }
deriving instance Eq OddsGame
deriving instance Show OddsGame
xml_game_id :: Int,
xml_game_date :: String, -- TODO
xml_game_time :: String, -- TODO
- xml_game_away_team :: OddsAwayTeamXml,
- xml_game_home_team :: OddsHomeTeamXml,
- xml_game_over_under :: OddsOverUnder }
+ xml_game_away_team :: OddsGameAwayTeamXml,
+ xml_game_home_team :: OddsGameHomeTeamXml,
+ xml_game_over_under :: OddsGameOverUnderXml }
deriving (Eq, 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
+
+
+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
+
+
+
data Odds =
Odds {
db_sport :: String,
db_title :: String,
db_line_time :: String }
+
+-- | Map 'Odds' to their children 'OddsGame's.
+data Odds_OddsGame =
+ Odds_OddsGame {
+ oog_odds_id :: DefaultKey Odds,
+ oog_odds_games_id :: DefaultKey OddsGame }
+
-- | 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
xml_games :: Message -> [OddsGameXml]
xml_games m = map game (xml_games_with_notes m)
+
instance FromXml Message where
type Db Message = Odds
instance XmlImport Message
+
+
+-- * Groundhog database schema.
+-- | This must come before the dbimport code.
+--
+mkPersist tsn_codegen_config [groundhog|
+- entity: Odds
+
+- entity: OddsCasino
+ dbName: odds_casinos
+ constructors:
+ - name: OddsCasino
+ uniques:
+ - name: unique_odds_casino
+ 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]
+
+- entity: OddsGameLine
+ dbName: odds_games_lines
+
+- entity: Odds_OddsGame
+ dbName: odds__odds_games
+
+- entity: OddsGame_OddsGameTeam
+ dbName: odds_games__odds_games_teams
+|]
+
instance DbImport Message where
- dbmigrate _= undefined
- dbimport = undefined
+ dbmigrate _=
+ run_dbmigrate $ do
+ 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)
+
+ -- 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)
+
+ -- Finaly, 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
+
+ -- ...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
+
+ -- 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
+
+ -- 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
+
+ return game_id
+
+ return ImportSucceeded
pickle_game_with_notes :: PU OddsGameWithNotes
pickle_game_with_notes =
-pickle_casino :: PU OddsCasinoXml
+pickle_casino :: PU OddsGameCasinoXml
pickle_casino =
xpElem "Casino" $
xpWrap (from_tuple, to_tuple) $
xpTriple
(xpAttr "ClientID" xpInt)
(xpAttr "Name" xpText)
- (xpOption xpPrim) -- Float
+ (xpOption xpPrim) -- Double
where
- from_tuple = uncurryN OddsCasinoXml
+ from_tuple = uncurryN OddsGameCasinoXml
-- Use record wildcards to avoid unused field warnings.
- to_tuple OddsCasinoXml{..} = (xml_casino_client_id,
- xml_casino_name,
- xml_casino_line)
+ to_tuple OddsGameCasinoXml{..} = (xml_casino_client_id,
+ xml_casino_name,
+ xml_casino_line)
-instance XmlPickler OddsCasinoXml where
+instance XmlPickler OddsGameCasinoXml where
xpickle = pickle_casino
-pickle_home_team :: PU OddsHomeTeamXml
+pickle_home_team :: PU OddsGameHomeTeamXml
pickle_home_team =
xpElem "HomeTeam" $
xpWrap (from_tuple, to_tuple) $
(xpElem "HomeTeamName" xpText)
(xpList pickle_casino)
where
- from_tuple = uncurryN OddsHomeTeamXml
+ from_tuple = uncurryN OddsGameHomeTeamXml
-- Use record wildcards to avoid unused field warnings.
- to_tuple OddsHomeTeamXml{..} = (xml_home_team_id,
- xml_home_rotation_number,
- xml_home_abbr,
- xml_home_team_name,
- xml_home_casinos)
+ to_tuple OddsGameHomeTeamXml{..} = (xml_home_team_id,
+ xml_home_rotation_number,
+ xml_home_abbr,
+ xml_home_team_name,
+ xml_home_casinos)
-instance XmlPickler OddsHomeTeamXml where
+instance XmlPickler OddsGameHomeTeamXml where
xpickle = pickle_home_team
-pickle_away_team :: PU OddsAwayTeamXml
+pickle_away_team :: PU OddsGameAwayTeamXml
pickle_away_team =
xpElem "AwayTeam" $
xpWrap (from_tuple, to_tuple) $
(xpElem "AwayTeamName" xpText)
(xpList pickle_casino)
where
- from_tuple = uncurryN OddsAwayTeamXml
+ from_tuple = uncurryN OddsGameAwayTeamXml
-- Use record wildcards to avoid unused field warnings.
- to_tuple OddsAwayTeamXml{..} = (xml_away_team_id,
+ to_tuple OddsGameAwayTeamXml{..} = (xml_away_team_id,
xml_away_rotation_number,
xml_away_abbr,
xml_away_team_name,
xml_away_casinos)
-instance XmlPickler OddsAwayTeamXml where
+instance XmlPickler OddsGameAwayTeamXml where
xpickle = pickle_away_team
-pickle_over_under :: PU OddsOverUnder
+pickle_over_under :: PU OddsGameOverUnderXml
pickle_over_under =
xpElem "Over_Under" $
xpWrap (to_newtype, from_newtype) $
xpList pickle_casino
where
- from_newtype (OddsOverUnder cs) = cs
- to_newtype = OddsOverUnder
+ from_newtype (OddsGameOverUnderXml cs) = cs
+ to_newtype = OddsGameOverUnderXml
-instance XmlPickler OddsOverUnder where
+instance XmlPickler OddsGameOverUnderXml where
xpickle = pickle_over_under
-
--- * Groundhog database schema.
-mkPersist tsn_codegen_config [groundhog|
-- entity: Odds
-
-- entity: OddsCasino
- dbName: odds_casinos
- constructors:
- - name: OddsCasino
- uniques:
- - name: unique_odds_casino
- type: constraint
- fields: [casino_client_id]
-
-- entity: OddsTeam
- dbName: odds_teams
- constructors:
- - name: OddsTeam
- uniques:
- - name: unique_odds_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]
-|]
-
-
-- * Tasty Tests
odds_tests :: TestTree
odds_tests =