]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blob - src/TSN/XML/Injuries.hs
Move the XML modules into the XML subdirectory.
[dead/htsn-import.git] / src / TSN / XML / Injuries.hs
1 {-# LANGUAGE FlexibleInstances #-}
2 {-# LANGUAGE GADTs #-}
3 {-# LANGUAGE QuasiQuotes #-}
4 {-# LANGUAGE ScopedTypeVariables #-}
5 {-# LANGUAGE StandaloneDeriving #-}
6 {-# LANGUAGE TemplateHaskell #-}
7 {-# LANGUAGE TypeFamilies #-}
8
9 -- | Parse TSN XML for the DTD "injuriesxml.dtd". Each document
10 -- contains a root element \<message\> that in turn contains zero or
11 -- more \<listing\>s.
12 --
13 -- The listings will be mapped to a database table called "injuries"
14 -- automatically. The root message is not retained.
15 --
16 module TSN.XML.Injuries (
17 Listing,
18 Message( listings ),
19 injuries_tests )
20 where
21
22 import Data.Tuple.Curry ( uncurryN )
23 import Database.Groundhog()
24 import Database.Groundhog.TH (
25 defaultCodegenConfig,
26 groundhog,
27 mkPersist )
28 import Test.Tasty ( TestTree, testGroup )
29 import Test.Tasty.HUnit ( (@?=), testCase )
30 import Text.XML.HXT.Core (
31 PU,
32 XmlPickler(..),
33 xp4Tuple,
34 xp6Tuple,
35 xpElem,
36 xpList,
37 xpPrim,
38 xpText,
39 xpWrap )
40
41
42 import TSN.DbImport ( DbImport(..), import_generic )
43 import Xml ( pickle_unpickle )
44
45
46 data Listing =
47 Listing {
48 team :: String,
49 teamno :: Int,
50 injuries :: String,
51 updated :: Bool }
52 deriving (Eq, Show)
53
54 data Message =
55 Message {
56 xml_file_id :: Int,
57 heading :: String,
58 category :: String,
59 sport :: String,
60 listings :: [Listing],
61 time_stamp :: String }
62 deriving (Eq, Show)
63
64
65 mkPersist defaultCodegenConfig [groundhog|
66 - entity: Listing
67 dbName: injuries
68 |]
69
70
71 pickle_listing :: PU Listing
72 pickle_listing =
73 xpElem "listing" $
74 xpWrap (from_tuple, to_tuple) $
75 xp4Tuple (xpElem "team" xpText)
76 (xpElem "teamno" xpPrim)
77 (xpElem "injuries" xpText)
78 (xpElem "updated" xpPrim)
79 where
80 from_tuple = uncurryN Listing
81 to_tuple l = (team l, teamno l, injuries l, updated l)
82
83 instance XmlPickler Listing where
84 xpickle = pickle_listing
85
86
87 pickle_message :: PU Message
88 pickle_message =
89 xpElem "message" $
90 xpWrap (from_tuple, to_tuple) $
91 xp6Tuple (xpElem "XML_File_ID" xpPrim)
92 (xpElem "heading" xpText)
93 (xpElem "category" xpText)
94 (xpElem "sport" xpText)
95 (xpList pickle_listing)
96 (xpElem "time_stamp" xpText)
97 where
98 from_tuple = uncurryN Message
99 to_tuple m = (xml_file_id m,
100 heading m,
101 category m,
102 sport m,
103 listings m,
104 time_stamp m)
105
106 instance XmlPickler Message where
107 xpickle = pickle_message
108
109
110
111 instance DbImport Listing where
112 dbimport = import_generic listings
113
114 -- * Tasty Tests
115 injuries_tests :: TestTree
116 injuries_tests =
117 testGroup
118 "Injuries tests"
119 [ test_pickle_of_unpickle_is_identity ]
120
121
122 test_pickle_of_unpickle_is_identity :: TestTree
123 test_pickle_of_unpickle_is_identity =
124 testCase "pickle composed with unpickle is the identity" $ do
125 let path = "test/xml/injuriesxml.xml"
126 (expected :: [Message], actual) <- pickle_unpickle "message" path
127 actual @?= expected