]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blobdiff - src/TSN/XML/News.hs
Simplify some tests by passing a pickler instead of relying on a XmlPickler instance.
[dead/htsn-import.git] / src / TSN / XML / News.hs
index 8da43296e02d43a4b9cd6f8aad28cafc5e49df02..67611e512bbcf55d85caac39b61cfe766dc3957d 100644 (file)
@@ -3,7 +3,6 @@
 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE QuasiQuotes #-}
 {-# LANGUAGE RecordWildCards #-}
-{-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE StandaloneDeriving #-}
 {-# LANGUAGE TemplateHaskell #-}
 {-# LANGUAGE TypeFamilies #-}
@@ -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,
@@ -49,7 +46,7 @@ import Text.XML.HXT.Core (
 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
 
@@ -368,7 +361,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