]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blob - src/TSN/XML/News.hs
Use 'def' in a few places where default values are required.
[dead/htsn-import.git] / src / TSN / XML / News.hs
1 {-# LANGUAGE BangPatterns #-}
2 {-# LANGUAGE DeriveDataTypeable #-}
3 {-# LANGUAGE FlexibleInstances #-}
4 {-# LANGUAGE GADTs #-}
5 {-# LANGUAGE QuasiQuotes #-}
6 {-# LANGUAGE RecordWildCards #-}
7 {-# LANGUAGE ScopedTypeVariables #-}
8 {-# LANGUAGE StandaloneDeriving #-}
9 {-# LANGUAGE TemplateHaskell #-}
10 {-# LANGUAGE TypeFamilies #-}
11
12 -- | Parse TSN XML for the DTD "newsxml.dtd". Each document contains a
13 -- root element \<message\> that contains an entire news item.
14 --
15 module TSN.XML.News (
16 Message,
17 news_tests )
18 where
19
20 import Data.Data ( Data, constrFields, dataTypeConstrs, dataTypeOf )
21 import Data.List.Utils ( join, split )
22 import Data.Tuple.Curry ( uncurryN )
23 import Data.Typeable ( Typeable )
24 import Database.Groundhog (
25 defaultMigrationLogger,
26 insert,
27 migrate,
28 runMigration )
29 import Database.Groundhog.Core ( DefaultKey )
30 import Database.Groundhog.TH (
31 groundhog,
32 mkPersist )
33 import System.Console.CmdArgs.Default ( Default(..) )
34 import Test.Tasty ( TestTree, testGroup )
35 import Test.Tasty.HUnit ( (@?=), testCase )
36 import Text.XML.HXT.Core (
37 PU,
38 XmlPickler(..),
39 unpickleDoc,
40 xp12Tuple,
41 xpAttr,
42 xpElem,
43 xpInt,
44 xpList,
45 xpOption,
46 xpPair,
47 xpText,
48 xpTriple,
49 xpWrap )
50
51 import TSN.Codegen (
52 tsn_codegen_config,
53 tsn_db_field_namer ) -- Used in a test
54 import TSN.DbImport ( DbImport(..), ImportResult(..) )
55 import Xml ( ToFromXml(..), pickle_unpickle, unpickleable )
56
57
58
59 -- | The database type for teams as they show up in the news. We need
60 -- this separate from its XML representation because of the
61 -- DefaultKey pointing to a message. We don't know how to create one
62 -- of those unless we've just inserted a message into the database,
63 -- so it screws up pickling.
64 data NewsTeam =
65 NewsTeam {
66 nt_news_id :: DefaultKey Message, -- ^ foreign key.
67 db_team_name :: String }
68 deriving instance Eq NewsTeam -- Standalone instances necessary for
69 deriving instance Show NewsTeam -- Groundhog types with DefaultKeys
70
71 -- | The XML type for teams as they show up in the news. See
72 -- 'NewsTeam' for why there are two types.
73 data NewsTeamXml =
74 NewsTeamXml {
75 xml_team_name :: String }
76 deriving (Eq, Show)
77
78 -- | Specify how to convert between the two representations NewsTeam
79 -- (database) and NewsTeamXml (XML).
80 instance ToFromXml NewsTeam where
81 type Xml NewsTeam = NewsTeamXml
82 type Container NewsTeam = Message
83 -- Use a record wildcard here so GHC doesn't complain that we never
84 -- used our named fields.
85 to_xml (NewsTeam {..}) = NewsTeamXml db_team_name
86 -- We can't create a DefaultKey Message...
87 from_xml = error "Called from_xml on a NewsTeam."
88 -- unless we're handed one.
89 from_xml_fk key = (NewsTeam key) . xml_team_name
90
91
92 -- | The database type for locations as they show up in the news. We
93 -- need this separate from its XML representation because of the
94 -- DefaultKey pointing to a message. We don't know how to create one
95 -- of those unless we've just inserted a message into the database,
96 -- so it screws up pickling.
97 data NewsLocation =
98 NewsLocation {
99 loc_news_id :: DefaultKey Message, -- ^ foreign key.
100 db_city ::String,
101 db_state :: String,
102 db_country :: String }
103 deriving instance Eq NewsLocation -- Standalone instances necessary for
104 deriving instance Show NewsLocation -- Groundhog types with DefaultKeys
105
106 -- | The XML type for locations as they show up in the news. See
107 -- 'NewsLocation' for why there are two types.
108 data NewsLocationXml =
109 NewsLocationXml {
110 xml_city :: String,
111 xml_state :: String,
112 xml_country :: String }
113 deriving (Eq, Show)
114
115
116 -- | Specify how to convert between the two representations
117 -- NewsLocation (database) and NewsLocationXml (XML).
118 instance ToFromXml NewsLocation where
119 type Xml NewsLocation = NewsLocationXml
120 type Container NewsLocation = Message
121 -- Use a record wildcard here so GHC doesn't complain that we never
122 -- used our named fields.
123 to_xml (NewsLocation {..}) = NewsLocationXml db_city db_state db_country
124 -- We can't create a DefaultKey Message...
125 from_xml = error "Called from_xml on a NewsLocation."
126 -- unless we're given one.
127 from_xml_fk key (NewsLocationXml x y z) = NewsLocation key x y z
128
129
130 -- | The msg_id child of <message> contains an event_id attribute; we
131 -- embed it into the 'Message' type. We (pointlessly) use the "db_"
132 -- prefix here so that the two names collide on "id" when Groundhog
133 -- is creating its fields using our field namer.
134 data MsgId =
135 MsgId {
136 db_msg_id :: Int,
137 db_event_id :: Maybe Int }
138 deriving (Data, Eq, Show, Typeable)
139
140
141 data MessageXml =
142 MessageXml {
143 xml_xml_file_id :: Int,
144 xml_heading :: String,
145 xml_mid :: MsgId,
146 xml_category :: String,
147 xml_sport :: String,
148 xml_url :: String,
149 xml_teams :: [NewsTeamXml],
150 xml_locations :: [NewsLocationXml],
151 xml_sms :: String,
152 xml_text :: String,
153 xml_continue :: String,
154 xml_time_stamp :: String }
155 deriving (Eq, Show)
156
157 data Message =
158 Message {
159 db_mid :: MsgId,
160 db_sport :: String,
161 db_url :: String,
162 db_sms :: String,
163 db_text :: String,
164 db_continue :: String }
165 deriving (Data, Eq, Show, Typeable)
166
167 instance ToFromXml Message where
168 type Xml Message = MessageXml
169 type Container Message = ()
170
171 -- Use a record wildcard here so GHC doesn't complain that we never
172 -- used our named fields.
173 to_xml (Message {..}) =
174 MessageXml
175 def
176 def
177 db_mid
178 def
179 db_sport
180 db_url
181 def
182 def
183 db_sms
184 db_text
185 db_continue
186 def
187
188 -- We don't need the key argument (from_xml_fk) since the XML type
189 -- contains more information in this case.
190 from_xml (MessageXml _ _ c _ e f _ _ i j k _) =
191 Message c e f i j k
192
193
194 mkPersist tsn_codegen_config [groundhog|
195 - entity: NewsTeam
196 dbName: news_teams
197
198 - entity: NewsLocation
199 dbName: news_locations
200
201 - entity: Message
202 dbName: news
203 constructors:
204 - name: Message
205 fields:
206 - name: db_mid
207 embeddedType:
208 - {name: msg_id, dbName: msg_id}
209 - {name: event_id, dbName: event_id}
210 - embedded: MsgId
211 fields:
212 - name: db_msg_id
213 dbName: msg_id
214 - name: db_event_id
215 dbName: event_id
216 |]
217
218 pickle_news_team :: PU NewsTeamXml
219 pickle_news_team =
220 xpElem "team" $
221 xpWrap (from_string, to_string) xpText
222 where
223 to_string :: NewsTeamXml -> String
224 to_string = xml_team_name
225
226 from_string :: String -> NewsTeamXml
227 from_string = NewsTeamXml
228
229 instance XmlPickler NewsTeamXml where
230 xpickle = pickle_news_team
231
232 pickle_msg_id :: PU MsgId
233 pickle_msg_id =
234 xpElem "msg_id" $
235 xpWrap (from_tuple, to_tuple) $
236 xpPair xpInt (xpAttr "EventId" (xpOption xpInt))
237 where
238 from_tuple = uncurryN MsgId
239 to_tuple m = (db_msg_id m, db_event_id m)
240
241 instance XmlPickler MsgId where
242 xpickle = pickle_msg_id
243
244 pickle_location :: PU NewsLocationXml
245 pickle_location =
246 xpElem "location" $
247 xpWrap (from_tuple, to_tuple) $
248 xpTriple (xpElem "city" xpText)
249 (xpElem "state" xpText)
250 (xpElem "country" xpText)
251 where
252 from_tuple =
253 uncurryN NewsLocationXml
254 to_tuple l = (xml_city l, xml_state l, xml_country l)
255
256 instance XmlPickler NewsLocationXml where
257 xpickle = pickle_location
258
259
260 pickle_message :: PU MessageXml
261 pickle_message =
262 xpElem "message" $
263 xpWrap (from_tuple, to_tuple) $
264 xp12Tuple (xpElem "XML_File_ID" xpInt)
265 (xpElem "heading" xpText)
266 pickle_msg_id
267 (xpElem "category" xpText)
268 (xpElem "sport" xpText)
269 (xpElem "url" xpText)
270 (xpList $ pickle_news_team)
271 (xpList $ pickle_location)
272 (xpElem "SMS" xpText)
273 (xpElem "text" xpText)
274 pickle_continue
275 (xpElem "time_stamp" xpText)
276 where
277 from_tuple = uncurryN MessageXml
278 to_tuple m = (xml_xml_file_id m,
279 xml_heading m,
280 xml_mid m,
281 xml_category m,
282 xml_sport m,
283 xml_url m,
284 xml_teams m,
285 xml_locations m,
286 xml_sms m,
287 xml_text m,
288 xml_continue m,
289 xml_time_stamp m)
290
291 pickle_continue :: PU String
292 pickle_continue =
293 xpWrap (to_string, from_string) $
294 xpElem "continue" $
295 (xpList $ xpElem "P" xpText)
296 where
297 from_string :: String -> [String]
298 from_string = split "\n"
299
300 to_string :: [String] -> String
301 to_string = join "\n"
302
303 instance XmlPickler MessageXml where
304 xpickle = pickle_message
305
306
307
308 instance DbImport Message where
309 dbimport _ xml = do
310 runMigration defaultMigrationLogger $ do
311 migrate (undefined :: Message)
312 migrate (undefined :: NewsTeam)
313 migrate (undefined :: NewsLocation)
314 let root_element = unpickleDoc xpickle xml :: Maybe MessageXml
315 case root_element of
316 Nothing -> do
317 let errmsg = "Could not unpickle News message in dbimport."
318 return $ ImportFailed errmsg
319 Just message -> do
320 news_id <- insert (from_xml message :: Message)
321 let nts :: [NewsTeam] = map (from_xml_fk news_id)
322 (xml_teams message)
323 let nlocs :: [NewsLocation] = map (from_xml_fk news_id)
324 (xml_locations message)
325 nt_ids <- mapM insert nts
326 loc_ids <- mapM insert nlocs
327
328 return $ ImportSucceeded (1 + (length nt_ids) + (length loc_ids))
329
330
331 -- * Tasty Tests
332 news_tests :: TestTree
333 news_tests =
334 testGroup
335 "News tests"
336 [ test_news_fields_have_correct_names,
337 test_pickle_of_unpickle_is_identity,
338 test_unpickle_succeeds ]
339
340
341 test_news_fields_have_correct_names :: TestTree
342 test_news_fields_have_correct_names =
343 testCase "news fields get correct database names" $ do
344 mapM_ check (zip actual expected)
345 where
346 -- This is cool, it uses the (derived) Data instance of
347 -- News.Message to get its constructor names.
348 field_names :: [String]
349 field_names =
350 constrFields . head $ dataTypeConstrs $ dataTypeOf (undefined :: Message)
351
352 expected :: [String]
353 expected =
354 map (\x -> tsn_db_field_namer "herp" "derp" 8675309 x 90210) field_names
355
356 actual :: [String]
357 actual = ["mid", "sport", "url", "sms", "text", "continue"]
358
359 check (x,y) = (x @?= y)
360
361
362 -- | Warning, succeess of this test does not mean that unpickling
363 -- succeeded.
364 test_pickle_of_unpickle_is_identity :: TestTree
365 test_pickle_of_unpickle_is_identity =
366 testCase "pickle composed with unpickle is the identity" $ do
367 let path = "test/xml/newsxml.xml"
368 (expected :: [MessageXml], actual) <- pickle_unpickle "message" path
369 actual @?= expected
370
371
372 test_unpickle_succeeds :: TestTree
373 test_unpickle_succeeds =
374 testCase "unpickling succeeds" $ do
375 let path = "test/xml/newsxml.xml"
376 actual <- unpickleable path pickle_message
377 let expected = True
378 actual @?= expected