]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blobdiff - src/TSN/XML/Odds.hs
Make the Odds team rotation numbers optional.
[dead/htsn-import.git] / src / TSN / XML / Odds.hs
index bab8c28ee8e66a30ab05ac87a6c6bf5d26337ebf..934c3d340508f89a3d0c40b770ce49c3fd9e975d 100644 (file)
@@ -3,25 +3,23 @@
 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE QuasiQuotes #-}
 {-# LANGUAGE RecordWildCards #-}
-{-# LANGUAGE StandaloneDeriving #-}
 {-# LANGUAGE TemplateHaskell #-}
 {-# LANGUAGE TypeFamilies #-}
 
--- | Parse TSN XML for the DTD "Odds_XML.dtd". Each document contains
---   a root element \<message\> that contains a bunch of other
---   unorganized crap.
+-- | Parse TSN XML for the DTD \"Odds_XML.dtd\". Each document
+--   contains a root element \<message\> 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(..),
-  OddsGame_OddsGameTeamConstructor(..),
   OddsGameConstructor(..),
-  OddsGameLineConstructor(..),
-  OddsGameTeamConstructor(..) )
+  OddsGameLineConstructor(..) )
 where
 
 -- System imports.
@@ -31,10 +29,16 @@ import Data.Tuple.Curry ( uncurryN )
 import Database.Groundhog (
   (=.),
   (==.),
+  countAll,
+  deleteAll,
   insert_,
   migrate,
+  runMigration,
+  silentMigrationLogger,
   update )
 import Database.Groundhog.Core ( DefaultKey )
+import Database.Groundhog.Generic ( runDbConn )
+import Database.Groundhog.Sqlite ( withSqliteConn )
 import Database.Groundhog.TH (
   groundhog,
   mkPersist )
@@ -43,7 +47,6 @@ import Test.Tasty.HUnit ( (@?=), testCase )
 import Text.Read ( readMaybe )
 import Text.XML.HXT.Core (
   PU,
-  xp5Tuple,
   xp6Tuple,
   xp8Tuple,
   xpAttr,
@@ -60,14 +63,23 @@ import Text.XML.HXT.Core (
 import TSN.Codegen (
   tsn_codegen_config )
 import TSN.DbImport ( DbImport(..), ImportResult(..), run_dbmigrate )
-import TSN.Picklers ( xp_date, xp_time, xp_time_stamp )
-import TSN.XmlImport ( XmlImport(..), XmlImportFk(..) )
+import TSN.Picklers ( xp_date_padded, xp_time, xp_time_stamp )
+import TSN.Team ( Team(..) )
+import TSN.XmlImport ( XmlImport(..), XmlImportFkTeams(..) )
 import Xml (
+  Child(..),
   FromXml(..),
-  FromXmlFk(..),
+  FromXmlFkTeams(..),
   ToDb(..),
   pickle_unpickle,
-  unpickleable )
+  unpickleable,
+  unsafe_unpickle )
+
+
+-- | The DTD to which this module corresponds. Used to invoke dbimport.
+--
+dtd :: String
+dtd = "Odds_XML.dtd"
 
 
 --
@@ -78,10 +90,10 @@ import Xml (
 
 
 -- | 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 =
@@ -121,39 +133,28 @@ instance ToDb OddsGameCasinoXml where
 
 instance FromXml OddsGameCasinoXml where
   -- | We convert from XML to the database by dropping the line field.
+  --
   from_xml OddsGameCasinoXml{..} =
     OddsCasino {
       casino_client_id = xml_casino_client_id,
       casino_name      = xml_casino_name }
 
 
--- | This allows us to call 'insert_xml' on an 'OddsGameCasinoXml'
---   without first converting it to the database representation.
-instance XmlImport OddsGameCasinoXml
-
-
--- * OddsGameTeam
-
-
--- | The database representation of teams as they appear in odds
---   games.
+-- | This allows us to insert the XML representation 'OddsGameCasinoXml'
+--   directly.
 --
-data OddsGameTeam =
-  OddsGameTeam {
-    db_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.
-    db_abbr            :: String,
-    db_team_name       :: String }
-  deriving (Eq, Show)
+instance XmlImport OddsGameCasinoXml
 
 
--- * OddsGameHomeTeam/OddsGameHomeTeamXml
+-- * OddsGameHomeTeamXml / OddsGameAwayTeamXml
 
 -- | The XML representation of a \<HomeTeam\>, as found in \<Game\>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 {
@@ -165,17 +166,18 @@ data OddsGameHomeTeamXml =
                                         --   so we ignore the probable
                                         --   upper bound of three
                                         --   characters.
-    xml_home_rotation_number :: Int,
-    xml_home_abbr            :: String,
-    xml_home_team_name       :: String,
-    xml_home_casinos         :: [OddsGameCasinoXml] }
+    xml_home_team_rotation_number :: Maybe 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)
 
 instance ToDb OddsGameHomeTeamXml where
   -- | The database representation of an 'OddsGameHomeTeamXml' is an
   --   'OddsGameTeam'.
   --
-  type Db OddsGameHomeTeamXml = OddsGameTeam
+  type Db OddsGameHomeTeamXml = Team
 
 instance FromXml OddsGameHomeTeamXml where
   -- | We convert from XML to the database by dropping the lines and
@@ -183,21 +185,21 @@ instance FromXml OddsGameHomeTeamXml where
   --   themselves).
   --
   from_xml OddsGameHomeTeamXml{..} =
-    OddsGameTeam {
-      db_team_id   = xml_home_team_id,
-      db_abbr      = xml_home_abbr,
-      db_team_name = xml_home_team_name }
+    Team {
+      team_id   = xml_home_team_id,
+      abbreviation = Just xml_home_team_abbr,
+      name = Just xml_home_team_name }
 
--- | XmlImport allows us to call 'insert_xml' directly on an
---   'OddsGameHomeTeamXml' without explicitly converting it to the
---   associated database type.
+-- | This allows us to insert the XML representation
+--   'OddsGameHomeTeamXml' directly.
 --
 instance XmlImport OddsGameHomeTeamXml where
 
 
--- * OddsGameAwayTeam/OddsGameAwayTeamXml
 
 -- | The XML representation of a \<AwayTeam\>, as found in \<Game\>s.
+--   This is basically the same as 'OddsGameHomeTeamXml', but the two
+--   types have different picklers.
 --
 data OddsGameAwayTeamXml =
   OddsGameAwayTeamXml {
@@ -207,44 +209,35 @@ data OddsGameAwayTeamXml =
                                         --   on lengthless text fields, so
                                         --   we ignore the probable upper
                                         --   bound of three characters
-    xml_away_rotation_number :: Int,
-    xml_away_abbr            :: String,
-    xml_away_team_name       :: String,
-    xml_away_casinos         :: [OddsGameCasinoXml] }
+    xml_away_team_rotation_number :: Maybe 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)
 
 instance ToDb OddsGameAwayTeamXml where
-  -- | The database representation of an 'OddsGameAwayTeamXml' is an
-  --   'OddsGameTeam'.
+  -- | The database representation of an 'OddsGameAwayTeamXml' is a
+  --   'Team'.
   --
-  type Db OddsGameAwayTeamXml = OddsGameTeam
+  type Db OddsGameAwayTeamXml = Team
 
 instance FromXml OddsGameAwayTeamXml 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{..} = OddsGameTeam
+  from_xml OddsGameAwayTeamXml{..} = Team
                                        xml_away_team_id
-                                       xml_away_abbr
-                                       xml_away_team_name
+                                       (Just xml_away_team_abbr)
+                                       (Just xml_away_team_name)
 
--- | XmlImport allows us to call 'insert_xml' directly on an
---   'OddsGameAwayTeamXml' without explicitly converting it to the
---   associated database type.
+-- | This allows us to insert the XML representation
+--   'OddsGameAwayTeamXml' directly.
 --
 instance XmlImport OddsGameAwayTeamXml where
 
 
--- * OddsGame_OddsGameTeam
-
--- | 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 }
-
 
 -- * OddsGameOverUnderXml
 
