]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blob - src/TSN/XML/GameInfo.hs
Add GameInfo support for CBASK_Lineup_XML.dtd.
[dead/htsn-import.git] / src / TSN / XML / GameInfo.hs
1 {-# LANGUAGE FlexibleInstances #-}
2 {-# LANGUAGE GADTs #-}
3 {-# LANGUAGE QuasiQuotes #-}
4 {-# LANGUAGE RecordWildCards #-}
5 {-# LANGUAGE TemplateHaskell #-}
6 {-# LANGUAGE TypeFamilies #-}
7
8 -- | GameInfo represents a collection of DTDs that we don't really
9 -- handle but want to make available. The raw XML gets stored in the
10 -- database along with the XML_File_ID, but we don't parse any of it.
11 --
12 -- See also: TSN.XML.SportInfo
13 --
14 module TSN.XML.GameInfo (
15 dtds,
16 gameinfo_tests,
17 parse_xml,
18 -- * WARNING: these are private but exported to silence warnings
19 GameInfoConstructor(..) )
20 where
21
22 -- System imports.
23 import Data.Either ( rights )
24 import Data.Time.Clock ( UTCTime )
25 import Database.Groundhog (
26 countAll,
27 migrate,
28 runMigration,
29 silentMigrationLogger )
30 import Database.Groundhog.Generic ( runDbConn )
31 import Database.Groundhog.Sqlite ( withSqliteConn )
32 import Database.Groundhog.TH (
33 groundhog,
34 mkPersist )
35 import Test.Tasty ( TestTree, testGroup )
36 import Test.Tasty.HUnit ( (@?=), testCase )
37 import Text.XML.HXT.Core ( XmlTree )
38 import Text.XML.HXT.DOM.ShowXml ( xshow )
39
40 -- Local imports.
41 import TSN.Codegen ( tsn_codegen_config )
42 import TSN.DbImport (
43 DbImport(..),
44 ImportResult(..),
45 run_dbmigrate )
46 import TSN.Parse (
47 parse_message,
48 parse_xmlfid,
49 parse_xml_time_stamp )
50 import TSN.XmlImport ( XmlImport(..) )
51 import Xml (
52 FromXml(..),
53 ToDb(..),
54 unsafe_read_document )
55
56
57 -- | The DTDs for everything that we consider "Game Info."
58 --
59 -- TODO: This is the list from the old implementation. We need to
60 -- make sure that we are really receiving XML for these DTDs
61 -- (i.e. the names are correct).
62 --
63 -- Those marked \"TSN DTD\" are the ones for which we did not
64 -- receive any XML during implementation; therefore the TSN DTD was
65 -- used. This matters because it is almost certainly incorrect, so
66 -- we can expect import failures when we finally do see some XML.
67 --
68 dtds :: [String]
69 dtds =
70 [ "CBASK_Lineup_XML.dtd", -- TSN DTD
71 "cbaskpreviewxml.dtd", -- missing DTD
72 "cflpreviewxml.dtd", -- missing DTD
73 "Matchup_NBA_NHL_XML.dtd", -- missing DTD
74 "mlbpreviewxml.dtd",
75 "MLB_Gaming_Matchup_XML.dtd",
76 "MLB.dtd", -- missing DTD
77 "MLB_Lineup_XML.dtd",
78 "MLB_Matchup_XML.dtd",
79 "MLS_Preview_XML.dtd",
80 "NBA_Gaming_Matchup_XML.dtd",
81 "NBA.dtd", -- missing DTD
82 "NBA_Playoff_Matchup_XML.dtd",
83 "NBALineupXML.dtd",
84 "nbapreviewxml.dtd",
85 "NCAA_FB_Preview_XML.dtd", -- missing DTD
86 "nflpreviewxml.dtd", -- missing DTD
87 "NFL_NCAA_FB_Matchup_XML.dtd", -- missing DTD
88 "nhlpreviewxml.dtd",
89 "recapxml.dtd",
90 "WorldBaseballPreviewXML.dtd" -- missing DTD
91 ]
92
93
94 -- | XML representation of a GameInfo \<message\>.
95 --
96 data Message =
97 Message {
98 xml_dtd :: String,
99 xml_xml_file_id :: Int,
100 xml_time_stamp :: UTCTime,
101 xml_xml :: String }
102 deriving (Eq, Show)
103
104
105 -- | Attempt to parse a 'Message' from an 'XmlTree'. If we cannot,
106 -- we fail with an error message.
107 --
108 parse_xml :: String -> XmlTree -> Either String Message
109 parse_xml dtdname xmltree = do
110 xmlfid <- parse_xmlfid xmltree
111 timestamp <- parse_xml_time_stamp xmltree
112 message <- parse_message xmltree
113 return $ Message dtdname (fromInteger xmlfid) timestamp (xshow [message])
114
115
116 -- | Database representation of a 'Message'.
117 --
118 data GameInfo =
119 GameInfo {
120 db_dtd :: String,
121 db_xml_file_id :: Int,
122 db_time_stamp :: UTCTime,
123 db_xml :: String }
124
125
126 instance ToDb Message where
127 -- | The database analogue of a 'Message' is an 'GameInfo'.
128 type Db Message = GameInfo
129
130 instance FromXml Message where
131 -- | The XML to DB conversion is trivial here.
132 --
133 from_xml Message{..} = GameInfo {
134 db_dtd = xml_dtd,
135 db_xml_file_id = xml_xml_file_id,
136 db_time_stamp = xml_time_stamp,
137 db_xml = xml_xml }
138
139
140 -- | This allows us to insert the XML representation 'Message'
141 -- directly.
142 --
143 instance XmlImport Message
144
145
146 --
147 -- Database code
148 --
149
150 instance DbImport Message where
151 dbmigrate _ =
152 run_dbmigrate $ migrate (undefined :: GameInfo)
153
154 -- | We import a 'Message' by inserting the whole thing at
155 -- once. Nothing fancy going on here.
156 dbimport msg = do
157 insert_xml_ msg
158 return ImportSucceeded
159
160
161 -- | The database schema for GameInfo is trivial; all we need is for
162 -- the XML_File_ID to be unique.
163 --
164 mkPersist tsn_codegen_config [groundhog|
165 - entity: GameInfo
166 constructors:
167 - name: GameInfo
168 uniques:
169 - name: unique_game_info
170 type: constraint
171 # Prevent multiple imports of the same message.
172 fields: [db_xml_file_id]
173 |]
174
175
176 --
177 -- Tasty Tests
178 --
179
180 -- | A list of all tests for this module.
181 --
182 gameinfo_tests :: TestTree
183 gameinfo_tests =
184 testGroup
185 "GameInfo tests"
186 [ test_parse_xml_succeeds,
187 test_dbimport_succeeds ]
188
189
190 -- | Sample XML documents for GameInfo types.
191 --
192 gameinfo_test_files :: [FilePath]
193 gameinfo_test_files =
194 [ "test/xml/gameinfo/CBASK_Lineup_XML.xml",
195 "test/xml/gameinfo/MLB_Gaming_Matchup_XML.xml",
196 "test/xml/gameinfo/MLB_Lineup_XML.xml",
197 "test/xml/gameinfo/MLB_Matchup_XML.xml",
198 "test/xml/gameinfo/mlbpreviewxml.xml",
199 "test/xml/gameinfo/MLS_Preview_XML.xml",
200 "test/xml/gameinfo/NBA_Gaming_Matchup_XML.xml",
201 "test/xml/gameinfo/NBALineupXML.xml",
202 "test/xml/gameinfo/NBA_Playoff_Matchup_XML.xml",
203 "test/xml/gameinfo/nbapreviewxml.xml",
204 "test/xml/gameinfo/nhlpreviewxml.xml",
205 "test/xml/gameinfo/recapxml.xml" ]
206
207
208 -- | Make sure we can parse every element of 'gameinfo_test_files'.
209 --
210 test_parse_xml_succeeds :: TestTree
211 test_parse_xml_succeeds =
212 testGroup "parse_xml" $ map check gameinfo_test_files
213 where
214 check t = testCase t $ do
215 x <- unsafe_read_document t
216 let result = parse_xml "dummy" x
217 let actual = case result of -- isRight appears in base-4.7
218 Left _ -> False
219 Right _ -> True
220 let expected = True
221 actual @?= expected
222
223
224 -- | Ensure that each element of 'gameinfo_test_files' can be imported
225 -- by counting the total number of database records (after
226 -- importing) and comparing it against the length of
227 -- 'gameinfo_test_files'.
228 --
229 test_dbimport_succeeds :: TestTree
230 test_dbimport_succeeds = testCase "dbimport succeeds" $ do
231 xmltrees <- mapM unsafe_read_document gameinfo_test_files
232 let msgs = rights $ map (parse_xml "dummy") xmltrees
233 actual <- withSqliteConn ":memory:" $ runDbConn $ do
234 runMigration silentMigrationLogger $ do
235 migrate (undefined :: GameInfo)
236 mapM_ dbimport msgs
237 countAll (undefined :: GameInfo)
238
239 actual @?= expected
240 where
241 expected = length gameinfo_test_files