]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blobdiff - src/TSN/XML/Odds.hs
Replace all raw DELETE queries with deleteAll.
[dead/htsn-import.git] / src / TSN / XML / Odds.hs
index 5551bee08f48b5c6ce1fd08f33448eca221ce7aa..b8888af2052d62f7fd5e85fdc61f907d9aaae20d 100644 (file)
@@ -7,16 +7,16 @@
 {-# 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
-  Odds_OddsGameConstructor(..),
   OddsCasinoConstructor(..),
   OddsConstructor(..),
   OddsGame_OddsGameTeamConstructor(..),
@@ -32,11 +32,16 @@ import Data.Tuple.Curry ( uncurryN )
 import Database.Groundhog (
   (=.),
   (==.),
+  countAll,
+  deleteAll,
   insert_,
-  insertByAll,
   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 )
@@ -62,11 +67,43 @@ 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 )
-import TSN.XmlImport ( XmlImport(..) )
-import Xml ( FromXml(..), ToDb(..), pickle_unpickle, unpickleable )
+import TSN.Picklers ( xp_date, xp_time, xp_time_stamp )
+import TSN.XmlImport ( XmlImport(..), XmlImportFk(..) )
+import Xml (
+  FromXml(..),
+  FromXmlFk(..),
+  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
+--
+
+-- * OddsGameCasino/OddsGameCasinoXml
+
+
+-- | The casinos should have their own table, but the lines don't
+--   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
+--   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)
+
 
 -- | 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
@@ -88,19 +125,6 @@ home_away_line :: OddsGameCasinoXml -> Maybe Double
 home_away_line = join . (fmap readMaybe) . xml_casino_line
 
 
--- | 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 ToDb OddsGameCasinoXml where
   -- | The database representation of an 'OddsGameCasinoXml' is an
@@ -108,18 +132,25 @@ instance ToDb OddsGameCasinoXml where
   --
   type Db OddsGameCasinoXml = OddsCasino
 
+
 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.
+
+-- | This allows us to insert the XML representation 'OddsGameCasinoXml'
+--   directly.
+--
 instance XmlImport OddsGameCasinoXml
 
 
+-- * OddsGameTeam
+
+
 -- | The database representation of teams as they appear in odds
 --   games.
 --
@@ -136,6 +167,8 @@ data OddsGameTeam =
   deriving (Eq, Show)
 
 
+-- * OddsGameHomeTeam/OddsGameHomeTeamXml
+
 -- | The XML representation of a \<HomeTeam\>, as found in \<Game\>s.
 --
 data OddsGameHomeTeamXml =
@@ -171,13 +204,14 @@ instance FromXml OddsGameHomeTeamXml where
       db_abbr      = xml_home_abbr,
       db_team_name = 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.
 --
 data OddsGameAwayTeamXml =
@@ -210,14 +244,16 @@ instance FromXml OddsGameAwayTeamXml where
                                        xml_away_abbr
                                        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,
@@ -225,6 +261,8 @@ data OddsGame_OddsGameTeam =
     ogogt_home_team_id  :: DefaultKey OddsGameTeam }
 
 
+-- * OddsGameOverUnderXml
+
 -- | XML representation of the over/under. A wrapper around a bunch of
 --   casino elements.
 --
@@ -233,9 +271,11 @@ newtype OddsGameOverUnderXml =
   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 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.
@@ -253,19 +293,22 @@ data OddsGameLine =
     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_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 }
-  deriving (Eq, Show)
 
