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