@@ -260,7 +253,7 @@ newtype OddsGameOverUnderXml =
 
 -- | 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
+--   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.
@@ -287,29 +280,35 @@ 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_game_away_team_rotation_number :: Int,
-    db_game_home_team_rotation_number :: Int }
+    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 a game.
+-- | XML representation of an 'OddsGame'.
 --
 data OddsGameXml =
   OddsGameXml {
     xml_game_id         :: Int,
     xml_game_date       :: UTCTime, -- ^ Contains only the date
     xml_game_time       :: UTCTime, -- ^ Contains only the time
-    xml_game_away_team  :: OddsGameAwayTeamXml,
-    xml_game_home_team  :: OddsGameHomeTeamXml,
-    xml_game_over_under :: OddsGameOverUnderXml }
+    xml_away_team  :: OddsGameAwayTeamXml,
+    xml_home_team  :: OddsGameHomeTeamXml,
+    xml_over_under :: OddsGameOverUnderXml }
   deriving (Eq, Show)
 
 -- | Pseudo-field that lets us get the 'OddsGameCasinoXml's out of
---   xml_game_over_under.
+--   xml_over_under.
 --
-xml_game_over_under_casinos :: OddsGameXml -> [OddsGameCasinoXml]
-xml_game_over_under_casinos = xml_casinos . xml_game_over_under
+xml_over_under_casinos :: OddsGameXml -> [OddsGameCasinoXml]
+xml_over_under_casinos = xml_casinos . xml_over_under
 
 
 instance ToDb OddsGameXml where
