File: FromXML.hs

package info (click to toggle)
haskell-xcb-types 0.7.0-1
  • links: PTS, VCS
  • area: main
  • in suites: jessie, jessie-kfreebsd
  • size: 92 kB
  • sloc: haskell: 633; makefile: 2
file content (474 lines) | stat: -rw-r--r-- 15,724 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
-- |
-- Module    :  Data.XCB.FromXML
-- Copyright :  (c) Antoine Latter 2008
-- License   :  BSD3
--
-- Maintainer:  Antoine Latter <aslatter@gmail.com>
-- Stability :  provisional
-- Portability: portable
--
-- Handls parsing the data structures from XML files.
--
-- In order to support copying events and errors across module
-- boundaries, all modules which may have cross-module event copies and
-- error copies must be parsed at once.
--
-- There is no provision for preserving the event copy and error copy
-- declarations - the copies are handled during parsing.
module Data.XCB.FromXML(fromFiles
                       ,fromStrings
                       ) where

import Data.XCB.Types
import Data.XCB.Utils

import Text.XML.Light

import Data.List as List
import qualified Data.Map as Map
import Data.Maybe

import Control.Applicative ((<$>))
import Control.Monad
import Control.Monad.Reader

import System.IO (openFile, IOMode (ReadMode), hSetEncoding, utf8, hGetContents)

-- |Process the listed XML files.
-- Any files which fail to parse are silently dropped.
-- Any declaration in an XML file which fail to parse are
-- silently dropped.
fromFiles :: [FilePath] -> IO [XHeader]
fromFiles xs = do
  strings <- sequence $ map readFileUTF8 xs
  return $ fromStrings strings

-- | Like 'readFile', but forces the encoding
-- of the file to UTF8.
readFileUTF8 :: FilePath -> IO String
readFileUTF8 fp = do
  h <- openFile fp ReadMode
  hSetEncoding h utf8
  hGetContents h

-- |Process the strings as if they were XML files.
-- Any files which fail to parse are silently dropped.
-- Any declaration in an XML file which fail to parse are
-- silently dropped.
fromStrings :: [String] -> [XHeader]
fromStrings xs =
   let rs = mapAlt fromString xs
       Just headers = runReaderT rs headers
   in headers 

-- The 'Parse' monad.  Provides the name of the
-- current module, and a list of all of the modules.
type Parse = ReaderT ([XHeader],Name) Maybe

-- operations in the 'Parse' monad

localName :: Parse Name
localName = snd `liftM` ask

allModules :: Parse [XHeader]
allModules = fst `liftM` ask

-- a generic function for looking up something from
-- a named XHeader.
--
-- this implements searching both the current module and
-- the xproto module if the name is not specified.
lookupThingy :: ([XDecl] -> Maybe a)
             -> (Maybe Name)
             -> Parse (Maybe a)
lookupThingy f Nothing = do
  lname <- localName
  liftM2 mplus (lookupThingy f $ Just lname)
               (lookupThingy f $ Just "xproto") -- implicit xproto import
lookupThingy f (Just mname) = do
  xs <- allModules
  return $ do
    x <- findXHeader mname xs
    f $ xheader_decls x

-- lookup an event declaration by name.
lookupEvent :: Maybe Name -> Name -> Parse (Maybe EventDetails)
lookupEvent mname evname = flip lookupThingy mname $ \decls ->
                 findEvent evname decls

-- lookup an error declaration by name.
lookupError :: Maybe Name -> Name -> Parse (Maybe ErrorDetails)
lookupError mname ername = flip lookupThingy mname $ \decls ->
                 findError ername decls

findXHeader :: Name -> [XHeader] -> Maybe XHeader
findXHeader name = List.find $ \ x -> xheader_header x == name

findError :: Name -> [XDecl] -> Maybe ErrorDetails
findError pname xs =
      case List.find f xs of
        Nothing -> Nothing
        Just (XError name code elems) -> Just $ ErrorDetails name code elems
        _ -> error "impossible: fatal error in Data.XCB.FromXML.findError"
    where  f (XError name _ _) | name == pname = True
           f _ = False 
                                       
