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