]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blobdiff - src/TSN/XML/Heartbeat.hs
Migrate TSN.XML.Heartbeat to fixed-vector-hetero.
[dead/htsn-import.git] / src / TSN / XML / Heartbeat.hs
index 4e0ba07f8b3cc15c1ae13e4e18bcb94724cf0955..39a2bc469d8739f2ef7bb96ff0be80286dad9140 100644 (file)
@@ -1,15 +1,20 @@
+{-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE ScopedTypeVariables #-}
 
 -- | Handle documents defined by Heartbeat.dtd.
 --
 module TSN.XML.Heartbeat (
+  dtd,
   verify,
   -- * Tests
   heartbeat_tests )
 where
 
 -- System imports.
+import Data.Time.Clock ( UTCTime )
 import Data.Tuple.Curry ( uncurryN )
+import qualified Data.Vector.HFixed as H ( HVector, convert )
+import qualified GHC.Generics as GHC ( Generic )
 import Test.Tasty ( TestTree, testGroup )
 import Test.Tasty.HUnit ( (@?=), testCase )
 import Text.XML.HXT.Core (
@@ -24,18 +29,28 @@ import Text.XML.HXT.Core (
 
 -- Local imports.
 import TSN.DbImport ( ImportResult(..) )
+import TSN.Picklers ( xp_time_stamp )
 import Xml ( pickle_unpickle, unpickleable )
 
 
+-- | The DTD to which this module corresponds.
+--
+dtd :: String
+dtd = "Heartbeat.dtd"
+
 -- | The data structure that holds the XML representation of a
 --   Heartbeat message.
 --
 data Message =
-  Message {
-    xml_file_id :: Int,
-    heading :: String,
-    time_stamp :: String }
-  deriving (Eq, Show)
+  Message
+    Int     -- xml_file_id
+    String  -- heading
+    UTCTime -- time_stamp
+  deriving (Eq, GHC.Generic, Show)
+
+-- | For 'H.convert'.
+--
+instance H.HVector Message
 
 
 -- | A (un)pickler that turns a Heartbeat XML file into a 'Message'
@@ -44,15 +59,12 @@ data Message =
 pickle_message :: PU Message
 pickle_message =
   xpElem "message" $
-    xpWrap (from_tuple, to_tuple) $
+    xpWrap (from_tuple, H.convert) $
     xpTriple (xpElem "XML_File_ID" xpInt)
              (xpElem "heading" xpText)
-             (xpElem "time_stamp" xpText)
+             (xpElem "time_stamp" xp_time_stamp)
   where
     from_tuple = uncurryN Message
-    to_tuple m = (xml_file_id m,
-                  heading m,
-                  time_stamp m)
 
 
 -- | Verify (and report) the received heartbeat. We return
@@ -63,7 +75,7 @@ verify :: XmlTree -> IO ImportResult
 verify xml = do
   let root_element = unpickleDoc pickle_message xml
   return $ case root_element of
-    Nothing -> ImportFailed "Could not unpickle document in import_generic."
+    Nothing -> ImportFailed "Could not unpickle document to be verified."
     Just _  -> ImportSkipped "Heartbeat received. Thump."
 
 --
@@ -81,7 +93,7 @@ heartbeat_tests =
 
 
 -- | If we unpickle something and then pickle it, we should wind up
---   with the same thing we started with. WARNING: succeess of this
+--   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