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