]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blob - src/TSN/XML/Scores.hs
Update two comments.
[dead/htsn-import.git] / src / TSN / XML / Scores.hs
1 {-# LANGUAGE DeriveDataTypeable #-}
2 {-# LANGUAGE FlexibleInstances #-}
3 {-# LANGUAGE GADTs #-}
4 {-# LANGUAGE QuasiQuotes #-}
5 {-# LANGUAGE RecordWildCards #-}
6 {-# LANGUAGE TemplateHaskell #-}
7 {-# LANGUAGE TypeFamilies #-}
8
9 -- | Parse TSN XML for the DTD \"scoresxml.dtd\". Each document
10 -- contains a single \<game\> and some \<location\>s.
11 --
12 module TSN.XML.Scores (
13 dtd,
14 pickle_message,
15 -- * Tests
16 scores_tests,
17 -- * WARNING: these are private but exported to silence warnings
18 Score_ScoreLocationConstructor(..),
19 ScoreConstructor(..),
20 ScoreGameConstructor(..),
21 ScoreGameTeamConstructor(..),
22 ScoreLocationConstructor(..),
23 ScoreGame_ScoreGameTeamConstructor(..) )
24 where
25
26 -- System imports.
27 import Data.Data ( Data )
28 import Data.Time ( UTCTime )
29 import Data.Tuple.Curry ( uncurryN )
30 import Data.Typeable ( Typeable )
31 import Database.Groundhog (
32 countAll,
33 deleteAll,
34 insert,
35 insert_,
36 migrate,
37 runMigration,
38 silentMigrationLogger )
39 import Database.Groundhog.Core ( DefaultKey )
40 import Database.Groundhog.Generic ( runDbConn )
41 import Database.Groundhog.Sqlite ( withSqliteConn )
42 import Database.Groundhog.TH (
43 defaultCodegenConfig,
44 groundhog,
45 mkPersist )
46 import Test.Tasty ( TestTree, testGroup )
47 import Test.Tasty.HUnit ( (@?=), testCase )
48 import Text.XML.HXT.Core (
49 PU,
50 xp7Tuple,
51 xp11Tuple,
52 xpAttr,
53 xpElem,
54 xpInt,
55 xpList,
56 xpOption,
57 xpPair,
58 xpPrim,
59 xpText,
60 xpTriple,
61 xpWrap )
62
63 -- Local imports.
64 import TSN.Codegen (
65 tsn_codegen_config )
66 import TSN.DbImport ( DbImport(..), ImportResult(..), run_dbmigrate )
67 import TSN.Picklers ( xp_time_stamp )
68 import TSN.XmlImport ( XmlImport(..), XmlImportFk(..) )
69 import Xml (
70 Child(..),
71 FromXml(..),
72 FromXmlFk(..),
73 ToDb(..),
74 pickle_unpickle,
75 unpickleable,
76 unsafe_unpickle )
77
78
79 -- | The DTD to which this module corresponds. Used to invoke dbimport.
80 --
81 dtd :: String
82 dtd = "scoresxml.dtd"
83
84
85 ---
86 --- DB/XML Data types
87 ---
88
89
90 -- * Score / Message
91
92 -- | Database representation of a 'Message'. It lacks the
93 -- 'xml_locations' and 'xml_game' which are related via foreign keys
94 -- instead.
95 --
96 data Score =
97 Score {
98 db_xml_file_id :: Int,
99 db_heading :: String,
100 db_game_id :: Int,
101 db_schedule_id :: Int,
102 db_tsnupdate :: Maybe Bool,
103 db_category :: String,
104 db_sport :: String,
105 db_season_type :: String,
106 db_time_stamp :: UTCTime }
107
108
109 -- | XML representation of the top level \<message\> element (i.e. a
110 -- 'Score').
111 --
112 data Message =
113 Message {
114 xml_xml_file_id :: Int,
115 xml_heading :: String,
116 xml_game_id :: Int,
117 xml_schedule_id :: Int,
118 xml_tsnupdate :: Maybe Bool,
119 xml_category :: String,
120 xml_sport :: String,
121 xml_locations :: [ScoreLocation],
122 xml_season_type :: String,
123 xml_game :: ScoreGameXml,
124 xml_time_stamp :: UTCTime }
125 deriving (Eq, Show)
126
127 instance ToDb Message where
128 -- | The database representation of a 'Message' is a 'Score'.
129 type Db Message = Score
130
131 instance FromXml Message where
132 -- | When converting from the XML representation to the database
133 -- one, we drop the list of locations which will be foreign-keyed to
134 -- us instead.
135 from_xml Message{..} =
136 Score {
137 db_xml_file_id = xml_xml_file_id,
138 db_heading = xml_heading,
139 db_game_id = xml_game_id,
140 db_schedule_id = xml_schedule_id,
141 db_tsnupdate = xml_tsnupdate,
142 db_category = xml_category,
143 db_sport = xml_sport,
144 db_season_type = xml_season_type,
145 db_time_stamp = xml_time_stamp }
146
147
148 -- | This lets us insert the XML representation 'Message' directly.
149 --
150 instance XmlImport Message
151
152
153 -- * ScoreGame / ScoreGameXml
154
155 -- | This is an embedded field within 'SportsGame'. Each \<status\>
156 -- element has two attributes, a numeral and a type. It also
157 -- contains some text. Rather than put these in their own table, we
158 -- include them in the parent 'SportsGame'.
159 --
160 data ScoreGameStatus =
161 ScoreGameStatus {
162 db_status_numeral :: Int,
163 db_status_type :: String, -- ^ These are probably only one-character long,
164 -- but they all take the same amount of space
165 -- in Postgres.
166 db_status_text :: String }
167 deriving (Data, Eq, Show, Typeable)
168
169
170 -- | Database representation of a game.
171 --
172 data ScoreGame =
173 ScoreGame {
174 db_scores_id :: DefaultKey Score,
175 db_vscore :: Int,
176 db_hscore :: Int,
177 db_time_r :: Maybe String, -- ^ Time remaining, the format is uncertain.
178 db_status :: ScoreGameStatus,
179 db_notes :: Maybe String }
180
181
182 -- | XML representation of a \<game\> element (i.e. a 'ScoreGame').
183 --
184 data ScoreGameXml =
185 ScoreGameXml {
186 xml_vteam :: ScoreGameVTeam,
187 xml_hteam :: ScoreGameHTeam,
188 xml_vscore :: Int,
189 xml_hscore :: Int,
190 xml_time_r :: Maybe String, -- ^ Time remaining, the format is uncertain.
191 xml_status :: ScoreGameStatus,
192 xml_notes :: Maybe String }
193 deriving (Eq, Show)
194
195 -- | Pseudo-accessor to get the 'ScoreGameTeam' out of 'xml_vteam'.
196 vteam :: ScoreGameXml -> ScoreGameTeam
197 vteam g = let (ScoreGameVTeam t) = xml_vteam g in t
198
199 -- | Pseudo-accessor to get the 'ScoreGameTeam' out of 'xml_hteam'.
200 hteam :: ScoreGameXml -> ScoreGameTeam
201 hteam g = let (ScoreGameHTeam t) = xml_hteam g in t
202
203 instance ToDb ScoreGameXml where
204 -- | The database representation of a 'ScoreGameXml' is a
205 -- 'ScoreGame'.
206 --
207 type Db ScoreGameXml = ScoreGame
208
209
210 instance Child ScoreGameXml where
211 -- | Each 'ScoreGameXml' is contained in (i.e. has a foreign key to)
212 -- a 'Score'.
213 --
214 type Parent ScoreGameXml = Score
215
216
217 instance FromXmlFk ScoreGameXml where
218 from_xml_fk fk ScoreGameXml{..} =
219 ScoreGame {
220 db_scores_id = fk,
221 db_vscore = xml_vscore,
222 db_hscore = xml_hscore,
223 db_time_r = xml_time_r,
224 db_status = xml_status,
225 db_notes = xml_notes }
226
227 -- | This lets us import the database representation 'ScoreGameXml'
228 -- directly.
229 --
230 instance XmlImportFk ScoreGameXml
231
232
233 -- * ScoreGameTeam
234
235 -- | A team that appears in a 'ScoreGame'. This is meant to represent
236 -- both home and away teams.
237 --
238 data ScoreGameTeam =
239 ScoreGameTeam {
240 team_id :: String,
241 team_name :: String }
242 deriving (Eq, Show)
243
244 -- | A wrapper around 'ScoreGameTeam' that lets us distinguish between
245 -- home and away teams. See also 'ScoreGameHTeam'.
246 --
247 newtype ScoreGameVTeam =
248 ScoreGameVTeam ScoreGameTeam
249 deriving (Eq, Show)
250
251
252 -- | A wrapper around 'ScoreGameTeam' that lets us distinguish between
253 -- home and away teams. See also 'ScoreGameVTeam'.
254 --
255 newtype ScoreGameHTeam =
256 ScoreGameHTeam ScoreGameTeam
257 deriving (Eq, Show)
258
259
260 -- * ScoreGame_ScoreGameTeam
261
262 -- | Join a 'ScoreGame' with its home/away teams. Database-only. We
263 -- use a join table because the teams are kept unique. The first
264 -- argument is the game id, the second argument is the visiting team
265 -- (vteam) id, and the last argument is the home team (hteam) id.
266 --
267 data ScoreGame_ScoreGameTeam =
268 ScoreGame_ScoreGameTeam
269 (DefaultKey ScoreGame) -- game id
270 (DefaultKey ScoreGameTeam) -- vteam id
271 (DefaultKey ScoreGameTeam) -- hteam id
272
273
274 -- * ScoreLocation
275
276 -- | Database and XML representation of a \<location\>. This is almost
277 -- identical to 'TSN.XML.NewsLocation', but the city/state have not
278 -- appeared optional here so far.
279 --
280 data ScoreLocation =
281 ScoreLocation {
282 city :: String,
283 state :: String,
284 country :: String }
285 deriving (Eq, Show)
286
287
288 -- * Score_ScoreLocation
289
290 -- | Join each 'Score' with its 'ScoreLocation's. Database-only. We
291 -- use a join table because the locations are kept unique.
292 --
293 data Score_ScoreLocation =
294 Score_ScoreLocation
295 (DefaultKey Score)
296 (DefaultKey ScoreLocation)
297
298
299
300 instance DbImport Message where
301 dbmigrate _ =
302 run_dbmigrate $ do
303 migrate (undefined :: Score)
304 migrate (undefined :: ScoreGame)
305 migrate (undefined :: ScoreGameTeam)
306 migrate (undefined :: ScoreGame_ScoreGameTeam)
307 migrate (undefined :: ScoreLocation)
308 migrate (undefined :: Score_ScoreLocation)
309
310 dbimport m = do
311 -- Insert the message and get its ID.
312 msg_id <- insert_xml m
313
314 -- Insert all of the locations contained within this message and
315 -- collect their IDs in a list.
316 location_ids <- mapM insert (xml_locations m)
317
318 -- Now use that list to construct 'Score_ScoreLocation' objects,
319 -- and insert them.
320 mapM_ (insert_ . Score_ScoreLocation msg_id) location_ids
321
322 -- Insert the game and its hteam/vteam, noting the IDs.
323 game_id <- insert_xml_fk msg_id (xml_game m)
324 vteam_id <- insert (vteam $ xml_game m)
325 hteam_id <- insert (hteam $ xml_game m)
326
327 -- Finally add a 'ScoreGame_ScoreGameTeam' mapping the
328 -- aforementioned game to its hteam/vteam.
329 insert_ $ ScoreGame_ScoreGameTeam game_id vteam_id hteam_id
330
331 return ImportSucceeded
332
333
334 -- These types don't have special XML representations or field name
335 -- collisions so we use the defaultCodegenConfig and give their
336 -- fields nice simple names.
337 mkPersist defaultCodegenConfig [groundhog|
338 - entity: ScoreGameTeam
339 dbName: scores_games_teams
340 constructors:
341 - name: ScoreGameTeam
342 uniques:
343 - name: unique_scores_games_team
344 type: constraint
345 fields: [team_id]
346
347 - entity: ScoreLocation
348 dbName: scores_locations
349 constructors:
350 - name: ScoreLocation
351 uniques:
352 - name: unique_scores_location
353 type: constraint
354 fields: [city, state, country]
355
356 |]
357
358
359
360 -- These types have fields with e.g. db_ and xml_ prefixes, so we
361 -- use our own codegen to peel those off before naming the columns.
362 mkPersist tsn_codegen_config [groundhog|
363 - entity: Score
364 dbName: scores
365 constructors:
366 - name: Score
367 uniques:
368 - name: unique_scores
369 type: constraint
370 # Prevent multiple imports of the same message.
371 fields: [db_xml_file_id]
372
373 - embedded: ScoreGameStatus
374 fields:
375 - name: db_status_numeral
376 dbName: status_numeral
377 - name: db_status_type
378 dbName: status_type
379 - name: db_status_text
380 dbName: status_text
381
382 - entity: ScoreGame
383 dbName: scores_games
384 constructors:
385 - name: ScoreGame
386 fields:
387 - name: db_scores_id
388 reference:
389 onDelete: cascade
390 - name: db_status
391 embeddedType:
392 - { name: status_numeral, dbName: status_numeral }
393 - { name: status_type, dbName: status_type }
394 - { name: status_text, dbName: status_text }
395
396 - entity: ScoreGame_ScoreGameTeam
397 dbName: scores_games__scores_games_teams
398 constructors:
399 - name: ScoreGame_ScoreGameTeam
400 fields:
401 - name: scoreGame_ScoreGameTeam0 # Default created by mkNormalFieldName
402 dbName: scores_games_id
403 reference:
404 onDelete: cascade
405 - name: scoreGame_ScoreGameTeam1 # Default created by mkNormalFieldName
406 dbName: scores_games_teams_vteam_id
407 reference:
408 onDelete: cascade
409 - name: scoreGame_ScoreGameTeam2 # Default created by mkNormalFieldName
410 dbName: scores_games_teams_hteam_id
411 reference:
412 onDelete: cascade
413
414 - entity: Score_ScoreLocation
415 dbName: scores__scores_locations
416 constructors:
417 - name: Score_ScoreLocation
418 fields:
419 - name: score_ScoreLocation0 # Default created by mkNormalFieldName
420 dbName: scores_id
421 reference:
422 onDelete: cascade
423 - name: score_ScoreLocation1 # Default created by mkNormalFieldName
424 dbName: scores_locations_id
425 reference:
426 onDelete: cascade
427 |]
428
429
430 --
431 -- Pickling
432 --
433
434 -- | Convert a 'Message' to/from \<message\>.
435 --
436 pickle_message :: PU Message
437 pickle_message =
438 xpElem "message" $
439 xpWrap (from_tuple, to_tuple) $
440 xp11Tuple (xpElem "XML_File_ID" xpInt)
441 (xpElem "heading" xpText)
442 (xpElem "game_id" xpInt)
443 (xpElem "schedule_id" xpInt)
444 (xpOption $ xpElem "tsnupdate" xpPrim)
445 (xpElem "category" xpText)
446 (xpElem "sport" xpText)
447 (xpList pickle_location)
448 (xpElem "seasontype" xpText)
449 pickle_game
450 (xpElem "time_stamp" xp_time_stamp)
451 where
452 from_tuple = uncurryN Message
453 to_tuple m = (xml_xml_file_id m,
454 xml_heading m,
455 xml_game_id m,
456 xml_schedule_id m,
457 xml_tsnupdate m,
458 xml_category m,
459 xml_sport m,
460 xml_locations m,
461 xml_season_type m,
462 xml_game m,
463 xml_time_stamp m)
464
465
466
467 -- | Convert a 'ScoreLocation' to/from \<location\>.
468 --
469 pickle_location :: PU ScoreLocation
470 pickle_location =
471 xpElem "location" $
472 xpWrap (from_tuple, to_tuple) $
473 xpTriple (xpElem "city" xpText)
474 (xpElem "state" xpText)
475 (xpElem "country" xpText)
476 where
477 from_tuple =
478 uncurryN ScoreLocation
479 to_tuple l = (city l, state l, country l)
480
481
482 -- | Convert a 'ScoreGameStatus' to/from \<status\>.
483 --
484 pickle_status :: PU ScoreGameStatus
485 pickle_status =
486 xpElem "status" $
487 xpWrap (from_tuple, to_tuple) $
488 xpTriple (xpAttr "numeral" xpInt)
489 (xpAttr "type" xpText)
490 xpText
491 where
492 from_tuple = uncurryN ScoreGameStatus
493 to_tuple ScoreGameStatus{..} = (db_status_numeral,
494 db_status_type,
495 db_status_text)
496
497
498 -- | Convert a 'ScoreGameXml' to/from \<game\>.
499 --
500 pickle_game :: PU ScoreGameXml
501 pickle_game =
502 xpElem "game" $
503 xpWrap (from_tuple, to_tuple) $
504 xp7Tuple pickle_vteam
505 pickle_hteam
506 (xpElem "vscore" xpInt)
507 (xpElem "hscore" xpInt)
508 (xpOption $ xpElem "time_r" xpText)
509 pickle_status
510 (xpOption $ xpElem "notes" xpText)
511 where
512 from_tuple = uncurryN ScoreGameXml
513 to_tuple ScoreGameXml{..} = (xml_vteam,
514 xml_hteam,
515 xml_vscore,
516 xml_hscore,
517 xml_time_r,
518 xml_status,
519 xml_notes)
520
521
522 -- | Convert a 'ScoreGameVTeam' to/from \<vteam\>.
523 --
524 pickle_vteam :: PU ScoreGameVTeam
525 pickle_vteam =
526 xpElem "vteam" $
527 xpWrap (from_tuple, to_tuple) $
528 xpPair (xpAttr "id" xpText)
529 xpText
530 where
531 from_tuple = ScoreGameVTeam . uncurry ScoreGameTeam
532 to_tuple (ScoreGameVTeam ScoreGameTeam{..}) = (team_id, team_name)
533
534
535 -- | Convert a 'ScoreGameVTeam' to/from \<hteam\>. Identical to
536 -- 'pickle_vteam' modulo the \"h\" and \"v\".
537 --
538 pickle_hteam :: PU ScoreGameHTeam
539 pickle_hteam =
540 xpElem "hteam" $
541 xpWrap (from_tuple, to_tuple) $
542 xpPair (xpAttr "id" xpText)
543 xpText
544 where
545 from_tuple = ScoreGameHTeam . uncurry ScoreGameTeam
546 to_tuple (ScoreGameHTeam ScoreGameTeam{..}) = (team_id, team_name)
547
548
549
550 ---
551 --- Tasty tests
552 ---
553
554 -- | A list of all tests for this module.
555 --
556 scores_tests :: TestTree
557 scores_tests =
558 testGroup
559 "Scores tests"
560 [ test_on_delete_cascade,
561 test_pickle_of_unpickle_is_identity,
562 test_unpickle_succeeds ]
563
564
565 -- | If we unpickle something and then pickle it, we should wind up
566 -- with the same thing we started with. WARNING: success of this
567 -- test does not mean that unpickling succeeded.
568 --
569 test_pickle_of_unpickle_is_identity :: TestTree
570 test_pickle_of_unpickle_is_identity = testGroup "pickle-unpickle tests"
571 [ check "pickle composed with unpickle is the identity"
572 "test/xml/scoresxml.xml",
573
574 check "pickle composed with unpickle is the identity (no locations)"
575 "test/xml/scoresxml-no-locations.xml" ]
576 where
577 check desc path = testCase desc $ do
578 (expected, actual) <- pickle_unpickle pickle_message path
579 actual @?= expected
580
581
582 -- | Make sure we can actually unpickle these things.
583 --
584 test_unpickle_succeeds :: TestTree
585 test_unpickle_succeeds = testGroup "unpickle tests"
586 [ check "unpickling succeeds"
587 "test/xml/scoresxml.xml",
588
589 check "unpickling succeeds (no locations)"
590 "test/xml/scoresxml-no-locations.xml" ]
591 where
592 check desc path = testCase desc $ do
593 actual <- unpickleable path pickle_message
594 let expected = True
595 actual @?= expected
596
597
598 -- | Make sure everything gets deleted when we delete the top-level
599 -- record.
600 --
601 test_on_delete_cascade :: TestTree
602 test_on_delete_cascade = testGroup "cascading delete tests"
603 [ check "unpickling succeeds"
604 "test/xml/scoresxml.xml"
605 4, -- 2 teams, 2 locations
606
607 check "unpickling succeeds (no locations)"
608 "test/xml/scoresxml-no-locations.xml"
609 2 -- 2 teams, 0 locations
610 ]
611 where
612 check desc path expected = testCase desc $ do
613 score <- unsafe_unpickle path pickle_message
614 let a = undefined :: Score
615 let b = undefined :: ScoreGame
616 let c = undefined :: ScoreGameTeam
617 let d = undefined :: ScoreGame_ScoreGameTeam
618 let e = undefined :: ScoreLocation
619 let f = undefined :: Score_ScoreLocation
620 actual <- withSqliteConn ":memory:" $ runDbConn $ do
621 runMigration silentMigrationLogger $ do
622 migrate a
623 migrate b
624 migrate c
625 migrate d
626 migrate e
627 migrate f
628 _ <- dbimport score
629 -- No idea how 'delete' works, so do this instead.
630 deleteAll a
631 count_a <- countAll a
632 count_b <- countAll b
633 count_c <- countAll c
634 count_d <- countAll d
635 count_e <- countAll e
636 count_f <- countAll f
637 return $ sum [count_a, count_b, count_c,
638 count_d, count_e, count_f ]
639 actual @?= expected