{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
--- | Parse TSN XML for the DTD "newsxml.dtd". Each document contains a
--- root element \<message\> that contains an entire news item.
+-- | Parse TSN XML for the DTD \"newsxml.dtd\". Each document contains
+-- a root element \<message\> that contains an entire news item.
--
module TSN.XML.News (
pickle_message,
import TSN.Codegen (
tsn_codegen_config,
tsn_db_field_namer ) -- Used in a test
+import TSN.Database ( insert_or_select )
import TSN.DbImport ( DbImport(..), ImportResult(..), run_dbmigrate )
import TSN.Picklers ( xp_time_stamp )
import TSN.XmlImport ( XmlImport(..) )
-- embed it into the 'News' type. We (pointlessly) use the "db_"
-- prefix here so that the two names don't collide on "id" when
-- Groundhog is creating its fields using our field namer.
+--
data MsgId =
MsgId {
db_msg_id :: Int,
deriving (Data, Eq, Show, Typeable)
--- | The XML representation of a news item (message).
+-- | The XML representation of a news item (\<message\>).
--
data Message =
Message {
instance ToDb Message where
+ -- | The database representation of 'Message' is 'News'.
type Db Message = News
-- | Convert the XML representation 'Message' to the database
db_continue = xml_continue,
db_time_stamp = xml_time_stamp }
--- | This lets us call 'insert_xml' on a 'Message'.
+-- | This lets us insert the XML representation 'Message' directly.
--
instance XmlImport Message
deriving (Eq, Show)
-instance ToDb NewsTeam where
- -- | The database representaion of a 'NewsTeam' is itself.
- type Db NewsTeam = NewsTeam
-
--- | This is needed to define the XmlImport instance for NewsTeam.
---
-instance FromXml NewsTeam where
- -- | How to we get a 'NewsTeam' from itself?
- from_xml = id
-
--- | Allow us to call 'insert_xml' on the XML representation of
--- NewsTeams.
---
-instance XmlImport NewsTeam
-
-
-- * News_NewsTeam
country :: String }
deriving (Eq, Show)
-instance ToDb NewsLocation where
- -- | The database representation of a 'NewsLocation' is itself.
- type Db NewsLocation = NewsLocation
-
--- | This is needed to define the XmlImport instance for NewsLocation.
---
-instance FromXml NewsLocation where
- -- | How to we get a 'NewsLocation' from itself?
- from_xml = id
-
--- | Allow us to call 'insert_xml' on the XML representation of
--- NewsLocations.
---
-instance XmlImport NewsLocation
-
-- * News_NewsLocation
instance DbImport Message where
dbmigrate _ =
run_dbmigrate $ do
- migrate (undefined :: NewsTeam)
- migrate (undefined :: NewsLocation)
migrate (undefined :: News)
+ migrate (undefined :: NewsTeam)
migrate (undefined :: News_NewsTeam)
+ migrate (undefined :: NewsLocation)
migrate (undefined :: News_NewsLocation)
dbimport message = do
-- because we know that most teams will already exist, and we
-- 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)
+ nt_ids <- mapM insert_or_select (xml_teams message)
-- Now that the teams have been inserted, create
-- news__news_team records mapping beween the two.
mapM_ insert_ news_news_teams
-- Do all of that over again for the NewsLocations.
- loc_ids <- mapM insert_xml_or_select (xml_locations message)
+ loc_ids <- mapM insert_or_select (xml_locations message)
let news_news_locations = map (News_NewsLocation news_id) loc_ids
mapM_ insert_ news_news_locations
onDelete: cascade
|]
+
--
-- XML Picklers
--