]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blobdiff - src/TSN/XML/Odds.hs
Make team names and abbreviations optional.
[dead/htsn-import.git] / src / TSN / XML / Odds.hs
index 3fd29068b2ad94638730460877e9dbc53cd718b5..b76be762dee067d4b2125ad28668b21bfc3ab7eb 100644 (file)
@@ -3,7 +3,6 @@
 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE QuasiQuotes #-}
 {-# LANGUAGE RecordWildCards #-}
-{-# LANGUAGE StandaloneDeriving #-}
 {-# LANGUAGE TemplateHaskell #-}
 {-# LANGUAGE TypeFamilies #-}
 
 --   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(..),
+  OddsGame_TeamConstructor(..),
   OddsGameConstructor(..),
-  OddsGameLineConstructor(..),
-  OddsGameTeamConstructor(..) )
+  OddsGameLineConstructor(..) )
 where
 
 -- System imports.
@@ -31,10 +30,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 )
@@ -60,14 +65,22 @@ 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.Picklers ( xp_date_padded, xp_time, xp_time_stamp )
+import TSN.Team ( Team(..) )
 import TSN.XmlImport ( XmlImport(..), XmlImportFk(..) )
 import Xml (
   FromXml(..),
   FromXmlFk(..),
   ToDb(..),
   pickle_unpickle,
-  unpickleable )
+  unpickleable,
+  unsafe_unpickle )
+
+
+-- | The DTD to which this module corresponds. Used to invoke dbimport.
+--
+dtd :: String
+dtd = "Odds_XML.dtd"
 
 
 --
@@ -134,28 +147,11 @@ instance FromXml OddsGameCasinoXml where
 instance XmlImport OddsGameCasinoXml
 
 
--- * OddsGameTeam
-
-
--- | The database representation of teams as they appear in odds
---   games.
---
-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)
-
-
--- * 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.
 --
 data OddsGameHomeTeamXml =
   OddsGameHomeTeamXml {
@@ -177,7 +173,7 @@ 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
@@ -185,10 +181,10 @@ 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,
+      team_abbreviation = Just xml_home_abbr,
+      team_name = Just xml_home_team_name }
 
 -- | This allows us to insert the XML representation
 --   'OddsGameHomeTeamXml' directly.
@@ -196,9 +192,10 @@ instance FromXml OddsGameHomeTeamXml where
 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 {
@@ -215,20 +212,20 @@ data OddsGameAwayTeamXml =
   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_abbr)
+                                       (Just xml_away_team_name)
 
 -- | This allows us to insert the XML representation
 --   'OddsGameAwayTeamXml' directly.
@@ -240,11 +237,11 @@ instance XmlImport OddsGameAwayTeamXml 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 OddsGame_Team =
+  OddsGame_Team {
+    ogt_odds_games_id :: DefaultKey OddsGame,
+    ogt_away_team_id  :: DefaultKey Team,
+    ogt_home_team_id  :: DefaultKey Team }
 
 
 -- * OddsGameOverUnderXml
@@ -455,16 +452,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:
@@ -480,24 +467,24 @@ mkPersist tsn_codegen_config [groundhog|
     - name: OddsGameLine
       fields:
         - name: ogl_odds_games_id
-          references:
+          reference:
             onDelete: cascade
         - name: ogl_odds_casinos_id
-          references:
+          reference:
             onDelete: cascade
 
-- entity: OddsGame_OddsGameTeam
-  dbName: odds_games__odds_games_teams
+- entity: OddsGame_Team
+  dbName: odds_games__teams
   constructors:
-    - name: OddsGame_OddsGameTeam
+    - name: OddsGame_Team
       fields:
-        - name: ogogt_odds_games_id
+        - name: ogt_odds_games_id
           reference:
             onDelete: cascade
-        - name: ogogt_away_team_id
+        - name: ogt_away_team_id
           reference:
             onDelete: cascade
-        - name: ogogt_home_team_id
+        - name: ogt_home_team_id
           reference:
             onDelete: cascade
 |]
@@ -505,11 +492,11 @@ mkPersist tsn_codegen_config [groundhog|
 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 :: OddsGame_Team)
       migrate (undefined :: OddsGameLine)
 
   dbimport m = do
@@ -519,21 +506,20 @@ instance DbImport Message where
     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.
+      -- pointing to "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
+      -- 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_OddsGameTeam {
-                ogogt_odds_games_id = game_id,
-                ogogt_away_team_id = away_team_id,
-                ogogt_home_team_id = home_team_id }
+      insert_ OddsGame_Team {
+                ogt_odds_games_id = game_id,
+                ogt_away_team_id = away_team_id,
+                ogt_home_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
@@ -679,7 +665,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
@@ -731,7 +717,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 ]
 
 
@@ -742,7 +729,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",
@@ -778,3 +765,57 @@ test_unpickle_succeeds = testGroup "unpickle tests"
       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
+    ]
+  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 :: OddsGame_Team
+      let f = undefined :: OddsGameLine
+      actual <- withSqliteConn ":memory:" $ runDbConn $ do
+                  runMigration silentMigrationLogger $ do
+                    migrate a
+                    migrate b
+                    migrate c
+                    migrate d
+                    migrate e
+                    migrate f
+                  _ <- dbimport odds
+                  deleteAll b
+                  count_a <- countAll a
+                  count_b <- countAll b
+                  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 ]
+      actual @?= expected