]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blobdiff - src/TSN/XML/Odds.hs
Combine the odds game date/time into one DB field.
[dead/htsn-import.git] / src / TSN / XML / Odds.hs
index 2bc52216148e6c173bec6bfb7f953de764c30d1d..bbed4af08def3425c9ad550ba28836e60d41faf8 100644 (file)
@@ -3,24 +3,31 @@
 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE QuasiQuotes #-}
 {-# LANGUAGE RecordWildCards #-}
-{-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE StandaloneDeriving #-}
 {-# LANGUAGE TemplateHaskell #-}
 {-# LANGUAGE TypeFamilies #-}
 
-module TSN.XML.Odds (
-  Odds,
-  Message,
-  odds_tests )
-where
-
-
 -- | Parse TSN XML for the DTD "Odds_XML.dtd". Each document contains
 --   a root element \<message\> that contains a bunch of other
 --   unorganized crap.
 --
+module TSN.XML.Odds (
+  pickle_message,
+  -- * Tests
+  odds_tests,
+  -- * WARNING: these are private but exported to silence warnings
+  Odds_OddsGameConstructor(..),
+  OddsCasinoConstructor(..),
+  OddsConstructor(..),
+  OddsGame_OddsGameTeamConstructor(..),
+  OddsGameConstructor(..),
+  OddsGameLineConstructor(..),
+  OddsGameTeamConstructor(..) )
+where
 
-import Control.Monad ( forM_ )
+-- System imports.
+import Control.Monad ( forM_, join )
+import Data.Time ( UTCTime(..) )
 import Data.Tuple.Curry ( uncurryN )
 import Database.Groundhog (
   (=.),
@@ -35,9 +42,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,
@@ -47,29 +54,42 @@ import Text.XML.HXT.Core (
   xpList,
   xpOption,
   xpPair,
-  xpPrim,
   xpText,
   xpTriple,
   xpWrap )
 
+-- Local imports.
 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(..), 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
+--   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
@@ -81,21 +101,52 @@ data OddsCasino =
     casino_name :: String }
   deriving (Eq, Show)
 
+
 instance FromXml OddsGameCasinoXml where
+  -- | The database representation of an 'OddsGameCasinoXml' is an
+  --   'OddsCasino'.
+  --
   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 OddsGameCasinoXml{..} = OddsCasino
-                                     xml_casino_client_id
-                                     xml_casino_name
+  -- | 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
 
 
+-- | 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)
+
+
+-- | The XML representation of a \<HomeTeam\>, as found in \<Game\>s.
+--
 data OddsGameHomeTeamXml =
   OddsGameHomeTeamXml {
-    xml_home_team_id         :: Int,
+    xml_home_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.
     xml_home_rotation_number :: Int,
     xml_home_abbr            :: String,
     xml_home_team_name       :: String,
@@ -103,33 +154,38 @@ data OddsGameHomeTeamXml =
   deriving (Eq, Show)
 
 instance FromXml OddsGameHomeTeamXml where
+  -- | The database representation of an 'OddsGameHomeTeamXml' is an
+  --   'OddsGameTeam'.
+  --
   type Db OddsGameHomeTeamXml = OddsGameTeam
-  from_xml OddsGameHomeTeamXml{..} = OddsGameTeam
-                                       xml_home_team_id
-                                       xml_home_abbr
-                                       xml_home_team_name
 
+  -- | 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 OddsGameHomeTeamXml{..} =
+    OddsGameTeam {
+      db_team_id   = xml_home_team_id,
+      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.
+--
 instance XmlImport OddsGameHomeTeamXml where
 
 
-data OddsGameTeam =
-  OddsGameTeam {
-    db_team_id         :: Int,
-    db_abbr            :: String,
-    db_team_name       :: String }
-  deriving (Eq, Show)
-
-
--- | 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 }
-
+-- | The XML representation of a \<AwayTeam\>, as found in \<Game\>s.
+--
 data OddsGameAwayTeamXml =
   OddsGameAwayTeamXml {
-    xml_away_team_id         :: Int,
+    xml_away_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
     xml_away_rotation_number :: Int,
     xml_away_abbr            :: String,
     xml_away_team_name       :: String,
@@ -137,83 +193,143 @@ data OddsGameAwayTeamXml =
   deriving (Eq, Show)
 
 instance FromXml OddsGameAwayTeamXml where
+  -- | The database representation of an 'OddsGameAwayTeamXml' is an
+  --   'OddsGameTeam'.
+  --
   type Db OddsGameAwayTeamXml = OddsGameTeam
+
+  -- | 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
                                        xml_away_team_id
                                        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.
+--
 instance XmlImport OddsGameAwayTeamXml where
 
--- | Can't use a newtype with Groundhog.
+
+-- | 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 }
+
+
+-- | XML representation of the over/under. A wrapper around a bunch of
+--   casino elements.
+--
 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.
+--   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 }
 
+
+-- | 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_game_id           :: Int,
-    db_game_date         :: String, -- TODO
-    db_game_time         :: String, -- TODO
+    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 instance Eq OddsGame
-deriving instance Show OddsGame
+  deriving (Eq, Show)
 
+-- | XML representation of a game.
+--
 data OddsGameXml =
   OddsGameXml {
     xml_game_id         :: Int,
-    xml_game_date       :: String, -- TODO
-    xml_game_time       :: String, -- TODO
+    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 }
   deriving (Eq, Show)
 
--- | Pseudo-field that lets us get the 'OddsCasino's out of
+-- | Pseudo-field that lets us get the 'OddsGameCasinoXml'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
+  -- | The database representation of an 'OddsGameXml' is an
+  --   'OddsGame'.
+  --
   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
+  -- | 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{..} =
+    OddsGame {
+      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_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.
+--
+instance XmlImport 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 }
+    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 {
-    oog_odds_id       :: DefaultKey Odds,
-    oog_odds_games_id :: DefaultKey OddsGame }
+--
+data Odds_OddsGame = Odds_OddsGame
+                       (DefaultKey Odds)
+                       (DefaultKey OddsGame)
+
 
 -- | This is our best guess at what occurs in the Odds_XML
 --   documents. It looks like each consecutive set of games can
@@ -234,7 +350,7 @@ data OddsGameWithNotes =
     game :: OddsGameXml }
   deriving (Eq, Show)
 
--- | The XML representation of Odds.
+-- | The XML representation of 'Odds'.
 data Message =
   Message {
     xml_xml_file_id :: Int,
@@ -249,25 +365,34 @@ data Message =
 
 -- | Pseudo-field that lets us get the 'OddsGame's out of
 --   'xml_games_with_notes'.
+--
 xml_games :: Message -> [OddsGameXml]
 xml_games m = map game (xml_games_with_notes m)
 
 
 instance FromXml Message where
+  -- | The database representation of a 'Message' is 'Odds'.
+  --
   type Db Message = Odds
 
-  -- We don't need the key argument (from_xml_fk) since the XML type
-  -- contains more information in this case.
-  from_xml (Message _ _ _ d e f _ _) =
-    Odds d e f
-
+  -- | To convert from the XML representation to the database one, we
+  --   just drop a bunch of fields.
+  --
+  from_xml Message{..} =
+    Odds {
+      db_sport = xml_sport,
+      db_title = xml_title,
+      db_line_time = xml_line_time }
+
+-- | This lets us call 'insert_xml' on a Message directly, without
+--   having to convert it to its database representation explicitly.
+--
 instance XmlImport Message
 
 
 
--- * Groundhog database schema.
--- | This must come before the dbimport code.
---
+-- Groundhog database schema. This must come before the DbImport
+-- instance definition.
 mkPersist tsn_codegen_config [groundhog|
 - entity: Odds
 
@@ -304,6 +429,13 @@ mkPersist tsn_codegen_config [groundhog|
 
 - entity: Odds_OddsGame
   dbName: odds__odds_games
+  constructors:
+    - name: Odds_OddsGame
+      fields:
+        - name: odds_OddsGame0 # Default created by mkNormalFieldName
+          dbName: odds_id
+        - name: odds_OddsGame1 # Default created by mkNormalFieldName
+          dbName: odds_games_id
 
 - entity: OddsGame_OddsGameTeam
   dbName: odds_games__odds_games_teams
@@ -337,9 +469,13 @@ instance DbImport Message where
       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)
+      -- 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
       -- game and the lines for the casinos all wind up in the same
@@ -350,12 +486,12 @@ instance DbImport Message where
         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
+        let ogl = OddsGameLine {
+                    ogl_odds_games_id = game_id,
+                    ogl_odds_casinos_id = ou_casino_id,
+                    ogl_over_under = (xml_casino_line c),
+                    ogl_away_line = Nothing,
+                    ogl_home_line = Nothing }
 
         insertByAll ogl
 
@@ -366,20 +502,26 @@ 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
 
     return ImportSucceeded
 
+-- | Pickler for an 'OddsGame' optionally preceded by some notes.
+--
 pickle_game_with_notes :: PU OddsGameWithNotes
 pickle_game_with_notes =
   xpWrap (from_pair, to_pair) $
@@ -391,7 +533,8 @@ pickle_game_with_notes =
     to_pair OddsGameWithNotes{..} = (notes, game)
 
 
-
+-- | Pickler for an 'OddsGameCasinoXml'.
+--
 pickle_casino :: PU OddsGameCasinoXml
 pickle_casino =
   xpElem "Casino" $
@@ -399,7 +542,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.
@@ -407,16 +550,15 @@ pickle_casino =
                                       xml_casino_name,
                                       xml_casino_line)
 
-instance XmlPickler OddsGameCasinoXml where
-  xpickle = pickle_casino
-
 
+-- | Pickler for an 'OddsGameHomeTeamXml'.
+--
 pickle_home_team :: PU OddsGameHomeTeamXml
 pickle_home_team =
   xpElem "HomeTeam" $
     xpWrap (from_tuple, to_tuple) $
       xp5Tuple
-        (xpElem "HomeTeamID" xpInt)
+        (xpElem "HomeTeamID" xpText)
         (xpElem "HomeRotationNumber" xpInt)
         (xpElem "HomeAbbr" xpText)
         (xpElem "HomeTeamName" xpText)
@@ -430,16 +572,15 @@ pickle_home_team =
                                         xml_home_team_name,
                                         xml_home_casinos)
 
-instance XmlPickler OddsGameHomeTeamXml where
-  xpickle = pickle_home_team
-
 
+-- | Pickler for an 'OddsGameAwayTeamXml'.
+--
 pickle_away_team :: PU OddsGameAwayTeamXml
 pickle_away_team =
   xpElem "AwayTeam" $
     xpWrap (from_tuple, to_tuple) $
       xp5Tuple
-        (xpElem "AwayTeamID" xpInt)
+        (xpElem "AwayTeamID" xpText)
         (xpElem "AwayRotationNumber" xpInt)
         (xpElem "AwayAbbr" xpText)
         (xpElem "AwayTeamName" xpText)
@@ -448,16 +589,15 @@ pickle_away_team =
     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_name,
-                                 xml_away_casinos)
-
+                                        xml_away_rotation_number,
+                                        xml_away_abbr,
+                                        xml_away_team_name,
+                                        xml_away_casinos)
 