findEvent :: Name -> [XDecl] -> Maybe EventDetails
findEvent pname xs = 
      case List.find f xs of
        Nothing -> Nothing
        Just (XEvent name code elems noseq) ->
            Just $ EventDetails name code elems noseq
        _ -> error "impossible: fatal error in Data.XCB.FromXML.findEvent"
   where f (XEvent name _ _ _) | name == pname = True
         f _ = False 

data EventDetails = EventDetails Name Int [StructElem] (Maybe Bool)
data ErrorDetails = ErrorDetails Name Int [StructElem]

---

-- extract a single XHeader from a single XML document
fromString :: String -> ReaderT [XHeader] Maybe XHeader
fromString str = do
  el@(Element _qname _ats cnt _) <- lift $ parseXMLDoc str
  guard $ el `named` "xcb"
  header <- el `attr` "header"
  let name = el `attr` "extension-name"
      xname = el `attr` "extension-xname"
      maj_ver = el `attr` "major-version" >>= readM
      min_ver = el `attr` "minor-version" >>= readM
      multiword = el `attr` "extension-multiword" >>= readM . ensureUpper
  decls <- withReaderT (\r -> (r,header)) $ extractDecls cnt
  return $ XHeader {xheader_header = header
                   ,xheader_xname = xname
                   ,xheader_name = name
                   ,xheader_multiword = multiword
                   ,xheader_major_version = maj_ver
                   ,xheader_minor_version = min_ver
                   ,xheader_decls = decls
                   }

-- attempts to extract declarations from XML content, discarding failures.
extractDecls :: [Content] -> Parse [XDecl]
extractDecls = mapAlt declFromElem . onlyElems

-- attempt to extract a module declaration from an XML element
declFromElem :: Element -> Parse XDecl
declFromElem el
    | el `named` "request" = xrequest el
    | el `named` "event"   = xevent el
    | el `named` "eventcopy" = xevcopy el
    | el `named` "error" = xerror el
    | el `named` "errorcopy" = xercopy el
    | el `named` "struct" = xstruct el
    | el `named` "union" = xunion el
    | el `named` "xidtype" = xidtype el
    | el `named` "xidunion" = xidunion el
    | el `named` "typedef" = xtypedef el
    | el `named` "enum" = xenum el
    | el `named` "import" = ximport el
    | otherwise = mzero


ximport :: Element -> Parse XDecl
ximport = return . XImport . strContent

xenum :: Element -> Parse XDecl
xenum el = do
  nm <- el `attr` "name"
  fields <- mapAlt enumField $ elChildren el
  guard $ not $ null fields
  return $ XEnum nm fields

enumField :: Element -> Parse (EnumElem Type)
enumField el = do
  guard $ el `named` "item"
  name <- el `attr` "name"
  let expr = firstChild el >>= expression
  return $ EnumElem name expr

xrequest :: Element -> Parse XDecl
xrequest el = do
  nm <- el `attr` "name"
  code <- el `attr` "opcode" >>= readM
  -- TODO - I don't think I like 'mapAlt' here.
  -- I don't want to be silently dropping fields
  fields <- mapAlt structField $ elChildren el
  let reply = getReply el
  return $ XRequest nm code fields reply

getReply :: Element -> Maybe XReply
getReply el = do
  childElem <- unqual "reply" `findChild` el
  fields <- mapM structField $ elChildren childElem
  guard $ not $ null fields
  return fields

xevent :: Element -> Parse XDecl
xevent el = do
  name <- el `attr` "name"
  number <- el `attr` "number" >>= readM
  let noseq = ensureUpper `liftM` (el `attr` "no-sequence-number") >>= readM
  fields <- mapM structField $ elChildren el
  guard $ not $ null fields
  return $ XEvent name number fields noseq

xevcopy :: Element -> Parse XDecl
xevcopy el = do
  name <- el `attr` "name"
  number <- el `attr` "number" >>= readM
  ref <- el `attr` "ref"
  -- do we have a qualified ref?
  let (mname,evname) = splitRef ref
  details <- lookupEvent mname evname
  return $ let EventDetails _ _ fields noseq =
                 case details of
                   Nothing ->
                       error $ "Unresolved event: " ++ show mname ++ " " ++ ref
                   Just x -> x  
           in XEvent name number fields noseq

