]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blob - src/TSN/XML/Odds.hs
Export the Game types from TSN.XML.Odds.
[dead/htsn-import.git] / src / TSN / XML / Odds.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 \"Odds_XML.dtd\". Each document
10 -- contains a root element \<message\> that contains a bunch of
11 -- other... disorganized... information.
12 --
13 module TSN.XML.Odds (
14 OddsGameAwayTeamXml(..), -- Used in TSN.XML.JFile
15 OddsGameHomeTeamXml(..), -- Used in TSN.XML.JFile
16 OddsGameTeam(..), -- Used in TSN.XML.JFile
17 dtd,
18 pickle_message,
19 -- * Tests
20 odds_tests,
21 -- * WARNING: these are private but exported to silence warnings
22 OddsCasinoConstructor(..),
23 OddsConstructor(..),
24 OddsGame_OddsGameTeamConstructor(..),
25 OddsGameConstructor(..),
26 OddsGameLineConstructor(..),
27 OddsGameTeamConstructor(..) )
28 where
29
30 -- System imports.
31 import Control.Monad ( forM_, join )
32 import Data.Time ( UTCTime(..) )
33 import Data.Tuple.Curry ( uncurryN )
34 import Database.Groundhog (
35 (=.),
36 (==.),
37 countAll,
38 deleteAll,
39 insert_,
40 migrate,
41 runMigration,
42 silentMigrationLogger,
43 update )
44 import Database.Groundhog.Core ( DefaultKey )
45 import Database.Groundhog.Generic ( runDbConn )
46 import Database.Groundhog.Sqlite ( withSqliteConn )
47 import Database.Groundhog.TH (
48 groundhog,
49 mkPersist )
50 import Test.Tasty ( TestTree, testGroup )
51 import Test.Tasty.HUnit ( (@?=), testCase )
52 import Text.Read ( readMaybe )
53 import Text.XML.HXT.Core (
54 PU,
55 xp5Tuple,
56 xp6Tuple,
57 xp8Tuple,
58 xpAttr,
59 xpElem,
60 xpInt,
61 xpList,
62 xpOption,
63 xpPair,
64 xpText,
65 xpTriple,
66 xpWrap )
67
68 -- Local imports.
69 import TSN.Codegen (
70 tsn_codegen_config )
71 import TSN.DbImport ( DbImport(..), ImportResult(..), run_dbmigrate )
72 import TSN.Picklers ( xp_date_padded, xp_time, xp_time_stamp )
73 import TSN.XmlImport ( XmlImport(..), XmlImportFk(..) )
74 import Xml (
75 FromXml(..),
76 FromXmlFk(..),
77 ToDb(..),
78 pickle_unpickle,
79 unpickleable,
80 unsafe_unpickle )
81
82
83 -- | The DTD to which this module corresponds. Used to invoke dbimport.
84 --
85 dtd :: String
86 dtd = "Odds_XML.dtd"
87
88
89 --
90 -- DB/XML data types
91 --
92
93 -- * OddsGameCasino/OddsGameCasinoXml
94
95
96 -- | The casinos should have their own table, but the lines don't
97 -- belong in that table (there is a separate table for
98 -- 'OddsGameLine' which associates the two).
99 --
100 -- We drop the \"Game\" prefix because the casinos really aren't
101 -- children of the games; the XML just makes it seem that way.
102 --
103 data OddsCasino =
104 OddsCasino {
105 casino_client_id :: Int,
106 casino_name :: String }
107 deriving (Eq, Show)
108
109
110 -- | The home/away lines are 'Double's, but the over/under lines are
111 -- textual. If we want to use one data type for both, we have to go
112 -- with a 'String' and then attempt to 'read' a 'Double' later when we
113 -- go to insert the thing.
114 --
115 data OddsGameCasinoXml =
116 OddsGameCasinoXml {
117 xml_casino_client_id :: Int,
118 xml_casino_name :: String,
119 xml_casino_line :: Maybe String }
120 deriving (Eq, Show)
121
122
123 -- | Try to get a 'Double' out of the 'xml_casino_line' which is a
124 -- priori textual (because it might be an over/under line).
125 --
126 home_away_line :: OddsGameCasinoXml -> Maybe Double
127 home_away_line = join . (fmap readMaybe) . xml_casino_line
128
129
130
131 instance ToDb OddsGameCasinoXml where
132 -- | The database representation of an 'OddsGameCasinoXml' is an
133 -- 'OddsCasino'.
134 --
135 type Db OddsGameCasinoXml = OddsCasino
136
137
138 instance FromXml OddsGameCasinoXml where
139 -- | We convert from XML to the database by dropping the line field.
140 --
141 from_xml OddsGameCasinoXml{..} =
142 OddsCasino {
143 casino_client_id = xml_casino_client_id,
144 casino_name = xml_casino_name }
145
146
147 -- | This allows us to insert the XML representation 'OddsGameCasinoXml'
148 -- directly.
149 --
150 instance XmlImport OddsGameCasinoXml
151
152
153 -- * OddsGameTeam
154
155
156 -- | The database representation of teams as they appear in odds
157 -- games.
158 --
159 data OddsGameTeam =
160 OddsGameTeam {
161 db_team_id :: String, -- ^ The home/away team IDs are
162 -- three characters but Postgres
163 -- imposes no performance penalty
164 -- on lengthless text fields, so
165 -- we ignore the probable upper
166 -- bound of three characters.
167 db_abbr :: String,
168 db_team_name :: String }
169 deriving (Eq, Show)
170
171
172 -- * OddsGameHomeTeam/OddsGameHomeTeamXml
173
174 -- | The XML representation of a \<HomeTeam\>, as found in \<Game\>s.
175 --
176 data OddsGameHomeTeamXml =
177 OddsGameHomeTeamXml {
178 xml_home_team_id :: String, -- ^ The home/away team IDs
179 -- are three characters but
180 -- Postgres imposes no
181 -- performance penalty on
182 -- lengthless text fields,
183 -- so we ignore the probable
184 -- upper bound of three
185 -- characters.
186 xml_home_rotation_number :: Int,
187 xml_home_abbr :: String,
188 xml_home_team_name :: String,
189 xml_home_casinos :: [OddsGameCasinoXml] }
190 deriving (Eq, Show)
191
192 instance ToDb OddsGameHomeTeamXml where
193 -- | The database representation of an 'OddsGameHomeTeamXml' is an
194 -- 'OddsGameTeam'.
195 --
196 type Db OddsGameHomeTeamXml = OddsGameTeam
197
198 instance FromXml OddsGameHomeTeamXml where
199 -- | We convert from XML to the database by dropping the lines and
200 -- rotation number (which are specific to the games, not the teams
201 -- themselves).
202 --
203 from_xml OddsGameHomeTeamXml{..} =
204 OddsGameTeam {
205 db_team_id = xml_home_team_id,
206 db_abbr = xml_home_abbr,
207 db_team_name = xml_home_team_name }
208
209 -- | This allows us to insert the XML representation
210 -- 'OddsGameHomeTeamXml' directly.
211 --
212 instance XmlImport OddsGameHomeTeamXml where
213
214
215 -- * OddsGameAwayTeam/OddsGameAwayTeamXml
216
217 -- | The XML representation of a \<AwayTeam\>, as found in \<Game\>s.
218 --
219 data OddsGameAwayTeamXml =
220 OddsGameAwayTeamXml {
221 xml_away_team_id :: String, -- ^ The home/away team IDs are
222 -- three characters but Postgres
223 -- imposes no performance penalty
224 -- on lengthless text fields, so
225 -- we ignore the probable upper
226 -- bound of three characters
227 xml_away_rotation_number :: Int,
228 xml_away_abbr :: String,
229 xml_away_team_name :: String,
230 xml_away_casinos :: [OddsGameCasinoXml] }
231 deriving (Eq, Show)
232
233 instance ToDb OddsGameAwayTeamXml where
234 -- | The database representation of an 'OddsGameAwayTeamXml' is an
235 -- 'OddsGameTeam'.
236 --
237 type Db OddsGameAwayTeamXml = OddsGameTeam
238
239 instance FromXml OddsGameAwayTeamXml where
240 -- | We convert from XML to the database by dropping the lines and
241 -- rotation number (which are specific to the games, not the teams
242 -- themselves).
243 --
244 from_xml OddsGameAwayTeamXml{..} = OddsGameTeam
245 xml_away_team_id
246 xml_away_abbr
247 xml_away_team_name
248
249 -- | This allows us to insert the XML representation
250 -- 'OddsGameAwayTeamXml' directly.
251 --
252 instance XmlImport OddsGameAwayTeamXml where
253
254
255 -- * OddsGame_OddsGameTeam
256
257 -- | Database mapping between games and their home/away teams.
258 --
259 data OddsGame_OddsGameTeam =
260 OddsGame_OddsGameTeam {
261 ogogt_odds_games_id :: DefaultKey OddsGame,
262 ogogt_away_team_id :: DefaultKey OddsGameTeam,
263 ogogt_home_team_id :: DefaultKey OddsGameTeam }
264
265
266 -- * OddsGameOverUnderXml
267
268 -- | XML representation of the over/under. A wrapper around a bunch of
269 -- casino elements.
270 --
271 newtype OddsGameOverUnderXml =
272 OddsGameOverUnderXml { xml_casinos :: [OddsGameCasinoXml] }
273 deriving (Eq, Show)
274
275
276 -- * OddsGameLine
277
278 -- | This database representation of the casino lines can't be
279 -- constructed from the one in the XML. The casinos within
280 -- Game-\>HomeTeam, Game-\>AwayTeam, and Game-\>Over_Under are all more or
281 -- less the same. We don't need a bajillion different tables to
282 -- store that, just one tying the casino/game pair to the three
283 -- lines.
284 --
285 -- The one small difference between the over/under casinos and the
286 -- home/away ones is that the home/away lines are all 'Double's, but
287 -- the over/under lines appear to be textual.
288 --
289 data OddsGameLine =
290 OddsGameLine {
291 ogl_odds_games_id :: DefaultKey OddsGame,
292 ogl_odds_casinos_id :: DefaultKey OddsCasino,
293 ogl_over_under :: Maybe String,
294 ogl_away_line :: Maybe Double,
295 ogl_home_line :: Maybe Double }
296
297
298 -- * OddsGame/OddsGameXml
299
300 -- | Database representation of a game. We retain the rotation number
301 -- of the home/away teams, since those are specific to the game and
302 -- not the teams.
303 --
304 data OddsGame =
305 OddsGame {
306 db_odds_id :: DefaultKey Odds,
307 db_game_id :: Int,
308 db_game_time :: UTCTime, -- ^ Contains both the date and time.
309 db_game_away_team_rotation_number :: Int,
310 db_game_home_team_rotation_number :: Int }
311
312
313 -- | XML representation of an 'OddsGame'.
314 --
315 data OddsGameXml =
316 OddsGameXml {
317 xml_game_id :: Int,
318 xml_game_date :: UTCTime, -- ^ Contains only the date
319 xml_game_time :: UTCTime, -- ^ Contains only the time
320 xml_game_away_team :: OddsGameAwayTeamXml,
321 xml_game_home_team :: OddsGameHomeTeamXml,
322 xml_game_over_under :: OddsGameOverUnderXml }
323 deriving (Eq, Show)
324
325 -- | Pseudo-field that lets us get the 'OddsGameCasinoXml's out of
326 -- xml_game_over_under.
327 --
328 xml_game_over_under_casinos :: OddsGameXml -> [OddsGameCasinoXml]
329 xml_game_over_under_casinos = xml_casinos . xml_game_over_under
330
331
332 instance ToDb OddsGameXml where
333 -- | The database representation of an 'OddsGameXml' is an
334 -- 'OddsGame'.
335 --
336 type Db OddsGameXml = OddsGame
337
338 instance FromXmlFk OddsGameXml where
339 -- | Each 'OddsGameXml' is contained in an 'Odds'. In other words
340 -- the foreign key for 'OddsGame' points to an 'Odds'.
341 --
342 type Parent OddsGameXml = Odds
343
344 -- | To convert from the XML representation to the database one, we
345 -- drop the home/away teams and the casino lines, but retain the
346 -- home/away rotation numbers.
347 --
348 from_xml_fk fk OddsGameXml{..} =
349 OddsGame {
350 db_odds_id = fk,
351 db_game_id = xml_game_id,
352
353 db_game_time = UTCTime
354 (utctDay xml_game_date) -- Take the day part from one,
355 (utctDayTime xml_game_time), -- the time from the other.
356
357 db_game_away_team_rotation_number =
358 (xml_away_rotation_number xml_game_away_team),
359
360 db_game_home_team_rotation_number =
361 (xml_home_rotation_number xml_game_home_team) }
362
363 -- | This lets us insert the XML representation 'OddsGameXml' directly.
364 --
365 instance XmlImportFk OddsGameXml
366
367
368 -- * OddsGameWithNotes
369
370 -- | This is our best guess at what occurs in the Odds_XML
371 -- documents. It looks like each consecutive set of games can
372 -- optionally have some notes appear before it. Each \"note\" comes
373 -- as its own \<Notes\>...\</Notes\> element.
374 --
375 -- The notes are ignored completely in the database; we only bother
376 -- with them to ensure that we're (un)pickling correctly.
377 --
378 -- We can't group the notes with a \"set\" of 'OddsGame's, because
379 -- that leads to ambiguity in parsing. Since we're going to ignore
380 -- the notes anyway, we just stick them with an arbitrary
381 -- game. C'est la vie.
382 --
383 data OddsGameWithNotes =
384 OddsGameWithNotes {
385 notes :: [String],
386 game :: OddsGameXml }
387 deriving (Eq, Show)
388
389
390 -- * Odds/Message
391
392 -- | Database representation of a 'Message'.
393 --
394 data Odds =
395 Odds {
396 db_xml_file_id :: Int,
397 db_sport :: String,
398 db_title :: String,
399 db_line_time :: String, -- ^ We don't parse these as a 'UTCTime'
400 -- because their timezones are ambiguous
401 -- (and the date is less than useful when
402 -- it might be off by an hour).
403 db_time_stamp :: UTCTime }
404
405
406 -- | The XML representation of 'Odds'.
407 --
408 data Message =
409 Message {
410 xml_xml_file_id :: Int,
411 xml_heading :: String,
412 xml_category :: String,
413 xml_sport :: String,
414 xml_title :: String,
415 xml_line_time :: String,
416 xml_games_with_notes :: [OddsGameWithNotes],
417 xml_time_stamp :: UTCTime }
418 deriving (Eq, Show)
419
420 -- | Pseudo-field that lets us get the 'OddsGame's out of
421 -- 'xml_games_with_notes'.
422 --
423 xml_games :: Message -> [OddsGameXml]
424 xml_games m = map game (xml_games_with_notes m)
425
426
427 instance ToDb Message where
428 -- | The database representation of a 'Message' is 'Odds'.
429 --
430 type Db Message = Odds
431
432 instance FromXml Message where
433 -- | To convert from the XML representation to the database one, we
434 -- just drop a bunch of fields.
435 --
436 from_xml Message{..} =
437 Odds {
438 db_xml_file_id = xml_xml_file_id,
439 db_sport = xml_sport,
440 db_title = xml_title,
441 db_line_time = xml_line_time,
442 db_time_stamp = xml_time_stamp }
443
444 -- | This lets us insert the XML representation 'Message' directly.
445 --
446 instance XmlImport Message
447
448
449 --
450 -- Database code
451 --
452
453 -- Groundhog database schema. This must come before the DbImport
454 -- instance definition. Don't know why.
455 mkPersist tsn_codegen_config [groundhog|
456 - entity: Odds
457 constructors:
458 - name: Odds
459 uniques:
460 - name: unique_odds
461 type: constraint
462 # Prevent multiple imports of the same message.
463 fields: [db_xml_file_id]
464
465 - entity: OddsCasino
466 dbName: odds_casinos
467 constructors:
468 - name: OddsCasino
469 uniques:
470 - name: unique_odds_casino
471 type: constraint
472 fields: [casino_client_id]
473
474 - entity: OddsGameTeam
475 dbName: odds_games_teams
476 constructors:
477 - name: OddsGameTeam
478 uniques:
479 - name: unique_odds_games_team
480 type: constraint
481 fields: [db_team_id]
482
483
484 - entity: OddsGame
485 dbName: odds_games
486 constructors:
487 - name: OddsGame
488 fields:
489 - name: db_odds_id
490 reference:
491 onDelete: cascade
492
493 - entity: OddsGameLine
494 dbName: odds_games_lines
495 constructors:
496 - name: OddsGameLine
497 fields:
498 - name: ogl_odds_games_id
499 reference:
500 onDelete: cascade
501 - name: ogl_odds_casinos_id
502 reference:
503 onDelete: cascade
504
505 - entity: OddsGame_OddsGameTeam
506 dbName: odds_games__odds_games_teams
507 constructors:
508 - name: OddsGame_OddsGameTeam
509 fields:
510 - name: ogogt_odds_games_id
511 reference:
512 onDelete: cascade
513 - name: ogogt_away_team_id
514 reference:
515 onDelete: cascade
516 - name: ogogt_home_team_id
517 reference:
518 onDelete: cascade
519 |]
520
521 instance DbImport Message where
522 dbmigrate _=
523 run_dbmigrate $ do
524 migrate (undefined :: Odds)
525 migrate (undefined :: OddsCasino)
526 migrate (undefined :: OddsGameTeam)
527 migrate (undefined :: OddsGame)
528 migrate (undefined :: OddsGame_OddsGameTeam)
529 migrate (undefined :: OddsGameLine)
530
531 dbimport m = do
532 -- Insert the root "odds" element and acquire its primary key (id).
533 odds_id <- insert_xml m
534
535 forM_ (xml_games m) $ \g -> do
536 -- Next, we insert the home and away teams. We do this before
537 -- inserting the game itself because the game has two foreign keys
538 -- pointing to odds_games_teams.
539 -- Next to insert the home and away teams.
540 away_team_id <- insert_xml_or_select (xml_game_away_team g)
541 home_team_id <- insert_xml_or_select (xml_game_home_team g)
542
543 -- Now insert the game, keyed to the "odds",
544 game_id <- insert_xml_fk odds_id g
545
546 -- Insert a record into odds_games__odds_games_teams mapping the
547 -- home/away teams to this game. Use the full record syntax
548 -- because the types would let us mix up the home/away teams.
549 insert_ OddsGame_OddsGameTeam {
550 ogogt_odds_games_id = game_id,
551 ogogt_away_team_id = away_team_id,
552 ogogt_home_team_id = home_team_id }
553
554 -- Finaly, we insert the lines. The over/under entries for this
555 -- game and the lines for the casinos all wind up in the same
556 -- table, odds_games_lines. We can insert the over/under entries
557 -- freely with empty away/home lines:
558 forM_ (xml_game_over_under_casinos g) $ \c -> do
559 -- Start by inderting the casino.
560 ou_casino_id <- insert_xml_or_select c
561
562 -- Now add the over/under entry with the casino's id.
563 let ogl = OddsGameLine {
564 ogl_odds_games_id = game_id,
565 ogl_odds_casinos_id = ou_casino_id,
566 ogl_over_under = (xml_casino_line c),
567 ogl_away_line = Nothing,
568 ogl_home_line = Nothing }
569
570 insert_ ogl
571
572 -- ...but then when we insert the home/away team lines, we
573 -- prefer to update the existing entry rather than overwrite it
574 -- or add a new record.
575 forM_ (xml_away_casinos $ xml_game_away_team g) $ \c -> do
576 -- insert, or more likely retrieve the existing, casino
577 a_casino_id <- insert_xml_or_select c
578
579 -- Get a Maybe Double instead of the Maybe String that's in there.
580 let away_line = home_away_line c
581
582 -- Unconditionally update that casino's away team line with ours.
583 update [Ogl_Away_Line =. away_line] $ -- WHERE
584 Ogl_Odds_Casinos_Id ==. a_casino_id
585
586 -- Repeat all that for the home team.
587 forM_ (xml_home_casinos $ xml_game_home_team g) $ \c ->do
588 h_casino_id <- insert_xml_or_select c
589 let home_line = home_away_line c
590 update [Ogl_Home_Line =. home_line] $ -- WHERE
591 Ogl_Odds_Casinos_Id ==. h_casino_id
592
593 return game_id
594
595 return ImportSucceeded
596
597
598 --
599 -- Pickling
600 --
601
602 -- | Pickler for an 'OddsGame' optionally preceded by some notes.
603 --
604 pickle_game_with_notes :: PU OddsGameWithNotes
605 pickle_game_with_notes =
606 xpWrap (from_pair, to_pair) $
607 xpPair
608 (xpList $ xpElem "Notes" xpText)
609 pickle_game
610 where
611 from_pair = uncurry OddsGameWithNotes
612 to_pair OddsGameWithNotes{..} = (notes, game)
613
614
615 -- | Pickler for an 'OddsGameCasinoXml'.
616 --
617 pickle_casino :: PU OddsGameCasinoXml
618 pickle_casino =
619 xpElem "Casino" $
620 xpWrap (from_tuple, to_tuple) $
621 xpTriple
622 (xpAttr "ClientID" xpInt)
623 (xpAttr "Name" xpText)
624 (xpOption xpText)
625 where
626 from_tuple = uncurryN OddsGameCasinoXml
627 -- Use record wildcards to avoid unused field warnings.
628 to_tuple OddsGameCasinoXml{..} = (xml_casino_client_id,
629 xml_casino_name,
630 xml_casino_line)
631
632
633 -- | Pickler for an 'OddsGameHomeTeamXml'.
634 --
635 pickle_home_team :: PU OddsGameHomeTeamXml
636 pickle_home_team =
637 xpElem "HomeTeam" $
638 xpWrap (from_tuple, to_tuple) $
639 xp5Tuple
640 (xpElem "HomeTeamID" xpText)
641 (xpElem "HomeRotationNumber" xpInt)
642 (xpElem "HomeAbbr" xpText)
643 (xpElem "HomeTeamName" xpText)
644 (xpList pickle_casino)
645 where
646 from_tuple = uncurryN OddsGameHomeTeamXml
647 -- Use record wildcards to avoid unused field warnings.
648 to_tuple OddsGameHomeTeamXml{..} = (xml_home_team_id,
649 xml_home_rotation_number,
650 xml_home_abbr,
651 xml_home_team_name,
652 xml_home_casinos)
653
654
655 -- | Pickler for an 'OddsGameAwayTeamXml'.
656 --
657 pickle_away_team :: PU OddsGameAwayTeamXml
658 pickle_away_team =
659 xpElem "AwayTeam" $
660 xpWrap (from_tuple, to_tuple) $
661 xp5Tuple
662 (xpElem "AwayTeamID" xpText)
663 (xpElem "AwayRotationNumber" xpInt)
664 (xpElem "AwayAbbr" xpText)
665 (xpElem "AwayTeamName" xpText)
666 (xpList pickle_casino)
667 where
668 from_tuple = uncurryN OddsGameAwayTeamXml
669 -- Use record wildcards to avoid unused field warnings.
670 to_tuple OddsGameAwayTeamXml{..} = (xml_away_team_id,
671 xml_away_rotation_number,
672 xml_away_abbr,
673 xml_away_team_name,
674 xml_away_casinos)
675
676
677
678 -- | Pickler for an 'OddsGameOverUnderXml'.
679 --
680 pickle_over_under :: PU OddsGameOverUnderXml
681 pickle_over_under =
682 xpElem "Over_Under" $
683 xpWrap (to_newtype, from_newtype) $
684 xpList pickle_casino
685 where
686 from_newtype (OddsGameOverUnderXml cs) = cs
687 to_newtype = OddsGameOverUnderXml
688
689
690 -- | Pickler for an 'OddsGameXml'.
691 --
692 pickle_game :: PU OddsGameXml
693 pickle_game =
694 xpElem "Game" $
695 xpWrap (from_tuple, to_tuple) $
696 xp6Tuple
697 (xpElem "GameID" xpInt)
698 (xpElem "Game_Date" xp_date_padded)
699 (xpElem "Game_Time" xp_time)
700 pickle_away_team
701 pickle_home_team
702 pickle_over_under
703 where
704 from_tuple = uncurryN OddsGameXml
705 -- Use record wildcards to avoid unused field warnings.
706 to_tuple OddsGameXml{..} = (xml_game_id,
707 xml_game_date,
708 xml_game_time,
709 xml_game_away_team,
710 xml_game_home_team,
711 xml_game_over_under)
712
713
714 -- | Pickler for the top-level 'Message'.
715 --
716 pickle_message :: PU Message
717 pickle_message =
718 xpElem "message" $
719 xpWrap (from_tuple, to_tuple) $
720 xp8Tuple (xpElem "XML_File_ID" xpInt)
721 (xpElem "heading" xpText)
722 (xpElem "category" xpText)
723 (xpElem "sport" xpText)
724 (xpElem "Title" xpText)
725 (xpElem "Line_Time" xpText)
726 (xpList pickle_game_with_notes)
727 (xpElem "time_stamp" xp_time_stamp)
728 where
729 from_tuple = uncurryN Message
730 to_tuple m = (xml_xml_file_id m,
731 xml_heading m,
732 xml_category m,
733 xml_sport m,
734 xml_title m,
735 xml_line_time m,
736 xml_games_with_notes m,
737 xml_time_stamp m)
738
739
740 --
741 -- Tasty Tests
742 --
743
744 -- | A list of all tests for this module.
745 --
746 odds_tests :: TestTree
747 odds_tests =
748 testGroup
749 "Odds tests"
750 [ test_on_delete_cascade,
751 test_pickle_of_unpickle_is_identity,
752 test_unpickle_succeeds ]
753
754
755 -- | If we unpickle something and then pickle it, we should wind up
756 -- with the same thing we started with. WARNING: success of this
757 -- test does not mean that unpickling succeeded.
758 --
759 test_pickle_of_unpickle_is_identity :: TestTree
760 test_pickle_of_unpickle_is_identity = testGroup "pickle-unpickle tests"
761 [ check "pickle composed with unpickle is the identity"
762 "test/xml/Odds_XML.xml",
763
764 check "pickle composed with unpickle is the identity (non-int team_id)"
765 "test/xml/Odds_XML-noninteger-team-id.xml",
766
767 check "pickle composed with unpickle is the identity (positive(+) line)"
768 "test/xml/Odds_XML-positive-line.xml",
769
770 check "pickle composed with unpickle is the identity (large file)"
771 "test/xml/Odds_XML-largefile.xml" ]
772 where
773 check desc path = testCase desc $ do
774 (expected, actual) <- pickle_unpickle pickle_message path
775 actual @?= expected
776
777
778 -- | Make sure we can actually unpickle these things.
779 --
780 test_unpickle_succeeds :: TestTree
781 test_unpickle_succeeds = testGroup "unpickle tests"
782 [ check "unpickling succeeds"
783 "test/xml/Odds_XML.xml",
784
785 check "unpickling succeeds (non-int team_id)"
786 "test/xml/Odds_XML-noninteger-team-id.xml",
787
788 check "unpickling succeeds (positive(+) line)"
789 "test/xml/Odds_XML-positive-line.xml",
790
791 check "unpickling succeeds (large file)"
792 "test/xml/Odds_XML-largefile.xml" ]
793 where
794 check desc path = testCase desc $ do
795 actual <- unpickleable path pickle_message
796 let expected = True
797 actual @?= expected
798
799
800 -- | Make sure everything gets deleted when we delete the top-level
801 -- record.
802 --
803 test_on_delete_cascade :: TestTree
804 test_on_delete_cascade = testGroup "cascading delete tests"
805 [ check "deleting odds deletes its children"
806 "test/xml/Odds_XML.xml"
807 13 -- 5 casinos, 8 teams
808 ,
809
810 check "deleting odds deletes its children (non-int team_id)"
811 "test/xml/Odds_XML-noninteger-team-id.xml"
812 51 -- 5 casinos, 46 teams
813 ,
814
815 check "deleting odds deleted its children (positive(+) line)"
816 "test/xml/Odds_XML-positive-line.xml"
817 17 -- 5 casinos, 12 teams
818 ,
819
820 check "deleting odds deleted its children (large file)"
821 "test/xml/Odds_XML-largefile.xml"
822 189 -- 5 casinos, 184 teams
823 ]
824 where
825 check desc path expected = testCase desc $ do
826 odds <- unsafe_unpickle path pickle_message
827 let a = undefined :: Odds
828 let b = undefined :: OddsCasino
829 let c = undefined :: OddsGameTeam
830 let d = undefined :: OddsGame
831 let e = undefined :: OddsGame_OddsGameTeam
832 let f = undefined :: OddsGameLine
833 actual <- withSqliteConn ":memory:" $ runDbConn $ do
834 runMigration silentMigrationLogger $ do
835 migrate a
836 migrate b
837 migrate c
838 migrate d
839 migrate e
840 migrate f
841 _ <- dbimport odds
842 deleteAll a
843 count_a <- countAll a
844 count_b <- countAll b
845 count_c <- countAll c
846 count_d <- countAll d
847 count_e <- countAll e
848 count_f <- countAll f
849 return $ sum [count_a, count_b, count_c,
850 count_d, count_e, count_f ]
851 actual @?= expected