You can not select more than 25 topics
Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.
82 lines
2.0 KiB
82 lines
2.0 KiB
|
14 years ago
|
{-# LANGUAGE NoMonomorphismRestriction #-}
|
||
|
|
{-# LANGUAGE OverloadedStrings #-}
|
||
|
|
{-# LANGUAGE TupleSections #-}
|
||
|
|
|
||
|
|
-- Marshalling between XML and Native Types
|
||
|
|
|
||
|
|
|
||
|
14 years ago
|
module Network.Xmpp.Pickle
|
||
|
14 years ago
|
( mbToBool
|
||
|
|
, xpElemEmpty
|
||
|
|
, xmlLang
|
||
|
|
, xpLangTag
|
||
|
|
, xpNodeElem
|
||
|
|
, ignoreAttrs
|
||
|
|
, mbl
|
||
|
|
, lmb
|
||
|
|
, right
|
||
|
|
, unpickleElem'
|
||
|
|
, unpickleElem
|
||
|
|
, pickleElem
|
||
|
|
, ppElement
|
||
|
|
) where
|
||
|
14 years ago
|
|
||
|
14 years ago
|
import Data.XML.Types
|
||
|
|
import Data.XML.Pickle
|
||
|
|
|
||
|
14 years ago
|
import Network.Xmpp.Types
|
||
|
14 years ago
|
|
||
|
14 years ago
|
import Text.XML.Stream.Elements
|
||
|
14 years ago
|
|
||
|
14 years ago
|
mbToBool :: Maybe t -> Bool
|
||
|
14 years ago
|
mbToBool (Just _) = True
|
||
|
|
mbToBool _ = False
|
||
|
|
|
||
|
14 years ago
|
xpElemEmpty :: Name -> PU [Node] ()
|
||
|
|
xpElemEmpty name = xpWrap (\((),()) -> ())
|
||
|
|
(\() -> ((),())) $
|
||
|
14 years ago
|
xpElem name xpUnit xpUnit
|
||
|
|
|
||
|
14 years ago
|
xmlLang :: Name
|
||
|
|
xmlLang = Name "lang" Nothing (Just "xml")
|
||
|
|
|
||
|
|
xpLangTag :: PU [Attribute] (Maybe LangTag)
|
||
|
|
xpLangTag = xpAttrImplied xmlLang xpPrim
|
||
|
|
|
||
|
14 years ago
|
xpNodeElem :: PU [Node] a -> PU Element a
|
||
|
|
xpNodeElem xp = PU { pickleTree = \x -> head $ (pickleTree xp x) >>= \y ->
|
||
|
|
case y of
|
||
|
|
NodeElement e -> [e]
|
||
|
14 years ago
|
_ -> []
|
||
|
14 years ago
|
, unpickleTree = \x -> case unpickleTree xp $ [NodeElement x] of
|
||
|
|
Left l -> Left l
|
||
|
|
Right (a,(_,c)) -> Right (a,(Nothing,c))
|
||
|
|
}
|
||
|
14 years ago
|
|
||
|
|
ignoreAttrs :: PU t ((), b) -> PU t b
|
||
|
14 years ago
|
ignoreAttrs = xpWrap snd ((),)
|
||
|
14 years ago
|
|
||
|
14 years ago
|
mbl :: Maybe [a] -> [a]
|
||
|
14 years ago
|
mbl (Just l) = l
|
||
|
|
mbl Nothing = []
|
||
|
|
|
||
|
14 years ago
|
lmb :: [t] -> Maybe [t]
|
||
|
14 years ago
|
lmb [] = Nothing
|
||
|
|
lmb x = Just x
|
||
|
|
|
||
|
14 years ago
|
right :: Either [Char] t -> t
|
||
|
14 years ago
|
right (Left l) = error l
|
||
|
|
right (Right r) = r
|
||
|
|
|
||
|
14 years ago
|
unpickleElem' :: PU [Node] c -> Element -> c
|
||
|
|
unpickleElem' p x = case unpickle (xpNodeElem p) x of
|
||
|
14 years ago
|
Left l -> error $ l ++ "\n saw: " ++ ppElement x
|
||
|
14 years ago
|
Right r -> r
|
||
|
14 years ago
|
|
||
|
14 years ago
|
-- Given a pickler and an element, produces an object.
|
||
|
14 years ago
|
unpickleElem :: PU [Node] a -> Element -> Either String a
|
||
|
|
unpickleElem p x = unpickle (xpNodeElem p) x
|
||
|
|
|
||
|
14 years ago
|
-- Given a pickler and an object, produces an Element.
|
||
|
14 years ago
|
pickleElem :: PU [Node] a -> a -> Element
|
||
|
14 years ago
|
pickleElem p = pickle $ xpNodeElem p
|