]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blob - src/Xml.hs
Split the (Parent a) associated type into a new Child class.
[dead/htsn-import.git] / src / Xml.hs
1 {-# LANGUAGE FlexibleContexts #-}
2 {-# LANGUAGE TypeFamilies #-}
3
4 -- | General XML stuff.
5 --
6 module Xml (
7 Child(..),
8 DtdName(..),
9 FromXml(..),
10 FromXmlFk(..),
11 FromXmlFkTeams(..),
12 ToDb(..),
13 parse_opts,
14 pickle_unpickle,
15 unpickleable,
16 unsafe_read_document,
17 unsafe_unpickle )
18 where
19
20 -- System imports.
21 import Control.Exception ( SomeException(..), catch )
22 import Database.Groundhog.Core ( PersistEntity(..) )
23 import Text.XML.HXT.Core (
24 (>>>),
25 (/>),
26 PU,
27 SysConfigList,
28 XmlTree,
29 isElem,
30 no,
31 readDocument,
32 runX,
33 withRemoveWS,
34 withSubstDTDEntities,
35 withValidate,
36 xpickleVal,
37 xunpickleDocument,
38 xunpickleVal,
39 yes )
40
41
42 -- Local imports.
43 import TSN.Team ( Team(..) )
44
45
46 -- | Common associated type shared by 'FromXml' and 'FromXmlFk'. This
47 -- basically just forces the client to define the \"database
48 -- version\" of his type.
49 --
50 class ToDb a where
51 -- | Each instance @a@ must declare its associated database type @Db a@.
52 type Db a :: *
53
54 -- | A typeclass for XML types that can be converted into an
55 -- associated database type. The story behind this is long, but
56 -- basically, we need to different types most XML thingies we're
57 -- going to import: a database type and an XML type.
58 --
59 -- Both Groundhog and HXT are very particular about the types that
60 -- they can use, and there's no way to reuse e.g. a type that HXT
61 -- can pickle in Groundhog. This typeclass gives us a standard way
62 -- to get the database type from the XML type that we have to define
63 -- for HXT.
64 --
65 class (ToDb a) => FromXml a where
66 -- | A function for getting a @Db a@ out of an @a@.
67 from_xml :: a -> Db a
68
69
70 -- | A class for XML representations which are children of other
71 -- elements. The foal is to associate a child XML element with its
72 -- parent element's database type. This is required to construct the
73 -- database analogue of @a@ in the 'FromXmlFk' and 'FromXmlFkTeams'
74 -- classes.
75 --
76 class Child a where
77 -- | The type of our parent object, i.e. to the type to whom our
78 -- foreign key will point.
79 type Parent a :: *
80
81
82 -- | Some database types cannot be constructed from the XML type
83 -- alone; they must be supplied a foreign key to a parent object
84 -- first. Members of this class can be converted from an XML
85 -- representation to a database representation in this manner.
86 --
87 class (Child a, ToDb a) => FromXmlFk a where
88 -- | The function that produces a @Db a@ out of a foreign key and an
89 -- @a@. The parameter order makes it easier to map this function
90 -- over a bunch of things.
91 from_xml_fk :: DefaultKey (Parent a) -> a -> Db a
92
93
94 -- | A further refinement of 'FromXmlFk'. These types need not only a
95 -- foreign key to a parent in order to make the XML -> DB
96 -- conversion, but also two foreign keys to away/home teams (as
97 -- represented in "TSN.Team").
98 --
99 class (Child a, ToDb a) => FromXmlFkTeams a where
100 -- | The function that produces a @Db a@ out of a parent foreign
101 -- key, two team foreign keys, and an @a@. The parameter order makes
102 -- it easier to map this function over a bunch of things.
103 from_xml_fk_teams :: DefaultKey (Parent a)
104 -> DefaultKey Team -- ^ The away team FK
105 -> DefaultKey Team -- ^ The home team FK
106 -> a
107 -> Db a
108
109
110 -- | Represents the DTD filename (\"SYSTEM\") part of the DOCTYPE
111 -- definition.
112 newtype DtdName = DtdName String
113
114 -- | A list of options passed to 'readDocument' when we parse an XML
115 -- document. All cosmetic whitespace should be removed, otherwise we
116 -- would have to parse whitespace in each (un)pickler.
117 --
118 parse_opts :: SysConfigList
119 parse_opts = [ withRemoveWS yes,
120 withSubstDTDEntities no,
121 withValidate no ]
122
123
124 -- | Given an @unpickler@ and a @filepath@, attempt to unpickle the
125 -- root element of @filepath@ using @unpickler@ and return both the
126 -- original unpickled object and one constructed by pickling and
127 -- unpickling that original. This is used in a number of XML tests
128 -- which pickle/unpickle and then make sure that the output is the
129 -- same as the input.
130 --
131 -- We return the object instead of an XmlTree (which would save us
132 -- an unpickle call) because otherwise the type of @a@ in the call
133 -- to 'xpickle' would be ambiguous. By returning some @a@s, we allow
134 -- the caller to annotate its type.
135 --
136 -- Note that this will happily pickle nothing to nothing and then
137 -- unpickle it back to more nothing. So the fact that the
138 -- before/after results from this function agree does not mean that
139 -- the document was successfully unpickled!
140 --
141 pickle_unpickle :: PU a -- ^ @unpickler@ returning an @a@
142 -> FilePath -- ^ Path to the document to unpickle.
143 -> IO ([a], [a])
144 pickle_unpickle unpickler filepath = do
145 -- We need to check only the root message element since
146 -- readDocument produces a bunch of other junk.
147 expected <- runX arr_getobj
148 actual <- runX $ arr_getobj
149 >>>
150 xpickleVal unpickler
151 >>>
152 xunpickleVal unpickler
153
154 return (expected, actual)
155 where
156 arr_getobj = readDocument parse_opts filepath
157 />
158 isElem -- Drop the extra junk readDocument pulls in.
159 >>>
160 xunpickleVal unpickler
161
162
163
164 -- | Is the given XML file unpickleable? Unpickling will be attempted
165 -- using the @unpickler@ argument. If we unilaterally used the
166 -- generic 'xpickle' function for our unpickler, a type ambiguity
167 -- would result. By taking the unpickler as an argument, we allow
168 -- the caller to indirectly specify a concrete type.
169 --
170 -- Apologies the the name; unpickleable means \"we can unpickle
171 -- it\", not \"not pickleable.\"
172 --
173 unpickleable :: FilePath -> PU a -> IO Bool
174 unpickleable filepath unpickler = do
175 xmldoc <- try_unpickle `catch` (\(SomeException _) -> return [])
176 return $ (not . null) xmldoc
177 where
178 try_unpickle = runX $ readDocument parse_opts filepath
179 >>>
180 xunpickleVal unpickler
181
182
183 -- | Unpickle from a 'FilePath' using the given pickler. Explode if it
184 -- doesn't work.
185 --
186 unsafe_unpickle :: FilePath -> PU a -> IO a
187 unsafe_unpickle filepath unpickler =
188 fmap head $ runX $ xunpickleDocument unpickler parse_opts filepath
189
190
191 -- | Read an XML document from a 'FilePath' into an XmlTree. Explode if it
192 -- doesn't work.
193 --
194 unsafe_read_document :: FilePath -> IO XmlTree
195 unsafe_read_document filepath =
196 fmap head $ runX $ readDocument parse_opts filepath