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