X-Git-Url: http://gitweb.michael.orlitzky.com/?a=blobdiff_plain;f=src%2FTSN%2FXML%2FWeather.hs;h=e9515edad67fb85901d596d1e7857cddfa035b28;hb=b8d151d034a338242ee1193638ff077614d10580;hp=f3b60af69c7fb52e013bdab5d5b11d2d6d21b24d;hpb=7815ba497d075c63c76418fc2c2b914ebe56b712;p=dead%2Fhtsn-import.git diff --git a/src/TSN/XML/Weather.hs b/src/TSN/XML/Weather.hs index f3b60af..e9515ed 100644 --- a/src/TSN/XML/Weather.hs +++ b/src/TSN/XML/Weather.hs @@ -5,7 +5,7 @@ {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} --- | Parse TSN XML for the DTD "weatherxml.dtd". Each document +-- | Parse TSN XML for the DTD \"weatherxml.dtd\". Each document -- contains a bunch of forecasts, which each contain one league, and -- that league contains a bunch of listings. -- @@ -14,9 +14,7 @@ module TSN.XML.Weather ( -- * Tests weather_tests, -- * WARNING: these are private but exported to silence warnings - Weather_WeatherForecastConstructor(..), WeatherConstructor(..), - WeatherForecast_WeatherForecastListingConstructor(..), WeatherForecastConstructor(..), WeatherForecastListingConstructor(..) ) where @@ -25,9 +23,7 @@ where import Control.Monad ( forM_ ) import Data.Time ( UTCTime ) import Data.Tuple.Curry ( uncurryN ) -import Database.Groundhog ( - insert_, - migrate ) +import Database.Groundhog ( migrate ) import Database.Groundhog.Core ( DefaultKey ) import Database.Groundhog.TH ( groundhog, @@ -50,36 +46,68 @@ import Text.XML.HXT.Core ( import TSN.Codegen ( tsn_codegen_config ) import TSN.DbImport ( DbImport(..), ImportResult(..), run_dbmigrate ) -import TSN.Picklers ( xp_gamedate ) -import TSN.XmlImport ( XmlImport(..) ) -import Xml ( FromXml(..), ToDb(..), pickle_unpickle, unpickleable ) +import TSN.Picklers ( xp_gamedate, xp_time_stamp ) +import TSN.XmlImport ( XmlImport(..), XmlImportFk(..) ) +import Xml ( + FromXml(..), + FromXmlFk(..), + ToDb(..), + pickle_unpickle, + unpickleable ) +-- +-- DB/XML Data types +-- + +-- * WeatherForecastListing/WeatherForecastListingXml + +-- | XML representation of a weather forecast listing. +-- +data WeatherForecastListingXml = + WeatherForecastListingXml { + xml_teams :: String, + xml_weather :: String } + deriving (Eq, Show) --- | Database/XML representation of a weather forecast listing. +-- | Database representation of a weather forecast listing. -- data WeatherForecastListing = WeatherForecastListing { + db_weather_forecasts_id :: DefaultKey WeatherForecast, db_teams :: String, db_weather :: String } - deriving (Eq, Show) --- | The database analogue of a 'WeatherForecastListing' is itself. -instance ToDb WeatherForecastListing where - type Db WeatherForecastListing = WeatherForecastListing --- | This is needed to define the XmlImport instance for --- 'WeatherForecastListing'. +-- | The database analogue of a 'WeatherForecastListingXml' is +-- 'WeatherForecastListing'. +-- +instance ToDb WeatherForecastListingXml where + type Db WeatherForecastListingXml = WeatherForecastListing + +-- | This is needed to define the 'XmlImportFk' instance for +-- 'WeatherForecastListing'. -- -instance FromXml WeatherForecastListing where - from_xml = id +instance FromXmlFk WeatherForecastListingXml where + -- | Each 'WeatherForecastListingXml' is contained in a + -- 'WeatherForecast'. + -- + type Parent WeatherForecastListingXml = WeatherForecast + + from_xml_fk fk WeatherForecastListingXml{..} = + WeatherForecastListing { + db_weather_forecasts_id = fk, + db_teams = xml_teams, + db_weather = xml_weather } --- | Allows us to call 'insert_xml' on the XML representation of --- WeatherForecastListing. +-- | This allows us to insert the XML representation +-- 'WeatherForecastListingXml' directly. -- -instance XmlImport WeatherForecastListing +instance XmlImportFk WeatherForecastListingXml +-- * WeatherLeague + -- | XML representation of a league, as they appear in the weather -- documents. There is no associated database representation because -- the league element really adds no information besides its own @@ -90,14 +118,17 @@ instance XmlImport WeatherForecastListing data WeatherLeague = WeatherLeague { league_name :: Maybe String, - listings :: [WeatherForecastListing] } + listings :: [WeatherForecastListingXml] } deriving (Eq, Show) +-- * WeatherForecast/WeatherForecastXml + -- | Database representation of a weather forecast. -- data WeatherForecast = WeatherForecast { + db_weather_id :: DefaultKey Weather, db_game_date :: UTCTime, db_league_name :: Maybe String } @@ -111,33 +142,41 @@ data WeatherForecastXml = xml_league :: WeatherLeague } deriving (Eq, Show) - instance ToDb WeatherForecastXml where -- | The database representation of a 'WeatherForecastXml' is a -- 'WeatherForecast'. -- type Db WeatherForecastXml = WeatherForecast -instance FromXml WeatherForecastXml where +instance FromXmlFk WeatherForecastXml where + type Parent WeatherForecastXml = Weather + -- | To convert a 'WeatherForecastXml' into a 'WeatherForecast', we -- replace the 'WeatherLeague' with its name. -- - from_xml WeatherForecastXml{..} = - WeatherForecast { db_game_date = xml_game_date, - db_league_name = (league_name xml_league) } + from_xml_fk fk WeatherForecastXml{..} = + WeatherForecast { + db_weather_id = fk, + db_game_date = xml_game_date, + db_league_name = (league_name xml_league) } + -- | This allows us to call 'insert_xml' on an 'WeatherForecastXml' -- without first converting it to the database representation. -- -instance XmlImport WeatherForecastXml +instance XmlImportFk WeatherForecastXml + +-- * Weather/Message -- | The database representation of a weather message. -- data Weather = Weather { + db_xml_file_id :: Int, db_sport :: String, - db_title :: String } + db_title :: String, + db_time_stamp :: UTCTime } -- | The XML representation of a weather message. @@ -150,10 +189,9 @@ data Message = xml_sport :: String, xml_title :: String, xml_forecasts :: [WeatherForecastXml], - xml_time_stamp :: String } + xml_time_stamp :: UTCTime } deriving (Eq, Show) - instance ToDb Message where -- | The database representation of 'Message' is 'Weather'. -- @@ -165,62 +203,49 @@ instance FromXml Message where -- from_xml Message{..} = Weather { + db_xml_file_id = xml_xml_file_id, db_sport = xml_sport, - db_title = xml_title } + db_title = xml_title, + db_time_stamp = xml_time_stamp } --- | This allows us to call 'insert_xml' on a 'Message' without first --- converting it to the database representation. +-- | This allows us to insert the XML representation 'Message' +-- directly. -- instance XmlImport Message --- | A mapping between 'Weather' objects and their children --- 'WeatherForecast's. -- -data Weather_WeatherForecast = - Weather_WeatherForecast - (DefaultKey Weather) - (DefaultKey WeatherForecast) - --- | A mapping between 'WeatherForecast' objects and their children --- 'WeatherForecastListing's. +-- Database stuff -- -data WeatherForecast_WeatherForecastListing = - WeatherForecast_WeatherForecastListing - (DefaultKey WeatherForecast) - (DefaultKey WeatherForecastListing) mkPersist tsn_codegen_config [groundhog| - entity: Weather + constructors: + - name: Weather + uniques: + - name: unique_weather + type: constraint + # Prevent multiple imports of the same message. + fields: [db_xml_file_id] - entity: WeatherForecast dbName: weather_forecasts - -- entity: WeatherForecastListing - dbName: weather_forecast_listings - -- entity: Weather_WeatherForecast - dbName: weather__weather_forecasts constructors: - - name: Weather_WeatherForecast + - name: WeatherForecast fields: - - name: weather_WeatherForecast0 # Default created by mkNormalFieldName - dbName: weather_id - - name: weather_WeatherForecast1 # Default created by mkNormalFieldName - dbName: weather_forecasts_id + - name: db_weather_id + reference: + onDelete: cascade -- entity: WeatherForecast_WeatherForecastListing - dbName: weather_forecasts__weather_forecast_listings +- entity: WeatherForecastListing + dbName: weather_forecast_listings constructors: - - name: WeatherForecast_WeatherForecastListing + - name: WeatherForecastListing fields: - # Default by mkNormalFieldName - - name: weatherForecast_WeatherForecastListing0 - dbName: weather_forecasts_id + - name: db_weather_forecasts_id + reference: + onDelete: cascade - # Default by mkNormalFieldName - - name: weatherForecast_WeatherForecastListing1 - dbName: weather_forecast_listings_id |] @@ -230,8 +255,6 @@ instance DbImport Message where migrate (undefined :: Weather) migrate (undefined :: WeatherForecast) migrate (undefined :: WeatherForecastListing) - migrate (undefined :: Weather_WeatherForecast) - migrate (undefined :: WeatherForecast_WeatherForecastListing) dbimport m = do -- The weather database schema has a nice linear structure. First @@ -240,25 +263,21 @@ instance DbImport Message where -- Next insert all of the forecasts, one at a time. forM_ (xml_forecasts m) $ \forecast -> do - forecast_id <- insert_xml forecast - - -- Map this forecast to its parent weather record. - insert_ (Weather_WeatherForecast weather_id forecast_id) + forecast_id <- insert_xml_fk weather_id forecast -- Insert all of this forecast's listings. - forM_ (listings $ xml_league forecast) $ \listing -> do - listing_id <- insert_xml listing - - -- Map this listing to its parent forecast. - insert_ $ WeatherForecast_WeatherForecastListing forecast_id listing_id + mapM_ (insert_xml_fk_ forecast_id) (listings $ xml_league forecast) return ImportSucceeded +--- +--- Pickling +--- --- | Pickler to convert a 'WeatherForecastListing' to/from XML. +-- | Pickler to convert a 'WeatherForecastListingXml' to/from XML. -- -pickle_listing :: PU WeatherForecastListing +pickle_listing :: PU WeatherForecastListingXml pickle_listing = xpElem "listing" $ xpWrap (from_pair, to_pair) $ @@ -266,8 +285,8 @@ pickle_listing = (xpElem "teams" xpText) (xpElem "weather" xpText) where - from_pair = uncurry WeatherForecastListing - to_pair WeatherForecastListing{..} = (db_teams, db_weather) + from_pair = uncurry WeatherForecastListingXml + to_pair WeatherForecastListingXml{..} = (xml_teams, xml_weather) -- | Pickler to convert a 'WeatherLeague' to/from XML. @@ -313,7 +332,7 @@ pickle_message = (xpElem "sport" xpText) (xpElem "title" xpText) (xpList pickle_forecast) - (xpElem "time_stamp" xpText) + (xpElem "time_stamp" xp_time_stamp) where from_tuple = uncurryN Message to_tuple Message{..} = (xml_xml_file_id, @@ -353,7 +372,7 @@ test_pickle_of_unpickle_is_identity = test_unpickle_succeeds :: TestTree test_unpickle_succeeds = testCase "unpickling succeeds" $ do - let path = "test/xml/weatherxml.xml" - actual <- unpickleable path pickle_message - let expected = True - actual @?= expected + let path = "test/xml/weatherxml.xml" + actual <- unpickleable path pickle_message + let expected = True + actual @?= expected