]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blob - src/TSN/XML/Heartbeat.hs
Remove unused XmlPickler instances (this might need to be revisited if regular-xmlpic...
[dead/htsn-import.git] / src / TSN / XML / Heartbeat.hs
1 {-# LANGUAGE ScopedTypeVariables #-}
2
3 -- | Handle documents defined by Heartbeat.dtd.
4 --
5 module TSN.XML.Heartbeat (
6 heartbeat_tests,
7 verify )
8 where
9
10 -- System imports.
11 import Data.Tuple.Curry ( uncurryN )
12 import Test.Tasty ( TestTree, testGroup )
13 import Test.Tasty.HUnit ( (@?=), testCase )
14 import Text.XML.HXT.Core (
15 PU,
16 unpickleDoc,
17 XmlTree,
18 xpTriple,
19 xpElem,
20 xpInt,
21 xpText,
22 xpWrap )
23
24 -- Local imports.
25 import TSN.DbImport ( ImportResult(..) )
26 import Xml ( pickle_unpickle, unpickleable )
27
28
29 -- | The data structure that holds the XML representation of a
30 -- Heartbeat message.
31 data Message =
32 Message {
33 xml_file_id :: Int,
34 heading :: String,
35 time_stamp :: String }
36 deriving (Eq, Show)
37
38
39 -- | A (un)pickler that turns a Heartbeat XML file into a 'Message'
40 -- and vice-versa.
41 pickle_message :: PU Message
42 pickle_message =
43 xpElem "message" $
44 xpWrap (from_tuple, to_tuple) $
45 xpTriple (xpElem "XML_File_ID" xpInt)
46 (xpElem "heading" xpText)
47 (xpElem "time_stamp" xpText)
48 where
49 from_tuple = uncurryN Message
50 to_tuple m = (xml_file_id m,
51 heading m,
52 time_stamp m)
53
54
55 -- | Verify (and report) the received heartbeat. We return
56 -- 'ImportSkipped' because we want to indicate that we processed the
57 -- file but there was nothing to import.
58 --
59 verify :: XmlTree -> IO ImportResult
60 verify xml = do
61 let root_element = unpickleDoc pickle_message xml
62 return $ case root_element of
63 Nothing -> ImportFailed "Could not unpickle document in import_generic."
64 Just _ -> ImportSkipped "Heartbeat received. Thump."
65
66
67 -- * Tasty Tests
68 heartbeat_tests :: TestTree
69 heartbeat_tests =
70 testGroup
71 "Heartbeat tests"
72 [ test_pickle_of_unpickle_is_identity,
73 test_unpickle_succeeds ]
74
75
76 -- | Warning: succeess of this test does not mean that unpickling
77 -- succeeded.
78 --
79 test_pickle_of_unpickle_is_identity :: TestTree
80 test_pickle_of_unpickle_is_identity =
81 testCase "pickle composed with unpickle is the identity" $ do
82 let path = "test/xml/Heartbeat.xml"
83 (expected :: [Message], actual) <- pickle_unpickle pickle_message path
84 actual @?= expected
85
86
87 -- | Make sure we can unpickle the sample file.
88 --
89 test_unpickle_succeeds :: TestTree
90 test_unpickle_succeeds =
91 testCase "unpickling succeeds" $ do
92 let path = "test/xml/Heartbeat.xml"
93 actual <- unpickleable path pickle_message
94 let expected = True
95 actual @?= expected