]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blob - src/TSN/XML/GameInfo.hs
d165c194957c57cac0fe8f11c113a194d5628290
[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 game_info_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.String.Utils ( replace )
25 import Data.Time.Clock ( UTCTime )
26 import Database.Groundhog (
27 countAll,
28 insert_,
29 migrate,
30 runMigration,
31 silentMigrationLogger )
32 import Database.Groundhog.Generic ( runDbConn )
33 import Database.Groundhog.Sqlite ( withSqliteConn )
34 import Database.Groundhog.TH (
35 defaultCodegenConfig,
36 groundhog,
37 mkPersist )
38 import Test.Tasty ( TestTree, testGroup )
39 import Test.Tasty.HUnit ( (@?=), testCase )
40 import Text.XML.HXT.Core ( XmlTree )
41 import Text.XML.HXT.DOM.ShowXml ( xshow )
42
43 -- Local imports.
44 import TSN.DbImport (
45 DbImport(..),
46 ImportResult(..),
47 run_dbmigrate )
48 import TSN.Parse (
49 ParseError,
50 parse_game_id,
51 parse_message,
52 parse_schedule_id,
53 parse_xmlfid,
54 parse_xml_time_stamp )
55 import Xml ( unsafe_read_document )
56
57
58 -- | The DTDs for everything that we consider \"Game Info.\"
59 --
60 -- TODO: This is the list from the old implementation. We need to
61 -- make sure that we are really receiving XML for these DTDs
62 -- (i.e. the names are correct).
63 --
64 dtds :: [String]
65 dtds =
66 [ "CBASK_Lineup_XML.dtd",
67 "cbaskpreviewxml.dtd",
68 "cflpreviewxml.dtd",
69 "Matchup_NBA_NHL_XML.dtd",
70 "mlbpreviewxml.dtd",
71 "MLB_Gaming_Matchup_XML.dtd",
72 "MLB_Lineup_XML.dtd",
73 "MLB_Matchup_XML.dtd",
74 "MLS_Preview_XML.dtd",
75 "NBA_Gaming_Matchup_XML.dtd",
76 "NBA_Playoff_Matchup_XML.dtd",
77 "NBALineupXML.dtd",
78 "nbapreviewxml.dtd",
79 "NCAA_FB_Preview_XML.dtd",
80 "nflpreviewxml.dtd",
81 "NFL_NCAA_FB_Matchup_XML.dtd",
82 "nhlpreviewxml.dtd",
83 "recapxml.dtd",
84 "WorldBaseballPreviewXML.dtd" ]
85
86
87 -- | This serves as both the database and XML representation of a
88 -- GameInfo \<message\>.
89 --
90 -- The 'game_id' and 'schedule_id' fields are foreign keys, but they
91 -- key into multiple tables and key on records which may not exist
92 -- when we import the GameInfo document. We therefore don't declare
93 -- them as foreign keys; i.e. we don't require them to point
94 -- anywhere in particular. But if they do, that's nice.
95 --
96 data GameInfo =
97 GameInfo {
98 dtd :: String,
99 xml_file_id :: Int,
100 game_id :: Maybe Int, -- ^ These are optional because they are missing
101 -- from at least the MLB_Matchup_XML.dtd documents.
102 -- They provide foreign keys into any tables storing
103 -- games with their IDs.
104
105 schedule_id :: Maybe Int, -- ^ Optional key into any table storing a
106 -- schedule along with its ID. We've noticed
107 -- them missing in e.g. recapxml.dtd documents.
108 time_stamp :: UTCTime,
109 xml :: String }
110 deriving (Eq, Show)
111
112
113 -- | Attempt to parse a 'GameInfo' from an 'XmlTree'. If we cannot,
114 -- we fail with an error message.
115 --
116 parse_xml :: String -> XmlTree -> Either ParseError GameInfo
117 parse_xml dtdname xmltree = do
118 xmlfid <- parse_xmlfid xmltree
119 game_id <- parse_game_id xmltree
120 schedule_id <- parse_schedule_id xmltree
121 timestamp <- parse_xml_time_stamp xmltree
122 message <- parse_message xmltree
123 return $ GameInfo
124 dtdname
125 xmlfid
126 game_id
127 schedule_id
128 timestamp
129 (xshow [message])
130
131 --
132 -- * Database code
133 --
134
135 instance DbImport GameInfo where
136 dbmigrate _ =
137 run_dbmigrate $ migrate (undefined :: GameInfo)
138
139 -- | We import a 'GameInfo' by inserting the whole thing at
140 -- once. Nothing fancy going on here.
141 dbimport msg = do
142 insert_ msg
143 return ImportSucceeded
144
145
146 -- | The database schema for GameInfo is trivial; all we need is for
147 -- the XML_File_ID to be unique.
148 --
149 mkPersist defaultCodegenConfig [groundhog|
150 - entity: GameInfo
151 dbName: game_info
152 constructors:
153 - name: GameInfo
154 uniques:
155 - name: unique_game_info
156 type: constraint
157 # Prevent multiple imports of the same message.
158 fields: [xml_file_id]
159 |]
160
161
162 --
163 -- Tasty Tests
164 --
165
166 -- | A list of all tests for this module.
167 --
168 game_info_tests :: TestTree
169 game_info_tests =
170 testGroup
171 "GameInfo tests"
172 [ test_accessors,
173 test_parse_xml_succeeds,
174 test_dbimport_succeeds ]
175
176
177 -- | Make sure the accessors work and that we can parse one file. Ok,
178 -- so the real point of this is to make the unused fields (dtd, xml,
179 -- ...) warning go away without having to mangle the groundhog code.
180 --
181 test_accessors :: TestTree
182 test_accessors = testCase "we can access a parsed game_info" $ do
183 xmltree <- unsafe_read_document "test/xml/gameinfo/recapxml.xml"
184 let Right t = parse_xml "recapxml.dtd" xmltree
185 let a1 = dtd t
186 let ex1 = "recapxml.dtd"
187 let a2 = xml_file_id t
188 let ex2 = 21201550
189 let a3 = show $ time_stamp t
190 let ex3 = "2014-05-31 15:13:00 UTC"
191 let a4 = game_id t
192 let ex4 = Just 39978
193 let a5 = schedule_id t
194 let ex5 = Just 39978
195 let a6 = take 9 (xml t)
196 let ex6 = "<message>"
197 let actual = (a1,a2,a3,a4,a5,a6)
198 let expected = (ex1,ex2,ex3,ex4,ex5,ex6)
199 actual @?= expected
200
201
202 -- | Sample XML documents for GameInfo types.
203 --
204 game_info_test_files :: [FilePath]
205 game_info_test_files =
206 map (change_suffix . add_path) dtds
207 where
208 add_path = ("test/xml/gameinfo/" ++ )
209 change_suffix = replace ".dtd" ".xml"
210
211 -- | Make sure we can parse every element of 'game_info_test_files'.
212 --
213 test_parse_xml_succeeds :: TestTree
214 test_parse_xml_succeeds =
215 testGroup "parse_xml" $ map check game_info_test_files
216 where
217 check t = testCase t $ do
218 x <- unsafe_read_document t
219 let result = parse_xml "dummy" x
220 let actual = case result of -- isRight appears in base-4.7
221 Left _ -> False
222 Right _ -> True
223 let expected = True
224 actual @?= expected
225
226
227 -- | Ensure that each element of 'game_info_test_files' can be imported
228 -- by counting the total number of database records (after
229 -- importing) and comparing it against the length of
230 -- 'game_info_test_files'.
231 --
232 test_dbimport_succeeds :: TestTree
233 test_dbimport_succeeds = testCase "dbimport succeeds" $ do
234 xmltrees <- mapM unsafe_read_document game_info_test_files
235 let msgs = rights $ map (parse_xml "dummy") xmltrees
236 actual <- withSqliteConn ":memory:" $ runDbConn $ do
237 runMigration silentMigrationLogger $
238 migrate (undefined :: GameInfo)
239 mapM_ dbimport msgs
240 countAll (undefined :: GameInfo)
241
242 actual @?= expected
243 where
244 expected = length game_info_test_files