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