@@ -318,51 +317,81 @@ instance ToDb OddsGameXml where
   --
   type Db OddsGameXml = OddsGame
 
-instance FromXmlFk OddsGameXml where
+
+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 home/away teams and the casino lines, but retain the
-  --   home/away rotation numbers.
+  --   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_away_team_rotation_number =
-        (xml_away_rotation_number xml_game_away_team),
+      db_away_team_rotation_number =
+        (xml_away_team_rotation_number xml_away_team),
+
+      db_home_team_rotation_number =
+        (xml_home_team_rotation_number xml_home_team),
+
+      db_away_team_starter_id =
+        (fmap fst $ xml_away_team_starter xml_away_team),
+
+      db_away_team_starter_name =
+        (fmap snd $ xml_away_team_starter xml_away_team),
+
+      db_home_team_starter_id =
+        (fmap fst $ xml_home_team_starter xml_home_team),
 
-      db_game_home_team_rotation_number =
-        (xml_home_rotation_number xml_game_home_team) }
+      db_home_team_starter_name =
+        (fmap snd $ xml_home_team_starter xml_home_team) }
 
--- | This lets us call 'insert_xml_fk' directly on an 'OddsGameXml'
---   without converting it to the database representation explicitly.
+
+-- | This lets us insert the XML representation 'OddsGameXml' directly.
 --
-instance XmlImportFk OddsGameXml
+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 <Notes>...</Notes> element.
+--   optionally have some notes appear before it. Each \"note\" comes
+--   as its own \<Notes\>...\</Notes\> 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
+--   \<League_Name\> 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 \<League_Name\> 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)
@@ -370,8 +399,8 @@ data OddsGameWithNotes =
 
 -- * Odds/Message
 
