]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blobdiff - src/TSN/XML/InjuriesDetail.hs
Fix pickle/unpickle of non-interger team_ids and add a test case for it.
[dead/htsn-import.git] / src / TSN / XML / InjuriesDetail.hs
index a7a7da30904e79a84775fc1d9559f180cc531415..c06768ed554c2f9aa399afd948f23838f79ace62 100644 (file)
@@ -1,7 +1,6 @@
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE QuasiQuotes #-}
-{-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE StandaloneDeriving #-}
 {-# LANGUAGE TemplateHaskell #-}
 {-# LANGUAGE TypeFamilies #-}
 --   are not retained.
 --
 module TSN.XML.InjuriesDetail (
-  Message,
-  injuries_detail_tests )
+  injuries_detail_tests,
+  pickle_message )
 where
 
 import Data.Time ( UTCTime )
 import Data.Tuple.Curry ( uncurryN )
 import Database.Groundhog (
-  defaultMigrationLogger,
-  migrate,
-  runMigration )
+  migrate )
 import Database.Groundhog.TH (
   defaultCodegenConfig,
   groundhog,
@@ -36,7 +33,6 @@ import Test.Tasty ( TestTree, testGroup )
 import Test.Tasty.HUnit ( (@?=), testCase )
 import Text.XML.HXT.Core (
   PU,
-  XmlPickler(..),
   xpTriple,
   xp6Tuple,
   xp10Tuple,
@@ -49,14 +45,15 @@ import Text.XML.HXT.Core (
   xpWrap )
 
 import TSN.Picklers( xp_date, xp_team_id )
-import TSN.DbImport ( DbImport(..), ImportResult(..) )
+import TSN.DbImport ( DbImport(..), ImportResult(..), run_dbmigrate )
 import TSN.XmlImport ( XmlImport(..) )
 import Xml ( FromXml(..), pickle_unpickle, unpickleable )
 
 
 data PlayerListing =
   PlayerListing {
-    team_id   :: Int,
+    team_id   :: String, -- ^ TeamIDs are (apparently) three characters long
+                         --   and not necessarily numeric.
     player_id :: Int,
     date      :: UTCTime,
     pos       :: String,
@@ -77,7 +74,9 @@ instance XmlImport PlayerListing
 
 data Listing =
   Listing {
-    listing_team_id :: Int -- ^ Avoid conflict with PlayerListing's team_id
+    listing_team_id :: String -- ^ Avoid conflict with PlayerListing's team_id.
+                              --   TeamIDs are (apparently) three characters
+                              --   long and not necessarily numeric.
     , full_name :: String, -- ^ Team full name
     player_listings :: [PlayerListing] }
   deriving (Eq, Show)
@@ -98,12 +97,16 @@ instance DbImport Message where
     mapM_ insert_xml (concatMap player_listings $ listings msg)
     return ImportSucceeded
 
-  dbmigrate _ =
-    runMigration defaultMigrationLogger $ migrate (undefined :: PlayerListing)
+  dbmigrate _ = run_dbmigrate $ migrate (undefined :: PlayerListing)
 
 mkPersist defaultCodegenConfig [groundhog|
 - entity: PlayerListing
-  dbName: injuries_detail
+  dbName: injuries_detail_player_listings
+  constructors:
+    - name: PlayerListing
+      fields:
+        - name: team_id
+          type: varchar(3)
 |]
 
 
@@ -134,8 +137,6 @@ pickle_player_listing =
                    injured pl,
                    injury_type pl)
 
-instance XmlPickler PlayerListing where
-  xpickle = pickle_player_listing
 
 pickle_listing :: PU Listing
 pickle_listing =
@@ -148,9 +149,6 @@ pickle_listing =
     from_tuple = uncurryN Listing
     to_tuple l = (listing_team_id l, full_name l, player_listings l)
 
-instance XmlPickler Listing where
-  xpickle = pickle_listing
-
 
 pickle_message :: PU Message
 pickle_message =
@@ -171,9 +169,6 @@ pickle_message =
                   listings m,
                   time_stamp m)
 
-instance XmlPickler Message where
-  xpickle = pickle_message
-
 
 -- * Tasty Tests
 injuries_detail_tests :: TestTree
@@ -187,17 +182,27 @@ injuries_detail_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/Injuries_Detail_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/Injuries_Detail_XML.xml",
+
+    check "pickle composed with unpickle is the identity (non-int team_id)"
+          "test/xml/Injuries_Detail_XML-noninteger-team-id.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/Injuries_Detail_XML.xml"
-  actual <- unpickleable path pickle_message
-  let expected = True
-  actual @?= expected
+test_unpickle_succeeds = testGroup "unpickle tests"
+  [ check "unpickling succeeds"
+          "test/xml/Injuries_Detail_XML.xml",
+
+    check "unpickling succeeds (non-int team_id)"
+          "test/xml/Injuries_Detail_XML-noninteger-team-id.xml" ]
+  where
+    check desc path = testCase desc $ do
+      actual <- unpickleable path pickle_message
+      let expected = True
+      actual @?= expected