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