--- | Database and representation of the top-level Odds object (a
---   'Message').
+-- | Database representation of a 'Message'.
+--
 data Odds =
   Odds {
     db_xml_file_id :: Int,
@@ -385,6 +414,7 @@ data Odds =
 
 
 -- | The XML representation of 'Odds'.
+--
 data Message =
   Message {
     xml_xml_file_id :: Int,
@@ -421,8 +451,7 @@ instance FromXml Message where
       db_line_time = xml_line_time,
       db_time_stamp = xml_time_stamp }
 
--- | This lets us call 'insert_xml' on a Message directly, without
---   having to convert it to its database representation explicitly.
+-- | This lets us insert the XML representation 'Message' directly.
 --
 instance XmlImport Message
 
@@ -452,16 +481,6 @@ mkPersist tsn_codegen_config [groundhog|
           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:
@@ -470,6 +489,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
@@ -477,66 +502,40 @@ mkPersist tsn_codegen_config [groundhog|
     - name: OddsGameLine
       fields:
         - name: ogl_odds_games_id
-          references:
-            onDelete: cascade
-        - name: ogl_odds_casinos_id
-          references:
-            onDelete: cascade
-
-- entity: OddsGame_OddsGameTeam
-  dbName: odds_games__odds_games_teams
-  constructors:
-    - name: OddsGame_OddsGameTeam
-      fields:
-        - name: ogogt_odds_games_id
-          reference:
-            onDelete: cascade
-        - name: ogogt_away_team_id
           reference:
             onDelete: cascade
-        - name: ogogt_home_team_id
+        - 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 :: OddsGameTeam)
       migrate (undefined :: 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
 
-    forM_ (xml_games m) $ \g -> do
-      -- 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.
-      -- 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)
-
-      -- Now insert the game, keyed to the "odds",
-      game_id <- insert_xml_fk odds_id g
-
-      -- Insert a record into odds_games__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_OddsGameTeam {
-                ogogt_odds_games_id = game_id,
-                ogogt_away_team_id = away_team_id,
-                ogogt_home_team_id = home_team_id }
-
-      -- Finaly, we insert the lines. The over/under entries for this
+    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:
-      forM_ (xml_game_over_under_casinos g) $ \c -> do
+      forM_ (xml_over_under_casinos game) $ \c -> do
         -- Start by inderting the casino.
         ou_casino_id <- insert_xml_or_select c
 
@@ -553,7 +552,7 @@ instance DbImport Message where
       -- ...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
+      forM_ (xml_away_team_casinos $ xml_away_team game) $ \c -> do
         -- insert, or more likely retrieve the existing, casino
         a_casino_id <- insert_xml_or_select c
 
@@ -565,7 +564,7 @@ instance DbImport Message 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
+      forM_ (xml_home_team_casinos $ xml_home_team game) $ \c ->do
         h_casino_id <- insert_xml_or_select c
         let home_line = home_away_line c
         update [Ogl_Home_Line =. home_line] $ -- WHERE
@@ -585,12 +584,13 @@ instance DbImport Message where
 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'.
@@ -617,21 +617,25 @@ pickle_home_team :: PU OddsGameHomeTeamXml
 pickle_home_team =
   xpElem "HomeTeam" $
     xpWrap (from_tuple, to_tuple) $
-      xp5Tuple
+      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))
         (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_rotation_number,
+                                        xml_home_team_abbr,
                                         xml_home_team_name,
-                                        xml_home_casinos)
-
+                                        xml_home_team_starter,
+                                        xml_home_team_casinos)
 
 -- | Pickler for an 'OddsGameAwayTeamXml'.
 --
@@ -639,20 +643,25 @@ pickle_away_team :: PU OddsGameAwayTeamXml
 pickle_away_team =
   xpElem "AwayTeam" $
     xpWrap (from_tuple, to_tuple) $
-      xp5Tuple
+      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))
         (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_rotation_number,
+                                        xml_away_team_abbr,
                                         xml_away_team_name,
-                                        xml_away_casinos)
+                                        xml_away_team_starter,
+                                        xml_away_team_casinos)
 
 
 
@@ -676,7 +685,7 @@ pickle_game =
   xpWrap (from_tuple, to_tuple) $
   xp6Tuple
     (xpElem "GameID" xpInt)
-    (xpElem "Game_Date" xp_date)
+    (xpElem "Game_Date" xp_date_padded)
     (xpElem "Game_Time" xp_time)
     pickle_away_team
     pickle_home_team
@@ -687,9 +696,9 @@ pickle_game =
     to_tuple OddsGameXml{..} = (xml_game_id,
                                 xml_game_date,
                                 xml_game_time,
-                                xml_game_away_team,
-                                xml_game_home_team,
-                                xml_game_over_under)
+                                xml_away_team,
+                                xml_home_team,
+                                xml_over_under)
 
 
 -- | Pickler for the top-level 'Message'.
@@ -728,7 +737,8 @@ 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 ]
 
 
@@ -739,7 +749,7 @@ odds_tests =
 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",
+          "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",
@@ -748,7 +758,10 @@ test_pickle_of_unpickle_is_identity = testGroup "pickle-unpickle tests"
           "test/xml/Odds_XML-positive-line.xml",
 
     check "pickle composed with unpickle is the identity (large file)"
-          "test/xml/Odds_XML-largefile.xml" ]
+          "test/xml/Odds_XML-largefile.xml",
+
+    check "pickle composed with unpickle is the identity (league name)"
+          "test/xml/Odds_XML-league-name.xml" ]
   where
     check desc path = testCase desc $ do
       (expected, actual) <- pickle_unpickle pickle_message path
@@ -769,9 +782,67 @@ test_unpickle_succeeds = testGroup "unpickle tests"
           "test/xml/Odds_XML-positive-line.xml",
 
     check "unpickling succeeds (large file)"
-          "test/xml/Odds_XML-largefile.xml" ]
+          "test/xml/Odds_XML-largefile.xml",
+
+    check "unpickling succeeds (league name)"
+          "test/xml/Odds_XML-league-name.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
+    ]
+  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
+                  runMigration silentMigrationLogger $ 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