]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blob - src/TSN/XML/News.hs
Remove unused StandaloneDeriving pragmas.
[dead/htsn-import.git] / src / TSN / XML / News.hs
1 {-# LANGUAGE DeriveDataTypeable #-}
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 \"newsxml.dtd\". Each document contains
10 -- a root element \<message\> that contains an entire news item.
11 --
12 module TSN.XML.News (
13 dtd,
14 pickle_message,
15 -- * Tests
16 news_tests,
17 -- * WARNING: these are private but exported to silence warnings
18 News_NewsLocationConstructor(..),
19 News_NewsTeamConstructor(..),
20 NewsConstructor(..),
21 NewsLocationConstructor(..),
22 NewsTeamConstructor(..) )
23 where
24
25 -- System imports.
26 import Data.Data ( Data, constrFields, dataTypeConstrs, dataTypeOf )
27 import Data.Time.Clock ( UTCTime )
28 import Data.List.Utils ( join, split )
29 import Data.Tuple.Curry ( uncurryN )
30 import Data.Typeable ( Typeable )
31 import Database.Groundhog (
32 countAll,
33 deleteAll,
34 insert_,
35 migrate,
36 runMigration,
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 (
42 defaultCodegenConfig,
43 groundhog,
44 mkPersist )
45 import Test.Tasty ( TestTree, testGroup )
46 import Test.Tasty.HUnit ( (@?=), testCase )
47 import Text.XML.HXT.Core (
48 PU,
49 xp13Tuple,
50 xpAttr,
51 xpElem,
52 xpInt,
53 xpList,
54 xpOption,
55 xpPair,
56 xpText,
57 xpTriple,
58 xpWrap )
59
60 -- Local imports.
61 import TSN.Codegen (
62 tsn_codegen_config,
63 tsn_db_field_namer ) -- Used in a test
64 import TSN.Database ( insert_or_select )
65 import TSN.DbImport ( DbImport(..), ImportResult(..), run_dbmigrate )
66 import TSN.Picklers ( xp_time_stamp )
67 import TSN.XmlImport ( XmlImport(..) )
68 import Xml (
69 FromXml(..),
70 ToDb(..),
71 pickle_unpickle,
72 unpickleable,
73 unsafe_unpickle )
74
75
76 -- | The DTD to which this module corresponds. Used to invoke dbimport.
77 --
78 dtd :: String
79 dtd = "newsxml.dtd"
80
81
82 --
83 -- DB/XML Data types
84 --
85
86 -- * News/Message
87
88 -- | The msg_id child of <message> contains an event_id attribute; we
89 -- embed it into the 'News' type. We (pointlessly) use the "db_"
90 -- prefix here so that the two names don't collide on "id" when
91 -- Groundhog is creating its fields using our field namer.
92 --
93 data MsgId =
94 MsgId {
95 db_msg_id :: Int,
96 db_event_id :: Maybe Int }
97 deriving (Data, Eq, Show, Typeable)
98
99
100 -- | The XML representation of a news item (\<message\>).
101 --
102 data Message =
103 Message {
104 xml_xml_file_id :: Int,
105 xml_heading :: String,
106 xml_mid :: MsgId,
107 xml_category :: String,
108 xml_sport :: String,
109 xml_url :: Maybe String,
110 xml_teams :: [NewsTeam],
111 xml_locations :: [NewsLocation],
112 xml_sms :: String,
113 xml_editor :: Maybe String,
114 xml_text :: Maybe String, -- Text and continue seem to show up in pairs,
115 xml_continue :: Maybe String, -- either both present or both missing.
116 xml_time_stamp :: UTCTime }
117 deriving (Eq, Show)
118
119
120 -- | The database representation of a news item. We drop several
121 -- uninteresting fields from 'Message', and omit the list fields which
122 -- will be represented as join tables.
123 --
124 data News =
125 News {
126 db_xml_file_id :: Int,
127 db_mid :: MsgId,
128 db_sport :: String,
129 db_url :: Maybe String,
130 db_sms :: String,
131 db_editor :: Maybe String,
132 db_text :: Maybe String,
133 db_continue :: Maybe String,
134 db_time_stamp :: UTCTime }
135 deriving (Data, Eq, Show, Typeable)
136
137
138
139 instance ToDb Message where
140 -- | The database representation of 'Message' is 'News'.
141 type Db Message = News
142
143 -- | Convert the XML representation 'Message' to the database
144 -- representation 'News'.
145 --
146 instance FromXml Message where
147 -- | We use a record wildcard so GHC doesn't complain that we never
148 -- used the field names.
149 --
150 from_xml Message{..} = News { db_xml_file_id = xml_xml_file_id,
151 db_mid = xml_mid,
152 db_sport = xml_sport,
153 db_url = xml_url,
154 db_sms = xml_sms,
155 db_editor = xml_editor,
156 db_text = xml_text,
157 db_continue = xml_continue,
158 db_time_stamp = xml_time_stamp }
159
160 -- | This lets us insert the XML representation 'Message' directly.
161 --
162 instance XmlImport Message
163
164
165 -- * NewsTeam
166
167 -- | The database type for teams as they show up in the news.
168 --
169 data NewsTeam =
170 NewsTeam { team_name :: String }
171 deriving (Eq, Show)
172
173
174
175 -- * News_NewsTeam
176
177 -- | Mapping between News records and NewsTeam records in the
178 -- database. We don't name the fields because we don't use the names
179 -- explicitly; that means we have to give them nice database names
180 -- via groundhog.
181 --
182 data News_NewsTeam = News_NewsTeam
183 (DefaultKey News)
184 (DefaultKey NewsTeam)
185
186
187 -- * NewsLocation
188
189 -- | The database type for locations as they show up in the news.
190 --
191 data NewsLocation =
192 NewsLocation {
193 city :: Maybe String,
194 state :: Maybe String,
195 country :: String }
196 deriving (Eq, Show)
197
198
199 -- * News_NewsLocation
200
201 -- | Mapping between News records and NewsLocation records in the
202 -- database. We don't name the fields because we don't use the names
203 -- explicitly; that means we have to give them nice database names
204 -- via groundhog.
205 --
206 data News_NewsLocation = News_NewsLocation
207 (DefaultKey News)
208 (DefaultKey NewsLocation)
209
210
211
212 --
213 -- Database code
214 --
215
216 -- | Define 'dbmigrate' and 'dbimport' for 'Message's. The import is
217 -- slightly non-generic because of our 'News_NewsTeam' and
218 -- 'News_NewsLocation' join tables.
219 --
220 instance DbImport Message where
221 dbmigrate _ =
222 run_dbmigrate $ do
223 migrate (undefined :: News)
224 migrate (undefined :: NewsTeam)
225 migrate (undefined :: News_NewsTeam)
226 migrate (undefined :: NewsLocation)
227 migrate (undefined :: News_NewsLocation)
228
229 dbimport message = do
230 -- Insert the message and acquire its primary key (unique ID)
231 news_id <- insert_xml message
232
233 -- And insert each one into its own table. We use insert_xml_or_select
234 -- because we know that most teams will already exist, and we
235 -- want to get back the id for the existing team when
236 -- there's a collision.
237 nt_ids <- mapM insert_or_select (xml_teams message)
238
239 -- Now that the teams have been inserted, create
240 -- news__news_team records mapping beween the two.
241 let news_news_teams = map (News_NewsTeam news_id) nt_ids
242 mapM_ insert_ news_news_teams
243
244 -- Do all of that over again for the NewsLocations.
245 loc_ids <- mapM insert_or_select (xml_locations message)
246 let news_news_locations = map (News_NewsLocation news_id) loc_ids
247 mapM_ insert_ news_news_locations
248
249 return ImportSucceeded
250
251
252 -- These types don't have special XML representations or field name
253 -- collisions so we use the defaultCodegenConfig and give their
254 -- fields nice simple names.
255 mkPersist defaultCodegenConfig [groundhog|
256 - entity: NewsTeam
257 dbName: news_teams
258 constructors:
259 - name: NewsTeam
260 uniques:
261 - name: unique_news_team
262 type: constraint
263 fields: [team_name]
264
265 - entity: NewsLocation
266 dbName: news_locations
267 constructors:
268 - name: NewsLocation
269 uniques:
270 - name: unique_news_location
271 type: constraint
272 fields: [city, state, country]
273
274 |]
275
276
277 -- These types have fields with e.g. db_ and xml_ prefixes, so we
278 -- use our own codegen to peel those off before naming the columns.
279 mkPersist tsn_codegen_config [groundhog|
280 - entity: News
281 constructors:
282 - name: News
283 uniques:
284 - name: unique_news
285 type: constraint
286 # Prevent multiple imports of the same message.
287 fields: [db_xml_file_id]
288 fields:
289 - name: db_mid
290 embeddedType:
291 - {name: msg_id, dbName: msg_id}
292 - {name: event_id, dbName: event_id}
293
294 - embedded: MsgId
295 fields:
296 - name: db_msg_id
297 dbName: msg_id
298 - name: db_event_id
299 dbName: event_id
300
301 - entity: News_NewsTeam
302 dbName: news__news_teams
303 constructors:
304 - name: News_NewsTeam
305 fields:
306 - name: news_NewsTeam0 # Default created by mkNormalFieldName
307 dbName: news_id
308 reference:
309 onDelete: cascade
310 - name: news_NewsTeam1 # Default created by mkNormalFieldName
311 dbName: news_teams_id
312 reference:
313 onDelete: cascade
314
315 - entity: News_NewsLocation
316 dbName: news__news_locations
317 constructors:
318 - name: News_NewsLocation
319 fields:
320 - name: news_NewsLocation0 # Default created by mkNormalFieldName
321 dbName: news_id
322 reference:
323 onDelete: cascade
324 - name: news_NewsLocation1 # Default created by mkNormalFieldName
325 dbName: news_locations_id
326 reference:
327 onDelete: cascade
328 |]
329
330
331 --
332 -- XML Picklers
333 --
334
335 -- | Convert a 'NewsTeam' to/from XML.
336 --
337 pickle_news_team :: PU NewsTeam
338 pickle_news_team =
339 xpElem "team" $
340 xpWrap (from_string, to_string) xpText
341 where
342 to_string :: NewsTeam -> String
343 to_string = team_name
344
345 from_string :: String -> NewsTeam
346 from_string = NewsTeam
347
348
349 -- | Convert a 'MsgId' to/from XML.
350 --
351 pickle_msg_id :: PU MsgId
352 pickle_msg_id =
353 xpElem "msg_id" $
354 xpWrap (from_tuple, to_tuple) $
355 xpPair xpInt (xpAttr "EventId" (xpOption xpInt))
356 where
357 from_tuple = uncurryN MsgId
358 to_tuple m = (db_msg_id m, db_event_id m)
359
360
361 -- | Convert a 'NewsLocation' to/from XML.
362 --
363 pickle_location :: PU NewsLocation
364 pickle_location =
365 xpElem "location" $
366 xpWrap (from_tuple, to_tuple) $
367 xpTriple (xpOption (xpElem "city" xpText))
368 (xpOption (xpElem "state" xpText))
369 (xpElem "country" xpText)
370 where
371 from_tuple =
372 uncurryN NewsLocation
373 to_tuple l = (city l, state l, country l)
374
375
376 -- | Convert a 'Message' to/from XML.
377 --
378 pickle_message :: PU Message
379 pickle_message =
380 xpElem "message" $
381 xpWrap (from_tuple, to_tuple) $
382 xp13Tuple (xpElem "XML_File_ID" xpInt)
383 (xpElem "heading" xpText)
384 pickle_msg_id
385 (xpElem "category" xpText)
386 (xpElem "sport" xpText)
387 (xpElem "url" $ xpOption xpText)
388 (xpList pickle_news_team)
389 (xpList pickle_location)
390 (xpElem "SMS" xpText)
391 (xpOption (xpElem "Editor" xpText))
392 (xpOption (xpElem "text" xpText))
393 pickle_continue
394 (xpElem "time_stamp" xp_time_stamp)
395 where
396 from_tuple = uncurryN Message
397 to_tuple m = (xml_xml_file_id m, -- Verbose,
398 xml_heading m, -- but
399 xml_mid m, -- eliminates
400 xml_category m, -- GHC
401 xml_sport m, -- warnings
402 xml_url m, -- .
403 xml_teams m, -- .
404 xml_locations m, -- .
405 xml_sms m,
406 xml_editor m,
407 xml_text m,
408 xml_continue m,
409 xml_time_stamp m)
410
411 -- | We combine all of the \<continue\> elements into one 'String'
412 -- while unpickling and do the reverse while pickling.
413 --
414 pickle_continue :: PU (Maybe String)
415 pickle_continue =
416 xpOption $
417 xpWrap (to_string, from_string) $
418 xpElem "continue" $
419 xpList (xpElem "P" xpText)
420 where
421 from_string :: String -> [String]
422 from_string = split "\n"
423
424 to_string :: [String] -> String
425 to_string = join "\n"
426
427
428 --
429 -- Tasty Tests
430 --
431
432 -- | A list of all tests for this module.
433 --
434 news_tests :: TestTree
435 news_tests =
436 testGroup
437 "News tests"
438 [ test_news_fields_have_correct_names,
439 test_on_delete_cascade,
440 test_pickle_of_unpickle_is_identity,
441 test_unpickle_succeeds ]
442
443
444 -- | Make sure our codegen is producing the correct database names.
445 --
446 test_news_fields_have_correct_names :: TestTree
447 test_news_fields_have_correct_names =
448 testCase "news fields get correct database names" $
449 mapM_ check (zip actual expected)
450 where
451 -- This is cool, it uses the (derived) Data instance of
452 -- News.News to get its constructor names.
453 field_names :: [String]
454 field_names =
455 constrFields . head $ dataTypeConstrs $ dataTypeOf (undefined :: News)
456
457 expected :: [String]
458 expected =
459 map (\x -> tsn_db_field_namer "herp" "derp" 8675309 x 90210) field_names
460
461 actual :: [String]
462 actual = ["xml_file_id",
463 "mid",
464 "sport",
465 "url",
466 "sms",
467 "editor",
468 "text",
469 "continue"]
470
471 check (x,y) = (x @?= y)
472
473
474 -- | If we unpickle something and then pickle it, we should wind up
475 -- with the same thing we started with. WARNING: success of this
476 -- test does not mean that unpickling succeeded.
477 --
478 test_pickle_of_unpickle_is_identity :: TestTree
479 test_pickle_of_unpickle_is_identity = testGroup "pickle-unpickle tests"
480 [ check "pickle composed with unpickle is the identity"
481 "test/xml/newsxml.xml",
482
483 check "pickle composed with unpickle is the identity (with Editor)"
484 "test/xml/newsxml-with-editor.xml" ]
485 where
486 check desc path = testCase desc $ do
487 (expected, actual) <- pickle_unpickle pickle_message path
488 actual @?= expected
489
490
491 -- | Make sure we can actually unpickle these things.
492 --
493 test_unpickle_succeeds :: TestTree
494 test_unpickle_succeeds = testGroup "unpickle tests"
495 [ check "unpickling succeeds"
496 "test/xml/newsxml.xml",
497
498 check "unpickling succeeds (with Editor)"
499 "test/xml/newsxml-with-editor.xml" ]
500 where
501 check desc path = testCase desc $ do
502 actual <- unpickleable path pickle_message
503 let expected = True
504 actual @?= expected
505
506
507 -- | Make sure everything gets deleted when we delete the top-level
508 -- record.
509 --
510 test_on_delete_cascade :: TestTree
511 test_on_delete_cascade = testGroup "cascading delete tests"
512 [ check "deleting news deletes its children"
513 "test/xml/newsxml.xml"
514 4 -- 2 news_teams and 2 news_locations that should remain.
515 ]
516 where
517 check desc path expected = testCase desc $ do
518 news <- unsafe_unpickle path pickle_message
519 let a = undefined :: News
520 let b = undefined :: NewsTeam
521 let c = undefined :: News_NewsTeam
522 let d = undefined :: NewsLocation
523 let e = undefined :: News_NewsLocation
524 actual <- withSqliteConn ":memory:" $ runDbConn $ do
525 runMigration silentMigrationLogger $ do
526 migrate a
527 migrate b
528 migrate c
529 migrate d
530 migrate e
531 _ <- dbimport news
532 deleteAll a
533 count_a <- countAll a
534 count_b <- countAll b
535 count_c <- countAll c
536 count_d <- countAll d
537 count_e <- countAll e
538 return $ count_a + count_b + count_c + count_d + count_e
539 actual @?= expected