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