]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blob - src/TSN/XML/Odds.hs
Add League_Name, AStarter, and HStarter support to 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 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 xp6Tuple,
52 xp8Tuple,
53 xpAttr,
54 xpElem,
55 xpInt,
56 xpList,
57 xpOption,
58 xpPair,
59 xpText,
60 xpTriple,
61 xpWrap )
62
63 -- Local imports.
64 import TSN.Codegen (
65 tsn_codegen_config )
66 import TSN.DbImport ( DbImport(..), ImportResult(..), run_dbmigrate )
67 import TSN.Picklers ( xp_date_padded, xp_time, xp_time_stamp )
68 import TSN.Team ( Team(..) )
69 import TSN.XmlImport ( XmlImport(..), XmlImportFk(..) )
70 import Xml (
71 FromXml(..),
72 FromXmlFk(..),
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 team_abbreviation = Just xml_home_team_abbr,
191 team_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 -- * OddsGame_OddsGameTeam
242
243 -- | Database mapping between games and their home/away teams.
244 --
245 data OddsGame_Team =
246 OddsGame_Team {
247 ogt_odds_games_id :: DefaultKey OddsGame,
248 ogt_away_team_id :: DefaultKey Team,
249 ogt_home_team_id :: DefaultKey Team }
250
251
252 -- * OddsGameOverUnderXml
253
254 -- | XML representation of the over/under. A wrapper around a bunch of
255 -- casino elements.
256 --
257 newtype OddsGameOverUnderXml =
258 OddsGameOverUnderXml { xml_casinos :: [OddsGameCasinoXml] }
259 deriving (Eq, Show)
260
261
262 -- * OddsGameLine
263
264 -- | This database representation of the casino lines can't be
265 -- constructed from the one in the XML. The casinos within
266 -- Game-\>HomeTeam, Game-\>AwayTeam, and Game-\>Over_Under are all more or
267 -- less the same. We don't need a bajillion different tables to
268 -- store that, just one tying the casino/game pair to the three
269 -- lines.
270 --
271 -- The one small difference between the over/under casinos and the
272 -- home/away ones is that the home/away lines are all 'Double's, but
273 -- the over/under lines appear to be textual.
274 --
275 data OddsGameLine =
276 OddsGameLine {
277 ogl_odds_games_id :: DefaultKey OddsGame,
278 ogl_odds_casinos_id :: DefaultKey OddsCasino,
279 ogl_over_under :: Maybe String,
280 ogl_away_line :: Maybe Double,
281 ogl_home_line :: Maybe Double }
282
283
284 -- * OddsGame/OddsGameXml
285
286 -- | Database representation of a game. We retain the rotation number
287 -- of the home/away teams, since those are specific to the game and
288 -- not the teams.
289 --
290 data OddsGame =
291 OddsGame {
292 db_odds_id :: DefaultKey Odds,
293 db_game_id :: Int,
294 db_game_time :: UTCTime, -- ^ Contains both the date and time.
295 db_away_team_rotation_number :: Int,
296 db_home_team_rotation_number :: Int,
297 db_away_team_starter_id :: Maybe Int,
298 db_away_team_starter_name :: Maybe String,
299 db_home_team_starter_id :: Maybe Int,
300 db_home_team_starter_name :: Maybe String }
301
302
303 -- | XML representation of an 'OddsGame'.
304 --
305 data OddsGameXml =
306 OddsGameXml {
307 xml_game_id :: Int,
308 xml_game_date :: UTCTime, -- ^ Contains only the date
309 xml_game_time :: UTCTime, -- ^ Contains only the time
310 xml_away_team :: OddsGameAwayTeamXml,
311 xml_home_team :: OddsGameHomeTeamXml,
312 xml_over_under :: OddsGameOverUnderXml }
313 deriving (Eq, Show)
314
315 -- | Pseudo-field that lets us get the 'OddsGameCasinoXml's out of
316 -- xml_over_under.
317 --
318 xml_over_under_casinos :: OddsGameXml -> [OddsGameCasinoXml]
319 xml_over_under_casinos = xml_casinos . xml_over_under
320
321
322 instance ToDb OddsGameXml where
323 -- | The database representation of an 'OddsGameXml' is an
324 -- 'OddsGame'.
325 --
326 type Db OddsGameXml = OddsGame
327
328 instance FromXmlFk OddsGameXml where
329 -- | Each 'OddsGameXml' is contained in an 'Odds'. In other words
330 -- the foreign key for 'OddsGame' points to an 'Odds'.
331 --
332 type Parent OddsGameXml = Odds
333
334 -- | To convert from the XML representation to the database one, we
335 -- drop the home/away teams and the casino lines, but retain the
336 -- home/away rotation numbers and the starters.
337 --
338 from_xml_fk fk OddsGameXml{..} =
339 OddsGame {
340 db_odds_id = fk,
341 db_game_id = xml_game_id,
342
343 db_game_time = UTCTime
344 (utctDay xml_game_date) -- Take the day part from one,
345 (utctDayTime xml_game_time), -- the time from the other.
346
347 db_away_team_rotation_number =
348 (xml_away_team_rotation_number xml_away_team),
349
350 db_home_team_rotation_number =
351 (xml_home_team_rotation_number xml_home_team),
352
353 db_away_team_starter_id =
354 (fmap fst $ xml_away_team_starter xml_away_team),
355
356 db_away_team_starter_name =
357 (fmap snd $ xml_away_team_starter xml_away_team),
358
359 db_home_team_starter_id =
360 (fmap fst $ xml_home_team_starter xml_home_team),
361
362 db_home_team_starter_name =
363 (fmap snd $ xml_home_team_starter xml_home_team) }
364
365
366 -- | This lets us insert the XML representation 'OddsGameXml' directly.
367 --
368 instance XmlImportFk OddsGameXml
369
370
371 -- * OddsGameWithNotes
372
373 -- | This is our best guess at what occurs in the Odds_XML
374 -- documents. It looks like each consecutive set of games can
375 -- optionally have some notes appear before it. Each \"note\" comes
376 -- as its own \<Notes\>...\</Notes\> element.
377 --
378 -- The notes are ignored completely in the database; we only bother
379 -- with them to ensure that we're (un)pickling correctly.
380 --
381 -- We can't group the notes with a \"set\" of 'OddsGame's, because
382 -- that leads to ambiguity in parsing. Since we're going to ignore
383 -- the notes anyway, we just stick them with an arbitrary
384 -- game. C'est la vie.
385 --
386 -- We have to take the same approach with the league. The
387 -- \<League_Name\> elements are sitting outside of the games, and
388 -- are presumably supposed to be interpreted in \"chronological\"
389 -- order; i.e. the current league stays the same until we see
390 -- another \<League_Name\> element. Unfortunately, that's not how
391 -- XML works. So we're forced to ignore the league in the database
392 -- and pull the same trick, pairing them with games.
393 --
394 data OddsGameWithNotes =
395 OddsGameWithNotes {
396 league :: Maybe String,
397 notes :: [String],
398 game :: OddsGameXml }
399 deriving (Eq, Show)
400
401
402 -- * Odds/Message
403
404 -- | Database representation of a 'Message'.
405 --
406 data Odds =
407 Odds {
408 db_xml_file_id :: Int,
409 db_sport :: String,
410 db_title :: String,
411 db_line_time :: String, -- ^ We don't parse these as a 'UTCTime'
412 -- because their timezones are ambiguous
413 -- (and the date is less than useful when
414 -- it might be off by an hour).
415 db_time_stamp :: UTCTime }
416
417
418 -- | The XML representation of 'Odds'.
419 --
420 data Message =
421 Message {
422 xml_xml_file_id :: Int,
423 xml_heading :: String,
424 xml_category :: String,
425 xml_sport :: String,
426 xml_title :: String,
427 xml_line_time :: String,
428 xml_games_with_notes :: [OddsGameWithNotes],
429 xml_time_stamp :: UTCTime }
430 deriving (Eq, Show)
431
432 -- | Pseudo-field that lets us get the 'OddsGame's out of
433 -- 'xml_games_with_notes'.
434 --
435 xml_games :: Message -> [OddsGameXml]
436 xml_games m = map game (xml_games_with_notes m)
437
438
439 instance ToDb Message where
440 -- | The database representation of a 'Message' is 'Odds'.
441 --
442 type Db Message = Odds
443
444 instance FromXml Message where
445 -- | To convert from the XML representation to the database one, we
446 -- just drop a bunch of fields.
447 --
448 from_xml Message{..} =
449 Odds {
450 db_xml_file_id = xml_xml_file_id,
451 db_sport = xml_sport,
452 db_title = xml_title,
453 db_line_time = xml_line_time,
454 db_time_stamp = xml_time_stamp }
455
456 -- | This lets us insert the XML representation 'Message' directly.
457 --
458 instance XmlImport Message
459
460
461 --
462 -- Database code
463 --
464
465 -- Groundhog database schema. This must come before the DbImport
466 -- instance definition. Don't know why.
467 mkPersist tsn_codegen_config [groundhog|
468 - entity: Odds
469 constructors:
470 - name: Odds
471 uniques:
472 - name: unique_odds
473 type: constraint
474 # Prevent multiple imports of the same message.
475 fields: [db_xml_file_id]
476
477 - entity: OddsCasino
478 dbName: odds_casinos
479 constructors:
480 - name: OddsCasino
481 uniques:
482 - name: unique_odds_casino
483 type: constraint
484 fields: [casino_client_id]
485
486 - entity: OddsGame
487 dbName: odds_games
488 constructors:
489 - name: OddsGame
490 fields:
491 - name: db_odds_id
492 reference:
493 onDelete: cascade
494
495 - entity: OddsGameLine
496 dbName: odds_games_lines
497 constructors:
498 - name: OddsGameLine
499 fields:
500 - name: ogl_odds_games_id
501 reference:
502 onDelete: cascade
503 - name: ogl_odds_casinos_id
504 reference:
505 onDelete: cascade
506
507 - entity: OddsGame_Team
508 dbName: odds_games__teams
509 constructors:
510 - name: OddsGame_Team
511 fields:
512 - name: ogt_odds_games_id
513 reference:
514 onDelete: cascade
515 - name: ogt_away_team_id
516 reference:
517 onDelete: cascade
518 - name: ogt_home_team_id
519 reference:
520 onDelete: cascade
521 |]
522
523 instance DbImport Message where
524 dbmigrate _=
525 run_dbmigrate $ do
526 migrate (undefined :: Team)
527 migrate (undefined :: Odds)
528 migrate (undefined :: OddsCasino)
529 migrate (undefined :: OddsGame)
530 migrate (undefined :: OddsGame_Team)
531 migrate (undefined :: OddsGameLine)
532
533 dbimport m = do
534 -- Insert the root "odds" element and acquire its primary key (id).
535 odds_id <- insert_xml m
536
537 forM_ (xml_games m) $ \g -> do
538 -- Next, we insert the home and away teams. We do this before
539 -- inserting the game itself because the game has two foreign keys
540 -- pointing to "teams".
541 away_team_id <- insert_xml_or_select (xml_away_team g)
542 home_team_id <- insert_xml_or_select (xml_home_team g)
543
544 -- Now insert the game, keyed to the "odds",
545 game_id <- insert_xml_fk odds_id g
546
547 -- Insert a record into odds_games__teams mapping the
548 -- home/away teams to this game. Use the full record syntax
549 -- because the types would let us mix up the home/away teams.
550 insert_ OddsGame_Team {
551 ogt_odds_games_id = game_id,
552 ogt_away_team_id = away_team_id,
553 ogt_home_team_id = home_team_id }
554
555 -- Finaly, we insert the lines. The over/under entries for this
556 -- game and the lines for the casinos all wind up in the same
557 -- table, odds_games_lines. We can insert the over/under entries
558 -- freely with empty away/home lines:
559 forM_ (xml_over_under_casinos g) $ \c -> do
560 -- Start by inderting the casino.
561 ou_casino_id <- insert_xml_or_select c
562
563 -- Now add the over/under entry with the casino's id.
564 let ogl = OddsGameLine {
565 ogl_odds_games_id = game_id,
566 ogl_odds_casinos_id = ou_casino_id,
567 ogl_over_under = (xml_casino_line c),
568 ogl_away_line = Nothing,
569 ogl_home_line = Nothing }
570
571 insert_ ogl
572
573 -- ...but then when we insert the home/away team lines, we
574 -- prefer to update the existing entry rather than overwrite it
575 -- or add a new record.
576 forM_ (xml_away_team_casinos $ xml_away_team g) $ \c -> do
577 -- insert, or more likely retrieve the existing, casino
578 a_casino_id <- insert_xml_or_select c
579
580 -- Get a Maybe Double instead of the Maybe String that's in there.
581 let away_line = home_away_line c
582
583 -- Unconditionally update that casino's away team line with ours.
584 update [Ogl_Away_Line =. away_line] $ -- WHERE
585 Ogl_Odds_Casinos_Id ==. a_casino_id
586
587 -- Repeat all that for the home team.
588 forM_ (xml_home_team_casinos $ xml_home_team g) $ \c ->do
589 h_casino_id <- insert_xml_or_select c
590 let home_line = home_away_line c
591 update [Ogl_Home_Line =. home_line] $ -- WHERE
592 Ogl_Odds_Casinos_Id ==. h_casino_id
593
594 return game_id
595
596 return ImportSucceeded
597
598
599 --
600 -- Pickling
601 --
602
603 -- | Pickler for an 'OddsGame' optionally preceded by some notes.
604 --
605 pickle_game_with_notes :: PU OddsGameWithNotes
606 pickle_game_with_notes =
607 xpWrap (from_pair, to_pair) $
608 xpTriple
609 (xpOption $ xpElem "League_Name" xpText)
610 (xpList $ xpElem "Notes" xpText)
611 pickle_game
612 where
613 from_pair = uncurryN OddsGameWithNotes
614 to_pair OddsGameWithNotes{..} = (league, notes, game)
615
616
617 -- | Pickler for an 'OddsGameCasinoXml'.
618 --
619 pickle_casino :: PU OddsGameCasinoXml
620 pickle_casino =
621 xpElem "Casino" $
622 xpWrap (from_tuple, to_tuple) $
623 xpTriple
624 (xpAttr "ClientID" xpInt)
625 (xpAttr "Name" xpText)
626 (xpOption xpText)
627 where
628 from_tuple = uncurryN OddsGameCasinoXml
629 -- Use record wildcards to avoid unused field warnings.
630 to_tuple OddsGameCasinoXml{..} = (xml_casino_client_id,
631 xml_casino_name,
632 xml_casino_line)
633
634
635 -- | Pickler for an 'OddsGameHomeTeamXml'.
636 --
637 pickle_home_team :: PU OddsGameHomeTeamXml
638 pickle_home_team =
639 xpElem "HomeTeam" $
640 xpWrap (from_tuple, to_tuple) $
641 xp6Tuple
642 (xpElem "HomeTeamID" xpText)
643 (xpElem "HomeRotationNumber" xpInt)
644 (xpElem "HomeAbbr" xpText)
645 (xpElem "HomeTeamName" xpText)
646 (-- This is an ugly way to get both the HStarter ID attribute
647 -- and contents.
648 xpOption (xpElem "HStarter" $ xpPair (xpAttr "ID" xpInt) xpText))
649 (xpList pickle_casino)
650 where
651 from_tuple = uncurryN OddsGameHomeTeamXml
652
653 -- Use record wildcards to avoid unused field warnings.
654 to_tuple OddsGameHomeTeamXml{..} = (xml_home_team_id,
655 xml_home_team_rotation_number,
656 xml_home_team_abbr,
657 xml_home_team_name,
658 xml_home_team_starter,
659 xml_home_team_casinos)
660
661 -- | Pickler for an 'OddsGameAwayTeamXml'.
662 --
663 pickle_away_team :: PU OddsGameAwayTeamXml
664 pickle_away_team =
665 xpElem "AwayTeam" $
666 xpWrap (from_tuple, to_tuple) $
667 xp6Tuple
668 (xpElem "AwayTeamID" xpText)
669 (xpElem "AwayRotationNumber" xpInt)
670 (xpElem "AwayAbbr" xpText)
671 (xpElem "AwayTeamName" xpText)
672 (-- This is an ugly way to get both the AStarter ID attribute
673 -- and contents.
674 xpOption (xpElem "AStarter" $ xpPair (xpAttr "ID" xpInt) xpText))
675 (xpList pickle_casino)
676 where
677 from_tuple = uncurryN OddsGameAwayTeamXml
678
679 -- Use record wildcards to avoid unused field warnings.
680 to_tuple OddsGameAwayTeamXml{..} = (xml_away_team_id,
681 xml_away_team_rotation_number,
682 xml_away_team_abbr,
683 xml_away_team_name,
684 xml_away_team_starter,
685 xml_away_team_casinos)
686
687
688
689 -- | Pickler for an 'OddsGameOverUnderXml'.
690 --
691 pickle_over_under :: PU OddsGameOverUnderXml
692 pickle_over_under =
693 xpElem "Over_Under" $
694 xpWrap (to_newtype, from_newtype) $
695 xpList pickle_casino
696 where
697 from_newtype (OddsGameOverUnderXml cs) = cs
698 to_newtype = OddsGameOverUnderXml
699
700
701 -- | Pickler for an 'OddsGameXml'.
702 --
703 pickle_game :: PU OddsGameXml
704 pickle_game =
705 xpElem "Game" $
706 xpWrap (from_tuple, to_tuple) $
707 xp6Tuple
708 (xpElem "GameID" xpInt)
709 (xpElem "Game_Date" xp_date_padded)
710 (xpElem "Game_Time" xp_time)
711 pickle_away_team
712 pickle_home_team
713 pickle_over_under
714 where
715 from_tuple = uncurryN OddsGameXml
716 -- Use record wildcards to avoid unused field warnings.
717 to_tuple OddsGameXml{..} = (xml_game_id,
718 xml_game_date,
719 xml_game_time,
720 xml_away_team,
721 xml_home_team,
722 xml_over_under)
723
724
725 -- | Pickler for the top-level 'Message'.
726 --
727 pickle_message :: PU Message
728 pickle_message =
729 xpElem "message" $
730 xpWrap (from_tuple, to_tuple) $
731 xp8Tuple (xpElem "XML_File_ID" xpInt)
732 (xpElem "heading" xpText)
733 (xpElem "category" xpText)
734 (xpElem "sport" xpText)
735 (xpElem "Title" xpText)
736 (xpElem "Line_Time" xpText)
737 (xpList pickle_game_with_notes)
738 (xpElem "time_stamp" xp_time_stamp)
739 where
740 from_tuple = uncurryN Message
741 to_tuple m = (xml_xml_file_id m,
742 xml_heading m,
743 xml_category m,
744 xml_sport m,
745 xml_title m,
746 xml_line_time m,
747 xml_games_with_notes m,
748 xml_time_stamp m)
749
750
751 --
752 -- Tasty Tests
753 --
754
755 -- | A list of all tests for this module.
756 --
757 odds_tests :: TestTree
758 odds_tests =
759 testGroup
760 "Odds tests"
761 [ test_on_delete_cascade,
762 test_pickle_of_unpickle_is_identity,
763 test_unpickle_succeeds ]
764
765
766 -- | If we unpickle something and then pickle it, we should wind up
767 -- with the same thing we started with. WARNING: success of this
768 -- test does not mean that unpickling succeeded.
769 --
770 test_pickle_of_unpickle_is_identity :: TestTree
771 test_pickle_of_unpickle_is_identity = testGroup "pickle-unpickle tests"
772 [ check "pickle composed with unpickle is the identity"
773 "test/xml/Odds_XML.xml",
774
775 check "pickle composed with unpickle is the identity (non-int team_id)"
776 "test/xml/Odds_XML-noninteger-team-id.xml",
777
778 check "pickle composed with unpickle is the identity (positive(+) line)"
779 "test/xml/Odds_XML-positive-line.xml",
780
781 check "pickle composed with unpickle is the identity (large file)"
782 "test/xml/Odds_XML-largefile.xml",
783
784 check "pickle composed with unpickle is the identity (league name)"
785 "test/xml/Odds_XML-league-name.xml" ]
786 where
787 check desc path = testCase desc $ do
788 (expected, actual) <- pickle_unpickle pickle_message path
789 actual @?= expected
790
791
792 -- | Make sure we can actually unpickle these things.
793 --
794 test_unpickle_succeeds :: TestTree
795 test_unpickle_succeeds = testGroup "unpickle tests"
796 [ check "unpickling succeeds"
797 "test/xml/Odds_XML.xml",
798
799 check "unpickling succeeds (non-int team_id)"
800 "test/xml/Odds_XML-noninteger-team-id.xml",
801
802 check "unpickling succeeds (positive(+) line)"
803 "test/xml/Odds_XML-positive-line.xml",
804
805 check "unpickling succeeds (large file)"
806 "test/xml/Odds_XML-largefile.xml",
807
808 check "unpickling succeeds (league name)"
809 "test/xml/Odds_XML-league-name.xml" ]
810 where
811 check desc path = testCase desc $ do
812 actual <- unpickleable path pickle_message
813 let expected = True
814 actual @?= expected
815
816
817 -- | Make sure everything gets deleted when we delete the top-level
818 -- record. The casinos and teams should be left behind.
819 --
820 test_on_delete_cascade :: TestTree
821 test_on_delete_cascade = testGroup "cascading delete tests"
822 [ check "deleting odds deletes its children"
823 "test/xml/Odds_XML.xml"
824 13 -- 5 casinos, 8 teams
825 ,
826
827 check "deleting odds deletes its children (non-int team_id)"
828 "test/xml/Odds_XML-noninteger-team-id.xml"
829 51 -- 5 casinos, 46 teams
830 ,
831
832 check "deleting odds deleted its children (positive(+) line)"
833 "test/xml/Odds_XML-positive-line.xml"
834 17 -- 5 casinos, 12 teams
835 ,
836
837 check "deleting odds deleted its children (large file)"
838 "test/xml/Odds_XML-largefile.xml"
839 189 -- 5 casinos, 184 teams
840 ,
841 check "deleting odds deleted its children (league name)"
842 "test/xml/Odds_XML-league-name.xml"
843 35 -- 5 casinos, 30 teams
844 ]
845 where
846 check desc path expected = testCase desc $ do
847 odds <- unsafe_unpickle path pickle_message
848 let a = undefined :: Team
849 let b = undefined :: Odds
850 let c = undefined :: OddsCasino
851 let d = undefined :: OddsGame
852 let e = undefined :: OddsGame_Team
853 let f = undefined :: OddsGameLine
854 actual <- withSqliteConn ":memory:" $ runDbConn $ do
855 runMigration silentMigrationLogger $ do
856 migrate a
857 migrate b
858 migrate c
859 migrate d
860 migrate e
861 migrate f
862 _ <- dbimport odds
863 deleteAll b
864 count_a <- countAll a
865 count_b <- countAll b
866 count_c <- countAll c
867 count_d <- countAll d
868 count_e <- countAll e
869 count_f <- countAll f
870 return $ sum [count_a, count_b, count_c,
871 count_d, count_e, count_f ]
872 actual @?= expected