]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blob - src/TSN/XML/Injuries.hs
Fixing compiler warnings by exporting stuff that shouldn't be exported (woo).
[dead/htsn-import.git] / src / TSN / XML / Injuries.hs
1 {-# LANGUAGE DeriveDataTypeable #-}
2 {-# LANGUAGE FlexibleInstances #-}
3 {-# LANGUAGE GADTs #-}
4 {-# LANGUAGE QuasiQuotes #-}
5 {-# LANGUAGE StandaloneDeriving #-}
6 {-# LANGUAGE TemplateHaskell #-}
7 {-# LANGUAGE TypeFamilies #-}
8
9 -- | Parse TSN XML for the DTD "injuriesxml.dtd". Each document
10 -- contains a root element \<message\> that in turn contains zero or
11 -- more \<listing\>s.
12 --
13 -- The listings will be mapped to a database table called "injuries"
14 -- automatically. The root message is not retained.
15 --
16 module TSN.XML.Injuries (
17 injuries_tests,
18 pickle_message,
19 -- * WARNING: these are private but exported to silence warnings
20 ListingConstructor(..) )
21 where
22
23 import Data.Data ( Data )
24 import Data.Typeable ( Typeable )
25 import Database.Groundhog (
26 migrate )
27 import Database.Groundhog.TH (
28 defaultCodegenConfig,
29 groundhog,
30 mkPersist )
31 import Data.Tuple.Curry ( uncurryN )
32 import Test.Tasty ( TestTree, testGroup )
33 import Test.Tasty.HUnit ( (@?=), testCase )
34 import Text.XML.HXT.Core (
35 PU,
36 xp4Tuple,
37 xp6Tuple,
38 xpAttr,
39 xpElem,
40 xpInt,
41 xpList,
42 xpOption,
43 xpPair,
44 xpPrim,
45 xpText,
46 xpWrap )
47
48
49 import TSN.DbImport ( DbImport(..), ImportResult(..), run_dbmigrate )
50 import TSN.XmlImport ( XmlImport(..) )
51 import Xml ( FromXml(..), pickle_unpickle, unpickleable )
52
53 data InjuriesTeam =
54 InjuriesTeam {
55 team_name :: String,
56 team_league :: Maybe String }
57 deriving (Data, Eq, Show, Typeable)
58
59 data Listing =
60 Listing {
61 team :: InjuriesTeam,
62 teamno :: Maybe Int,
63 injuries :: String,
64 updated :: Maybe Bool }
65 deriving (Eq, Show)
66
67 instance FromXml Listing where
68 type Db Listing = Listing
69 from_xml = id
70
71 instance XmlImport Listing
72
73 data Message =
74 Message {
75 xml_file_id :: Int,
76 heading :: String,
77 category :: String,
78 sport :: String,
79 listings :: [Listing],
80 time_stamp :: String }
81 deriving (Eq, Show)
82
83 instance DbImport Message where
84 dbimport msg = mapM_ insert_xml (listings msg) >> return ImportSucceeded
85
86 dbmigrate _ = run_dbmigrate $ migrate (undefined :: Listing)
87
88 mkPersist defaultCodegenConfig [groundhog|
89 - entity: Listing
90 dbName: injuries_listings
91 constructors:
92 - name: Listing
93 fields:
94 - name: team
95 embeddedType:
96 - {name: team_name, dbName: team_name}
97 - {name: team_league, dbName: team_league}
98 - embedded: InjuriesTeam
99 fields:
100 - name: team_name
101 - name: team_league
102 |]
103
104
105 pickle_injuries_team :: PU InjuriesTeam
106 pickle_injuries_team =
107 xpElem "team" $
108 xpWrap (from_tuple, to_tuple) $
109 xpPair xpText (xpOption $ xpAttr "league" xpText)
110 where
111 from_tuple = uncurryN InjuriesTeam
112 to_tuple m = (team_name m, team_league m)
113
114
115 pickle_listing :: PU Listing
116 pickle_listing =
117 xpElem "listing" $
118 xpWrap (from_tuple, to_tuple) $
119 xp4Tuple pickle_injuries_team
120 (xpOption $ xpElem "teamno" xpInt)
121 (xpElem "injuries" xpText)
122 (xpOption $ xpElem "updated" xpPrim)
123 where
124 from_tuple = uncurryN Listing
125 to_tuple l = (team l, teamno l, injuries l, updated l)
126
127
128 pickle_message :: PU Message
129 pickle_message =
130 xpElem "message" $
131 xpWrap (from_tuple, to_tuple) $
132 xp6Tuple (xpElem "XML_File_ID" xpInt)
133 (xpElem "heading" xpText)
134 (xpElem "category" xpText)
135 (xpElem "sport" xpText)
136 (xpList pickle_listing)
137 (xpElem "time_stamp" xpText)
138 where
139 from_tuple = uncurryN Message
140 to_tuple m = (xml_file_id m,
141 heading m,
142 category m,
143 sport m,
144 listings m,
145 time_stamp m)
146
147
148
149 -- * Tasty Tests
150 injuries_tests :: TestTree
151 injuries_tests =
152 testGroup
153 "Injuries tests"
154 [ test_pickle_of_unpickle_is_identity,
155 test_unpickle_succeeds ]
156
157
158 -- | Warning, succeess of this test does not mean that unpickling
159 -- succeeded.
160 test_pickle_of_unpickle_is_identity :: TestTree
161 test_pickle_of_unpickle_is_identity =
162 testCase "pickle composed with unpickle is the identity" $ do
163 let path = "test/xml/injuriesxml.xml"
164 (expected, actual) <- pickle_unpickle pickle_message path
165 actual @?= expected
166
167
168 test_unpickle_succeeds :: TestTree
169 test_unpickle_succeeds =
170 testCase "unpickling succeeds" $ do
171 let path = "test/xml/injuriesxml.xml"
172 actual <- unpickleable path pickle_message
173 let expected = True
174 actual @?= expected