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