]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blobdiff - src/TSN/XML/Injuries.hs
Fix typos and use xpAttrImplies where appropriate (one case).
[dead/htsn-import.git] / src / TSN / XML / Injuries.hs
index 92bf4e27757dca8c1de4320a920a982be609d1df..94baa19758ad1cbf961c8a2f0a690f3763ba1538 100644 (file)
@@ -1,7 +1,7 @@
+{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE QuasiQuotes #-}
-{-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE StandaloneDeriving #-}
 {-# LANGUAGE TemplateHaskell #-}
 {-# LANGUAGE TypeFamilies #-}
 --   contains a root element \<message\> that in turn contains zero or
 --   more \<listing\>s.
 --
---   The listings will be mapped to a database table called "injuries"
---   automatically. The root message is not retained.
+--   The listings will be mapped to a database table called
+--   \"injuries_listings\" automatically. The root message is not
+--   retained.
 --
 module TSN.XML.Injuries (
-  Listing,
-  Message( listings ),
-  injuries_tests )
+  pickle_message,
+  -- * Tests
+  injuries_tests,
+  -- * WARNING: these are private but exported to silence warnings
+  ListingConstructor(..) )
 where
 
-import Data.Tuple.Curry ( uncurryN )
-import Database.Groundhog()
+-- System imports.
+import Data.Data ( Data )
+import Data.Typeable ( Typeable )
+import Database.Groundhog (
+  migrate )
 import Database.Groundhog.TH (
   defaultCodegenConfig,
   groundhog,
   mkPersist )
+import Data.Tuple.Curry ( uncurryN )
 import Test.Tasty ( TestTree, testGroup )
 import Test.Tasty.HUnit ( (@?=), testCase )
 import Text.XML.HXT.Core (
   PU,
-  XmlPickler(..),
   xp4Tuple,
   xp6Tuple,
+  xpAttrImplied,
   xpElem,
+  xpInt,
   xpList,
+  xpOption,
+  xpPair,
   xpPrim,
   xpText,
   xpWrap )
 
+-- Local imports.
+import TSN.DbImport ( DbImport(..), ImportResult(..), run_dbmigrate )
+import TSN.XmlImport ( XmlImport(..) )
+import Xml ( FromXml(..), pickle_unpickle, unpickleable )
 
-import TSN.DbImport ( DbImport(..), import_generic )
-import Xml ( pickle_unpickle )
+-- | XML/Database representation of a team as they appear in the
+--   injuries documents.
+--
+data InjuriesTeam =
+  InjuriesTeam {
+    team_name :: String,
+    team_league :: Maybe String }
+  deriving (Data, Eq, Show, Typeable)
 
 
+-- | XML/Database representation of the injury listings.
+--
 data Listing =
   Listing {
-    team :: String,
-    teamno :: Int,
+    team :: InjuriesTeam,
+    teamno :: Maybe Int,
     injuries :: String,
-    updated :: Bool }
+    updated :: Maybe Bool }
   deriving (Eq, Show)
 
+
+instance FromXml Listing where
+  -- | The DB analogue of a 'Listing' is... itself!
+  type Db Listing = Listing
+
+  -- | To convert between a 'Listing' and a 'Listing', we do nothing.
+  from_xml = id
+
+-- | This lets us call 'insert_xml' on a 'Listing' without having to
+--   explicitly convert it to its database analogue first.
+--
+instance XmlImport Listing
+
+
+-- | XML representation of an injuriesxml \<message\>. This is only
+--   used for (un)pickling; 'Message's are not saved to the database.
+--
 data Message =
   Message {
     xml_file_id :: Int,
@@ -58,37 +97,68 @@ data Message =
     category :: String,
     sport :: String,
     listings :: [Listing],
-    time_stamp :: String }
+    time_stamp :: String -- ^ Slightly lax, but we don't save it, so who cares.
+  }
   deriving (Eq, Show)
 
+instance DbImport Message where
+  -- | We import a 'Message' by inserting all of its 'listings'.
+  --
+  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:
+        - name: team
+          embeddedType:
+            - {name: team_name, dbName: team_name}
+            - {name: team_league, dbName: team_league}
+- embedded: InjuriesTeam
+  fields:
+    - name: team_name
+    - name: team_league
 |]
 
 
+-- | A pickler for 'InjuriesTeam's that can convert them to/from XML.
+--
+pickle_injuries_team :: PU InjuriesTeam
+pickle_injuries_team =
+  xpElem "team" $
+    xpWrap (from_tuple, to_tuple) $
+    xpPair xpText (xpAttrImplied "league" xpText)
+  where
+    from_tuple = uncurryN InjuriesTeam
+    to_tuple m = (team_name m, team_league m)
+
+
+-- | A pickler for 'Listings's that can convert them to/from XML.
+--
 pickle_listing :: PU Listing
 pickle_listing =
   xpElem "listing" $
     xpWrap (from_tuple, to_tuple) $
-    xp4Tuple (xpElem "team" xpText)
-             (xpElem "teamno" xpPrim)
+    xp4Tuple pickle_injuries_team
+             (xpOption $ xpElem "teamno" xpInt)
              (xpElem "injuries" xpText)
-             (xpElem "updated" xpPrim)
+             (xpOption $ xpElem "updated" xpPrim)
   where
     from_tuple = uncurryN Listing
     to_tuple l = (team l, teamno l, injuries l, updated l)
 
-instance XmlPickler Listing where
-  xpickle = pickle_listing
-
 
+-- | A pickler for 'Message's that can convert them to/from XML.
+--
 pickle_message :: PU Message
 pickle_message =
   xpElem "message" $
     xpWrap (from_tuple, to_tuple) $
-    xp6Tuple (xpElem "XML_File_ID" xpPrim)
+    xp6Tuple (xpElem "XML_File_ID" xpInt)
              (xpElem "heading" xpText)
              (xpElem "category" xpText)
              (xpElem "sport" xpText)
@@ -103,25 +173,39 @@ pickle_message =
                   listings m,
                   time_stamp m)
 
-instance XmlPickler Message where
-  xpickle = pickle_message
-
-
 
-instance DbImport Listing where
-  dbimport = import_generic listings
+--
+-- Tasty Tests
+--
 
--- * Tasty Tests
+-- | A list of all tests for this module.
+--
 injuries_tests :: TestTree
 injuries_tests =
   testGroup
     "Injuries tests"
-    [ test_pickle_of_unpickle_is_identity ]
+    [ test_pickle_of_unpickle_is_identity,
+      test_unpickle_succeeds ]
 
 
+-- | If we unpickle something and then pickle it, we should wind up
+--   with the same thing we started with. WARNING: success 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/injuriesxml.xml"
-    (expected :: [Message], actual) <- pickle_unpickle "message" path
+    (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/injuriesxml.xml"
+  actual <- unpickleable path pickle_message
+  let expected = True
+  actual @?= expected