X-Git-Url: http://gitweb.michael.orlitzky.com/?a=blobdiff_plain;f=src%2FTSN%2FXML%2FNews.hs;h=49ff8b7d655ff1c41cc2ef1423b79948e4b8731c;hb=2069d0a786bf2c418f27574f5384eae39527d03f;hp=8da43296e02d43a4b9cd6f8aad28cafc5e49df02;hpb=ce9fabd584f2e8844b8b1ede9b29bb573e2033f7;p=dead%2Fhtsn-import.git diff --git a/src/TSN/XML/News.hs b/src/TSN/XML/News.hs index 8da4329..49ff8b7 100644 --- a/src/TSN/XML/News.hs +++ b/src/TSN/XML/News.hs @@ -3,7 +3,6 @@ {-# LANGUAGE GADTs #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE RecordWildCards #-} -{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} @@ -12,8 +11,8 @@ -- root element \ that contains an entire news item. -- module TSN.XML.News ( - Message, - news_tests ) + news_tests, + pickle_message ) where import Data.Data ( Data, constrFields, dataTypeConstrs, dataTypeOf ) @@ -21,10 +20,8 @@ import Data.List.Utils ( join, split ) import Data.Tuple.Curry ( uncurryN ) import Data.Typeable ( Typeable ) import Database.Groundhog ( - defaultMigrationLogger, insert_, - migrate, - runMigration ) + migrate ) import Database.Groundhog.Core ( DefaultKey ) import Database.Groundhog.TH ( defaultCodegenConfig, @@ -34,7 +31,6 @@ import Test.Tasty ( TestTree, testGroup ) import Test.Tasty.HUnit ( (@?=), testCase ) import Text.XML.HXT.Core ( PU, - XmlPickler(..), xp13Tuple, xpAttr, xpElem, @@ -43,13 +39,14 @@ import Text.XML.HXT.Core ( xpOption, xpPair, xpText, + xpText0, xpTriple, xpWrap ) import TSN.Codegen ( tsn_codegen_config, tsn_db_field_namer ) -- Used in a test -import TSN.DbImport ( DbImport(..), ImportResult(..) ) +import TSN.DbImport ( DbImport(..), ImportResult(..), run_dbmigrate ) import TSN.XmlImport ( XmlImport(..) ) import Xml ( FromXml(..), pickle_unpickle, unpickleable ) @@ -150,7 +147,7 @@ instance XmlImport Message instance DbImport Message where dbmigrate _ = - runMigration defaultMigrationLogger $ do + run_dbmigrate $ do migrate (undefined :: NewsTeam) migrate (undefined :: NewsLocation) migrate (undefined :: News) @@ -161,14 +158,11 @@ instance DbImport Message where -- Insert the message and acquire its primary key (unique ID) news_id <- insert_xml message - -- And insert each one into its own table. We use insertByAll_xml + -- And insert each one into its own table. We use insert_xml_or_select -- because we know that most teams will already exist, and we - -- want to get back a Left (id) for the existing team when - -- there's a collision. In fact, if the insert succeeds, we'll - -- get a Right (id) back, so we can disregard the Either - -- constructor entirely. That's what the (either id id) does. - either_nt_ids <- mapM insertByAll_xml (xml_teams message) - let nt_ids = map (either id id) either_nt_ids + -- want to get back the id for the existing team when + -- there's a collision. + nt_ids <- mapM insert_xml_or_select (xml_teams message) -- Now that the teams have been inserted, create -- news__news_team records mapping beween the two. @@ -176,8 +170,7 @@ instance DbImport Message where mapM_ insert_ news_news_teams -- Do all of that over again for the NewsLocations. - either_loc_ids <- mapM insertByAll_xml (xml_locations message) - let loc_ids = map (either id id) either_loc_ids + loc_ids <- mapM insert_xml_or_select (xml_locations message) let news_news_locations = map (News_NewsLocation news_id) loc_ids mapM_ insert_ news_news_locations @@ -244,8 +237,6 @@ pickle_news_team = from_string :: String -> NewsTeam from_string = NewsTeam -instance XmlPickler NewsTeam where - xpickle = pickle_news_team pickle_msg_id :: PU MsgId pickle_msg_id = @@ -256,8 +247,6 @@ pickle_msg_id = from_tuple = uncurryN MsgId to_tuple m = (db_msg_id m, db_event_id m) -instance XmlPickler MsgId where - xpickle = pickle_msg_id pickle_location :: PU NewsLocation pickle_location = @@ -271,8 +260,6 @@ pickle_location = uncurryN NewsLocation to_tuple l = (city l, state l, country l) -instance XmlPickler NewsLocation where - xpickle = pickle_location pickle_message :: PU Message @@ -284,7 +271,7 @@ pickle_message = pickle_msg_id (xpElem "category" xpText) (xpElem "sport" xpText) - (xpElem "url" xpText) + (xpElem "url" xpText0) (xpList pickle_news_team) (xpList pickle_location) (xpElem "SMS" xpText) @@ -321,9 +308,6 @@ pickle_message = to_string :: [String] -> String to_string = join "\n" -instance XmlPickler Message where - xpickle = pickle_message - -- * Tasty Tests @@ -368,7 +352,7 @@ test_pickle_of_unpickle_is_identity = testGroup "pickle-unpickle tests" "test/xml/newsxml-with-editor.xml" ] where check desc path = testCase desc $ do - (expected :: [Message], actual) <- pickle_unpickle "message" path + (expected, actual) <- pickle_unpickle pickle_message path actual @?= expected