]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blob - src/Xml.hs
Simplify some tests by passing a pickler instead of relying on a XmlPickler instance.
[dead/htsn-import.git] / src / Xml.hs
1 {-# LANGUAGE TypeFamilies #-}
2
3 -- | General XML stuff.
4 --
5 module Xml (
6 DtdName(..),
7 FromXml(..),
8 parse_opts,
9 pickle_unpickle,
10 unpickleable )
11 where
12
13 -- System imports.
14 import Control.Exception ( SomeException(..), catch )
15 import Text.XML.HXT.Core (
16 (>>>),
17 (/>),
18 PU,
19 SysConfigList,
20 XmlPickler(..),
21 isElem,
22 readDocument,
23 runX,
24 withRemoveWS,
25 xpickleVal,
26 xunpickleVal,
27 yes )
28
29
30 -- | A typeclass for XML types that can be converted into an
31 -- associated database type. The story behind this is long, but
32 -- basically, we need to different types most XML thingies we're
33 -- going to import: a database type and an XML type.
34 --
35 -- Both Groundhog and HXT are very particular about the types that
36 -- they can use, and there's no way to reuse e.g. a type that HXT
37 -- can pickle in Groundhog. This typeclass gives us a standard way
38 -- to get the database type from the XML type that we have to define
39 -- for HXT.
40 --
41 class FromXml a where
42 -- | Each instance @a@ must declare its associated database type @Db a@.
43 type Db a :: *
44
45 -- | And provide a function for getting a @Db a@ out of an @a@.
46 from_xml :: a -> Db a
47
48
49 -- | Represents the DTD filename (\"SYSTEM\") part of the DOCTYPE
50 -- definition.
51 newtype DtdName = DtdName String
52
53 -- | A list of options passed to 'readDocument' when we parse an XML
54 -- document. All cosmetic whitespace should be removed, otherwise we
55 -- would have to parse whitespace in each (un)pickler.
56 --
57 parse_opts :: SysConfigList
58 parse_opts = [ withRemoveWS yes ]
59
60
61 -- | Given an @unpickler@ and a @filepath@, attempt to unpickle the
62 -- root element of @filepath@ using @unpickler@ and return both the
63 -- original unpickled object and one constructed by pickling and
64 -- unpickling that original. This is used in a number of XML tests
65 -- which pickle/unpickle and then make sure that the output is the
66 -- same as the input.
67 --
68 -- We return the object instead of an XmlTree (which would save us
69 -- an unpickle call) because otherwise the type of @a@ in the call
70 -- to 'xpickle' would be ambiguous. By returning some @a@s, we allow
71 -- the caller to annotate its type.
72 --
73 -- Note that this will happily pickle nothing to nothing and then
74 -- unpickle it back to more nothing. So the fact that the
75 -- before/after results from this function agree does not mean that
76 -- the document was successfully unpickled!
77 --
78 pickle_unpickle :: PU a -- ^ @unpickler@ returning an @a@
79 -> FilePath -- ^ Path to the document to unpickle.
80 -> IO ([a], [a])
81 pickle_unpickle unpickler filepath = do
82 -- We need to check only the root message element since
83 -- readDocument produces a bunch of other junk.
84 expected <- runX arr_getobj
85 actual <- runX $ arr_getobj
86 >>>
87 xpickleVal unpickler
88 >>>
89 xunpickleVal unpickler
90
91 return (expected, actual)
92 where
93 arr_getobj = readDocument parse_opts filepath
94 />
95 isElem -- Drop the extra junk readDocument pulls in.
96 >>>
97 xunpickleVal unpickler
98
99
100
101 -- | Is the given XML file unpickleable? Unpickling will be attempted
102 -- using the @unpickler@ argument. If we unilaterally used the
103 -- generic 'xpickle' function for our unpickler, a type ambiguity
104 -- would result. By taking the unpickler as an argument, we allow
105 -- the caller to indirectly specify a concrete type.
106 --
107 -- Apologies the the name; unpickleable means \"we can unpickle
108 -- it\", not \"not pickleable.\"
109 --
110 unpickleable :: FilePath -> PU a -> IO Bool
111 unpickleable filepath unpickler = do
112 xmldoc <- try_unpickle `catch` (\(SomeException _) -> return [])
113 return $ (not . null) xmldoc
114 where
115 try_unpickle = runX $ readDocument parse_opts filepath
116 >>>
117 xunpickleVal unpickler