2 {-# LANGUAGE DeriveDataTypeable #-}
3 {-# LANGUAGE DeriveGeneric #-}
4 {-# LANGUAGE FlexibleInstances #-}
6 {-# LANGUAGE QuasiQuotes #-}
7 {-# LANGUAGE RecordWildCards #-}
8 {-# LANGUAGE TemplateHaskell #-}
9 {-# LANGUAGE TypeFamilies #-}
11 -- | Parse TSN XML for the DTD
12 -- \"Auto_Racing_Schedule_XML.dtd\". There's a top-level
13 -- \<message\>, containing \<Listing\>s, containing \<RaceResults\>,
14 -- containing \<RaceResultsListing\>s.
16 module TSN.XML.AutoRacingSchedule (
20 auto_racing_schedule_tests,
21 -- * WARNING: these are private but exported to silence warnings
22 AutoRacingScheduleConstructor(..),
23 AutoRacingScheduleListingConstructor(..),
24 AutoRacingScheduleListingRaceResultRaceResultListingConstructor(..) )
28 import Control.Monad ( forM_ )
29 import Data.Time ( UTCTime(..) )
30 import Data.Tuple.Curry ( uncurryN )
31 import qualified Data.Vector.HFixed as H ( HVector, cons, convert )
32 import Database.Groundhog (
37 silentMigrationLogger )
38 import Database.Groundhog.Core ( DefaultKey )
39 import Database.Groundhog.Generic ( runDbConn )
40 import Database.Groundhog.Sqlite ( withSqliteConn )
41 import Database.Groundhog.TH (
44 import qualified GHC.Generics as GHC ( Generic )
45 import Test.Tasty ( TestTree, testGroup )
46 import Test.Tasty.HUnit ( (@?=), testCase )
47 import Text.XML.HXT.Core (
62 import TSN.DbImport ( DbImport(..), ImportResult(..), run_dbmigrate )
63 import TSN.Picklers ( xp_date_padded, xp_tba_time, xp_time_stamp )
64 import TSN.XmlImport ( XmlImport(..), XmlImportFk(..) )
75 -- | The DTD to which this module corresponds. Used to invoke dbimport.
78 dtd = "Auto_Racing_Schedule_XML.dtd"
84 -- * AutoRacingSchedule/Message
86 -- | Database representation of a 'Message'.
88 data AutoRacingSchedule =
90 db_xml_file_id :: Int,
92 db_category :: String,
95 db_complete_through :: String,
96 db_time_stamp :: UTCTime }
100 -- | XML Representation of an 'AutoRacingSchedule'.
104 xml_xml_file_id :: Int,
105 xml_heading :: String,
106 xml_category :: String,
109 xml_complete_through :: String,
110 xml_listings :: [AutoRacingScheduleListingXml],
111 xml_time_stamp :: UTCTime }
112 deriving (Eq, GHC.Generic, Show)
114 -- | For 'H.convert'.
116 instance H.HVector Message
119 instance ToDb Message where
120 -- | The database analogue of a 'Message' is a 'AutoRacingSchedule'.
122 type Db Message = AutoRacingSchedule
125 -- | The 'FromXml' instance for 'Message' is required for the
126 -- 'XmlImport' instance.
128 instance FromXml Message where
129 -- | To convert a 'Message' to an 'AutoRacingSchedule', we just drop
130 -- the 'xml_listings'.
132 from_xml Message{..} =
134 db_xml_file_id = xml_xml_file_id,
135 db_heading = xml_heading,
136 db_category = xml_category,
137 db_sport = xml_sport,
138 db_title = xml_title,
139 db_complete_through = xml_complete_through,
140 db_time_stamp = xml_time_stamp }
143 -- | This allows us to insert the XML representation 'Message'
146 instance XmlImport Message
149 -- * AutoRacingScheduleListing/AutoRacingScheduleListingXml
151 -- | Database representation of a \<Listing\> contained within a
152 -- \<message\>. We combine the race date/time into a single
153 -- race_time, drop the race results list, and add a foreign key to
156 data AutoRacingScheduleListing =
157 AutoRacingScheduleListing {
158 db_auto_racing_schedules_id :: DefaultKey AutoRacingSchedule,
160 db_race_time :: UTCTime,
161 db_race_name :: String,
162 db_track_name :: String,
163 db_location :: String,
164 db_tv_listing :: Maybe String,
166 db_track_length :: String -- ^ Sometimes the word "miles" shows up.
170 -- | XML representation of a \<Listing\> contained within a
173 data AutoRacingScheduleListingXml =
174 AutoRacingScheduleListingXml {
176 xml_race_date :: UTCTime,
177 xml_race_time :: Maybe UTCTime,
178 xml_race_name :: String,
179 xml_track_name :: String,
180 xml_location :: String,
181 xml_tv_listing :: Maybe String,
183 xml_track_length :: String, -- ^ Sometimes the word \"miles\" shows up,
184 -- so we can't do the right thing and use
186 xml_race_results :: [AutoRacingScheduleListingRaceResult] }
187 deriving (Eq, GHC.Generic, Show)
189 -- | For 'H.convert'.
191 instance H.HVector AutoRacingScheduleListingXml
194 -- | Pseudo-accessor to get the race result listings out of a
195 -- 'AutoRacingScheduleListingXml'. A poor man's lens.
197 result_listings :: AutoRacingScheduleListingXml
198 -> [AutoRacingScheduleListingRaceResultRaceResultListingXml]
199 result_listings = (concatMap xml_race_result_listing) . xml_race_results
202 instance ToDb AutoRacingScheduleListingXml where
203 -- | The database analogue of an 'AutoRacingScheduleListingXml' is
204 -- an 'AutoRacingScheduleListing'.
206 type Db AutoRacingScheduleListingXml = AutoRacingScheduleListing
209 instance Child AutoRacingScheduleListingXml where
210 -- | Each 'AutoRacingScheduleListingXml' is contained in (i.e. has a
211 -- foreign key to) a 'AutoRacingSchedule'.
213 type Parent AutoRacingScheduleListingXml = AutoRacingSchedule
216 instance FromXmlFk AutoRacingScheduleListingXml where
217 -- | To convert an 'AutoRacingScheduleListingXml' to an
218 -- 'AutoRacingScheduleListing', we add the foreign key and drop
219 -- the 'xml_race_results'. We also mash the date/time together
222 from_xml_fk fk AutoRacingScheduleListingXml{..} =
223 AutoRacingScheduleListing {
224 db_auto_racing_schedules_id = fk,
225 db_race_id = xml_race_id,
226 db_race_time = make_race_time xml_race_date xml_race_time,
227 db_race_name = xml_race_name,
228 db_track_name = xml_track_name,
229 db_location = xml_location,
230 db_tv_listing = xml_tv_listing,
232 db_track_length = xml_track_length }
234 -- | Make the database \"race time\" from the XML
235 -- date/time. Simply take the day part from one and the time
238 make_race_time d Nothing = d
239 make_race_time d (Just t) = UTCTime (utctDay d) (utctDayTime t)
242 -- | This allows us to insert the XML representation
243 -- 'AutoRacingScheduleListingXml' directly.
245 instance XmlImportFk AutoRacingScheduleListingXml
249 -- * AutoRacingScheduleListingRaceResult
251 -- | The XML representation of \<message\> -> \<Listing\> ->
252 -- \<RaceResults\>. This element serves only to contain
253 -- \<RaceResultsListing\>s, so we don't store the intermediate table
256 newtype AutoRacingScheduleListingRaceResult =
257 AutoRacingScheduleListingRaceResult {
258 xml_race_result_listing ::
259 [AutoRacingScheduleListingRaceResultRaceResultListingXml] }
263 -- * AutoRacingScheduleListingRaceResultRaceResultListing / AutoRacingScheduleListingRaceResultRaceResultListingXml
265 -- Sorry about the names yo.
268 -- | Database representation of \<RaceResultListing\> within
269 -- \<RaceResults\> within \<Listing\> within... \<message\>!
270 -- The leading underscores prevent unused field warnings.
272 data AutoRacingScheduleListingRaceResultRaceResultListing =
273 AutoRacingScheduleListingRaceResultRaceResultListing {
274 _db_auto_racing_schedules_listings_id ::
275 DefaultKey AutoRacingScheduleListing,
276 _db_finish_position :: Int,
277 _db_driver_id :: Int,
279 _db_leading_laps :: Int,
280 _db_listing_laps :: Int, -- ^ Avoid clash with race's \"laps\" field.
281 _db_earnings :: String, -- ^ This should be an Int, but can have commas.
282 _db_status :: Maybe String -- ^ They can be empty
284 deriving ( GHC.Generic )
288 instance H.HVector AutoRacingScheduleListingRaceResultRaceResultListing
291 -- | XML Representation of an
292 -- 'AutoRacingScheduleListingRaceResultRaceResultListing'.
293 -- The leading underscores prevent unused field warnings.
295 data AutoRacingScheduleListingRaceResultRaceResultListingXml =
296 AutoRacingScheduleListingRaceResultRaceResultListingXml {
297 _xml_finish_position :: Int,
298 _xml_driver_id :: Int,
300 _xml_leading_laps :: Int,
301 _xml_listing_laps :: Int, -- ^ Avoids clash with race's \"laps\" field.
302 _xml_earnings :: String, -- ^ Should be an 'Int', but can have commas.
303 _xml_status :: Maybe String -- ^ They can be empty
305 deriving (Eq, GHC.Generic, Show)
307 -- | For 'H.convert'.
309 instance H.HVector AutoRacingScheduleListingRaceResultRaceResultListingXml
312 instance ToDb AutoRacingScheduleListingRaceResultRaceResultListingXml where
313 -- | The database representation of an
314 -- 'AutoRacingScheduleListingRaceResultRaceResultListingXml' is an
315 -- 'AutoRacingScheduleListingRaceResultRaceResultListing'.
317 type Db AutoRacingScheduleListingRaceResultRaceResultListingXml =
318 AutoRacingScheduleListingRaceResultRaceResultListing
321 instance Child AutoRacingScheduleListingRaceResultRaceResultListingXml where
322 -- | Each 'AutoRacingScheduleListingRaceResultRaceResultListingXml'
323 -- is contained in (i.e. has a foreign key to) an
324 -- 'AutoRacingScheduleListing'. We skip the intermediate
327 type Parent AutoRacingScheduleListingRaceResultRaceResultListingXml =
328 AutoRacingScheduleListing
331 instance FromXmlFk AutoRacingScheduleListingRaceResultRaceResultListingXml where
333 -- 'AutoRacingScheduleListingRaceResultRaceResultListingXml' to an
334 -- 'AutoRacingScheduleListingRaceResultRaceResultListing', we just
335 -- add the foreign key to the parent 'AutoRacingScheduleListing'.
340 -- | This allows us to insert the XML representation
341 -- 'AutoRacingScheduleListingRaceResultRaceResultListingXml'
344 instance XmlImportFk AutoRacingScheduleListingRaceResultRaceResultListingXml
351 instance DbImport Message where
354 migrate (undefined :: AutoRacingSchedule)
355 migrate (undefined :: AutoRacingScheduleListing)
357 :: AutoRacingScheduleListingRaceResultRaceResultListing)
360 -- | We insert the message, then use its ID to insert the listings,
361 -- using their IDs to insert the race result listings.
364 msg_id <- insert_xml m
366 forM_ (xml_listings m) $ \listing -> do
367 listing_id <- insert_xml_fk msg_id listing
369 mapM_ (insert_xml_fk_ listing_id) (result_listings listing)
371 return ImportSucceeded
374 mkPersist tsn_codegen_config [groundhog|
375 - entity: AutoRacingSchedule
376 dbName: auto_racing_schedules
378 - name: AutoRacingSchedule
380 - name: unique_auto_racing_schedules
382 # Prevent multiple imports of the same message.
383 fields: [db_xml_file_id]
385 - entity: AutoRacingScheduleListing
386 dbName: auto_racing_schedules_listings
388 - name: AutoRacingScheduleListing
390 - name: db_auto_racing_schedules_id
394 - entity: AutoRacingScheduleListingRaceResultRaceResultListing
395 dbName: auto_racing_schedules_listings_race_result_listings
397 - name: AutoRacingScheduleListingRaceResultRaceResultListing
399 - name: _db_auto_racing_schedules_listings_id
410 -- | Pickler for the top-level 'Message'.
412 pickle_message :: PU Message
415 xpWrap (from_tuple, H.convert) $
416 xp8Tuple (xpElem "XML_File_ID" xpInt)
417 (xpElem "heading" xpText)
418 (xpElem "category" xpText)
419 (xpElem "sport" xpText)
420 (xpElem "Title" xpText)
421 (xpElem "Complete_Through" xpText)
422 (xpList pickle_listing)
423 (xpElem "time_stamp" xp_time_stamp)
425 from_tuple = uncurryN Message
428 -- | Convert an 'AutoRacingScheduleListingXml' to/from XML.
430 pickle_listing :: PU AutoRacingScheduleListingXml
433 xpWrap (from_tuple, H.convert) $
434 xp10Tuple (xpElem "RaceID" xpInt)
435 (xpElem "Race_Date" xp_date_padded)
436 (xpElem "Race_Time" xp_tba_time)
437 (xpElem "RaceName" xpText)
438 (xpElem "TrackName" xpText)
439 (xpElem "Location" xpText)
440 (xpElem "TV_Listing" $ xpOption xpText)
441 (xpElem "Laps" xpInt)
442 (xpElem "TrackLength" xpText)
443 (xpList pickle_race_results)
445 from_tuple = uncurryN AutoRacingScheduleListingXml
449 -- | Convert an 'AutoRacingScheduleListingRaceResult' to/from XML.
451 pickle_race_results :: PU AutoRacingScheduleListingRaceResult
452 pickle_race_results =
453 xpElem "RaceResults" $
454 xpWrap (to_result, from_result) $
455 xpList pickle_race_results_listing
457 to_result = AutoRacingScheduleListingRaceResult
458 from_result = xml_race_result_listing
462 -- 'AutoRacingScheduleListingRaceResultRaceResultListingXml' to/from
465 pickle_race_results_listing ::
466 PU AutoRacingScheduleListingRaceResultRaceResultListingXml
467 pickle_race_results_listing =
468 xpElem "RaceResultsListing" $
469 xpWrap (from_tuple, H.convert) $
470 xp7Tuple (xpElem "FinishPosition" xpInt)
471 (xpElem "DriverID" xpInt)
472 (xpElem "Name" xpText)
473 (xpElem "LeadingLaps" xpInt)
474 (xpElem "Laps" xpInt)
475 (xpElem "Earnings" xpText)
476 (xpElem "Status" (xpOption xpText))
479 uncurryN AutoRacingScheduleListingRaceResultRaceResultListingXml
486 -- | A list of all tests for this module.
488 auto_racing_schedule_tests :: TestTree
489 auto_racing_schedule_tests =
491 "AutoRacingSchedule tests"
492 [ test_on_delete_cascade,
493 test_pickle_of_unpickle_is_identity,
494 test_unpickle_succeeds ]
496 -- | If we unpickle something and then pickle it, we should wind up
497 -- with the same thing we started with. WARNING: success of this
498 -- test does not mean that unpickling succeeded.
500 test_pickle_of_unpickle_is_identity :: TestTree
501 test_pickle_of_unpickle_is_identity = testGroup "pickle-unpickle tests"
502 [ check "pickle composed with unpickle is the identity"
503 "test/xml/Auto_Racing_Schedule_XML.xml",
505 check "pickle composed with unpickle is the identity (miles track length)"
506 "test/xml/Auto_Racing_Schedule_XML-miles-track-length.xml" ]
508 check desc path = testCase desc $ do
509 (expected, actual) <- pickle_unpickle pickle_message path
513 -- | Make sure we can actually unpickle these things.
515 test_unpickle_succeeds :: TestTree
516 test_unpickle_succeeds = testGroup "unpickle tests"
517 [ check "unpickling succeeds"
518 "test/xml/Auto_Racing_Schedule_XML.xml",
520 check "unpickling succeeds (non-int team_id)"
521 "test/xml/Auto_Racing_Schedule_XML-miles-track-length.xml" ]
523 check desc path = testCase desc $ do
524 actual <- unpickleable path pickle_message
529 -- | Make sure everything gets deleted when we delete the top-level
532 test_on_delete_cascade :: TestTree
533 test_on_delete_cascade = testGroup "cascading delete tests"
534 [ check "deleting auto_racing_schedules deletes its children"
535 "test/xml/Auto_Racing_Schedule_XML.xml" ,
537 check ("deleting auto_racing_schedules deletes its children " ++
538 "(miles track length)")
539 "test/xml/Auto_Racing_Schedule_XML-miles-track-length.xml" ]
541 check desc path = testCase desc $ do
542 sched <- unsafe_unpickle path pickle_message
543 let a = undefined :: AutoRacingSchedule
544 let b = undefined :: AutoRacingScheduleListing
545 let c = undefined :: AutoRacingScheduleListingRaceResultRaceResultListing
547 actual <- withSqliteConn ":memory:" $ runDbConn $ do
548 runMigration silentMigrationLogger $ do
554 count_a <- countAll a
555 count_b <- countAll b
556 count_c <- countAll c
557 return $ sum [count_a, count_b, count_c]