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