]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blobdiff - src/TSN/XML/Odds.hs
Fix unpickling of non-integer team_ids in TSN.XML.Odds (with tests).
[dead/htsn-import.git] / src / TSN / XML / Odds.hs
index 2105ce7fe3e8d97f5d195adb2de516074aae50c0..dde6a0920c101ee0115665b7bc04fbaaeaf06beb 100644 (file)
@@ -3,7 +3,6 @@
 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE QuasiQuotes #-}
 {-# LANGUAGE RecordWildCards #-}
-{-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE StandaloneDeriving #-}
 {-# LANGUAGE TemplateHaskell #-}
 {-# LANGUAGE TypeFamilies #-}
 --   unorganized crap.
 --
 module TSN.XML.Odds (
-  Odds,
-  Message,
-  odds_tests )
+  odds_tests,
+  pickle_message )
 where
 
-import Control.Monad ( forM_ )
+import Control.Monad ( forM_, join )
 import Data.Tuple.Curry ( uncurryN )
 import Database.Groundhog (
   (=.),
@@ -33,9 +31,9 @@ import Database.Groundhog.TH (
   mkPersist )
 import Test.Tasty ( TestTree, testGroup )
 import Test.Tasty.HUnit ( (@?=), testCase )
+import Text.Read ( readMaybe )
 import Text.XML.HXT.Core (
   PU,
-  XmlPickler(..),
   xp5Tuple,
   xp6Tuple,
   xp8Tuple,
@@ -53,19 +51,31 @@ import Text.XML.HXT.Core (
 import TSN.Codegen (
   tsn_codegen_config )
 import TSN.DbImport ( DbImport(..), ImportResult(..), run_dbmigrate )
+import TSN.Picklers ( xp_team_id )
 import TSN.XmlImport ( XmlImport(..) )
 import Xml ( FromXml(..), pickle_unpickle, unpickleable )
 
 
 
+-- | 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.
+--
 data OddsGameCasinoXml =
   OddsGameCasinoXml {
     xml_casino_client_id :: Int,
     xml_casino_name      :: String,
-    xml_casino_line      :: Maybe Double }
+    xml_casino_line      :: Maybe String }
   deriving (Eq, Show)
 
 
+-- | 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
+
 -- | 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.)
@@ -93,7 +103,7 @@ instance XmlImport OddsGameCasinoXml
 
 data OddsGameHomeTeamXml =
   OddsGameHomeTeamXml {
-    xml_home_team_id         :: Int,
+    xml_home_team_id         :: String, -- ^ These are three-character IDs.
     xml_home_rotation_number :: Int,
     xml_home_abbr            :: String,
     xml_home_team_name       :: String,
@@ -112,7 +122,7 @@ instance XmlImport OddsGameHomeTeamXml where
 
 data OddsGameTeam =
   OddsGameTeam {
-    db_team_id         :: Int,
+    db_team_id         :: String, -- ^ The home/away team IDs are 3 characters
     db_abbr            :: String,
     db_team_name       :: String }
   deriving (Eq, Show)
@@ -127,7 +137,7 @@ data OddsGame_OddsGameTeam =
 
 data OddsGameAwayTeamXml =
   OddsGameAwayTeamXml {
-    xml_away_team_id         :: Int,
+    xml_away_team_id         :: String, -- ^ These are 3 character IDs.
     xml_away_rotation_number :: Int,
     xml_away_abbr            :: String,
     xml_away_team_name       :: String,
@@ -150,14 +160,20 @@ 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 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 }
 
@@ -282,6 +298,9 @@ mkPersist tsn_codegen_config [groundhog|
   dbName: odds_games_teams
   constructors:
     - name: OddsGameTeam
+      fields:
+        - name: db_team_id
+          type: varchar(3)
       uniques:
         - name: unique_odds_games_team
           type: constraint
@@ -364,14 +383,18 @@ instance DbImport Message where
         -- insert, or more likely retrieve the existing, casino
         a_casino_id <- insert_xml_or_select c
 
+        -- 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 =. (xml_casino_line c)] $ -- WHERE
+        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
+        let home_line = home_away_line c
+        update [Ogl_Home_Line =. home_line] $ -- WHERE
           Ogl_Odds_Casinos_Id ==. h_casino_id
 
       return game_id
@@ -397,7 +420,7 @@ pickle_casino =
   xpTriple
     (xpAttr "ClientID" xpInt)
     (xpAttr "Name" xpText)
-    (xpOption xpPrim) -- Double
+    (xpOption xpText)
   where
     from_tuple = uncurryN OddsGameCasinoXml
     -- Use record wildcards to avoid unused field warnings.
@@ -405,16 +428,13 @@ pickle_casino =
                                       xml_casino_name,
                                       xml_casino_line)
 
-instance XmlPickler OddsGameCasinoXml where
-  xpickle = pickle_casino
-
 
 pickle_home_team :: PU OddsGameHomeTeamXml
 pickle_home_team =
   xpElem "HomeTeam" $
     xpWrap (from_tuple, to_tuple) $
       xp5Tuple
-        (xpElem "HomeTeamID" xpInt)
+        (xpElem "HomeTeamID" xp_team_id)
         (xpElem "HomeRotationNumber" xpInt)
         (xpElem "HomeAbbr" xpText)
         (xpElem "HomeTeamName" xpText)
@@ -428,8 +448,6 @@ pickle_home_team =
                                         xml_home_team_name,
                                         xml_home_casinos)
 
-instance XmlPickler OddsGameHomeTeamXml where
-  xpickle = pickle_home_team
 
 
 pickle_away_team :: PU OddsGameAwayTeamXml
@@ -437,7 +455,7 @@ pickle_away_team =
   xpElem "AwayTeam" $
     xpWrap (from_tuple, to_tuple) $
       xp5Tuple
-        (xpElem "AwayTeamID" xpInt)
+        (xpElem "AwayTeamID" xp_team_id)
         (xpElem "AwayRotationNumber" xpInt)
         (xpElem "AwayAbbr" xpText)
         (xpElem "AwayTeamName" xpText)
@@ -452,9 +470,6 @@ pickle_away_team =
                                  xml_away_casinos)
 
 
-instance XmlPickler OddsGameAwayTeamXml where
-  xpickle = pickle_away_team
-
 
 pickle_over_under :: PU OddsGameOverUnderXml
 pickle_over_under =
@@ -465,8 +480,6 @@ pickle_over_under =
     from_newtype (OddsGameOverUnderXml cs) = cs
     to_newtype = OddsGameOverUnderXml
 
-instance XmlPickler OddsGameOverUnderXml where
-  xpickle = pickle_over_under
 
 
 pickle_game :: PU OddsGameXml
@@ -490,9 +503,6 @@ pickle_game =
                                 xml_game_home_team,
                                 xml_game_over_under)
 
-instance XmlPickler OddsGameXml where
-  xpickle = pickle_game
-
 
 pickle_message :: PU Message
 pickle_message =
@@ -518,11 +528,6 @@ pickle_message =
                   xml_time_stamp m)
 
 
-instance XmlPickler Message where
-  xpickle = pickle_message
-
-
-
 
 -- * Tasty Tests
 odds_tests :: TestTree
@@ -536,17 +541,33 @@ odds_tests =
 -- | Warning, succeess 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" ]
+  where
+    check desc path = testCase desc $ do
+      (expected, actual) <- pickle_unpickle pickle_message path
+      actual @?= expected
 
 
 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" ]
+  where
+    check desc path = testCase desc $ do
+      actual <- unpickleable path pickle_message
+      let expected = True
+      actual @?= expected