]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blob - src/TSN/XML/Weather.hs
Migrate TSN.XML.Weather to fixed-vector-hetero.
[dead/htsn-import.git] / src / TSN / XML / Weather.hs
1 {-# LANGUAGE DeriveGeneric #-}
2 {-# LANGUAGE FlexibleInstances #-}
3 {-# LANGUAGE GADTs #-}
4 {-# LANGUAGE QuasiQuotes #-}
5 {-# LANGUAGE RecordWildCards #-}
6 {-# LANGUAGE TemplateHaskell #-}
7 {-# LANGUAGE TypeFamilies #-}
8
9 -- | Parse TSN XML for the DTD \"weatherxml.dtd\". Each document
10 -- contains a bunch of forecasts, which each contain zero or more
11 -- leagues, which in turn (each) contain a bunch of listings.
12 --
13 module TSN.XML.Weather (
14 dtd,
15 is_type1,
16 pickle_message,
17 teams_are_normal,
18 -- * Tests
19 weather_tests,
20 -- * WARNING: these are private but exported to silence warnings
21 WeatherConstructor(..),
22 WeatherDetailedWeatherListingItemConstructor(..),
23 WeatherForecastConstructor(..),
24 WeatherForecastListingConstructor(..) )
25 where
26
27 -- System imports.
28 import Control.Monad ( forM_ )
29 import Data.Time ( UTCTime )
30 import Data.Tuple.Curry ( uncurryN )
31 import qualified Data.Vector.HFixed as H ( HVector, cons, convert )
32 import Database.Groundhog (
33 countAll,
34 deleteAll,
35 insert_,
36 migrate,
37 runMigration,
38 silentMigrationLogger )
39 import Database.Groundhog.Core ( DefaultKey )
40 import Database.Groundhog.Generic ( runDbConn )
41 import Database.Groundhog.Sqlite ( withSqliteConn )
42 import Database.Groundhog.TH (
43 groundhog,
44 mkPersist )
45 import qualified GHC.Generics as GHC ( Generic )
46 import Test.Tasty ( TestTree, testGroup )
47 import Test.Tasty.HUnit ( (@?=), testCase )
48 import Text.XML.HXT.Core (
49 PU,
50 XmlTree,
51 (/>),
52 (>>>),
53 addNav,
54 descendantAxis,
55 filterAxis,
56 followingSiblingAxis,
57 hasName,
58 remNav,
59 runLA,
60 xp8Tuple,
61 xp9Tuple,
62 xpAttr,
63 xpElem,
64 xpInt,
65 xpList,
66 xpOption,
67 xpPair,
68 xpText,
69 xpTriple,
70 xpWrap )
71
72 -- Local imports.
73 import TSN.Codegen (
74 tsn_codegen_config )
75 import TSN.DbImport ( DbImport(..), ImportResult(..), run_dbmigrate )
76 import TSN.Picklers ( xp_datetime, xp_gamedate, xp_time_stamp )
77 import TSN.XmlImport ( XmlImport(..), XmlImportFk(..) )
78 import Xml (
79 Child(..),
80 FromXml(..),
81 FromXmlFk(..),
82 ToDb(..),
83 pickle_unpickle,
84 unpickleable,
85 unsafe_read_document,
86 unsafe_unpickle )
87
88
89
90 -- | The DTD to which this module corresponds. Used to invoke dbimport.
91 --
92 dtd :: String
93 dtd = "weatherxml.dtd"
94
95
96 --
97 -- DB/XML Data types
98 --
99
100 -- * WeatherForecastListing/WeatherForecastListingXml
101
102 -- | XML representation of a weather forecast listing.
103 --
104 data WeatherForecastListingXml =
105 WeatherForecastListingXml {
106 xml_teams :: String,
107 xml_weather :: Maybe String }
108 deriving (Eq, GHC.Generic, Show)
109
110
111 -- | For 'H.convert'.
112 --
113 instance H.HVector WeatherForecastListingXml
114
115
116 -- | Database representation of a weather forecast listing. The
117 -- 'db_league_name' field should come from the containing \<league\>
118 -- element which is not stored in the database.
119 --
120 data WeatherForecastListing =
121 WeatherForecastListing {
122 db_weather_forecasts_id :: DefaultKey WeatherForecast,
123 db_league_name :: Maybe String,
124 db_teams :: String,
125 db_weather :: Maybe String }
126
127
128 -- | We don't make 'WeatherForecastListingXml' an instance of
129 -- 'FromXmlFk' because it needs some additional information, namely
130 -- the league name from its containing \<league\> element.
131 --
132 -- When supplied with a forecast id and a league name, this will
133 -- turn an XML listing into a database one.
134 --
135 from_xml_fk_league :: DefaultKey WeatherForecast
136 -> (Maybe String)
137 -> WeatherForecastListingXml
138 -> WeatherForecastListing
139 from_xml_fk_league fk ln WeatherForecastListingXml{..} =
140 WeatherForecastListing {
141 db_weather_forecasts_id = fk,
142 db_league_name = ln,
143 db_teams = xml_teams,
144 db_weather = xml_weather }
145
146
147 -- * WeatherLeague
148
149 -- | XML representation of a league, as they appear in the weather
150 -- documents. There is no associated database representation because
151 -- the league element really adds no information besides its own
152 -- (usually empty) name. The leagues contain listings, so we
153 -- associate the league name with each listing instead.
154 --
155 data WeatherLeague =
156 WeatherLeague {
157 league_name :: Maybe String,
158 listings :: [WeatherForecastListingXml] }
159 deriving (Eq, Show)
160
161
162 -- * WeatherForecast/WeatherForecastXml
163
164 -- | Database representation of a weather forecast.
165 --
166 data WeatherForecast =
167 WeatherForecast {
168 db_weather_id :: DefaultKey Weather,
169 db_game_date :: UTCTime }
170
171
172 -- | XML representation of a weather forecast.
173 --
174 data WeatherForecastXml =
175 WeatherForecastXml {
176 xml_game_date :: UTCTime,
177 xml_leagues :: [WeatherLeague] }
178 deriving (Eq, GHC.Generic, Show)
179
180
181 -- | For 'H.convert'.
182 --
183 instance H.HVector WeatherForecastXml
184
185
186 instance ToDb WeatherForecastXml where
187 -- | The database representation of a 'WeatherForecastXml' is a
188 -- 'WeatherForecast'.
189 --
190 type Db WeatherForecastXml = WeatherForecast
191
192
193 instance Child WeatherForecastXml where
194 -- | The database type containing a 'WeatherForecastXml' is
195 -- 'Weather'.
196 type Parent WeatherForecastXml = Weather
197
198
199 instance FromXmlFk WeatherForecastXml where
200
201 -- | To convert a 'WeatherForecastXml' into a 'WeatherForecast', we
202 -- add the foreign key to the containing 'Weather', and copy the
203 -- game date.
204 --
205 -- This is so short it's pointless to do it generically.
206 --
207 from_xml_fk fk WeatherForecastXml{..} =
208 WeatherForecast {
209 db_weather_id = fk,
210 db_game_date = xml_game_date }
211
212
213 -- | This allows us to call 'insert_xml' on an 'WeatherForecastXml'
214 -- without first converting it to the database representation.
215 --
216 instance XmlImportFk WeatherForecastXml
217
218 -- * WeatherDetailedWeatherXml
219
220 -- | XML Representation of a \<Detailed_Weather\>, which just contains
221 -- a bunch iof \<DW_Listing\>s. There is no associated database type
222 -- since these don't really contain any information.
223 --
224 data WeatherDetailedWeatherXml =
225 WeatherDetailedWeatherXml {
226 xml_detailed_listings :: [WeatherDetailedWeatherListingXml] }
227 deriving (Eq, Show)
228
229
230 -- * WeatherDetailedWeatherXml
231
232 -- | XML Representation of a \<DW_Listing\>. The sport and sport code
233 -- come as attributes, but then these just contain a bunch of
234 -- \<Item\>s. There is no associated database type since these don't
235 -- contain much information. The sport we already know from the
236 -- \<message\>, while the sport code is ignored since it's already
237 -- present in each \<Item\>s.
238 --
239 data WeatherDetailedWeatherListingXml =
240 WeatherDetailedWeatherListingXml
241 String -- xml_dtl_listing_sport, unused
242 String -- xml_dtl_listing_sport_code, unused
243 [WeatherDetailedWeatherListingItemXml] -- xml_items
244 deriving (Eq, GHC.Generic, Show)
245
246
247 -- | Accessor for the third field of WeatherDetailedWeatherListingXml.
248 -- We don't use field names to avoid the unused field warnings that
249 -- we'd otherwise get for the first two fields.
250 --
251 xml_items :: WeatherDetailedWeatherListingXml
252 -> [WeatherDetailedWeatherListingItemXml]
253 xml_items (WeatherDetailedWeatherListingXml _ _ items) = items
254
255
256 -- | For 'H.convert'.
257 --
258 instance H.HVector WeatherDetailedWeatherListingXml
259
260
261 -- * WeatherDetailedWeatherListingItem / WeatherDetailedWeatherListingItemXml
262
263 -- | Database representation of a detailed weather item. The away/home
264 -- teams don't use the representation in "TSN.Team" because all
265 -- we're given is a name, and a team id is required for "TSN.Team".
266 --
267 -- We also drop the sport name, because it's given in the parent
268 -- 'Weather'.
269 --
270 -- The leading underscores prevent unused field warnings.
271 --
272 data WeatherDetailedWeatherListingItem =
273 WeatherDetailedWeatherListingItem {
274 _db_dtl_weather_id :: DefaultKey Weather, -- ^ Avoid name collision by
275 -- using \"dtl\" prefix.
276 _db_sport_code :: String,
277 _db_game_id :: Int,
278 _db_dtl_game_date :: UTCTime, -- ^ Avoid name clash with \"dtl\" prefix
279 _db_away_team :: String,
280 _db_home_team :: String,
281 _db_weather_type :: Int,
282 _db_description :: Maybe String,
283 _db_temp_adjust :: Maybe String,
284 _db_temperature :: Int }
285 deriving ( GHC.Generic )
286
287 -- | For 'H.cons' and 'H.convert'.
288 --
289 instance H.HVector WeatherDetailedWeatherListingItem
290
291
292 -- | XML representation of a detailed weather item. Same as the
293 -- database representation, only without the foreign key and the
294 -- sport name that comes from the containing listing.
295 --
296 -- The leading underscores prevent unused field warnings.
297 --
298 data WeatherDetailedWeatherListingItemXml =
299 WeatherDetailedWeatherListingItemXml {
300 _xml_sport_code :: String,
301 _xml_game_id :: Int,
302 _xml_dtl_game_date :: UTCTime,
303 _xml_away_team :: String,
304 _xml_home_team :: String,
305 _xml_weather_type :: Int,
306 _xml_description :: Maybe String,
307 _xml_temp_adjust :: Maybe String,
308 _xml_temperature :: Int }
309 deriving (Eq, GHC.Generic, Show)
310
311
312 -- | For 'H.convert'.
313 --
314 instance H.HVector WeatherDetailedWeatherListingItemXml
315
316 instance ToDb WeatherDetailedWeatherListingItemXml where
317 -- | Our database analogue is a 'WeatherDetailedWeatherListingItem'.
318 type Db WeatherDetailedWeatherListingItemXml =
319 WeatherDetailedWeatherListingItem
320
321 instance Child WeatherDetailedWeatherListingItemXml where
322 -- | We skip two levels of containers and say that the items belong
323 -- to the top-level 'Weather'.
324 type Parent WeatherDetailedWeatherListingItemXml = Weather
325
326 instance FromXmlFk WeatherDetailedWeatherListingItemXml where
327 -- | To convert from the XML to database representation, we simply
328 -- add the foreign key (to Weather) and copy the rest of the fields.
329 from_xml_fk = H.cons
330
331 -- | This allows us to insert the XML representation directly without
332 -- having to do the manual XML -\> DB conversion.
333 --
334 instance XmlImportFk WeatherDetailedWeatherListingItemXml
335
336 -- * Weather/Message
337
338 -- | The database representation of a weather message. We don't
339 -- contain the forecasts or the detailed weather since those are
340 -- foreigned-keyed to us.
341 --
342 data Weather =
343 Weather {
344 db_xml_file_id :: Int,
345 db_sport :: String,
346 db_title :: String,
347 db_time_stamp :: UTCTime }
348
349
350 -- | The XML representation of a weather message.
351 --
352 data Message =
353 Message {
354 xml_xml_file_id :: Int,
355 xml_heading :: String,
356 xml_category :: String,
357 xml_sport :: String,
358 xml_title :: String,
359 xml_forecasts :: [WeatherForecastXml],
360 xml_detailed_weather :: Maybe WeatherDetailedWeatherXml,
361 xml_time_stamp :: UTCTime }
362 deriving (Eq, GHC.Generic, Show)
363
364
365 -- | For 'H.convert'.
366 --
367 instance H.HVector Message
368
369
370 instance ToDb Message where
371 -- | The database representation of 'Message' is 'Weather'.
372 --
373 type Db Message = Weather
374
375 instance FromXml Message where
376 -- | To get a 'Weather' from a 'Message', we drop a bunch of
377 -- unwanted fields.
378 --
379 from_xml Message{..} =
380 Weather {
381 db_xml_file_id = xml_xml_file_id,
382 db_sport = xml_sport,
383 db_title = xml_title,
384 db_time_stamp = xml_time_stamp }
385
386 -- | This allows us to insert the XML representation 'Message'
387 -- directly.
388 --
389 instance XmlImport Message
390
391
392 --
393 -- * Database stuff
394 --
395
396 mkPersist tsn_codegen_config [groundhog|
397 - entity: Weather
398 constructors:
399 - name: Weather
400 uniques:
401 - name: unique_weather
402 type: constraint
403 # Prevent multiple imports of the same message.
404 fields: [db_xml_file_id]
405
406 - entity: WeatherForecast
407 dbName: weather_forecasts
408 constructors:
409 - name: WeatherForecast
410 fields:
411 - name: db_weather_id
412 reference:
413 onDelete: cascade
414
415 - entity: WeatherForecastListing
416 dbName: weather_forecast_listings
417 constructors:
418 - name: WeatherForecastListing
419 fields:
420 - name: db_weather_forecasts_id
421 reference:
422 onDelete: cascade
423
424 # We rename the two fields that needed a "dtl" prefix to avoid a name
425 # clash.
426 - entity: WeatherDetailedWeatherListingItem
427 dbName: weather_detailed_items
428 constructors:
429 - name: WeatherDetailedWeatherListingItem
430 fields:
431 - name: _db_dtl_weather_id
432 dbName: weather_id
433 reference:
434 onDelete: cascade
435 - name: _db_dtl_game_date
436 dbName: game_date
437
438 |]
439
440
441
442 -- | There are two different types of documents that claim to be
443 -- \"weatherxml.dtd\". The first, more common type has listings
444 -- within forecasts. The second type has forecasts within
445 -- listings. Clearly we can't parse both of these using the same
446 -- parser!
447 --
448 -- For now we're simply punting on the issue and refusing to parse
449 -- the second type. This will check the given @xmltree@ to see if
450 -- there are any forecasts contained within listings. If there are,
451 -- then it's the second type that we don't know what to do with.
452 --
453 is_type1 :: XmlTree -> Bool
454 is_type1 xmltree =
455 case elements of
456 [] -> True
457 _ -> False
458 where
459 parse :: XmlTree -> [XmlTree]
460 parse = runLA $ hasName "/"
461 /> hasName "message"
462 /> hasName "listing"
463 /> hasName "forecast"
464
465 elements = parse xmltree
466
467
468 -- | Some weatherxml documents even have the Home/Away teams in the
469 -- wrong order. We can't parse that! This next bit of voodoo detects
470 -- whether or not there are any \<HomeTeam\> elements that are
471 -- directly followed by sibling \<AwayTeam\> elements. This is the
472 -- opposite of the usual order.
473 --
474 teams_are_normal :: XmlTree -> Bool
475 teams_are_normal xmltree =
476 case elements of
477 [] -> True
478 _ -> False
479 where
480 parse :: XmlTree -> [XmlTree]
481 parse = runLA $ hasName "/"
482 /> hasName "message"
483 /> hasName "Detailed_Weather"
484 /> hasName "DW_Listing"
485 /> hasName "Item"
486 >>> addNav
487 >>> descendantAxis
488 >>> filterAxis (hasName "HomeTeam")
489 >>> followingSiblingAxis
490 >>> remNav
491 >>> hasName "AwayTeam"
492
493 elements = parse xmltree
494
495
496 instance DbImport Message where
497 dbmigrate _ =
498 run_dbmigrate $ do
499 migrate (undefined :: Weather)
500 migrate (undefined :: WeatherForecast)
501 migrate (undefined :: WeatherForecastListing)
502 migrate (undefined :: WeatherDetailedWeatherListingItem)
503
504 dbimport m = do
505 -- First we insert the top-level weather record.
506 weather_id <- insert_xml m
507
508 -- Next insert all of the forecasts, one at a time.
509 forM_ (xml_forecasts m) $ \forecast -> do
510 forecast_id <- insert_xml_fk weather_id forecast
511
512 -- With the forecast id in hand, loop through this forecast's
513 -- leagues...
514 forM_ (xml_leagues forecast) $ \league -> do
515 -- Construct the function that converts an XML listing to a
516 -- database one.
517 let todb = from_xml_fk_league forecast_id (league_name league)
518
519 -- Now use it to convert all of the XML listings.
520 let db_listings = map todb (listings league)
521
522 -- And finally, insert those DB listings.
523 mapM_ insert_ db_listings
524
525 -- Now we do the detailed weather items.
526 case (xml_detailed_weather m) of
527 Nothing -> return ()
528 Just dw -> do
529 let detailed_listings = xml_detailed_listings dw
530 let items = concatMap xml_items detailed_listings
531 mapM_ (insert_xml_fk_ weather_id) items
532
533 return ImportSucceeded
534
535
536 --
537 -- * Pickling
538 --
539
540 -- | Pickler to convert a 'WeatherForecastListingXml' to/from XML.
541 --
542 pickle_listing :: PU WeatherForecastListingXml
543 pickle_listing =
544 xpElem "listing" $
545 xpWrap (from_pair, H.convert) $
546 xpPair
547 (xpElem "teams" xpText)
548 (xpElem "weather" (xpOption xpText))
549 where
550 from_pair = uncurry WeatherForecastListingXml
551
552
553
554 -- | Pickler to convert a 'WeatherLeague' to/from XML.
555 --
556 pickle_league :: PU WeatherLeague
557 pickle_league =
558 xpElem "league" $
559 xpWrap (from_pair, to_pair) $
560 xpPair
561 (xpAttr "name" $ xpOption xpText)
562 (xpList pickle_listing)
563 where
564 from_pair = uncurry WeatherLeague
565 to_pair WeatherLeague{..} = (league_name, listings)
566
567
568 -- | Pickler to convert a 'WeatherForecastXml' to/from XML.
569 --
570 pickle_forecast :: PU WeatherForecastXml
571 pickle_forecast =
572 xpElem "forecast" $
573 xpWrap (from_pair, to_pair) $
574 xpPair
575 (xpAttr "gamedate" xp_gamedate)
576 (xpList pickle_league)
577 where
578 from_pair = uncurry WeatherForecastXml
579 to_pair WeatherForecastXml{..} = (xml_game_date,
580 xml_leagues)
581
582
583
584 -- | (Un)pickle a 'WeatherDetailedWeatherListingItemXml'.
585 --
586 pickle_item :: PU WeatherDetailedWeatherListingItemXml
587 pickle_item =
588 xpElem "Item" $
589 xpWrap (from_tuple, H.convert) $
590 xp9Tuple (xpElem "Sportcode" xpText)
591 (xpElem "GameID" xpInt)
592 (xpElem "Gamedate" xp_datetime)
593 (xpElem "AwayTeam" xpText)
594 (xpElem "HomeTeam" xpText)
595 (xpElem "WeatherType" xpInt)
596 (xpElem "Description" (xpOption xpText))
597 (xpElem "TempAdjust" (xpOption xpText))
598 (xpElem "Temperature" xpInt)
599 where
600 from_tuple = uncurryN WeatherDetailedWeatherListingItemXml
601
602
603
604 -- | (Un)pickle a 'WeatherDetailedWeatherListingXml'.
605 --
606 pickle_dw_listing :: PU WeatherDetailedWeatherListingXml
607 pickle_dw_listing =
608 xpElem "DW_Listing" $
609 xpWrap (from_tuple, H.convert) $
610 xpTriple (xpAttr "SportCode" xpText)
611 (xpAttr "Sport" xpText)
612 (xpList pickle_item)
613 where
614 from_tuple = uncurryN WeatherDetailedWeatherListingXml
615
616
617 -- | (Un)pickle a 'WeatherDetailedWeatherXml'
618 --
619 pickle_detailed_weather :: PU WeatherDetailedWeatherXml
620 pickle_detailed_weather =
621 xpElem "Detailed_Weather" $
622 xpWrap (WeatherDetailedWeatherXml, xml_detailed_listings)
623 (xpList pickle_dw_listing)
624
625
626 -- | Pickler to convert a 'Message' to/from XML.
627 --
628 pickle_message :: PU Message
629 pickle_message =
630 xpElem "message" $
631 xpWrap (from_tuple, H.convert) $
632 xp8Tuple
633 (xpElem "XML_File_ID" xpInt)
634 (xpElem "heading" xpText)
635 (xpElem "category" xpText)
636 (xpElem "sport" xpText)
637 (xpElem "title" xpText)
638 (xpList pickle_forecast)
639 (xpOption pickle_detailed_weather)
640 (xpElem "time_stamp" xp_time_stamp)
641 where
642 from_tuple = uncurryN Message
643
644
645 --
646 -- * Tasty tests
647 --
648 weather_tests :: TestTree
649 weather_tests =
650 testGroup
651 "Weather tests"
652 [ test_on_delete_cascade,
653 test_pickle_of_unpickle_is_identity,
654 test_unpickle_succeeds,
655 test_types_detected_correctly,
656 test_normal_teams_detected_correctly ]
657
658
659 -- | If we unpickle something and then pickle it, we should wind up
660 -- with the same thing we started with. WARNING: success of this
661 -- test does not mean that unpickling succeeded.
662 --
663 test_pickle_of_unpickle_is_identity :: TestTree
664 test_pickle_of_unpickle_is_identity = testGroup "pickle-unpickle tests"
665 [ check "pickle composed with unpickle is the identity"
666 "test/xml/weatherxml.xml",
667
668 check "pickle composed with unpickle is the identity (detailed)"
669 "test/xml/weatherxml-detailed.xml" ]
670 where
671 check desc path = testCase desc $ do
672 (expected, actual) <- pickle_unpickle pickle_message path
673 actual @?= expected
674
675
676 -- | Make sure we can actually unpickle these things.
677 --
678 test_unpickle_succeeds :: TestTree
679 test_unpickle_succeeds = testGroup "unpickle tests"
680 [ check "unpickling succeeds"
681 "test/xml/weatherxml.xml",
682 check "unpickling succeeds (detailed)"
683 "test/xml/weatherxml-detailed.xml",
684 check "unpickling succeeds (empty weather)"
685 "test/xml/weatherxml-empty-weather.xml"]
686 where
687 check desc path = testCase desc $ do
688 actual <- unpickleable path pickle_message
689 let expected = True
690 actual @?= expected
691
692
693 -- | Make sure everything gets deleted when we delete the top-level
694 -- record.
695 --
696 test_on_delete_cascade :: TestTree
697 test_on_delete_cascade = testGroup "cascading delete tests"
698 [ check "deleting weather deletes its children"
699 "test/xml/weatherxml.xml",
700 check "deleting weather deletes its children (detailed)"
701 "test/xml/weatherxml-detailed.xml",
702 check "deleting weather deletes its children (empty weather)"
703 "test/xml/weatherxml-empty-weather.xml"]
704 where
705 check desc path = testCase desc $ do
706 weather <- unsafe_unpickle path pickle_message
707 let a = undefined :: Weather
708 let b = undefined :: WeatherForecast
709 let c = undefined :: WeatherForecastListing
710 let d = undefined :: WeatherDetailedWeatherListingItem
711 actual <- withSqliteConn ":memory:" $ runDbConn $ do
712 runMigration silentMigrationLogger $ do
713 migrate a
714 migrate b
715 migrate c
716 migrate d
717 _ <- dbimport weather
718 deleteAll a
719 count_a <- countAll a
720 count_b <- countAll b
721 count_c <- countAll c
722 count_d <- countAll d
723 return $ count_a + count_b + count_c + count_d
724 let expected = 0
725 actual @?= expected
726
727
728 -- | We want to make sure type1 documents are detected as type1, and
729 -- type2 documents detected as type2..
730 --
731 test_types_detected_correctly :: TestTree
732 test_types_detected_correctly =
733 testGroup "weatherxml types detected correctly"
734 [ check "test/xml/weatherxml.xml"
735 "first type detected correctly"
736 True,
737 check "test/xml/weatherxml-detailed.xml"
738 "first type detected correctly (detailed)"
739 True,
740 check "test/xml/weatherxml-empty-weather.xml"
741 "first type detected correctly (empty weather)"
742 True,
743 check "test/xml/weatherxml-type2.xml"
744 "second type detected correctly"
745 False ]
746 where
747 check path desc expected = testCase desc $ do
748 xmltree <- unsafe_read_document path
749 let actual = is_type1 xmltree
750 actual @?= expected
751
752
753 -- | We want to make sure normal teams are detected as normal, and the
754 -- backwards ones are flagged as backwards.
755 --
756 test_normal_teams_detected_correctly :: TestTree
757 test_normal_teams_detected_correctly =
758 testGroup "team order is detected correctly" [
759
760 check "normal teams are detected correctly"
761 "test/xml/weatherxml.xml"
762 True,
763
764 check "backwards teams are detected correctly"
765 "test/xml/weatherxml-backwards-teams.xml"
766 False ]
767 where
768 check desc path expected = testCase desc $ do
769 xmltree <- unsafe_read_document path
770 let actual = teams_are_normal xmltree
771 actual @?= expected