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