]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blob - src/TSN/XML/News.hs
Use Generics.to_tuple in TSN.XML.News.
[dead/htsn-import.git] / src / TSN / XML / News.hs
1 {-# LANGUAGE DeriveGeneric #-}
2 {-# LANGUAGE DeriveDataTypeable #-}
3 {-# LANGUAGE FlexibleInstances #-}
4 {-# LANGUAGE GADTs #-}
5 {-# LANGUAGE QuasiQuotes #-}
6 {-# LANGUAGE RecordWildCards #-}
7 {-# LANGUAGE TemplateHaskell #-}
8 {-# LANGUAGE TypeFamilies #-}
9
10 -- | Parse TSN XML for the DTD \"newsxml.dtd\". Each document contains
11 -- a root element \<message\> that contains an entire news item.
12 --
13 module TSN.XML.News (
14 dtd,
15 has_only_single_sms,
16 pickle_message,
17 -- * Tests
18 news_tests,
19 -- * WARNING: these are private but exported to silence warnings
20 News_LocationConstructor(..),
21 News_TeamConstructor(..),
22 NewsConstructor(..) )
23 where
24
25 -- System imports.
26 import Data.Data ( Data, constrFields, dataTypeConstrs, dataTypeOf )
27 import Data.Time.Clock ( UTCTime )
28 import Data.List.Utils ( join, split )
29 import Data.Tuple.Curry ( uncurryN )
30 import Data.Typeable ( Typeable )
31 import Database.Groundhog (
32 countAll,
33 deleteAll,
34 insert_,
35 migrate,
36 runMigration,
37 silentMigrationLogger )
38 import Database.Groundhog.Core ( DefaultKey )
39 import Database.Groundhog.Generic ( runDbConn )
40 import Database.Groundhog.Sqlite ( withSqliteConn )
41 import Database.Groundhog.TH (
42 groundhog,
43 mkPersist )
44 import qualified GHC.Generics as GHC ( Generic )
45 import Test.Tasty ( TestTree, testGroup )
46 import Test.Tasty.HUnit ( (@?=), testCase )
47 import Text.XML.HXT.Core (
48 PU,
49 XmlTree,
50 (/>),
51 (>>>),
52 addNav,
53 descendantAxis,
54 filterAxis,
55 followingSiblingAxis,
56 hasName,
57 remNav,
58 runLA,
59 xp13Tuple,
60 xpAttr,
61 xpElem,
62 xpInt,
63 xpList,
64 xpOption,
65 xpPair,
66 xpText,
67 xpWrap )
68
69 -- Local imports.
70 import Generics ( Generic(..), to_tuple )
71 import TSN.Codegen (
72 tsn_codegen_config,
73 tsn_db_field_namer ) -- Used in a test
74 import TSN.Database ( insert_or_select )
75 import TSN.DbImport ( DbImport(..), ImportResult(..), run_dbmigrate )
76 import TSN.Location ( Location(..), pickle_location )
77 import TSN.Picklers ( xp_time_stamp )
78 import TSN.Team ( Team(..) )
79 import TSN.XmlImport ( XmlImport(..) )
80 import Xml (
81 FromXml(..),
82 ToDb(..),
83 pickle_unpickle,
84 unpickleable,
85 unsafe_read_document,
86 unsafe_unpickle )
87
88
89 -- | The DTD to which this module corresponds. Used to invoke dbimport.
90 --
91 dtd :: String
92 dtd = "newsxml.dtd"
93
94
95 --
96 -- DB/XML Data types
97 --
98
99 -- * News/Message
100
101 -- | The msg_id child of \<message\> contains an event_id attribute; we
102 -- embed it into the 'News' type. We (pointlessly) use the \"db_\"
103 -- prefix here so that the two names don't collide on \"id\" when
104 -- Groundhog is creating its fields using our field namer.
105 --
106 data MsgId =
107 MsgId {
108 db_msg_id :: Int,
109 db_event_id :: Maybe Int }
110 deriving (Data, Eq, Show, Typeable)
111
112
113 -- | The XML representation of a news item (\<message\>).
114 --
115 data Message =
116 Message {
117 xml_xml_file_id :: Int,
118 xml_heading :: String,
119 xml_mid :: MsgId,
120 xml_category :: String,
121 xml_sport :: String,
122 xml_url :: Maybe String,
123 xml_teams :: [NewsTeamXml],
124 xml_locations :: [Location],
125 xml_sms :: Maybe String,
126 xml_editor :: Maybe String,
127 xml_text :: Maybe String, -- Text and continue seem to show up in pairs,
128 xml_continue :: Maybe String, -- either both present or both missing.
129 xml_time_stamp :: UTCTime }
130 deriving (Eq, GHC.Generic, Show)
131
132
133 -- | For 'Generics.to_tuple'.
134 --
135 instance Generic Message
136
137
138 -- | The database representation of a news item. We drop several
139 -- uninteresting fields from 'Message', and omit the list fields which
140 -- will be represented as join tables.
141 --
142 data News =
143 News {
144 db_xml_file_id :: Int,
145 db_mid :: MsgId,
146 db_sport :: String,
147 db_url :: Maybe String,
148 db_sms :: Maybe String,
149 db_editor :: Maybe String,
150 db_text :: Maybe String,
151 db_continue :: Maybe String,
152 db_time_stamp :: UTCTime }
153 deriving (Data, Eq, Show, Typeable)
154
155
156
157 instance ToDb Message where
158 -- | The database representation of 'Message' is 'News'.
159 type Db Message = News
160
161 -- | Convert the XML representation 'Message' to the database
162 -- representation 'News'.
163 --
164 instance FromXml Message where
165 -- | We use a record wildcard so GHC doesn't complain that we never
166 -- used the field names.
167 --
168 from_xml Message{..} = News { db_xml_file_id = xml_xml_file_id,
169 db_mid = xml_mid,
170 db_sport = xml_sport,
171 db_url = xml_url,
172 db_sms = xml_sms,
173 db_editor = xml_editor,
174 db_text = xml_text,
175 db_continue = xml_continue,
176 db_time_stamp = xml_time_stamp }
177
178 -- | This lets us insert the XML representation 'Message' directly.
179 --
180 instance XmlImport Message
181
182
183 -- * NewsTeamXml
184
185 -- | The XML type for teams as they show up in the news. We can't
186 -- reuse the representation from "TSN.Team" because our name doesn't
187 -- appear optional and we have no abbreviation.
188 --
189 data NewsTeamXml =
190 NewsTeamXml { xml_team_id :: String,
191 xml_team_name :: String }
192 deriving (Eq, GHC.Generic, Show)
193
194
195 -- | For 'Generics.to_tuple'.
196 --
197 instance Generic NewsTeamXml
198
199
200 instance ToDb NewsTeamXml where
201 -- | The database representation of 'NewsTeamXml' is 'Team'.
202 type Db NewsTeamXml = Team
203
204 -- | Convert the XML representation 'NewsTeamXml' to the database
205 -- representation 'Team'.
206 --
207 instance FromXml NewsTeamXml where
208 from_xml NewsTeamXml{..} =
209 Team { team_id = xml_team_id,
210 abbreviation = Nothing,
211 name = Just xml_team_name }
212
213 -- | Allow us to import 'NewsTeamXml' directly.
214 --
215 instance XmlImport NewsTeamXml
216
217
218 -- * News_Team
219
220 -- | Mapping between News records and Team records in the database. We
221 -- don't name the fields because we don't use the names explicitly;
222 -- that means we have to give them nice database names via
223 -- groundhog.
224 --
225 data News_Team = News_Team (DefaultKey News) (DefaultKey Team)
226
227
228 -- * News_Location
229
230 -- | Mapping between 'News' records and 'Location' records in the
231 -- database. We don't name the fields because we don't use the names
232 -- explicitly; that means we have to give them nice database names
233 -- via groundhog.
234 --
235 data News_Location = News_Location
236 (DefaultKey News)
237 (DefaultKey Location)
238
239
240
241
242 -- | Some newsxml documents contain two \<SMS\> elements in a row,
243 -- violating the DTD. The second one has always been empty, but it's
244 -- irrelevant: we can't parse these, and would like to detect them
245 -- in order to report the fact that the busted document is
246 -- unsupported.
247 --
248 -- This function detects whether two \<SMS\> elements appear in a
249 -- row, as siblings.
250 --
251 has_only_single_sms :: XmlTree -> Bool
252 has_only_single_sms xmltree =
253 case elements of
254 [] -> True
255 _ -> False
256 where
257 parse :: XmlTree -> [XmlTree]
258 parse = runLA $ hasName "/"
259 /> hasName "message"
260 >>> addNav
261 >>> descendantAxis
262 >>> filterAxis (hasName "SMS")
263 >>> followingSiblingAxis
264 >>> remNav
265 >>> hasName "SMS"
266
267 elements = parse xmltree
268
269
270 --
271 -- * Database code
272 --
273
274 -- | Define 'dbmigrate' and 'dbimport' for 'Message's. The import is
275 -- slightly non-generic because of our 'News_Team' and
276 -- 'News_Location' join tables.
277 --
278 instance DbImport Message where
279 dbmigrate _ =
280 run_dbmigrate $ do
281 migrate (undefined :: Location)
282 migrate (undefined :: News)
283 migrate (undefined :: Team)
284 migrate (undefined :: News_Team)
285 migrate (undefined :: News_Location)
286
287 dbimport message = do
288 -- Insert the message and acquire its primary key (unique ID)
289 news_id <- insert_xml message
290
291 -- Now insert the teams. We use insert_xml_or_select because we
292 -- know that most teams will already exist, and we want to get
293 -- back the id for the existing team when there's a collision.
294 team_ids <- mapM insert_xml_or_select (xml_teams message)
295
296 -- Now that the teams have been inserted, create
297 -- news__team records mapping beween the two.
298 let news_teams = map (News_Team news_id) team_ids
299 mapM_ insert_ news_teams
300
301 -- Do all of that over again for the Locations.
302 loc_ids <- mapM insert_or_select (xml_locations message)
303 let news_news_locations = map (News_Location news_id) loc_ids
304 mapM_ insert_ news_news_locations
305
306 return ImportSucceeded
307
308
309
310 -- These types have fields with e.g. db_ and xml_ prefixes, so we
311 -- use our own codegen to peel those off before naming the columns.
312 mkPersist tsn_codegen_config [groundhog|
313 - entity: News
314 constructors:
315 - name: News
316 uniques:
317 - name: unique_news
318 type: constraint
319 # Prevent multiple imports of the same message.
320 fields: [db_xml_file_id]
321 fields:
322 - name: db_mid
323 embeddedType:
324 - {name: msg_id, dbName: msg_id}
325 - {name: event_id, dbName: event_id}
326
327 - embedded: MsgId
328 fields:
329 - name: db_msg_id
330 dbName: msg_id
331 - name: db_event_id
332 dbName: event_id
333
334 - entity: News_Team
335 dbName: news__teams
336 constructors:
337 - name: News_Team
338 fields:
339 - name: news_Team0 # Default created by mkNormalFieldName
340 dbName: news_id
341 reference:
342 onDelete: cascade
343 - name: news_Team1 # Default created by mkNormalFieldName
344 dbName: teams_id
345 reference:
346 onDelete: cascade
347
348 - entity: News_Location
349 dbName: news__locations
350 constructors:
351 - name: News_Location
352 fields:
353 - name: news_Location0 # Default created by mkNormalFieldName
354 dbName: news_id
355 reference:
356 onDelete: cascade
357 - name: news_Location1 # Default created by mkNormalFieldName
358 dbName: locations_id
359 reference:
360 onDelete: cascade
361 |]
362
363
364 --
365 -- XML Picklers
366 --
367
368 -- | Convert a 'NewsTeamXml' to/from XML.
369 --
370 pickle_news_team :: PU NewsTeamXml
371 pickle_news_team =
372 xpElem "team" $
373 xpWrap (from_tuple, to_tuple) $
374 xpPair (xpAttr "id" xpText)
375 xpText -- team name
376 where
377 from_tuple = uncurry NewsTeamXml
378
379
380 -- | Convert a 'MsgId' to/from XML.
381 --
382 pickle_msg_id :: PU MsgId
383 pickle_msg_id =
384 xpElem "msg_id" $
385 xpWrap (from_tuple, to_tuple') $
386 xpPair xpInt (xpAttr "EventId" (xpOption xpInt))
387 where
388 from_tuple = uncurryN MsgId
389
390 -- Avoid unused field warnings.
391 to_tuple' m = (db_msg_id m, db_event_id m)
392
393
394
395 -- | Convert a 'Message' to/from XML.
396 --
397 pickle_message :: PU Message
398 pickle_message =
399 xpElem "message" $
400 xpWrap (from_tuple, to_tuple) $
401 xp13Tuple (xpElem "XML_File_ID" xpInt)
402 (xpElem "heading" xpText)
403 pickle_msg_id
404 (xpElem "category" xpText)
405 (xpElem "sport" xpText)
406 (xpElem "url" $ xpOption xpText)
407 (xpList pickle_news_team)
408 (xpList pickle_location)
409 (xpElem "SMS" $ xpOption xpText)
410 (xpOption (xpElem "Editor" xpText))
411 (xpOption (xpElem "text" xpText))
412 pickle_continue
413 (xpElem "time_stamp" xp_time_stamp)
414 where
415 from_tuple = uncurryN Message
416
417
418 -- | We combine all of the \<continue\> elements into one 'String'
419 -- while unpickling and do the reverse while pickling.
420 --
421 pickle_continue :: PU (Maybe String)
422 pickle_continue =
423 xpOption $
424 xpWrap (to_string, from_string) $
425 xpElem "continue" $
426 xpList (xpElem "P" xpText)
427 where
428 from_string :: String -> [String]
429 from_string = split "\n"
430
431 to_string :: [String] -> String
432 to_string = join "\n"
433
434
435 --
436 -- Tasty Tests
437 --
438
439 -- | A list of all tests for this module.
440 --
441 news_tests :: TestTree
442 news_tests =
443 testGroup
444 "News tests"
445 [ test_news_fields_have_correct_names,
446 test_on_delete_cascade,
447 test_pickle_of_unpickle_is_identity,
448 test_unpickle_succeeds,
449 test_sms_detected_correctly ]
450
451
452 -- | Make sure our codegen is producing the correct database names.
453 --
454 test_news_fields_have_correct_names :: TestTree
455 test_news_fields_have_correct_names =
456 testCase "news fields get correct database names" $
457 mapM_ check (zip actual expected)
458 where
459 -- This is cool, it uses the (derived) Data instance of
460 -- News.News to get its constructor names.
461 field_names :: [String]
462 field_names =
463 constrFields . head $ dataTypeConstrs $ dataTypeOf (undefined :: News)
464
465 expected :: [String]
466 expected =
467 map (\x -> tsn_db_field_namer "herp" "derp" 8675309 x 90210) field_names
468
469 actual :: [String]
470 actual = ["xml_file_id",
471 "mid",
472 "sport",
473 "url",
474 "sms",
475 "editor",
476 "text",
477 "continue"]
478
479 check (x,y) = (x @?= y)
480
481
482 -- | If we unpickle something and then pickle it, we should wind up
483 -- with the same thing we started with. WARNING: success of this
484 -- test does not mean that unpickling succeeded.
485 --
486 test_pickle_of_unpickle_is_identity :: TestTree
487 test_pickle_of_unpickle_is_identity = testGroup "pickle-unpickle tests"
488 [ check "pickle composed with unpickle is the identity"
489 "test/xml/newsxml.xml",
490
491 check "pickle composed with unpickle is the identity (with Editor)"
492 "test/xml/newsxml-with-editor.xml",
493
494 check "pickle composed with unpickle is the identity (empty SMS)"
495 "test/xml/newsxml-empty-sms.xml" ]
496 where
497 check desc path = testCase desc $ do
498 (expected, actual) <- pickle_unpickle pickle_message path
499 actual @?= expected
500
501
502 -- | Make sure we can actually unpickle these things.
503 --
504 test_unpickle_succeeds :: TestTree
505 test_unpickle_succeeds = testGroup "unpickle tests"
506 [ check "unpickling succeeds"
507 "test/xml/newsxml.xml",
508
509 check "unpickling succeeds (with Editor)"
510 "test/xml/newsxml-with-editor.xml",
511
512 check "unpickling succeeds (empty SMS)"
513 "test/xml/newsxml-empty-sms.xml" ]
514 where
515 check desc path = testCase desc $ do
516 actual <- unpickleable path pickle_message
517 let expected = True
518 actual @?= expected
519
520
521 -- | Make sure everything gets deleted when we delete the top-level
522 -- record.
523 --
524 test_on_delete_cascade :: TestTree
525 test_on_delete_cascade = testGroup "cascading delete tests"
526 [ check "deleting news deletes its children"
527 "test/xml/newsxml.xml"
528 4 -- 2 news_teams and 2 news_locations that should remain.
529 ,
530 check "deleting news deletes its children (empty SMS)"
531 "test/xml/newsxml-empty-sms.xml"
532 4 -- 2 news_teams and 2 news_locations
533 ]
534 where
535 check desc path expected = testCase desc $ do
536 news <- unsafe_unpickle path pickle_message
537 let a = undefined :: Location
538 let b = undefined :: News
539 let c = undefined :: Team
540 let d = undefined :: News_Team
541 let e = undefined :: News_Location
542 actual <- withSqliteConn ":memory:" $ runDbConn $ do
543 runMigration silentMigrationLogger $ do
544 migrate a
545 migrate b
546 migrate c
547 migrate d
548 migrate e
549 _ <- dbimport news
550 deleteAll b
551 count_a <- countAll a
552 count_b <- countAll b
553 count_c <- countAll c
554 count_d <- countAll d
555 count_e <- countAll e
556 return $ count_a + count_b + count_c + count_d + count_e
557 actual @?= expected
558
559
560 -- | We want to make sure the single-SMS documents and the multi-SMS
561 -- documents are identified correctly.
562 --
563 test_sms_detected_correctly :: TestTree
564 test_sms_detected_correctly =
565 testGroup "newsxml SMS count determined correctly"
566 [ check "test/xml/newsxml.xml"
567 "single SMS detected correctly"
568 True,
569 check "test/xml/newsxml-multiple-sms.xml"
570 "multiple SMS detected correctly"
571 False ]
572 where
573 check path desc expected = testCase desc $ do
574 xmltree <- unsafe_read_document path
575 let actual = has_only_single_sms xmltree
576 actual @?= expected