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