]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blob - src/TSN/XML/JFile.hs
84e6b66ebd642e148241a7d5acc042bb66dfa880
[dead/htsn-import.git] / src / TSN / XML / JFile.hs
1 {-# LANGUAGE FlexibleInstances #-}
2 {-# LANGUAGE GADTs #-}
3 {-# LANGUAGE QuasiQuotes #-}
4 {-# LANGUAGE RecordWildCards #-}
5 {-# LANGUAGE TemplateHaskell #-}
6 {-# LANGUAGE TypeFamilies #-}
7
8 -- | Parse TSN XML for the DTD \"jfilexml.dtd\". There's a top-level
9 -- \<message\>, containing a \<gamelist\>, containing
10 -- \<game\>s. Those games contain a bunch of other stuff. The
11 -- \<gamelist\> is pretty irrelevant; we ignore it and pretend that
12 -- a message contains a bunch of games.
13 --
14 module TSN.XML.JFile (
15 dtd,
16 pickle_message,
17 -- * Tests
18 jfile_tests,
19 -- * WARNING: these are private but exported to silence warnings
20 JFileConstructor(..),
21 JFileGameConstructor(..) )
22 where
23
24 -- System imports
25 import Control.Monad ( forM_ )
26 import Data.List ( intercalate )
27 import Data.String.Utils ( split )
28 import Data.Time ( UTCTime(..) )
29 import Data.Tuple.Curry ( uncurryN )
30 import Database.Groundhog (
31 countAll,
32 deleteAll,
33 migrate,
34 runMigration,
35 silentMigrationLogger )
36 import Database.Groundhog.Core ( DefaultKey )
37 import Database.Groundhog.Generic ( runDbConn )
38 import Database.Groundhog.Sqlite ( withSqliteConn )
39 import Database.Groundhog.TH (
40 groundhog,
41 mkPersist )
42 import Test.Tasty ( TestTree, testGroup )
43 import Test.Tasty.HUnit ( (@?=), testCase )
44 import Text.XML.HXT.Core (
45 PU,
46 xpTriple,
47 xp6Tuple,
48 xp14Tuple,
49 xp19Tuple,
50 xpAttr,
51 xpElem,
52 xpInt,
53 xpList,
54 xpOption,
55 xpPair,
56 xpPrim,
57 xpText,
58 xpText0,
59 xpWrap )
60
61
62 -- Local imports
63 import TSN.Codegen ( tsn_codegen_config )
64 import TSN.Database ( insert_or_select )
65 import TSN.DbImport ( DbImport(..), ImportResult(..), run_dbmigrate )
66 import TSN.Picklers (
67 xp_date,
68 xp_date_padded,
69 xp_datetime,
70 xp_tba_time,
71 xp_time_dots,
72 xp_time_stamp )
73 import TSN.Team (
74 FromXmlFkTeams(..),
75 HTeam(..),
76 Team(..),
77 VTeam(..) )
78 import TSN.XmlImport (
79 XmlImport(..),
80 XmlImportFkTeams(..) )
81 import Xml (
82 Child(..),
83 FromXml(..),
84 ToDb(..),
85 pickle_unpickle,
86 unpickleable,
87 unsafe_unpickle )
88
89
90
91 -- | The DTD to which this module corresponds. Used to invoke dbimport.
92 --
93 dtd :: String
94 dtd = "jfilexml.dtd"
95
96 --
97 -- DB/XML data types
98 --
99
100 -- * JFile/Message
101
102 -- | Database representation of a 'Message'.
103 --
104 data JFile =
105 JFile {
106 db_xml_file_id :: Int,
107 db_heading :: String,
108 db_category :: String,
109 db_sport :: String,
110 db_time_stamp :: UTCTime }
111
112
113
114 -- | XML Representation of an 'JFile'.
115 --
116 data Message =
117 Message {
118 xml_xml_file_id :: Int,
119 xml_heading :: String,
120 xml_category :: String,
121 xml_sport :: String,
122 xml_gamelist :: JFileGameListXml,
123 xml_time_stamp :: UTCTime }
124 deriving (Eq, Show)
125
126
127 instance ToDb Message where
128 -- | The database analogue of a 'Message' is a 'JFile'.
129 --
130 type Db Message = JFile
131
132
133 -- | The 'FromXml' instance for 'Message' is required for the
134 -- 'XmlImport' instance.
135 --
136 instance FromXml Message where
137 -- | To convert a 'Message' to an 'JFile', we just drop
138 -- the 'xml_gamelist'.
139 --
140 from_xml Message{..} =
141 JFile {
142 db_xml_file_id = xml_xml_file_id,
143 db_heading = xml_heading,
144 db_category = xml_category,
145 db_sport = xml_sport,
146 db_time_stamp = xml_time_stamp }
147
148
149 -- | This allows us to insert the XML representation 'Message'
150 -- directly.
151 --
152 instance XmlImport Message
153
154
155
156 -- * JFileGame/JFileGameXml
157
158 -- | This is an embedded type within each JFileGame. It has its own
159 -- element, \<Odds_Info\>, but there's only one of them per game. So
160 -- essentially all of these fields belong to a 'JFileGame'. Aaaannnd
161 -- most of them are redundant. We'll (un)pickle them for good
162 -- measure, but in the conversion to the database type, we can drop
163 -- all of the redundant information.
164 --
165 -- All of these are optional because TSN does actually leave the
166 -- whole thing empty from time to time.
167 --
168 -- We stick \"info\" on the home/away team ids to avoid a name clash
169 -- with the game itself.
170 --
171 data JFileGameOddsInfo =
172 JFileGameOddsInfo {
173 db_list_date :: Maybe UTCTime,
174 db_info_home_team_id :: Maybe String, -- redundant (Team)
175 db_info_away_team_id :: Maybe String, -- redundant (Team)
176 db_home_abbr :: Maybe String, -- redundant (Team)
177 db_away_abbr :: Maybe String, -- redundant (Team)
178 db_home_team_name :: Maybe String, -- redundant (Team)
179 db_away_team_name :: Maybe String, -- redundant (Team)
180 db_home_starter :: Maybe String,
181 db_away_starter :: Maybe String,
182 db_game_date :: Maybe UTCTime, -- redundant (JFileGame)
183 db_home_game_key :: Maybe Int,
184 db_away_game_key :: Maybe Int,
185 db_current_timestamp :: Maybe UTCTime,
186 db_live :: Maybe Bool,
187 db_notes :: String }
188 deriving (Eq, Show)
189
190
191 -- | Another embedded type within 'JFileGame'. These look like,
192 -- \<status numeral=\"4\"\>FINAL\</status\> within the XML, but
193 -- they're in one-to-one correspondence with the games.
194 --
195 data JFileGameStatus =
196 JFileGameStatus {
197 db_status_numeral :: Int,
198 db_status :: Maybe String }
199 deriving (Eq, Show)
200
201
202 -- | Database representation of a \<game\> contained within a
203 -- \<message\>, and, implicitly, a \<gamelist\>.
204 --
205 -- We've left out the game date, opting instead to combine the
206 -- date/time into the 'db_game_time' field.
207 --
208 data JFileGame =
209 JFileGame {
210 db_jfile_id :: DefaultKey JFile,
211 db_away_team_id :: DefaultKey Team,
212 db_home_team_id :: DefaultKey Team,
213 db_game_id :: Int,
214 db_schedule_id :: Int,
215 db_odds_info :: JFileGameOddsInfo,
216 db_season_type :: Maybe String,
217 db_game_time :: Maybe UTCTime,
218 db_vleague :: Maybe String,
219 db_hleague :: Maybe String,
220 db_vscore :: Int,
221 db_hscore :: Int,
222 db_time_remaining :: Maybe String,
223 db_game_status :: JFileGameStatus }
224
225
226 -- | XML representation of a \<game\> contained within a \<message\>,
227 -- and a \<gamelist\>. The Away/Home teams seem to coincide with
228 -- those of 'OddsGame', so we're reusing the DB type via the common
229 -- 'TSN.Team' structure. But the XML types are different, because
230 -- they have different picklers!
231 --
232 data JFileGameXml =
233 JFileGameXml {
234 xml_game_id :: Int,
235 xml_schedule_id :: Int,
236 xml_odds_info :: JFileGameOddsInfo,
237 xml_season_type :: Maybe String,
238 xml_game_date :: UTCTime,
239 xml_game_time :: Maybe UTCTime,
240 xml_vteam :: VTeam,
241 xml_vleague :: Maybe String,
242 xml_hteam :: HTeam,
243 xml_hleague :: Maybe String,
244 xml_vscore :: Int,
245 xml_hscore :: Int,
246 xml_time_remaining :: Maybe String,
247 xml_game_status :: JFileGameStatus }
248 deriving (Eq, Show)
249
250
251 -- * JFileGameListXml
252
253 -- | The XML representation of \<message\> -> \<gamelist\>. This
254 -- element serves only to contain \<game\>s, so we don't store the
255 -- intermediate table in the database.
256 --
257 newtype JFileGameListXml =
258 JFileGameListXml {
259 xml_games ::
260 [JFileGameXml] }
261 deriving (Eq, Show)
262
263
264 instance ToDb JFileGameXml where
265 -- | The database analogue of an 'JFileGameXml' is
266 -- an 'JFileGame'.
267 --
268 type Db JFileGameXml = JFileGame
269
270
271 instance Child JFileGameXml where
272 -- | Each 'JFileGameXml' is contained in (i.e. has a foreign key to)
273 -- a 'JFile'.
274 --
275 type Parent JFileGameXml = JFile
276
277
278 instance FromXmlFkTeams JFileGameXml where
279 -- | To convert an 'JFileGameXml' to an 'JFileGame', we add the
280 -- foreign keys for JFile and the home/away teams. We also mash
281 -- the date/time together into one field.
282 --
283 from_xml_fk_teams fk fk_away fk_home JFileGameXml{..} =
284 JFileGame {
285 db_jfile_id = fk,
286 db_away_team_id = fk_away,
287 db_home_team_id = fk_home,
288 db_game_id = xml_game_id,
289 db_schedule_id = xml_schedule_id,
290 db_odds_info = xml_odds_info,
291 db_season_type = xml_season_type,
292 db_game_time = make_game_time xml_game_date xml_game_time,
293 db_vleague = xml_vleague,
294 db_hleague = xml_hleague,
295 db_vscore = xml_vscore,
296 db_hscore = xml_hscore,
297 db_time_remaining = xml_time_remaining,
298 db_game_status = xml_game_status }
299 where
300 -- | Construct the database game time from the XML \<Game_Date\>
301 -- and \<Game_Time\> elements. The \<Game_Time\> elements
302 -- sometimes have a value of \"TBA\"; in that case, we don't
303 -- want to pretend that we know the time by setting it to
304 -- e.g. midnight, so instead we make the entire date/time
305 -- Nothing.
306 make_game_time :: UTCTime -> Maybe UTCTime -> Maybe UTCTime
307 make_game_time _ Nothing = Nothing
308 make_game_time d (Just t) = Just $ UTCTime (utctDay d) (utctDayTime t)
309
310
311 -- | This allows us to insert the XML representation
312 -- 'JFileGameXml' directly.
313 --
314 instance XmlImportFkTeams JFileGameXml
315
316
317 ---
318 --- Database stuff.
319 ---
320
321 instance DbImport Message where
322 dbmigrate _ =
323 run_dbmigrate $ do
324 migrate (undefined :: Team)
325 migrate (undefined :: JFile)
326 migrate (undefined :: JFileGame)
327
328 dbimport m = do
329 -- Insert the top-level message
330 msg_id <- insert_xml m
331
332 -- Now loop through the message's games
333 forM_ (xml_games $ xml_gamelist m) $ \game -> do
334 -- First we insert the home and away teams.
335 away_team_id <- insert_or_select (vteam $ xml_vteam game)
336 home_team_id <- insert_or_select (hteam $ xml_hteam game)
337
338 -- Now insert the game keyed to the "jfile" and its teams.
339 insert_xml_fk_teams_ msg_id away_team_id home_team_id game
340
341
342 return ImportSucceeded
343
344
345 mkPersist tsn_codegen_config [groundhog|
346 - entity: JFile
347 dbName: jfile
348 constructors:
349 - name: JFile
350 uniques:
351 - name: unique_jfile
352 type: constraint
353 # Prevent multiple imports of the same message.
354 fields: [db_xml_file_id]
355
356 - embedded: JFileGameStatus
357 fields:
358 - name: db_status_numeral
359 dbName: status_numeral
360 - name: db_status
361 dbName: status
362
363 # Many of the JFileGameOddsInfo fields are redundant and have
364 # been left out.
365 - embedded: JFileGameOddsInfo
366 fields:
367 - name: db_list_date
368 dbName: list_date
369 - name: db_home_starter
370 dbName: home_starter
371 - name: db_home_game_key
372 dbName: home_game_key
373 - name: db_away_game_key
374 dbName: away_game_key
375 - name: db_current_timestamp
376 dbName: current_timestamp
377 - name: db_live
378 dbName: live
379 - name: db_notes
380 dbName: notes
381
382 - entity: JFileGame
383 dbName: jfile_games
384 constructors:
385 - name: JFileGame
386 fields:
387 - name: db_jfile_id
388 reference:
389 onDelete: cascade
390 - name: db_away_team_id
391 reference:
392 onDelete: cascade
393 - name: db_home_team_id
394 reference:
395 onDelete: cascade
396 - name: db_odds_info
397 embeddedType:
398 - {name: list_date, dbName: list_date}
399 - {name: home_starter, dbName: home_starter}
400 - {name: away_starter, dbName: away_starter}
401 - {name: home_game_key, dbName: home_game_key}
402 - {name: away_game_key, dbName: away_game_key}
403 - {name: current_timestamp, dbName: current_timestamp}
404 - {name: live, dbName: live}
405 - {name: notes, dbName: notes}
406 - name: db_game_status
407 embeddedType:
408 - {name: status_numeral, dbName: status_numeral}
409 - {name: status, dbName: status}
410
411 |]
412
413
414
415 ---
416 --- Pickling
417 ---
418
419 -- | Pickler for the top-level 'Message'.
420 --
421 pickle_message :: PU Message
422 pickle_message =
423 xpElem "message" $
424 xpWrap (from_tuple, to_tuple) $
425 xp6Tuple (xpElem "XML_File_ID" xpInt)
426 (xpElem "heading" xpText)
427 (xpElem "category" xpText)
428 (xpElem "sport" xpText)
429 pickle_gamelist
430 (xpElem "time_stamp" xp_time_stamp)
431 where
432 from_tuple = uncurryN Message
433 to_tuple m = (xml_xml_file_id m,
434 xml_heading m,
435 xml_category m,
436 xml_sport m,
437 xml_gamelist m,
438 xml_time_stamp m)
439
440 pickle_gamelist :: PU JFileGameListXml
441 pickle_gamelist =
442 xpElem "gamelist" $
443 xpWrap (to_result, from_result) $ xpList pickle_game
444 where
445 to_result = JFileGameListXml
446 from_result = xml_games
447
448
449
450
451 pickle_game :: PU JFileGameXml
452 pickle_game =
453 xpElem "game" $
454 xpWrap (from_tuple, to_tuple) $
455 xp14Tuple (xpElem "game_id" xpInt)
456 (xpElem "schedule_id" xpInt)
457 pickle_odds_info
458 (xpElem "seasontype" (xpOption xpText))
459 (xpElem "Game_Date" xp_date_padded)
460 (xpElem "Game_Time" xp_tba_time)
461 pickle_away_team
462 (xpOption $ xpElem "vleague" xpText)
463 pickle_home_team
464 (xpOption $ xpElem "hleague" xpText)
465 (xpElem "vscore" xpInt)
466 (xpElem "hscore" xpInt)
467 (xpOption $ xpElem "time_r" xpText)
468 pickle_status
469 where
470 from_tuple = uncurryN JFileGameXml
471 to_tuple m = (xml_game_id m,
472 xml_schedule_id m,
473 xml_odds_info m,
474 xml_season_type m,
475 xml_game_date m,
476 xml_game_time m,
477 xml_vteam m,
478 xml_vleague m,
479 xml_hteam m,
480 xml_hleague m,
481 xml_vscore m,
482 xml_hscore m,
483 xml_time_remaining m,
484 xml_game_status m)
485
486 pickle_odds_info :: PU JFileGameOddsInfo
487 pickle_odds_info =
488 xpElem "Odds_Info" $
489 xpWrap (from_tuple, to_tuple) $
490 xp19Tuple (xpElem "ListDate" (xpOption xp_date))
491 (xpElem "HomeTeamID" (xpOption xpText))
492 (xpElem "AwayTeamID" (xpOption xpText))
493 (xpElem "HomeAbbr" (xpOption xpText))
494 (xpElem "AwayAbbr" (xpOption xpText))
495 (xpElem "HomeTeamName" (xpOption xpText))
496 (xpElem "AwayTeamName" (xpOption xpText))
497 (xpElem "HStarter" (xpOption xpText))
498 (xpElem "AStarter" (xpOption xpText))
499 (xpElem "GameDate" (xpOption xp_datetime))
500 (xpElem "HGameKey" (xpOption xpInt))
501 (xpElem "AGameKey" (xpOption xpInt))
502 (xpElem "CurrentTimeStamp" (xpOption xp_time_dots))
503 (xpElem "Live" (xpOption xpPrim))
504 (xpElem "Notes1" xpText0)
505 (xpElem "Notes2" xpText0)
506 (xpElem "Notes3" xpText0)
507 (xpElem "Notes4" xpText0)
508 (xpElem "Notes5" xpText0)
509 where
510 from_tuple (x1,x2,x3,x4,x5,x6,x7,x8,x9,x10,x11,x12,x13,x14,n1,n2,n3,n4,n5) =
511 JFileGameOddsInfo x1 x2 x3 x4 x5 x6 x7 x8 x9 x10 x11 x12 x13 x14 notes
512 where
513 notes = intercalate "\n" [n1,n2,n3,n4,n5]
514
515 to_tuple o = (db_list_date o,
516 db_info_home_team_id o,
517 db_info_away_team_id o,
518 db_home_abbr o,
519 db_away_abbr o,
520 db_home_team_name o,
521 db_away_team_name o,
522 db_home_starter o,
523 db_away_starter o,
524 db_game_date o,
525 db_home_game_key o,
526 db_away_game_key o,
527 db_current_timestamp o,
528 db_live o,
529 n1,n2,n3,n4,n5)
530 where
531 note_lines = split "\n" (db_notes o)
532 n1 = case note_lines of
533 (notes1:_) -> notes1
534 _ -> ""
535 n2 = case note_lines of
536 (_:notes2:_) -> notes2
537 _ -> ""
538 n3 = case note_lines of
539 (_:_:notes3:_) -> notes3
540 _ -> ""
541 n4 = case note_lines of
542 (_:_:_:notes4:_) -> notes4
543 _ -> ""
544 n5 = case note_lines of
545 (_:_:_:_:notes5:_) -> notes5
546 _ -> ""
547
548 -- | (Un)pickle a home team to/from the dual XML/DB representation
549 -- 'Team'.
550 --
551 pickle_home_team :: PU HTeam
552 pickle_home_team =
553 xpElem "hteam" $
554 xpWrap (from_tuple, to_tuple) $
555 xpTriple (xpAttr "teamid" xpText) -- Yeah, they're text.
556 (xpAttr "abbr" (xpOption xpText)) -- Some are blank
557 (xpOption xpText) -- Yup, some are nameless
558 where
559 from_tuple = HTeam . (uncurryN Team)
560 to_tuple (HTeam t) = (team_id t,
561 abbreviation t,
562 name t)
563
564
565 -- | (Un)pickle an away team to/from the dual XML/DB representation
566 -- 'Team'.
567 --
568 pickle_away_team :: PU VTeam
569 pickle_away_team =
570 xpElem "vteam" $
571 xpWrap (from_tuple, to_tuple) $
572 xpTriple (xpAttr "teamid" xpText) -- Yeah, they're text.
573 (xpAttr "abbr" (xpOption xpText)) -- Some are blank
574 (xpOption xpText) -- Yup, some are nameless
575 where
576 from_tuple = VTeam . (uncurryN Team)
577 to_tuple (VTeam t) = (team_id t,
578 abbreviation t,
579 name t)
580
581
582 pickle_status :: PU JFileGameStatus
583 pickle_status =
584 xpElem "status" $
585 xpWrap (from_tuple, to_tuple) $
586 xpPair (xpAttr "numeral" xpInt)
587 (xpOption xpText)
588 where
589 from_tuple = uncurry JFileGameStatus
590 to_tuple s = (db_status_numeral s,
591 db_status s)
592
593
594
595 --
596 -- Tasty Tests
597 --
598
599 -- | A list of all tests for this module.
600 --
601 jfile_tests :: TestTree
602 jfile_tests =
603 testGroup
604 "JFile tests"
605 [ test_on_delete_cascade,
606 test_pickle_of_unpickle_is_identity,
607 test_unpickle_succeeds ]
608
609
610 -- | If we unpickle something and then pickle it, we should wind up
611 -- with the same thing we started with. WARNING: success of this
612 -- test does not mean that unpickling succeeded.
613 --
614 test_pickle_of_unpickle_is_identity :: TestTree
615 test_pickle_of_unpickle_is_identity = testGroup "pickle-unpickle tests"
616 [ check "pickle composed with unpickle is the identity"
617 "test/xml/jfilexml.xml",
618 check "pickle composed with unpickle is the identity (missing fields)"
619 "test/xml/jfilexml-missing-fields.xml",
620
621 check "pickle composed with unpickle is the identity (TBA game time)"
622 "test/xml/jfilexml-tba-game-time.xml"]
623 where
624 check desc path = testCase desc $ do
625 (expected, actual) <- pickle_unpickle pickle_message path
626 actual @?= expected
627
628
629
630 -- | Make sure we can actually unpickle these things.
631 --
632 test_unpickle_succeeds :: TestTree
633 test_unpickle_succeeds = testGroup "unpickle tests"
634 [ check "unpickling succeeds" "test/xml/jfilexml.xml",
635
636 check "unpickling succeeds (missing fields)"
637 "test/xml/jfilexml-missing-fields.xml",
638
639 check "unpickling succeeds (TBA game time)"
640 "test/xml/jfilexml-tba-game-time.xml" ]
641 where
642 check desc path = testCase desc $ do
643 actual <- unpickleable path pickle_message
644
645 let expected = True
646 actual @?= expected
647
648
649
650 -- | Make sure everything gets deleted when we delete the top-level
651 -- record.
652 --
653 test_on_delete_cascade :: TestTree
654 test_on_delete_cascade = testGroup "cascading delete tests"
655 [ check "deleting auto_racing_results deletes its children"
656 "test/xml/jfilexml.xml"
657 20, -- teams
658
659 check "deleting auto_racing_results deletes its children (missing fields)"
660 "test/xml/jfilexml-missing-fields.xml"
661 44,
662
663 check "deleting auto_racing_results deletes its children (TBA game time)"
664 "test/xml/jfilexml-tba-game-time.xml"
665 8 ]
666 where
667 check desc path expected = testCase desc $ do
668 results <- unsafe_unpickle path pickle_message
669 let a = undefined :: Team
670 let b = undefined :: JFile
671 let c = undefined :: JFileGame
672
673 actual <- withSqliteConn ":memory:" $ runDbConn $ do
674 runMigration silentMigrationLogger $ do
675 migrate a
676 migrate b
677 migrate c
678 _ <- dbimport results
679 deleteAll b
680 count_a <- countAll a
681 count_b <- countAll b
682 count_c <- countAll c
683 return $ sum [count_a, count_b, count_c]
684 actual @?= expected