]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blobdiff - src/TSN/XML/InjuriesDetail.hs
Remove unused XmlPickler instances (this might need to be revisited if regular-xmlpic...
[dead/htsn-import.git] / src / TSN / XML / InjuriesDetail.hs
index e26cd1ce042f742b2de3f24c4de721688b95aa5f..856e800c8998d52bef68b3eaefa15887e417405a 100644 (file)
@@ -1,7 +1,6 @@
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE QuasiQuotes #-}
-{-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE StandaloneDeriving #-}
 {-# LANGUAGE TemplateHaskell #-}
 {-# LANGUAGE TypeFamilies #-}
@@ -18,8 +17,8 @@
 --   are not retained.
 --
 module TSN.XML.InjuriesDetail (
-  Message,
-  injuries_detail_tests )
+  injuries_detail_tests,
+  pickle_message )
 where
 
 import Data.Time ( UTCTime )
@@ -34,7 +33,6 @@ import Test.Tasty ( TestTree, testGroup )
 import Test.Tasty.HUnit ( (@?=), testCase )
 import Text.XML.HXT.Core (
   PU,
-  XmlPickler(..),
   xpTriple,
   xp6Tuple,
   xp10Tuple,
@@ -100,7 +98,7 @@ instance DbImport Message where
 
 mkPersist defaultCodegenConfig [groundhog|
 - entity: PlayerListing
-  dbName: injuries_detail
+  dbName: injuries_detail_player_listings
 |]
 
 
@@ -131,8 +129,6 @@ pickle_player_listing =
                    injured pl,
                    injury_type pl)
 
-instance XmlPickler PlayerListing where
-  xpickle = pickle_player_listing
 
 pickle_listing :: PU Listing
 pickle_listing =
@@ -145,9 +141,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 =
@@ -168,9 +161,6 @@ pickle_message =
                   listings m,
                   time_stamp m)
 
-instance XmlPickler Message where
-  xpickle = pickle_message
-
 
 -- * Tasty Tests
 injuries_detail_tests :: TestTree
@@ -187,7 +177,7 @@ 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
+    (expected, actual) <- pickle_unpickle pickle_message path
     actual @?= expected