]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blob - src/TSN/XML/InjuriesDetail.hs
171b879a79726aff861cd6a3744f9b9ed95a4ded
[dead/htsn-import.git] / src / TSN / XML / InjuriesDetail.hs
1 {-# LANGUAGE FlexibleInstances #-}
2 {-# LANGUAGE GADTs #-}
3 {-# LANGUAGE QuasiQuotes #-}
4 {-# LANGUAGE StandaloneDeriving #-}
5 {-# LANGUAGE TemplateHaskell #-}
6 {-# LANGUAGE TypeFamilies #-}
7
8 -- | Parse TSN XML for the DTD "Injuries_Detail_XML.dtd". Each
9 -- document contains a root element \<message\> that in turn
10 -- contains zero or more \<Listing\>s (note: capitalization). The
11 -- \<Listing\>s contain \<PlayerListing\>s then contain the real
12 -- meat; everything contained in the parent \<Listing\> can also be
13 -- found within the \<PlayerListing\>s.
14 --
15 -- The player listings will be mapped to a database table called
16 -- "injuries_detail" automatically. The root "message" and "listing"
17 -- are not retained.
18 --
19 module TSN.XML.InjuriesDetail (
20 injuries_detail_tests,
21 pickle_message,
22 -- * WARNING: these are private but exported to silence warnings
23 PlayerListingConstructor(..) )
24 where
25
26 import Data.Time ( UTCTime )
27 import Data.Tuple.Curry ( uncurryN )
28 import Database.Groundhog (
29 migrate )
30 import Database.Groundhog.TH (
31 defaultCodegenConfig,
32 groundhog,
33 mkPersist )
34 import Test.Tasty ( TestTree, testGroup )
35 import Test.Tasty.HUnit ( (@?=), testCase )
36 import Text.XML.HXT.Core (
37 PU,
38 xpTriple,
39 xp6Tuple,
40 xp10Tuple,
41 xpElem,
42 xpInt,
43 xpList,
44 xpOption,
45 xpPrim,
46 xpText,
47 xpWrap )
48
49 import TSN.Picklers( xp_date, xp_team_id )
50 import TSN.DbImport ( DbImport(..), ImportResult(..), run_dbmigrate )
51 import TSN.XmlImport ( XmlImport(..) )
52 import Xml ( FromXml(..), pickle_unpickle, unpickleable )
53
54
55 data PlayerListing =
56 PlayerListing {
57 team_id :: String, -- ^ TeamIDs are (apparently) three characters long
58 -- and not necessarily numeric.
59 player_id :: Int,
60 date :: UTCTime,
61 pos :: String,
62 name :: String,
63 injury :: String,
64 status :: String,
65 fantasy :: Maybe String, -- ^ Nobody knows what this is.
66 injured :: Bool,
67 injury_type :: String -- ^ "type" is a reserved keyword so we can't use it
68 }
69 deriving (Eq, Show)
70
71 instance FromXml PlayerListing where
72 type Db PlayerListing = PlayerListing
73 from_xml = id
74
75 instance XmlImport PlayerListing
76
77 data Listing =
78 Listing {
79 listing_team_id :: String -- ^ Avoid conflict with PlayerListing's team_id.
80 -- TeamIDs are (apparently) three characters
81 -- long and not necessarily numeric.
82 , full_name :: String, -- ^ Team full name
83 player_listings :: [PlayerListing] }
84 deriving (Eq, Show)
85
86
87 data Message =
88 Message {
89 xml_file_id :: Int,
90 heading :: String,
91 category :: String,
92 sport :: String,
93 listings :: [Listing],
94 time_stamp :: String }
95 deriving (Eq, Show)
96
97 instance DbImport Message where
98 dbimport msg = do
99 mapM_ insert_xml (concatMap player_listings $ listings msg)
100 return ImportSucceeded
101
102 dbmigrate _ = run_dbmigrate $ migrate (undefined :: PlayerListing)
103
104 mkPersist defaultCodegenConfig [groundhog|
105 - entity: PlayerListing
106 dbName: injuries_detail_player_listings
107 constructors:
108 - name: PlayerListing
109 fields:
110 - name: team_id
111 type: varchar(3)
112 |]
113
114
115 pickle_player_listing :: PU PlayerListing
116 pickle_player_listing =
117 xpElem "PlayerListing" $
118 xpWrap (from_tuple, to_tuple) $
119 xp10Tuple (xpElem "TeamID" xp_team_id)
120 (xpElem "PlayerID" xpInt)
121 (xpElem "Date" xp_date)
122 (xpElem "Pos" xpText)
123 (xpElem "Name" xpText)
124 (xpElem "Injury" xpText)
125 (xpElem "Status" xpText)
126 (xpElem "Fantasy" $ xpOption xpText)
127 (xpElem "Injured" xpPrim)
128 (xpElem "Type" xpText)
129 where
130 from_tuple = uncurryN PlayerListing
131 to_tuple pl = (team_id pl,
132 player_id pl,
133 date pl,
134 pos pl,
135 name pl,
136 injury pl,
137 status pl,
138 fantasy pl,
139 injured pl,
140 injury_type pl)
141
142
143 pickle_listing :: PU Listing
144 pickle_listing =
145 xpElem "Listing" $
146 xpWrap (from_tuple, to_tuple) $
147 xpTriple (xpElem "TeamID" xp_team_id)
148 (xpElem "FullName" xpText)
149 (xpList pickle_player_listing)
150 where
151 from_tuple = uncurryN Listing
152 to_tuple l = (listing_team_id l, full_name l, player_listings l)
153
154
155 pickle_message :: PU Message
156 pickle_message =
157 xpElem "message" $
158 xpWrap (from_tuple, to_tuple) $
159 xp6Tuple (xpElem "XML_File_ID" xpInt)
160 (xpElem "heading" xpText)
161 (xpElem "category" xpText)
162 (xpElem "sport" xpText)
163 (xpList pickle_listing)
164 (xpElem "time_stamp" xpText)
165 where
166 from_tuple = uncurryN Message
167 to_tuple m = (xml_file_id m,
168 heading m,
169 category m,
170 sport m,
171 listings m,
172 time_stamp m)
173
174
175 -- * Tasty Tests
176 injuries_detail_tests :: TestTree
177 injuries_detail_tests =
178 testGroup
179 "InjuriesDetail tests"
180 [ test_pickle_of_unpickle_is_identity,
181 test_unpickle_succeeds ]
182
183
184 -- | Warning, succeess of this test does not mean that unpickling
185 -- succeeded.
186 test_pickle_of_unpickle_is_identity :: TestTree
187 test_pickle_of_unpickle_is_identity = testGroup "pickle-unpickle tests"
188 [ check "pickle composed with unpickle is the identity"
189 "test/xml/Injuries_Detail_XML.xml",
190
191 check "pickle composed with unpickle is the identity (non-int team_id)"
192 "test/xml/Injuries_Detail_XML-noninteger-team-id.xml" ]
193 where
194 check desc path = testCase desc $ do
195 (expected, actual) <- pickle_unpickle pickle_message path
196 actual @?= expected
197
198
199 test_unpickle_succeeds :: TestTree
200 test_unpickle_succeeds = testGroup "unpickle tests"
201 [ check "unpickling succeeds"
202 "test/xml/Injuries_Detail_XML.xml",
203
204 check "unpickling succeeds (non-int team_id)"
205 "test/xml/Injuries_Detail_XML-noninteger-team-id.xml" ]
206 where
207 check desc path = testCase desc $ do
208 actual <- unpickleable path pickle_message
209 let expected = True
210 actual @?= expected