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