-- we need to do string processing to distinguish qualified from
-- unqualified types.
mkType :: String -> Type
mkType str =
    let (mname, name) = splitRef str
    in case mname of
         Just modifier -> QualType modifier name
         Nothing  -> UnQualType name

splitRef :: Name -> (Maybe Name, Name)
splitRef ref = case split ':' ref of
                 (x,"") -> (Nothing, x)
                 (a, b) -> (Just a, b)

-- |Neither returned string contains the first occurance of the
-- supplied Char.
split :: Char -> String -> (String, String)
split c = go
    where go [] = ([],[])
          go (x:xs) | x == c = ([],xs)
                    | otherwise = 
                        let (lefts, rights) = go xs
                        in (x:lefts,rights)
                 

xerror :: Element -> Parse XDecl
xerror el = do
  name <- el `attr` "name"
  number <- el `attr` "number" >>= readM
  fields <- mapM structField $ elChildren el
  guard $ not $ null fields
  return $ XError name number fields


xercopy :: Element -> Parse XDecl
xercopy el = do
  name <- el `attr` "name"
  number <- el `attr` "number" >>= readM
  ref <- el `attr` "ref"
  let (mname, ername) = splitRef ref
  details <- lookupError mname ername
  return $ XError name number $ case details of
               Nothing -> error $ "Unresolved error: " ++ show mname ++ " " ++ ref
               Just (ErrorDetails _ _ x) -> x

xstruct :: Element -> Parse XDecl
xstruct el = do
  name <- el `attr` "name"
  fields <- mapAlt structField $ elChildren el
  guard $ not $ null fields
  return $ XStruct name fields

xunion :: Element -> Parse XDecl
xunion el = do
  name <- el `attr` "name"
  fields <- mapAlt structField $ elChildren el
  guard $ not $ null fields
  return $ XUnion name fields

xidtype :: Element -> Parse XDecl
xidtype el = liftM XidType $ el `attr` "name"

xidunion :: Element -> Parse XDecl
xidunion el = do
  name <- el `attr` "name"
  let types = mapMaybe xidUnionElem $ elChildren el
  guard $ not $ null types
  return $ XidUnion name types

xidUnionElem :: Element -> Maybe XidUnionElem
xidUnionElem el = do
  guard $ el `named` "type"
  return $ XidUnionElem $ mkType $ strContent el

xtypedef :: Element -> Parse XDecl
xtypedef el = do
  oldtyp <- liftM mkType $ el `attr` "oldname"
  newname <- el `attr` "newname"
  return $ XTypeDef newname oldtyp


structField :: (MonadPlus m, Functor m) => Element -> m StructElem
structField el
    | el `named` "field" = do
        typ <- liftM mkType $ el `attr` "type"
        let enum = liftM mkType $ el `attr` "enum"
        let mask = liftM mkType $ el `attr` "mask"
        name <- el `attr` "name"
        return $ SField name typ enum mask

    | el `named` "pad" = do
        bytes <- el `attr` "bytes" >>= readM
        return $ Pad bytes

    | el `named` "list" = do
        typ <- liftM mkType $ el `attr` "type"
        name <- el `attr` "name"
        let enum = liftM mkType $ el `attr` "enum"
        let expr = firstChild el >>= expression
        return $ List name typ expr enum

    | el `named` "valueparam" = do
        mask_typ <- liftM mkType $ el `attr` "value-mask-type"
        mask_name <- el `attr` "value-mask-name"
        let mask_pad = el `attr` "value-mask-pad" >>= readM
        list_name <- el `attr` "value-list-name"
        return $ ValueParam mask_typ mask_name mask_pad list_name

    | el `named` "switch" = do
        nm <- el `attr` "name"
        (exprEl,caseEls) <- unconsChildren el
        expr <- expression exprEl
        cases <- mapM bitCase caseEls
        return $ Switch nm expr cases

    | el `named` "exprfield" = do
        typ <- liftM mkType $ el `attr` "type"
        name <- el `attr` "name"
        expr <- firstChild el >>= expression
        return $ ExprField name typ expr

    | el `named` "reply" = fail "" -- handled separate

    | el `named` "doc" = do
        fields <- el `children` "field"
        let mkField = \x -> fmap (\y -> (y, strContent x)) $ x `attr` "name"
            fields' = Map.fromList $ catMaybes $ map mkField fields
            sees = findChildren (unqual "see") el
            sees' = catMaybes $ flip map sees $ \s -> do typ <- s `attr` "type"
                                                         name <- s `attr` "name"
                                                         return (typ, name)
            brief = fmap strContent $ findChild (unqual "brief") el
        return $ Doc brief fields' sees'

    | el `named` "fd" = do
        name <- el `attr` "name"
        return $ Fd name

    | otherwise = let name = elName el
                  in error $ "I don't know what to do with structelem "
 ++ show name