--- | XML representation of a game.
+
+-- | XML representation of an 'OddsGame'.
 --
 data OddsGameXml =
   OddsGameXml {
@@ -290,13 +333,19 @@ instance ToDb OddsGameXml where
   --
   type Db OddsGameXml = OddsGame
 
-instance FromXml OddsGameXml where
+instance FromXmlFk 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
+
   -- | 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.
   --
-  from_xml OddsGameXml{..} =
+  from_xml_fk fk OddsGameXml{..} =
     OddsGame {
+      db_odds_id   = fk,
       db_game_id   = xml_game_id,
 
       db_game_time = UTCTime
@@ -309,44 +358,25 @@ instance FromXml OddsGameXml where
       db_game_home_team_rotation_number =
         (xml_home_rotation_number xml_game_home_team) }
 
--- | This lets us call 'insert_xml' directly on an 'OddsGameXml'
---   without converting it to the database representation explicitly.
+-- | This lets us insert the XML representation 'OddsGameXml' directly.
 --
-instance XmlImport OddsGameXml
-
+instance XmlImportFk OddsGameXml
 
--- | Database and representation of the top-level Odds object (a
---   'Message').
-data Odds =
-  Odds {
-    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).
-  }
-
-
--- | Map 'Odds' to their children 'OddsGame's.
---
-data Odds_OddsGame = Odds_OddsGame
-                       (DefaultKey Odds)
-                       (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 <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.
 --
 data OddsGameWithNotes =
   OddsGameWithNotes {
@@ -354,7 +384,25 @@ data OddsGameWithNotes =
     game :: OddsGameXml }
   deriving (Eq, Show)
 
+
+-- * 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,
@@ -364,7 +412,7 @@ data Message =
     xml_title :: String,
     xml_line_time :: String,
     xml_games_with_notes :: [OddsGameWithNotes],
-    xml_time_stamp :: String }
+    xml_time_stamp :: UTCTime }
   deriving (Eq, Show)
 
 -- | Pseudo-field that lets us get the 'OddsGame's out of
@@ -385,21 +433,32 @@ instance FromXml Message where
   --
   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_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
 
 
+--
+-- Database code
+--
 
 -- Groundhog database schema. This must come before the DbImport
--- instance definition.
+-- 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
@@ -424,25 +483,20 @@ mkPersist tsn_codegen_config [groundhog|
   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
 
 - entity: OddsGameLine
   dbName: odds_games_lines
-
-- entity: Odds_OddsGame
-  dbName: odds__odds_games
   constructors:
-    - name: Odds_OddsGame
+    - name: OddsGameLine
       fields:
-        - name: odds_OddsGame0 # Default created by mkNormalFieldName
-          dbName: odds_id
+        - name: ogl_odds_games_id
           reference:
             onDelete: cascade
-        - name: odds_OddsGame1 # Default created by mkNormalFieldName
-          dbName: odds_games_id
+        - name: ogl_odds_casinos_id
           reference:
             onDelete: cascade
 
@@ -469,7 +523,6 @@ instance DbImport Message where
       migrate (undefined :: OddsCasino)
       migrate (undefined :: OddsGameTeam)
       migrate (undefined :: OddsGame)
-      migrate (undefined :: Odds_OddsGame)
       migrate (undefined :: OddsGame_OddsGameTeam)
       migrate (undefined :: OddsGameLine)
 
@@ -477,19 +530,17 @@ instance DbImport Message where
     -- 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, 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.
@@ -514,12 +565,12 @@ instance DbImport Message where
                     ogl_away_line = Nothing,
                     ogl_home_line = Nothing }
 
-        insertByAll ogl
+        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
+      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
 
@@ -541,6 +592,11 @@ instance DbImport Message where
 
     return ImportSucceeded
 
+
+--
+-- Pickling
+--
+
 -- | Pickler for an 'OddsGame' optionally preceded by some notes.
 --
 pickle_game_with_notes :: PU OddsGameWithNotes
@@ -666,7 +722,7 @@ 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,
@@ -689,7 +745,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 ]
 
 
@@ -736,3 +793,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.
+--
+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 :: Odds
+      let b = undefined :: OddsCasino
+      let c = undefined :: OddsGameTeam
+      let d = undefined :: OddsGame
+      let e = undefined :: OddsGame_OddsGameTeam
+      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 a
+                  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