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