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