bitCase :: (MonadPlus m, Functor m) => Element -> m BitCase
bitCase el | el `named` "bitcase" = do
               let mName = el `attr` "name"
               (exprEl, fieldEls) <- unconsChildren el
               expr <- expression exprEl
               fields <- mapM structField fieldEls
               return $ BitCase mName expr fields
           | otherwise =
               let name = elName el
               in error $ "Invalid bitCase: " ++ show name

expression :: (MonadPlus m, Functor m) => Element -> m XExpression
expression el | el `named` "fieldref"
                    = return $ FieldRef $ strContent el
              | el `named` "enumref" = do
                   enumTy <- mkType <$> el `attr` "ref"
                   let enumVal = strContent el
                   guard $ enumVal /= ""
                   return $ EnumRef enumTy enumVal
              | el `named` "value"
                    = Value `liftM` readM (strContent el)
              | el `named` "bit"
                    = Bit `liftM` do
                        n <- readM (strContent el)
                        guard $ n >= 0
                        return n
              | el `named` "op" = do
                    binop <- el `attr` "op" >>= toBinop
                    [exprLhs,exprRhs] <- mapM expression $ elChildren el
                    return $ Op binop exprLhs exprRhs
              | el `named` "unop" = do
                    op <- el `attr` "op" >>= toUnop
                    expr <- firstChild el >>= expression
                    return $ Unop op expr
              | el `named` "popcount" = do
                    expr <- firstChild el >>= expression
                    return $ PopCount expr
              | el `named` "sumof" = do
                    ref <- el `attr` "ref"
                    return $ SumOf ref
              | otherwise =
                  let nm = elName el
                  in error $ "Unknown epression " ++ show nm ++ " in Data.XCB.FromXML.expression"


toBinop :: MonadPlus m => String -> m Binop
toBinop "+"  = return Add
toBinop "-"  = return Sub
toBinop "*"  = return Mult
toBinop "/"  = return Div
toBinop "&"  = return And
toBinop "&amp;" = return And
toBinop ">>" = return RShift
toBinop _ = mzero

toUnop :: MonadPlus m => String -> m Unop
toUnop "~" = return Complement
toUnop _ = mzero


----
----
-- Utility functions
----
----

firstChild :: MonadPlus m => Element -> m Element
firstChild = listToM . elChildren

unconsChildren :: MonadPlus m => Element -> m (Element, [Element])
unconsChildren el
    = case elChildren el of
        (x:xs) -> return (x,xs)
        _ -> mzero

listToM :: MonadPlus m => [a] -> m a
listToM [] = mzero
listToM (x:_) = return x

named :: Element -> String -> Bool
named (Element qname _ _ _) name | qname == unqual name = True
named _ _ = False

attr :: MonadPlus m => Element -> String -> m String
(Element _ xs _ _) `attr` name = case List.find p xs of
      Just (Attr _ res) -> return res
      _ -> mzero
    where p (Attr qname _) | qname == unqual name = True
          p _ = False

children :: MonadPlus m => Element -> String -> m [Element]
(Element _ _ xs _) `children` name = case List.filter p xs of
      [] -> mzero
      some -> return $ onlyElems some
    where p (Elem (Element n _ _ _)) | n == unqual name = True
          p _ = False

-- adapted from Network.CGI.Protocol
readM :: (MonadPlus m, Read a) => String -> m a
readM = liftM fst . listToM . reads