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