]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blob - src/TSN/XML/Injuries.hs
Fix typos and use xpAttrImplies where appropriate (one case).
[dead/htsn-import.git] / src / TSN / XML / Injuries.hs
1 {-# LANGUAGE DeriveDataTypeable #-}
2 {-# LANGUAGE FlexibleInstances #-}
3 {-# LANGUAGE GADTs #-}
4 {-# LANGUAGE QuasiQuotes #-}
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
14 -- \"injuries_listings\" automatically. The root message is not
15 -- retained.
16 --
17 module TSN.XML.Injuries (
18 pickle_message,
19 -- * Tests
20 injuries_tests,
21 -- * WARNING: these are private but exported to silence warnings
22 ListingConstructor(..) )
23 where
24
25 -- System imports.
26 import Data.Data ( Data )
27 import Data.Typeable ( Typeable )
28 import Database.Groundhog (
29 migrate )
30 import Database.Groundhog.TH (
31 defaultCodegenConfig,
32 groundhog,
33 mkPersist )
34 import Data.Tuple.Curry ( uncurryN )
35 import Test.Tasty ( TestTree, testGroup )
36 import Test.Tasty.HUnit ( (@?=), testCase )
37 import Text.XML.HXT.Core (
38 PU,
39 xp4Tuple,
40 xp6Tuple,
41 xpAttrImplied,
42 xpElem,
43 xpInt,
44 xpList,
45 xpOption,
46 xpPair,
47 xpPrim,
48 xpText,
49 xpWrap )
50
51 -- Local imports.
52 import TSN.DbImport ( DbImport(..), ImportResult(..), run_dbmigrate )
53 import TSN.XmlImport ( XmlImport(..) )
54 import Xml ( FromXml(..), pickle_unpickle, unpickleable )
55
56 -- | XML/Database representation of a team as they appear in the
57 -- injuries documents.
58 --
59 data InjuriesTeam =
60 InjuriesTeam {
61 team_name :: String,
62 team_league :: Maybe String }
63 deriving (Data, Eq, Show, Typeable)
64
65
66 -- | XML/Database representation of the injury listings.
67 --
68 data Listing =
69 Listing {
70 team :: InjuriesTeam,
71 teamno :: Maybe Int,
72 injuries :: String,
73 updated :: Maybe Bool }
74 deriving (Eq, Show)
75
76
77 instance FromXml Listing where
78 -- | The DB analogue of a 'Listing' is... itself!
79 type Db Listing = Listing
80
81 -- | To convert between a 'Listing' and a 'Listing', we do nothing.
82 from_xml = id
83
84 -- | This lets us call 'insert_xml' on a 'Listing' without having to
85 -- explicitly convert it to its database analogue first.
86 --
87 instance XmlImport Listing
88
89
90 -- | XML representation of an injuriesxml \<message\>. This is only
91 -- used for (un)pickling; 'Message's are not saved to the database.
92 --
93 data Message =
94 Message {
95 xml_file_id :: Int,
96 heading :: String,
97 category :: String,
98 sport :: String,
99 listings :: [Listing],
100 time_stamp :: String -- ^ Slightly lax, but we don't save it, so who cares.
101 }
102 deriving (Eq, Show)
103
104 instance DbImport Message where
105 -- | We import a 'Message' by inserting all of its 'listings'.
106 --
107 dbimport msg = mapM_ insert_xml (listings msg) >> return ImportSucceeded
108
109 dbmigrate _ = run_dbmigrate $ migrate (undefined :: Listing)
110
111 mkPersist defaultCodegenConfig [groundhog|
112 - entity: Listing
113 dbName: injuries_listings
114 constructors:
115 - name: Listing
116 fields:
117 - name: team
118 embeddedType:
119 - {name: team_name, dbName: team_name}
120 - {name: team_league, dbName: team_league}
121 - embedded: InjuriesTeam
122 fields:
123 - name: team_name
124 - name: team_league
125 |]
126
127
128 -- | A pickler for 'InjuriesTeam's that can convert them to/from XML.
129 --
130 pickle_injuries_team :: PU InjuriesTeam
131 pickle_injuries_team =
132 xpElem "team" $
133 xpWrap (from_tuple, to_tuple) $
134 xpPair xpText (xpAttrImplied "league" xpText)
135 where
136 from_tuple = uncurryN InjuriesTeam
137 to_tuple m = (team_name m, team_league m)
138
139
140 -- | A pickler for 'Listings's that can convert them to/from XML.
141 --
142 pickle_listing :: PU Listing
143 pickle_listing =
144 xpElem "listing" $
145 xpWrap (from_tuple, to_tuple) $
146 xp4Tuple pickle_injuries_team
147 (xpOption $ xpElem "teamno" xpInt)
148 (xpElem "injuries" xpText)
149 (xpOption $ xpElem "updated" xpPrim)
150 where
151 from_tuple = uncurryN Listing
152 to_tuple l = (team l, teamno l, injuries l, updated l)
153
154
155 -- | A pickler for 'Message's that can convert them to/from XML.
156 --
157 pickle_message :: PU Message
158 pickle_message =
159 xpElem "message" $
160 xpWrap (from_tuple, to_tuple) $
161 xp6Tuple (xpElem "XML_File_ID" xpInt)
162 (xpElem "heading" xpText)
163 (xpElem "category" xpText)
164 (xpElem "sport" xpText)
165 (xpList pickle_listing)
166 (xpElem "time_stamp" xpText)
167 where
168 from_tuple = uncurryN Message
169 to_tuple m = (xml_file_id m,
170 heading m,
171 category m,
172 sport m,
173 listings m,
174 time_stamp m)
175
176
177 --
178 -- Tasty Tests
179 --
180
181 -- | A list of all tests for this module.
182 --
183 injuries_tests :: TestTree
184 injuries_tests =
185 testGroup
186 "Injuries tests"
187 [ test_pickle_of_unpickle_is_identity,
188 test_unpickle_succeeds ]
189
190
191 -- | If we unpickle something and then pickle it, we should wind up
192 -- with the same thing we started with. WARNING: success of this
193 -- test does not mean that unpickling succeeded.
194 --
195 test_pickle_of_unpickle_is_identity :: TestTree
196 test_pickle_of_unpickle_is_identity =
197 testCase "pickle composed with unpickle is the identity" $ do
198 let path = "test/xml/injuriesxml.xml"
199 (expected, actual) <- pickle_unpickle pickle_message path
200 actual @?= expected
201
202
203 -- | Make sure we can actually unpickle these things.
204 --
205 test_unpickle_succeeds :: TestTree
206 test_unpickle_succeeds =
207 testCase "unpickling succeeds" $ do
208 let path = "test/xml/injuriesxml.xml"
209 actual <- unpickleable path pickle_message
210 let expected = True
211 actual @?= expected