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