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