1 {-# LANGUAGE DeriveGeneric #-}
2 {-# LANGUAGE FlexibleInstances #-}
4 {-# LANGUAGE QuasiQuotes #-}
5 {-# LANGUAGE RecordWildCards #-}
6 {-# LANGUAGE TemplateHaskell #-}
7 {-# LANGUAGE TypeFamilies #-}
9 -- | Parse TSN XML for the DTD \"Schedule_Changes_XML.dtd\". Each
10 -- \<message\> element contains zero or more \<Schedule_Change\>
11 -- which are just a wrapper around zero or more \<SC_Listing\>s.
13 -- The teams appear to use the shared "TSN.Team" representation.
15 module TSN.XML.ScheduleChanges (
19 schedule_changes_tests,
20 -- * WARNING: these are private but exported to silence warnings
21 ScheduleChangesConstructor(..),
22 ScheduleChangesListingConstructor(..) )
26 import Control.Monad ( forM_ )
27 import Data.Time ( UTCTime(..) )
28 import Data.Tuple.Curry ( uncurryN )
29 import Database.Groundhog (
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 (
42 import qualified GHC.Generics as GHC ( Generic )
43 import Test.Tasty ( TestTree, testGroup )
44 import Test.Tasty.HUnit ( (@?=), testCase )
45 import Text.XML.HXT.Core (
59 import Generics ( Generic(..), to_tuple )
60 import TSN.Codegen ( tsn_codegen_config )
61 import TSN.Database ( insert_or_select )
62 import TSN.DbImport ( DbImport(..), ImportResult(..), run_dbmigrate )
63 import TSN.Picklers ( xp_date_padded, xp_tba_time, xp_time_stamp )
64 import TSN.Team ( Team(..), HTeam(..), VTeam(..) )
65 import TSN.XmlImport ( XmlImport(..) )
75 -- | The DTD to which this module corresponds. Used to invoke
79 dtd = "Schedule_Changes_XML.dtd"
86 -- * ScheduleChanges/Message
88 -- | Database representation of a 'Message'. Comparatively, it lacks
89 -- the listings since they are linked via a foreign key.
91 data ScheduleChanges =
93 db_xml_file_id :: Int,
95 db_category :: String,
97 db_time_stamp :: UTCTime }
101 -- | XML representation of a \<Schedule_Change\> within a
102 -- \<message\>. These are wrappers around a bunch of
103 -- \<SC_Listing\>s, but they also contain the sport name for all of
104 -- the contained listings.
106 data ScheduleChangeXml =
108 xml_sc_sport :: String,
109 xml_sc_listings :: [ScheduleChangesListingXml] }
110 deriving (Eq, GHC.Generic, Show)
113 -- | For 'Generics.to_tuple'.
115 instance Generic ScheduleChangeXml
118 -- | XML representation of a 'ScheduleChanges'. It has the same
119 -- fields, but in addition contains the 'xml_listings'.
123 xml_xml_file_id :: Int,
124 xml_heading :: String,
125 xml_category :: String,
127 xml_schedule_changes :: [ScheduleChangeXml],
128 xml_time_stamp :: UTCTime }
129 deriving (Eq, GHC.Generic, Show)
132 -- | For 'Generics.to_tuple'.
134 instance Generic Message
137 instance ToDb Message where
138 -- | The database analogue of a 'Message' is a 'ScheduleChanges'.
140 type Db Message = ScheduleChanges
143 -- | The 'FromXml' instance for 'Message' is required for the
144 -- 'XmlImport' instance.
146 instance FromXml Message where
147 -- | To convert a 'Message' to an 'ScheduleChanges', we just drop
148 -- the 'xml_schedule_changes'.
150 from_xml Message{..} =
152 db_xml_file_id = xml_xml_file_id,
153 db_heading = xml_heading,
154 db_category = xml_category,
155 db_sport = xml_sport,
156 db_time_stamp = xml_time_stamp }
159 -- | This allows us to insert the XML representation 'Message'
162 instance XmlImport Message
166 -- * ScheduleChangesListing/ScheduleChangesListingXml
168 -- | An embedded type within 'ScheduleChangesListing'. These look
169 -- like, \<status numeral=\"4\"\>FINAL\</status\> within the XML,
170 -- but they're in one-to-one correspondence with the listings.
172 data ScheduleChangesListingStatus =
173 ScheduleChangesListingStatus {
174 db_status_numeral :: Int,
175 db_status :: Maybe String } -- Yes, they can be empty.
180 -- | Database representation of a \<SC_Listing\> contained within a
181 -- \<Schedule_Change\>, within a \<message\>. During the transition
182 -- to the database, we drop the intermediate \<Schedule_Change\>
183 -- leaving the listing keyed to the 'ScheduleChanges' itself.
185 -- The home/away teams reuse the 'Team' representation.
187 -- The sport name (sc_sport) is pulled out of the containing
188 -- \<Schedule_Change\> and embedded into the listings themselves.
190 data ScheduleChangesListing =
191 ScheduleChangesListing {
192 db_schedule_changes_id :: DefaultKey ScheduleChanges,
193 db_away_team_id :: DefaultKey Team,
194 db_home_team_id ::DefaultKey Team,
196 db_sc_sport :: String,
197 db_schedule_id :: Int,
198 db_game_time :: UTCTime,
199 db_location :: Maybe String,
202 db_listing_status :: ScheduleChangesListingStatus,
203 db_notes :: Maybe String }
206 -- | XML representation of a \<SC_Listing\> contained within a
207 -- \<Schedule_Change\>, within a \<message\>.
209 data ScheduleChangesListingXml =
210 ScheduleChangesListingXml {
212 xml_schedule_id :: Int,
213 xml_game_date :: UTCTime,
214 xml_game_time :: Maybe UTCTime,
215 xml_location :: Maybe String,
216 xml_away_team :: VTeam,
217 xml_home_team :: HTeam,
220 xml_listing_status :: ScheduleChangesListingStatus,
221 xml_notes :: Maybe String }
222 deriving (Eq, GHC.Generic, Show)
225 -- | For 'Generics.to_tuple'.
227 instance Generic ScheduleChangesListingXml
230 instance ToDb ScheduleChangesListingXml where
231 -- | The database analogue of an 'ScheduleChangesListingXml' is
232 -- an 'ScheduleChangesListing'.
234 type Db ScheduleChangesListingXml = ScheduleChangesListing
238 -- | We don't make 'ScheduleChangesListingXml' an instance of
239 -- 'FromXmlFkTeams' because it needs some additional information,
240 -- namely the sport name from its containing \<Schedule_Change\>.
241 -- But essentially we'll need to do the same thing as
242 -- 'from_xml_fk_teams'. This function accomplishes the same thing,
243 -- with the addition of the sport that's passed in.
245 -- The parameter order is for convenience later (see dbimport).
247 from_xml_fk_sport :: (DefaultKey ScheduleChanges)
248 -> String -- ^ The sport from our containing schedule change
249 -> (DefaultKey Team) -- ^ Away team FK
250 -> (DefaultKey Team) -- ^ Home team FK
251 -> ScheduleChangesListingXml
252 -> ScheduleChangesListing
253 from_xml_fk_sport fk sport fk_away fk_home ScheduleChangesListingXml{..} =
254 ScheduleChangesListing {
255 db_schedule_changes_id = fk,
256 db_away_team_id = fk_away,
257 db_home_team_id = fk_home,
260 db_schedule_id = xml_schedule_id,
261 db_game_time = make_game_time xml_game_date xml_game_time,
262 db_location = xml_location,
263 db_vscore = xml_vscore,
264 db_hscore = xml_hscore,
265 db_listing_status = xml_listing_status,
266 db_notes = xml_notes }
268 -- | Make the database \"game time\" from the XML
269 -- date/time. Simply take the day part from one and the time
272 make_game_time d Nothing = d
273 make_game_time d (Just t) = UTCTime (utctDay d) (utctDayTime t)
281 instance DbImport Message where
284 migrate (undefined :: Team)
285 migrate (undefined :: ScheduleChanges)
286 migrate (undefined :: ScheduleChangesListing)
289 -- Insert the top-level message
290 msg_id <- insert_xml m
292 -- Now loop through the message's schedule changes
293 forM_ (xml_schedule_changes m) $ \sc -> do
294 -- Construct the function that will turn an XML listing into a DB one.
295 -- This is only partially applied without the away/home team IDs.
296 let listing_xml_to_db = from_xml_fk_sport msg_id (xml_sc_sport sc)
298 -- Now loop through the listings so that we can handle the teams
299 -- one listing at a time.
300 forM_ (xml_sc_listings sc) $ \listing -> do
301 away_team_id <- insert_or_select (vteam $ xml_away_team listing)
302 home_team_id <- insert_or_select (hteam $ xml_home_team listing)
304 -- Finish constructing the xml -> db function.
305 let listing_xml_to_db' = listing_xml_to_db away_team_id home_team_id
306 let db_listing = listing_xml_to_db' listing
310 return ImportSucceeded
313 mkPersist tsn_codegen_config [groundhog|
314 - entity: ScheduleChanges
315 dbName: schedule_changes
317 - name: ScheduleChanges
319 - name: unique_schedule_changes
321 # Prevent multiple imports of the same message.
322 fields: [db_xml_file_id]
324 # Note: we drop the "sc" prefix from the db_sc_sport field.
325 - entity: ScheduleChangesListing
326 dbName: schedule_changes_listings
328 - name: ScheduleChangesListing
330 - name: db_schedule_changes_id
333 - name: db_away_team_id
336 - name: db_home_team_id
341 - name: db_listing_status
343 - {name: status_numeral, dbName: status_numeral}
344 - {name: status, dbName: status}
346 - embedded: ScheduleChangesListingStatus
348 - name: db_status_numeral
349 dbName: status_numeral
361 -- | An (un)pickler for the \<Away_Team\> elements.
363 pickle_away_team :: PU VTeam
366 xpWrap (from_tuple, to_tuple') $
367 xpPair (xpAttr "AT_ID" xpText)
370 from_tuple (x,y) = VTeam (Team x Nothing y)
371 to_tuple' (VTeam t) = (team_id t, name t)
374 -- | An (un)pickler for the \<Away_Team\> elements.
376 pickle_home_team :: PU HTeam
379 xpWrap (from_tuple, to_tuple') $
380 xpPair (xpAttr "HT_ID" xpText)
383 from_tuple (x,y) = HTeam (Team x Nothing y)
384 to_tuple' (HTeam t) = (team_id t, name t)
387 -- | An (un)pickler for the \<status\> elements.
389 pickle_status :: PU ScheduleChangesListingStatus
392 xpWrap (from_tuple, to_tuple') $
393 xpPair (xpAttr "numeral" xpInt)
396 from_tuple = uncurry ScheduleChangesListingStatus
398 -- Avouid unused field warnings.
399 to_tuple' ScheduleChangesListingStatus{..} =
400 (db_status_numeral, db_status)
402 -- | An (un)pickler for the \<SC_Listing\> elements.
404 pickle_listing :: PU ScheduleChangesListingXml
406 xpElem "SC_Listing" $
407 xpWrap (from_tuple, to_tuple) $
408 xp11Tuple (xpAttr "type" xpText)
409 (xpElem "Schedule_ID" xpInt)
410 (xpElem "Game_Date" xp_date_padded)
411 (xpElem "Game_Time" xp_tba_time)
412 (xpElem "Location" (xpOption xpText))
415 (xpElem "vscore" xpInt)
416 (xpElem "hscore" xpInt)
418 (xpElem "notes" (xpOption xpText))
420 from_tuple = uncurryN ScheduleChangesListingXml
423 -- | An (un)pickler for the \<Schedule_Change\> elements.
425 pickle_schedule_change :: PU ScheduleChangeXml
426 pickle_schedule_change =
427 xpElem "Schedule_Change" $
428 xpWrap (from_tuple, to_tuple) $
429 xpPair (xpAttr "Sport" xpText)
430 (xpList pickle_listing)
432 from_tuple = uncurry ScheduleChangeXml
435 -- | Pickler for the top-level 'Message'.
437 pickle_message :: PU Message
440 xpWrap (from_tuple, to_tuple) $
441 xp6Tuple (xpElem "XML_File_ID" xpInt)
442 (xpElem "heading" xpText)
443 (xpElem "category" xpText)
444 (xpElem "sport" xpText)
445 (xpList pickle_schedule_change)
446 (xpElem "time_stamp" xp_time_stamp)
448 from_tuple = uncurryN Message
455 -- | A list of all tests for this module.
457 schedule_changes_tests :: TestTree
458 schedule_changes_tests =
460 "ScheduleChanges tests"
461 [ test_on_delete_cascade,
462 test_pickle_of_unpickle_is_identity,
463 test_unpickle_succeeds ]
465 -- | If we unpickle something and then pickle it, we should wind up
466 -- with the same thing we started with. WARNING: success of this
467 -- test does not mean that unpickling succeeded.
469 test_pickle_of_unpickle_is_identity :: TestTree
470 test_pickle_of_unpickle_is_identity =
471 testCase "pickle composed with unpickle is the identity" $ do
472 let path = "test/xml/Schedule_Changes_XML.xml"
473 (expected, actual) <- pickle_unpickle pickle_message path
478 -- | Make sure we can actually unpickle these things.
480 test_unpickle_succeeds :: TestTree
481 test_unpickle_succeeds =
482 testCase "unpickling succeeds" $ do
483 let path = "test/xml/Schedule_Changes_XML.xml"
484 actual <- unpickleable path pickle_message
491 -- | Make sure everything gets deleted when we delete the top-level
494 test_on_delete_cascade :: TestTree
495 test_on_delete_cascade =
496 testCase "deleting auto_racing_results deletes its children" $ do
497 let path = "test/xml/Schedule_Changes_XML.xml"
498 results <- unsafe_unpickle path pickle_message
499 let a = undefined :: Team
500 let b = undefined :: ScheduleChanges
501 let c = undefined :: ScheduleChangesListing
503 actual <- withSqliteConn ":memory:" $ runDbConn $ do
504 runMigration silentMigrationLogger $ do
508 _ <- dbimport results
510 count_a <- countAll a
511 count_b <- countAll b
512 count_c <- countAll c
513 return $ sum [count_a, count_b, count_c]
514 let expected = 12 -- There are 16 team elements, but 4 are dupes,
515 -- so 12 unique teams should be left over.