]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blob - src/TSN/XML/GameInfo.hs
b13edd78af9c28c8e917fe3e2719a02291b5e6c4
[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 migrate,
29 runMigration,
30 silentMigrationLogger )
31 import Database.Groundhog.Generic ( runDbConn )
32 import Database.Groundhog.Sqlite ( withSqliteConn )
33 import Database.Groundhog.TH (
34 groundhog,
35 mkPersist )
36 import Test.Tasty ( TestTree, testGroup )
37 import Test.Tasty.HUnit ( (@?=), testCase )
38 import Text.XML.HXT.Core ( XmlTree )
39 import Text.XML.HXT.DOM.ShowXml ( xshow )
40
41 -- Local imports.
42 import TSN.Codegen ( tsn_codegen_config )
43 import TSN.DbImport (
44 DbImport(..),
45 ImportResult(..),
46 run_dbmigrate )
47 import TSN.Parse (
48 parse_message,
49 parse_xmlfid,
50 parse_xml_time_stamp )
51 import TSN.XmlImport ( XmlImport(..) )
52 import Xml (
53 FromXml(..),
54 ToDb(..),
55 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 -- | XML representation of a GameInfo \<message\>.
88 --
89 data Message =
90 Message {
91 xml_dtd :: String,
92 xml_xml_file_id :: Int,
93 xml_time_stamp :: UTCTime,
94 xml_xml :: String }
95 deriving (Eq, Show)
96
97
98 -- | Attempt to parse a 'Message' from an 'XmlTree'. If we cannot,
99 -- we fail with an error message.
100 --
101 parse_xml :: String -> XmlTree -> Either String Message
102 parse_xml dtdname xmltree = do
103 xmlfid <- parse_xmlfid xmltree
104 timestamp <- parse_xml_time_stamp xmltree
105 message <- parse_message xmltree
106 return $ Message dtdname (fromInteger xmlfid) timestamp (xshow [message])
107
108
109 -- | Database representation of a 'Message'.
110 --
111 data GameInfo =
112 GameInfo {
113 db_dtd :: String,
114 db_xml_file_id :: Int,
115 db_time_stamp :: UTCTime,
116 db_xml :: String }
117
118
119 instance ToDb Message where
120 -- | The database analogue of a 'Message' is an 'GameInfo'.
121 type Db Message = GameInfo
122
123 instance FromXml Message where
124 -- | The XML to DB conversion is trivial here.
125 --
126 from_xml Message{..} = GameInfo {
127 db_dtd = xml_dtd,
128 db_xml_file_id = xml_xml_file_id,
129 db_time_stamp = xml_time_stamp,
130 db_xml = xml_xml }
131
132
133 -- | This allows us to insert the XML representation 'Message'
134 -- directly.
135 --
136 instance XmlImport Message
137
138
139 --
140 -- Database code
141 --
142
143 instance DbImport Message where
144 dbmigrate _ =
145 run_dbmigrate $ migrate (undefined :: GameInfo)
146
147 -- | We import a 'Message' by inserting the whole thing at
148 -- once. Nothing fancy going on here.
149 dbimport msg = do
150 insert_xml_ msg
151 return ImportSucceeded
152
153
154 -- | The database schema for GameInfo is trivial; all we need is for
155 -- the XML_File_ID to be unique.
156 --
157 mkPersist tsn_codegen_config [groundhog|
158 - entity: GameInfo
159 constructors:
160 - name: GameInfo
161 uniques:
162 - name: unique_game_info
163 type: constraint
164 # Prevent multiple imports of the same message.
165 fields: [db_xml_file_id]
166 |]
167
168
169 --
170 -- Tasty Tests
171 --
172
173 -- | A list of all tests for this module.
174 --
175 game_info_tests :: TestTree
176 game_info_tests =
177 testGroup
178 "GameInfo tests"
179 [ test_parse_xml_succeeds,
180 test_dbimport_succeeds ]
181
182
183 -- | Sample XML documents for GameInfo types.
184 --
185 game_info_test_files :: [FilePath]
186 game_info_test_files =
187 map (change_suffix . add_path) dtds
188 where
189 add_path = ("test/xml/gameinfo/" ++ )
190 change_suffix = replace ".dtd" ".xml"
191
192 -- | Make sure we can parse every element of 'game_info_test_files'.
193 --
194 test_parse_xml_succeeds :: TestTree
195 test_parse_xml_succeeds =
196 testGroup "parse_xml" $ map check game_info_test_files
197 where
198 check t = testCase t $ do
199 x <- unsafe_read_document t
200 let result = parse_xml "dummy" x
201 let actual = case result of -- isRight appears in base-4.7
202 Left _ -> False
203 Right _ -> True
204 let expected = True
205 actual @?= expected
206
207
208 -- | Ensure that each element of 'game_info_test_files' can be imported
209 -- by counting the total number of database records (after
210 -- importing) and comparing it against the length of
211 -- 'game_info_test_files'.
212 --
213 test_dbimport_succeeds :: TestTree
214 test_dbimport_succeeds = testCase "dbimport succeeds" $ do
215 xmltrees <- mapM unsafe_read_document game_info_test_files
216 let msgs = rights $ map (parse_xml "dummy") xmltrees
217 actual <- withSqliteConn ":memory:" $ runDbConn $ do
218 runMigration silentMigrationLogger $ do
219 migrate (undefined :: GameInfo)
220 mapM_ dbimport msgs
221 countAll (undefined :: GameInfo)
222
223 actual @?= expected
224 where
225 expected = length game_info_test_files