-instance XmlPickler OddsGameAwayTeamXml where
-  xpickle = pickle_away_team
 
 
+-- | Pickler for an 'OddsGameOverUnderXml'.
+--
 pickle_over_under :: PU OddsGameOverUnderXml
 pickle_over_under =
   xpElem "Over_Under" $
@@ -467,18 +607,17 @@ pickle_over_under =
     from_newtype (OddsGameOverUnderXml cs) = cs
     to_newtype = OddsGameOverUnderXml
 
-instance XmlPickler OddsGameOverUnderXml where
-  xpickle = pickle_over_under
-
 
+-- | Pickler for an 'OddsGameXml'.
+--
 pickle_game :: PU OddsGameXml
 pickle_game =
   xpElem "Game" $
   xpWrap (from_tuple, to_tuple) $
   xp6Tuple
     (xpElem "GameID" xpInt)
-    (xpElem "Game_Date" xpText)
-    (xpElem "Game_Time" xpText)
+    (xpElem "Game_Date" xp_date)
+    (xpElem "Game_Time" xp_time)
     pickle_away_team
     pickle_home_team
     pickle_over_under
@@ -492,10 +631,9 @@ pickle_game =
                                 xml_game_home_team,
                                 xml_game_over_under)
 
-instance XmlPickler OddsGameXml where
-  xpickle = pickle_game
-
 
