]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blobdiff - src/TSN/XML/Injuries.hs
Fixing compiler warnings by exporting stuff that shouldn't be exported (woo).
[dead/htsn-import.git] / src / TSN / XML / Injuries.hs
index bea54d3c029deea97f395c4b444d538d9b24ead9..8002799c62e0e26f4bb7217740ac4651aaa0235f 100644 (file)
@@ -2,7 +2,6 @@
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE QuasiQuotes #-}
-{-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE StandaloneDeriving #-}
 {-# LANGUAGE TemplateHaskell #-}
 {-# LANGUAGE TypeFamilies #-}
 --   automatically. The root message is not retained.
 --
 module TSN.XML.Injuries (
-  Listing,
-  Message( listings ),
-  injuries_tests )
+  injuries_tests,
+  pickle_message,
+  -- * WARNING: these are private but exported to silence warnings
+  ListingConstructor(..) )
 where
 
 import Data.Data ( Data )
 import Data.Typeable ( Typeable )
-import Database.Groundhog()
+import Database.Groundhog (
+  migrate )
 import Database.Groundhog.TH (
   defaultCodegenConfig,
   groundhog,
@@ -32,7 +33,6 @@ import Test.Tasty ( TestTree, testGroup )
 import Test.Tasty.HUnit ( (@?=), testCase )
 import Text.XML.HXT.Core (
   PU,
-  XmlPickler(..),
   xp4Tuple,
   xp6Tuple,
   xpAttr,
@@ -46,9 +46,9 @@ import Text.XML.HXT.Core (
   xpWrap )
 
 
-import TSN.DbImport ( DbImport(..), import_generic )
-import Xml ( pickle_unpickle, unpickleable )
-
+import TSN.DbImport ( DbImport(..), ImportResult(..), run_dbmigrate )
+import TSN.XmlImport ( XmlImport(..) )
+import Xml ( FromXml(..), pickle_unpickle, unpickleable )
 
 data InjuriesTeam =
   InjuriesTeam {
@@ -64,6 +64,12 @@ data Listing =
     updated :: Maybe Bool }
   deriving (Eq, Show)
 
+instance FromXml Listing where
+  type Db Listing = Listing
+  from_xml = id
+
+instance XmlImport Listing
+
 data Message =
   Message {
     xml_file_id :: Int,
@@ -74,10 +80,14 @@ data Message =
     time_stamp :: String }
   deriving (Eq, Show)
 
+instance DbImport Message where
+  dbimport msg = mapM_ insert_xml (listings msg) >> return ImportSucceeded
+
+  dbmigrate _ = run_dbmigrate $ migrate (undefined :: Listing)
 
 mkPersist defaultCodegenConfig [groundhog|
 - entity: Listing
-  dbName: injuries
+  dbName: injuries_listings
   constructors:
     - name: Listing
       fields:
@@ -96,13 +106,11 @@ pickle_injuries_team :: PU InjuriesTeam
 pickle_injuries_team =
   xpElem "team" $
     xpWrap (from_tuple, to_tuple) $
-    xpPair xpText (xpAttr "league" (xpOption xpText))
+    xpPair xpText (xpOption $ xpAttr "league" xpText)
   where
     from_tuple = uncurryN InjuriesTeam
     to_tuple m = (team_name m, team_league m)
 
-instance XmlPickler InjuriesTeam where
-  xpickle = pickle_injuries_team
 
 pickle_listing :: PU Listing
 pickle_listing =
@@ -116,9 +124,6 @@ pickle_listing =
     from_tuple = uncurryN Listing
     to_tuple l = (team l, teamno l, injuries l, updated l)
 
-instance XmlPickler Listing where
-  xpickle = pickle_listing
-
 
 pickle_message :: PU Message
 pickle_message =
@@ -139,13 +144,7 @@ pickle_message =
                   listings m,
                   time_stamp m)
 
-instance XmlPickler Message where
-  xpickle = pickle_message
-
-
 
-instance DbImport Listing where
-  dbimport = import_generic listings
 
 -- * Tasty Tests
 injuries_tests :: TestTree
@@ -162,7 +161,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/injuriesxml.xml"
-    (expected :: [Message], actual) <- pickle_unpickle "message" path
+    (expected, actual) <- pickle_unpickle pickle_message path
     actual @?= expected