1 {-# LANGUAGE FlexibleInstances #-}
3 {-# LANGUAGE QuasiQuotes #-}
4 {-# LANGUAGE RecordWildCards #-}
5 {-# LANGUAGE TemplateHaskell #-}
6 {-# LANGUAGE TypeFamilies #-}
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.
14 module TSN.XML.JFile (
19 -- * WARNING: these are private but exported to silence warnings
21 JFileGameConstructor(..) )
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 (
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 (
42 import Test.Tasty ( TestTree, testGroup )
43 import Test.Tasty.HUnit ( (@?=), testCase )
44 import Text.XML.HXT.Core (
63 import TSN.Codegen ( tsn_codegen_config )
64 import TSN.DbImport ( DbImport(..), ImportResult(..), run_dbmigrate )
72 import TSN.Team ( Team(..) )
73 import TSN.XmlImport (
75 XmlImportFkTeams(..) )
87 -- | The DTD to which this module corresponds. Used to invoke dbimport.
98 -- | Database representation of a 'Message'.
102 db_xml_file_id :: Int,
103 db_heading :: String,
104 db_category :: String,
106 db_time_stamp :: UTCTime }
110 -- | XML Representation of an 'JFile'.
114 xml_xml_file_id :: Int,
115 xml_heading :: String,
116 xml_category :: String,
118 xml_gamelist :: JFileGameListXml,
119 xml_time_stamp :: UTCTime }
123 instance ToDb Message where
124 -- | The database analogue of a 'Message' is a 'JFile'.
126 type Db Message = JFile
129 -- | The 'FromXml' instance for 'Message' is required for the
130 -- 'XmlImport' instance.
132 instance FromXml Message where
133 -- | To convert a 'Message' to an 'JFile', we just drop
134 -- the 'xml_gamelist'.
136 from_xml Message{..} =
138 db_xml_file_id = xml_xml_file_id,
139 db_heading = xml_heading,
140 db_category = xml_category,
141 db_sport = xml_sport,
142 db_time_stamp = xml_time_stamp }
145 -- | This allows us to insert the XML representation 'Message'
148 instance XmlImport Message
151 -- * JFileGameAwayTeamXml / JFileGameHomeTeamXml
153 -- | The XML representation of a JFile away team. Its corresponding
154 -- database representation (along with that of the home team) is a
155 -- TSN.Team, but their XML representations are different.
156 data JFileGameAwayTeamXml =
157 JFileGameAwayTeamXml {
158 away_team_id :: String,
159 away_team_abbreviation :: Maybe String,
160 away_team_name :: Maybe String }
163 instance ToDb JFileGameAwayTeamXml where
164 -- | The database analogue of an 'JFileGameAwayTeamXml' is
167 type Db JFileGameAwayTeamXml = Team
169 instance FromXml JFileGameAwayTeamXml where
170 -- | To convert a 'JFileGameAwayTeamXml' to a 'Team', we do just
173 from_xml JFileGameAwayTeamXml{..} =
175 team_id = away_team_id,
176 abbreviation = away_team_abbreviation,
177 name = away_team_name }
179 -- | Allow us to import JFileGameAwayTeamXml directly.
180 instance XmlImport JFileGameAwayTeamXml
183 -- | The XML representation of a JFile home team. Its corresponding
184 -- database representation (along with that of the away team) is a
185 -- TSN.Team, but their XML representations are different.
186 data JFileGameHomeTeamXml =
187 JFileGameHomeTeamXml {
188 home_team_id :: String,
189 home_team_abbreviation :: Maybe String,
190 home_team_name :: Maybe String }
193 instance ToDb JFileGameHomeTeamXml where
194 -- | The database analogue of an 'JFileGameHomeTeamXml' is
197 type Db JFileGameHomeTeamXml = Team
199 instance FromXml JFileGameHomeTeamXml where
200 -- | To convert a 'JFileGameHomeTeamXml' to a 'Team', we do just
203 from_xml JFileGameHomeTeamXml{..} =
205 team_id = home_team_id,
206 abbreviation = home_team_abbreviation,
207 name = home_team_name }
209 -- | Allow us to import JFileGameHomeTeamXml directly.
210 instance XmlImport JFileGameHomeTeamXml
213 -- * JFileGame/JFileGameXml
215 -- | This is an embedded type within each JFileGame. It has its own
216 -- element, \<Odds_Info\>, but there's only one of them per game. So
217 -- essentially all of these fields belong to a 'JFileGame'. Aaaannnd
218 -- most of them are redundant. We'll (un)pickle them for good
219 -- measure, but in the conversion to the database type, we can drop
220 -- all of the redundant information.
222 -- All of these are optional because TSN does actually leave the
223 -- whole thing empty from time to time.
225 -- We stick \"info\" on the home/away team ids to avoid a name clash
226 -- with the game itself.
228 data JFileGameOddsInfo =
230 db_list_date :: Maybe UTCTime,
231 db_info_home_team_id :: Maybe String, -- redundant (Team)
232 db_info_away_team_id :: Maybe String, -- redundant (Team)
233 db_home_abbr :: Maybe String, -- redundant (Team)
234 db_away_abbr :: Maybe String, -- redundant (Team)
235 db_home_team_name :: Maybe String, -- redundant (Team)
236 db_away_team_name :: Maybe String, -- redundant (Team)
237 db_home_starter :: Maybe String,
238 db_away_starter :: Maybe String,
239 db_game_date :: Maybe UTCTime, -- redundant (JFileGame)
240 db_home_game_key :: Maybe Int,
241 db_away_game_key :: Maybe Int,
242 db_current_timestamp :: Maybe UTCTime,
243 db_live :: Maybe Bool,
248 -- | Another embedded type within 'JFileGame'. These look like,
249 -- \<status numeral=\"4\"\>FINAL\</status\> within the XML, but
250 -- they're in one-to-one correspondence with the games.
252 data JFileGameStatus =
254 db_status_numeral :: Int,
255 db_status :: Maybe String }
259 -- | Database representation of a \<game\> contained within a
260 -- \<message\>, and, implicitly, a \<gamelist\>.
262 -- We've left out the game date, opting instead to combine the
263 -- date/time into the 'db_game_time' field.
267 db_jfile_id :: DefaultKey JFile,
268 db_away_team_id :: DefaultKey Team,
269 db_home_team_id :: DefaultKey Team,
271 db_schedule_id :: Int,
272 db_odds_info :: JFileGameOddsInfo,
273 db_season_type :: Maybe String,
274 db_game_time :: UTCTime,
275 db_vleague :: Maybe String,
276 db_hleague :: Maybe String,
279 db_time_remaining :: Maybe String,
280 db_game_status :: JFileGameStatus }
283 -- | XML representation of a \<game\> contained within a \<message\>,
284 -- and a \<gamelist\>. The Away/Home teams seem to coincide with
285 -- those of 'OddsGame', so we're reusing the DB type via the common
286 -- 'TSN.Team' structure. But the XML types are different, because
287 -- they have different picklers!
292 xml_schedule_id :: Int,
293 xml_odds_info :: JFileGameOddsInfo,
294 xml_season_type :: Maybe String,
295 xml_game_date :: UTCTime,
296 xml_game_time :: UTCTime,
297 xml_vteam :: JFileGameAwayTeamXml,
298 xml_vleague :: Maybe String,
299 xml_hteam :: JFileGameHomeTeamXml,
300 xml_hleague :: Maybe String,
303 xml_time_remaining :: Maybe String,
304 xml_game_status :: JFileGameStatus }
308 -- * JFileGameListXml
310 -- | The XML representation of \<message\> -> \<gamelist\>. This
311 -- element serves only to contain \<game\>s, so we don't store the
312 -- intermediate table in the database.
314 newtype JFileGameListXml =
321 instance ToDb JFileGameXml where
322 -- | The database analogue of an 'JFileGameXml' is
325 type Db JFileGameXml = JFileGame
328 instance Child JFileGameXml where
329 -- | Each 'JFileGameXml' is contained in (i.e. has a foreign key to)
332 type Parent JFileGameXml = JFile
335 instance FromXmlFkTeams JFileGameXml where
336 -- | To convert an 'JFileGameXml' to an 'JFileGame', we add the
337 -- foreign keys for JFile and the home/away teams. We also mash
338 -- the date/time together into one field.
340 from_xml_fk_teams fk fk_away fk_home JFileGameXml{..} =
343 db_away_team_id = fk_away,
344 db_home_team_id = fk_home,
345 db_game_id = xml_game_id,
346 db_schedule_id = xml_schedule_id,
347 db_odds_info = xml_odds_info,
348 db_season_type = xml_season_type,
349 db_game_time = make_game_time xml_game_date xml_game_time,
350 db_vleague = xml_vleague,
351 db_hleague = xml_hleague,
352 db_vscore = xml_vscore,
353 db_hscore = xml_hscore,
354 db_time_remaining = xml_time_remaining,
355 db_game_status = xml_game_status }
357 -- | Make the database \"game time\" from the XML
358 -- date/time. Simply take the day part from one and the time
361 make_game_time d t = UTCTime (utctDay d) (utctDayTime t)
364 -- | This allows us to insert the XML representation
365 -- 'JFileGameXml' directly.
367 instance XmlImportFkTeams JFileGameXml
374 instance DbImport Message where
377 migrate (undefined :: Team)
378 migrate (undefined :: JFile)
379 migrate (undefined :: JFileGame)
382 -- Insert the top-level message
383 msg_id <- insert_xml m
385 -- Now loop through the message's games
386 forM_ (xml_games $ xml_gamelist m) $ \game -> do
387 -- First we insert the home and away teams.
388 away_team_id <- insert_xml_or_select (xml_vteam game)
389 home_team_id <- insert_xml_or_select (xml_hteam game)
391 -- First insert the game, keyed to the "jfile",
392 insert_xml_fk_teams_ msg_id away_team_id home_team_id game
395 return ImportSucceeded
398 mkPersist tsn_codegen_config [groundhog|
406 # Prevent multiple imports of the same message.
407 fields: [db_xml_file_id]
409 - embedded: JFileGameStatus
411 - name: db_status_numeral
412 dbName: status_numeral
416 # Many of the JFileGameOddsInfo fields are redundant and have
418 - embedded: JFileGameOddsInfo
422 - name: db_home_starter
424 - name: db_home_game_key
425 dbName: home_game_key
426 - name: db_away_game_key
427 dbName: away_game_key
428 - name: db_current_timestamp
429 dbName: current_timestamp
443 - name: db_away_team_id
446 - name: db_home_team_id
451 - {name: list_date, dbName: list_date}
452 - {name: home_starter, dbName: home_starter}
453 - {name: away_starter, dbName: away_starter}
454 - {name: home_game_key, dbName: home_game_key}
455 - {name: away_game_key, dbName: away_game_key}
456 - {name: current_timestamp, dbName: current_timestamp}
457 - {name: live, dbName: live}
458 - {name: notes, dbName: notes}
459 - name: db_game_status
461 - {name: status_numeral, dbName: status_numeral}
462 - {name: status, dbName: status}
472 -- | Pickler for the top-level 'Message'.
474 pickle_message :: PU Message
477 xpWrap (from_tuple, to_tuple) $
478 xp6Tuple (xpElem "XML_File_ID" xpInt)
479 (xpElem "heading" xpText)
480 (xpElem "category" xpText)
481 (xpElem "sport" xpText)
483 (xpElem "time_stamp" xp_time_stamp)
485 from_tuple = uncurryN Message
486 to_tuple m = (xml_xml_file_id m,
493 pickle_gamelist :: PU JFileGameListXml
496 xpWrap (to_result, from_result) $ xpList pickle_game
498 to_result = JFileGameListXml
499 from_result = xml_games
504 pickle_game :: PU JFileGameXml
507 xpWrap (from_tuple, to_tuple) $
508 xp14Tuple (xpElem "game_id" xpInt)
509 (xpElem "schedule_id" xpInt)
511 (xpElem "seasontype" (xpOption xpText))
512 (xpElem "Game_Date" xp_date_padded)
513 (xpElem "Game_Time" xp_time)
515 (xpOption $ xpElem "vleague" xpText)
517 (xpOption $ xpElem "hleague" xpText)
518 (xpElem "vscore" xpInt)
519 (xpElem "hscore" xpInt)
520 (xpOption $ xpElem "time_r" xpText)
523 from_tuple = uncurryN JFileGameXml
524 to_tuple m = (xml_game_id m,
536 xml_time_remaining m,
539 pickle_odds_info :: PU JFileGameOddsInfo
542 xpWrap (from_tuple, to_tuple) $
543 xp19Tuple (xpElem "ListDate" (xpOption xp_date))
544 (xpElem "HomeTeamID" (xpOption xpText))
545 (xpElem "AwayTeamID" (xpOption xpText))
546 (xpElem "HomeAbbr" (xpOption xpText))
547 (xpElem "AwayAbbr" (xpOption xpText))
548 (xpElem "HomeTeamName" (xpOption xpText))
549 (xpElem "AwayTeamName" (xpOption xpText))
550 (xpElem "HStarter" (xpOption xpText))
551 (xpElem "AStarter" (xpOption xpText))
552 (xpElem "GameDate" (xpOption xp_datetime))
553 (xpElem "HGameKey" (xpOption xpInt))
554 (xpElem "AGameKey" (xpOption xpInt))
555 (xpElem "CurrentTimeStamp" (xpOption xp_time_dots))
556 (xpElem "Live" (xpOption xpPrim))
557 (xpElem "Notes1" xpText0)
558 (xpElem "Notes2" xpText0)
559 (xpElem "Notes3" xpText0)
560 (xpElem "Notes4" xpText0)
561 (xpElem "Notes5" xpText0)
563 from_tuple (x1,x2,x3,x4,x5,x6,x7,x8,x9,x10,x11,x12,x13,x14,n1,n2,n3,n4,n5) =
564 JFileGameOddsInfo x1 x2 x3 x4 x5 x6 x7 x8 x9 x10 x11 x12 x13 x14 notes
566 notes = intercalate "\n" [n1,n2,n3,n4,n5]
568 to_tuple o = (db_list_date o,
569 db_info_home_team_id o,
570 db_info_away_team_id o,
580 db_current_timestamp o,
584 note_lines = split "\n" (db_notes o)
585 n1 = case note_lines of
588 n2 = case note_lines of
589 (_:notes2:_) -> notes2
591 n3 = case note_lines of
592 (_:_:notes3:_) -> notes3
594 n4 = case note_lines of
595 (_:_:_:notes4:_) -> notes4
597 n5 = case note_lines of
598 (_:_:_:_:notes5:_) -> notes5
601 pickle_home_team :: PU JFileGameHomeTeamXml
604 xpWrap (from_tuple, to_tuple) $
605 xpTriple (xpAttr "teamid" xpText) -- Yeah, they're text.
606 (xpAttr "abbr" (xpOption xpText)) -- Some are blank
607 (xpOption xpText) -- Yup, some are nameless
609 from_tuple = uncurryN JFileGameHomeTeamXml
610 to_tuple t = (home_team_id t,
611 home_team_abbreviation t,
615 pickle_away_team :: PU JFileGameAwayTeamXml
618 xpWrap (from_tuple, to_tuple) $
619 xpTriple (xpAttr "teamid" xpText) -- Yeah, they're text.
620 (xpAttr "abbr" (xpOption xpText)) -- Some are blank
621 (xpOption xpText) -- Yup, some are nameless
623 from_tuple = uncurryN JFileGameAwayTeamXml
624 to_tuple t = (away_team_id t,
625 away_team_abbreviation t,
629 pickle_status :: PU JFileGameStatus
632 xpWrap (from_tuple, to_tuple) $
633 xpPair (xpAttr "numeral" xpInt)
636 from_tuple = uncurry JFileGameStatus
637 to_tuple s = (db_status_numeral s,
646 -- | A list of all tests for this module.
648 jfile_tests :: TestTree
652 [ test_on_delete_cascade,
653 test_pickle_of_unpickle_is_identity,
654 test_unpickle_succeeds ]
657 -- | If we unpickle something and then pickle it, we should wind up
658 -- with the same thing we started with. WARNING: success of this
659 -- test does not mean that unpickling succeeded.
661 test_pickle_of_unpickle_is_identity :: TestTree
662 test_pickle_of_unpickle_is_identity = testGroup "pickle-unpickle tests"
663 [ check "pickle composed with unpickle is the identity"
664 "test/xml/jfilexml.xml",
665 check "pickle composed with unpickle is the identity (missing fields)"
666 "test/xml/jfilexml-missing-fields.xml" ]
668 check desc path = testCase desc $ do
669 (expected, actual) <- pickle_unpickle pickle_message path
674 -- | Make sure we can actually unpickle these things.
676 test_unpickle_succeeds :: TestTree
677 test_unpickle_succeeds = testGroup "unpickle tests"
678 [ check "unpickling succeeds" "test/xml/jfilexml.xml",
679 check "unpickling succeeds (missing fields)"
680 "test/xml/jfilexml-missing-fields.xml" ]
682 check desc path = testCase desc $ do
683 actual <- unpickleable path pickle_message
690 -- | Make sure everything gets deleted when we delete the top-level
693 test_on_delete_cascade :: TestTree
694 test_on_delete_cascade = testGroup "cascading delete tests"
695 [ check "deleting auto_racing_results deletes its children"
696 "test/xml/jfilexml.xml"
698 check "deleting auto_racing_results deletes its children (missing fields)"
699 "test/xml/jfilexml-missing-fields.xml"
702 check desc path expected = testCase desc $ do
703 results <- unsafe_unpickle path pickle_message
704 let a = undefined :: Team
705 let b = undefined :: JFile
706 let c = undefined :: JFileGame
708 actual <- withSqliteConn ":memory:" $ runDbConn $ do
709 runMigration silentMigrationLogger $ do
713 _ <- dbimport results
715 count_a <- countAll a
716 count_b <- countAll b
717 count_c <- countAll c
718 return $ sum [count_a, count_b, count_c]