+-- | Pickler for the top-level 'Message'.
+--
 pickle_message :: PU Message
 pickle_message =
   xpElem "message" $
@@ -520,13 +658,12 @@ pickle_message =
                   xml_time_stamp m)
 
 
-instance XmlPickler Message where
-  xpickle = pickle_message
-
-
-
+--
+-- Tasty Tests
+--
 
--- * Tasty Tests
+-- | A list of all tests for this module.
+--
 odds_tests :: TestTree
 odds_tests =
   testGroup
@@ -535,20 +672,46 @@ odds_tests =
       test_unpickle_succeeds ]
 
 
--- | Warning, succeess of this test does not mean that unpickling
---   succeeded.
+-- | If we unpickle something and then pickle it, we should wind up
+--   with the same thing we started with. 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",
+
+    check "pickle composed with unpickle is the identity (large file)"
+          "test/xml/Odds_XML-largefile.xml" ]
+  where
+    check desc path = testCase desc $ do
+      (expected, actual) <- pickle_unpickle pickle_message path
+      actual @?= expected
 
 
+-- | Make sure we can actually unpickle these things.
+--
 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",
+
+    check "unpickling succeeds (large file)"
+          "test/xml/Odds_XML-largefile.xml" ]
+  where
+    check desc path = testCase desc $ do
+      actual <- unpickleable path pickle_message
+      let expected = True
+      actual @?= expected