]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blob - src/TSN/XML/ScheduleChanges.hs
Migrate TSN.XML.ScheduleChanges to fixed-vector-hetero.
[dead/htsn-import.git] / src / TSN / XML / ScheduleChanges.hs
1 {-# LANGUAGE DeriveGeneric #-}
2 {-# LANGUAGE FlexibleInstances #-}
3 {-# LANGUAGE GADTs #-}
4 {-# LANGUAGE QuasiQuotes #-}
5 {-# LANGUAGE RecordWildCards #-}
6 {-# LANGUAGE TemplateHaskell #-}
7 {-# LANGUAGE TypeFamilies #-}
8
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.
12 --
13 -- The teams appear to use the shared "TSN.Team" representation.
14 --
15 module TSN.XML.ScheduleChanges (
16 dtd,
17 pickle_message,
18 -- * Tests
19 schedule_changes_tests,
20 -- * WARNING: these are private but exported to silence warnings
21 ScheduleChangesConstructor(..),
22 ScheduleChangesListingConstructor(..) )
23 where
24
25 -- System imports.
26 import Control.Monad ( forM_ )
27 import Data.Time ( UTCTime(..) )
28 import Data.Tuple.Curry ( uncurryN )
29 import qualified Data.Vector.HFixed as H ( HVector, convert )
30 import Database.Groundhog (
31 countAll,
32 deleteAll,
33 insert_,
34 migrate,
35 runMigration,
36 silentMigrationLogger )
37 import Database.Groundhog.Core ( DefaultKey )
38 import Database.Groundhog.Generic ( runDbConn )
39 import Database.Groundhog.Sqlite ( withSqliteConn )
40 import Database.Groundhog.TH (
41 groundhog,
42 mkPersist )
43 import qualified GHC.Generics as GHC ( Generic )
44 import Test.Tasty ( TestTree, testGroup )
45 import Test.Tasty.HUnit ( (@?=), testCase )
46 import Text.XML.HXT.Core (
47 PU,
48 xp6Tuple,
49 xp11Tuple,
50 xpAttr,
51 xpElem,
52 xpInt,
53 xpList,
54 xpOption,
55 xpPair,
56 xpText,
57 xpWrap )
58
59 -- Local imports.
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(..) )
66 import Xml (
67 FromXml(..),
68 ToDb(..),
69 pickle_unpickle,
70 unpickleable,
71 unsafe_unpickle )
72
73
74
75 -- | The DTD to which this module corresponds. Used to invoke
76 -- 'dbimport'.
77 --
78 dtd :: String
79 dtd = "Schedule_Changes_XML.dtd"
80
81
82 --
83 -- DB/XML data types
84 --
85
86 -- * ScheduleChanges/Message
87
88 -- | Database representation of a 'Message'. Comparatively, it lacks
89 -- the listings since they are linked via a foreign key.
90 --
91 data ScheduleChanges =
92 ScheduleChanges {
93 db_xml_file_id :: Int,
94 db_heading :: String,
95 db_category :: String,
96 db_sport :: String,
97 db_time_stamp :: UTCTime }
98 deriving (Eq, Show)
99
100
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.
105 --
106 data ScheduleChangeXml =
107 ScheduleChangeXml {
108 xml_sc_sport :: String,
109 xml_sc_listings :: [ScheduleChangesListingXml] }
110 deriving (Eq, GHC.Generic, Show)
111
112
113 -- | For 'H.convert'.
114 --
115 instance H.HVector ScheduleChangeXml
116
117
118 -- | XML representation of a 'ScheduleChanges'. It has the same
119 -- fields, but in addition contains the 'xml_listings'.
120 --
121 data Message =
122 Message {
123 xml_xml_file_id :: Int,
124 xml_heading :: String,
125 xml_category :: String,
126 xml_sport :: String,
127 xml_schedule_changes :: [ScheduleChangeXml],
128 xml_time_stamp :: UTCTime }
129 deriving (Eq, GHC.Generic, Show)
130
131
132 -- | For 'H.convert'.
133 --
134 instance H.HVector Message
135
136
137 instance ToDb Message where
138 -- | The database analogue of a 'Message' is a 'ScheduleChanges'.
139 --
140 type Db Message = ScheduleChanges
141
142
143 -- | The 'FromXml' instance for 'Message' is required for the
144 -- 'XmlImport' instance.
145 --
146 instance FromXml Message where
147 -- | To convert a 'Message' to an 'ScheduleChanges', we just drop
148 -- the 'xml_schedule_changes'.
149 --
150 from_xml Message{..} =
151 ScheduleChanges {
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 }
157
158
159 -- | This allows us to insert the XML representation 'Message'
160 -- directly.
161 --
162 instance XmlImport Message
163
164
165
166 -- * ScheduleChangesListing/ScheduleChangesListingXml
167
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.
171 --
172 -- The leading underscores prevent unused field warnings.
173 --
174 data ScheduleChangesListingStatus =
175 ScheduleChangesListingStatus {
176 _db_status_numeral :: Int,
177 _db_status :: Maybe String } -- Yes, they can be empty.
178 deriving (Eq, GHC.Generic, Show)
179
180
181 -- | For 'H.convert'.
182 --
183 instance H.HVector ScheduleChangesListingStatus
184
185
186 -- | Database representation of a \<SC_Listing\> contained within a
187 -- \<Schedule_Change\>, within a \<message\>. During the transition
188 -- to the database, we drop the intermediate \<Schedule_Change\>
189 -- leaving the listing keyed to the 'ScheduleChanges' itself.
190 --
191 -- The home/away teams reuse the 'Team' representation.
192 --
193 -- The sport name (sc_sport) is pulled out of the containing
194 -- \<Schedule_Change\> and embedded into the listings themselves.
195 --
196 data ScheduleChangesListing =
197 ScheduleChangesListing {
198 db_schedule_changes_id :: DefaultKey ScheduleChanges,
199 db_away_team_id :: DefaultKey Team,
200 db_home_team_id ::DefaultKey Team,
201 db_type :: String,
202 db_sc_sport :: String,
203 db_schedule_id :: Int,
204 db_game_time :: UTCTime,
205 db_location :: Maybe String,
206 db_vscore :: Int,
207 db_hscore :: Int,
208 db_listing_status :: ScheduleChangesListingStatus,
209 db_notes :: Maybe String }
210
211
212 -- | XML representation of a \<SC_Listing\> contained within a
213 -- \<Schedule_Change\>, within a \<message\>.
214 --
215 data ScheduleChangesListingXml =
216 ScheduleChangesListingXml {
217 xml_type :: String,
218 xml_schedule_id :: Int,
219 xml_game_date :: UTCTime,
220 xml_game_time :: Maybe UTCTime,
221 xml_location :: Maybe String,
222 xml_away_team :: VTeam,
223 xml_home_team :: HTeam,
224 xml_vscore :: Int,
225 xml_hscore :: Int,
226 xml_listing_status :: ScheduleChangesListingStatus,
227 xml_notes :: Maybe String }
228 deriving (Eq, GHC.Generic, Show)
229
230
231 -- | For 'H.convert'.
232 --
233 instance H.HVector ScheduleChangesListingXml
234
235
236 instance ToDb ScheduleChangesListingXml where
237 -- | The database analogue of an 'ScheduleChangesListingXml' is
238 -- an 'ScheduleChangesListing'.
239 --
240 type Db ScheduleChangesListingXml = ScheduleChangesListing
241
242
243
244 -- | We don't make 'ScheduleChangesListingXml' an instance of
245 -- 'FromXmlFkTeams' because it needs some additional information,
246 -- namely the sport name from its containing \<Schedule_Change\>.
247 -- But essentially we'll need to do the same thing as
248 -- 'from_xml_fk_teams'. This function accomplishes the same thing,
249 -- with the addition of the sport that's passed in.
250 --
251 -- The parameter order is for convenience later (see dbimport).
252 --
253 from_xml_fk_sport :: (DefaultKey ScheduleChanges)
254 -> String -- ^ The sport from our containing schedule change
255 -> (DefaultKey Team) -- ^ Away team FK
256 -> (DefaultKey Team) -- ^ Home team FK
257 -> ScheduleChangesListingXml
258 -> ScheduleChangesListing
259 from_xml_fk_sport fk sport fk_away fk_home ScheduleChangesListingXml{..} =
260 ScheduleChangesListing {
261 db_schedule_changes_id = fk,
262 db_away_team_id = fk_away,
263 db_home_team_id = fk_home,
264 db_type = xml_type,
265 db_sc_sport = sport,
266 db_schedule_id = xml_schedule_id,
267 db_game_time = make_game_time xml_game_date xml_game_time,
268 db_location = xml_location,
269 db_vscore = xml_vscore,
270 db_hscore = xml_hscore,
271 db_listing_status = xml_listing_status,
272 db_notes = xml_notes }
273 where
274 -- | Make the database \"game time\" from the XML
275 -- date/time. Simply take the day part from one and the time
276 -- from the other.
277 --
278 make_game_time d Nothing = d
279 make_game_time d (Just t) = UTCTime (utctDay d) (utctDayTime t)
280
281
282
283 --
284 -- * Database stuff.
285 --
286
287 instance DbImport Message where
288 dbmigrate _ =
289 run_dbmigrate $ do
290 migrate (undefined :: Team)
291 migrate (undefined :: ScheduleChanges)
292 migrate (undefined :: ScheduleChangesListing)
293
294 dbimport m = do
295 -- Insert the top-level message
296 msg_id <- insert_xml m
297
298 -- Now loop through the message's schedule changes
299 forM_ (xml_schedule_changes m) $ \sc -> do
300 -- Construct the function that will turn an XML listing into a DB one.
301 -- This is only partially applied without the away/home team IDs.
302 let listing_xml_to_db = from_xml_fk_sport msg_id (xml_sc_sport sc)
303
304 -- Now loop through the listings so that we can handle the teams
305 -- one listing at a time.
306 forM_ (xml_sc_listings sc) $ \listing -> do
307 away_team_id <- insert_or_select (vteam $ xml_away_team listing)
308 home_team_id <- insert_or_select (hteam $ xml_home_team listing)
309
310 -- Finish constructing the xml -> db function.
311 let listing_xml_to_db' = listing_xml_to_db away_team_id home_team_id
312 let db_listing = listing_xml_to_db' listing
313
314 insert_ db_listing
315
316 return ImportSucceeded
317
318
319 mkPersist tsn_codegen_config [groundhog|
320 - entity: ScheduleChanges
321 dbName: schedule_changes
322 constructors:
323 - name: ScheduleChanges
324 uniques:
325 - name: unique_schedule_changes
326 type: constraint
327 # Prevent multiple imports of the same message.
328 fields: [db_xml_file_id]
329
330 # Note: we drop the "sc" prefix from the db_sc_sport field.
331 - entity: ScheduleChangesListing
332 dbName: schedule_changes_listings
333 constructors:
334 - name: ScheduleChangesListing
335 fields:
336 - name: db_schedule_changes_id
337 reference:
338 onDelete: cascade
339 - name: db_away_team_id
340 reference:
341 onDelete: cascade
342 - name: db_home_team_id
343 reference:
344 onDelete: cascade
345 - name: db_sc_sport
346 dbName: sport
347 - name: db_listing_status
348 embeddedType:
349 - {name: status_numeral, dbName: status_numeral}
350 - {name: status, dbName: status}
351
352 - embedded: ScheduleChangesListingStatus
353 fields:
354 - name: _db_status_numeral
355 dbName: status_numeral
356 - name: _db_status
357 dbName: status
358
359 |]
360
361
362
363 --
364 -- * Pickling
365 --
366
367 -- | An (un)pickler for the \<Away_Team\> elements.
368 --
369 pickle_away_team :: PU VTeam
370 pickle_away_team =
371 xpElem "Away_Team" $
372 xpWrap (from_tuple, to_tuple') $
373 xpPair (xpAttr "AT_ID" xpText)
374 (xpOption xpText)
375 where
376 from_tuple (x,y) = VTeam (Team x Nothing y)
377 to_tuple' (VTeam t) = (team_id t, name t)
378
379
380 -- | An (un)pickler for the \<Away_Team\> elements.
381 --
382 pickle_home_team :: PU HTeam
383 pickle_home_team =
384 xpElem "Home_Team" $
385 xpWrap (from_tuple, to_tuple') $
386 xpPair (xpAttr "HT_ID" xpText)
387 (xpOption xpText)
388 where
389 from_tuple (x,y) = HTeam (Team x Nothing y)
390 to_tuple' (HTeam t) = (team_id t, name t)
391
392
393 -- | An (un)pickler for the \<status\> elements.
394 --
395 pickle_status :: PU ScheduleChangesListingStatus
396 pickle_status =
397 xpElem "status" $
398 xpWrap (from_tuple, H.convert) $
399 xpPair (xpAttr "numeral" xpInt)
400 (xpOption xpText)
401 where
402 from_tuple = uncurry ScheduleChangesListingStatus
403
404
405 -- | An (un)pickler for the \<SC_Listing\> elements.
406 --
407 pickle_listing :: PU ScheduleChangesListingXml
408 pickle_listing =
409 xpElem "SC_Listing" $
410 xpWrap (from_tuple, H.convert) $
411 xp11Tuple (xpAttr "type" xpText)
412 (xpElem "Schedule_ID" xpInt)
413 (xpElem "Game_Date" xp_date_padded)
414 (xpElem "Game_Time" xp_tba_time)
415 (xpElem "Location" (xpOption xpText))
416 pickle_away_team
417 pickle_home_team
418 (xpElem "vscore" xpInt)
419 (xpElem "hscore" xpInt)
420 pickle_status
421 (xpElem "notes" (xpOption xpText))
422 where
423 from_tuple = uncurryN ScheduleChangesListingXml
424
425
426 -- | An (un)pickler for the \<Schedule_Change\> elements.
427 --
428 pickle_schedule_change :: PU ScheduleChangeXml
429 pickle_schedule_change =
430 xpElem "Schedule_Change" $
431 xpWrap (from_tuple, H.convert) $
432 xpPair (xpAttr "Sport" xpText)
433 (xpList pickle_listing)
434 where
435 from_tuple = uncurry ScheduleChangeXml
436
437
438 -- | Pickler for the top-level 'Message'.
439 --
440 pickle_message :: PU Message
441 pickle_message =
442 xpElem "message" $
443 xpWrap (from_tuple, H.convert) $
444 xp6Tuple (xpElem "XML_File_ID" xpInt)
445 (xpElem "heading" xpText)
446 (xpElem "category" xpText)
447 (xpElem "sport" xpText)
448 (xpList pickle_schedule_change)
449 (xpElem "time_stamp" xp_time_stamp)
450 where
451 from_tuple = uncurryN Message
452
453
454
455 --
456 -- * Tests
457 --
458 -- | A list of all tests for this module.
459 --
460 schedule_changes_tests :: TestTree
461 schedule_changes_tests =
462 testGroup
463 "ScheduleChanges tests"
464 [ test_on_delete_cascade,
465 test_pickle_of_unpickle_is_identity,
466 test_unpickle_succeeds ]
467
468 -- | If we unpickle something and then pickle it, we should wind up
469 -- with the same thing we started with. WARNING: success of this
470 -- test does not mean that unpickling succeeded.
471 --
472 test_pickle_of_unpickle_is_identity :: TestTree
473 test_pickle_of_unpickle_is_identity =
474 testCase "pickle composed with unpickle is the identity" $ do
475 let path = "test/xml/Schedule_Changes_XML.xml"
476 (expected, actual) <- pickle_unpickle pickle_message path
477 actual @?= expected
478
479
480
481 -- | Make sure we can actually unpickle these things.
482 --
483 test_unpickle_succeeds :: TestTree
484 test_unpickle_succeeds =
485 testCase "unpickling succeeds" $ do
486 let path = "test/xml/Schedule_Changes_XML.xml"
487 actual <- unpickleable path pickle_message
488
489 let expected = True
490 actual @?= expected
491
492
493
494 -- | Make sure everything gets deleted when we delete the top-level
495 -- record.
496 --
497 test_on_delete_cascade :: TestTree
498 test_on_delete_cascade =
499 testCase "deleting auto_racing_results deletes its children" $ do
500 let path = "test/xml/Schedule_Changes_XML.xml"
501 results <- unsafe_unpickle path pickle_message
502 let a = undefined :: Team
503 let b = undefined :: ScheduleChanges
504 let c = undefined :: ScheduleChangesListing
505
506 actual <- withSqliteConn ":memory:" $ runDbConn $ do
507 runMigration silentMigrationLogger $ do
508 migrate a
509 migrate b
510 migrate c
511 _ <- dbimport results
512 deleteAll b
513 count_a <- countAll a
514 count_b <- countAll b
515 count_c <- countAll c
516 return $ sum [count_a, count_b, count_c]
517 let expected = 12 -- There are 16 team elements, but 4 are dupes,
518 -- so 12 unique teams should be left over.
519 actual @?= expected