13 changed files with 636 additions and 498 deletions
@ -0,0 +1,184 @@
@@ -0,0 +1,184 @@
|
||||
{-# LANGUAGE DeriveDataTypeable, NoMonomorphismRestriction #-} |
||||
|
||||
module Data.Conduit.Hexpat where |
||||
|
||||
import Control.Applicative((<$>)) |
||||
import Control.Exception |
||||
import Control.Monad |
||||
import Control.Monad.Trans |
||||
|
||||
import qualified Data.ByteString as BS |
||||
import Data.Conduit as C |
||||
import Data.Conduit.List as CL |
||||
import Data.Maybe |
||||
import Data.Typeable |
||||
|
||||
import Text.XML.Expat.Internal.IO hiding (parse) |
||||
import Text.XML.Expat.SAX |
||||
import Text.XML.Expat.Tree |
||||
|
||||
import Foreign.Ptr |
||||
|
||||
import Data.IORef |
||||
-- adapted from parseG |
||||
|
||||
-- | Parse a generalized list of ByteStrings containing XML to SAX events. |
||||
-- In the event of an error, FailDocument is the last element of the output list. |
||||
-- parseG :: forall tag text l . (GenericXMLString tag, GenericXMLString text, List l) => |
||||
-- ParseOptions tag text -- ^ Parse options |
||||
-- -> l ByteString -- ^ Input text (a lazy ByteString) |
||||
-- -> l (SAXEvent tag text) |
||||
-- parseG opts inputBlocks = runParser inputBlocks parser queueRef cacheRef |
||||
-- where |
||||
|
||||
data HexpatParser tag text a = HexpatParser |
||||
{ hParser :: Parser |
||||
, hQueueRef :: IORef [SAXEvent tag text] |
||||
} |
||||
|
||||
createParser |
||||
:: (GenericXMLString tag, GenericXMLString text) => |
||||
ParseOptions tag text -> IO (HexpatParser tag text a) |
||||
createParser opts = do |
||||
let enc = overrideEncoding opts |
||||
let mEntityDecoder = entityDecoder opts |
||||
|
||||
parser <- newParser enc |
||||
queueRef <- newIORef [] |
||||
|
||||
case mEntityDecoder of |
||||
Just deco -> setEntityDecoder parser deco $ \_ txt -> do |
||||
modifyIORef queueRef (CharacterData txt:) |
||||
Nothing -> return () |
||||
|
||||
setXMLDeclarationHandler parser $ \_ cVer cEnc cSd -> do |
||||
ver <- textFromCString cVer |
||||
mEnc <- if cEnc == nullPtr |
||||
then return Nothing |
||||
else Just <$> textFromCString cEnc |
||||
let sd = if cSd < 0 |
||||
then Nothing |
||||
else Just $ if cSd /= 0 then True else False |
||||
modifyIORef queueRef (XMLDeclaration ver mEnc sd:) |
||||
return True |
||||
|
||||
setStartElementHandler parser $ \_ cName cAttrs -> do |
||||
name <- textFromCString cName |
||||
attrs <- forM cAttrs $ \(cAttrName,cAttrValue) -> do |
||||
attrName <- textFromCString cAttrName |
||||
attrValue <- textFromCString cAttrValue |
||||
return (attrName, attrValue) |
||||
modifyIORef queueRef (StartElement name attrs:) |
||||
return True |
||||
|
||||
setEndElementHandler parser $ \_ cName -> do |
||||
name <- textFromCString cName |
||||
modifyIORef queueRef (EndElement name:) |
||||
return True |
||||
|
||||
setCharacterDataHandler parser $ \_ cText -> do |
||||
txt <- gxFromCStringLen cText |
||||
modifyIORef queueRef (CharacterData txt:) |
||||
return True |
||||
|
||||
setStartCDataHandler parser $ \_ -> do |
||||
modifyIORef queueRef (StartCData :) |
||||
return True |
||||
|
||||
setEndCDataHandler parser $ \_ -> do |
||||
modifyIORef queueRef (EndCData :) |
||||
return True |
||||
|
||||
setProcessingInstructionHandler parser $ \_ cTarget cText -> do |
||||
target <- textFromCString cTarget |
||||
txt <- textFromCString cText |
||||
modifyIORef queueRef (ProcessingInstruction target txt :) |
||||
return True |
||||
|
||||
setCommentHandler parser $ \_ cText -> do |
||||
txt <- textFromCString cText |
||||
modifyIORef queueRef (Comment txt :) |
||||
return True |
||||
|
||||
return (HexpatParser parser queueRef) |
||||
|
||||
data HexpatParseException = HexpatParseExceptio String deriving (Typeable, Show) |
||||
instance Exception HexpatParseException |
||||
|
||||
parseBS |
||||
:: (GenericXMLString text, GenericXMLString tag) => |
||||
ParseOptions tag text |
||||
-> Conduit BS.ByteString IO (SAXEvent tag text) |
||||
parseBS opts = conduitIO |
||||
(createParser opts) |
||||
(\_ -> return ()) |
||||
(\(HexpatParser parser queueRef) input -> do |
||||
error <- withParser parser $ \pp -> parseChunk pp input False |
||||
case error of |
||||
Nothing -> return () |
||||
Just (XMLParseError err _) -> |
||||
resourceThrow $ HexpatParseExceptio err |
||||
queue <- readIORef queueRef |
||||
writeIORef queueRef [] |
||||
return . IOProducing $ reverse queue |
||||
) |
||||
(\(HexpatParser parser queueRef) -> do |
||||
error <- withParser parser $ \pp -> parseChunk pp BS.empty True |
||||
case error of |
||||
Nothing -> return () |
||||
Just (XMLParseError err _) -> |
||||
resourceThrow $ HexpatParseExceptio err |
||||
queue <- readIORef queueRef |
||||
writeIORef queueRef [] |
||||
return $ reverse queue |
||||
) |
||||
|
||||
whileJust :: Monad m => m (Maybe a) -> m [a] |
||||
whileJust f = do |
||||
f' <- f |
||||
case f' of |
||||
Just x -> liftM (x :) $ whileJust f |
||||
Nothing -> return [] |
||||
|
||||
|
||||
|
||||
data StreamUnfinishedException = StreamUnfinishedException deriving (Typeable, Show) |
||||
instance Exception StreamUnfinishedException |
||||
|
||||
|
||||
elementFromEvents |
||||
:: (Eq tag, Show tag, MonadIO m, Resource m) => |
||||
Sink (SAXEvent tag text) m (NodeG [] tag text) |
||||
elementFromEvents = do |
||||
Just (StartElement name attrs) <- CL.head |
||||
children <- liftM catMaybes . whileJust $ do |
||||
next' <- CL.peek |
||||
next <- case next' of |
||||
Nothing -> liftIO . throwIO $ StreamUnfinishedException |
||||
Just n -> return n |
||||
case next of |
||||
StartElement _ _ -> Just . Just <$> elementFromEvents |
||||
EndElement n -> if n == name then CL.drop 1 >> return Nothing |
||||
else error $ "closing wrong element: " |
||||
++ show n ++ " instead of " ++ show name |
||||
CharacterData txt -> CL.drop 1 >> (return . Just . Just $ Text txt) |
||||
_ -> return $ Just Nothing |
||||
return $ Element name attrs children |
||||
|
||||
openElementFromEvents |
||||
:: Resource m => Sink (SAXEvent tag text) m (NodeG [] tag text) |
||||
openElementFromEvents = do |
||||
throwOutJunk |
||||
Just (StartElement name attrs) <- CL.head |
||||
return $ Element name attrs [] |
||||
|
||||
throwOutJunk :: Resource m => Sink (SAXEvent t t1) m () |
||||
throwOutJunk = do |
||||
next <- peek |
||||
case next of |
||||
Nothing -> return () |
||||
Just (StartElement _ _) -> return () |
||||
_ -> CL.drop 1 >> throwOutJunk |
||||
|
||||
saxToElements = C.sequence $ throwOutJunk >> elementFromEvents |
||||
|
||||
@ -1,30 +1,40 @@
@@ -1,30 +1,40 @@
|
||||
{-# LANGUAGE OverloadedStrings #-} |
||||
|
||||
module Network.XMPP.Bind where |
||||
|
||||
import Control.Monad.Trans |
||||
import Control.Monad.Trans.State |
||||
|
||||
import Data.Text as Text |
||||
import Data.XML.Types |
||||
|
||||
import Network.XMPP.Monad |
||||
import Network.XMPP.Types |
||||
import Network.XMPP.Pickle |
||||
import Network.XMPP.Marshal |
||||
|
||||
bindSt resource= SIQ $ IQ Nothing Nothing "bind" Set |
||||
(Element "{urn:ietf:params:xml:ns:xmpp-bind}bind" |
||||
[] |
||||
(maybe [] (return . textToNode) resource)) |
||||
import Text.XML.Expat.Pickle |
||||
|
||||
bindReqIQ resource= SIQ $ IQ Nothing Nothing "bind" Set |
||||
(pickleElem |
||||
(bindP . xpOption |
||||
$ xpElemNodes "resource" (xpContent xpText)) |
||||
resource |
||||
) |
||||
|
||||
jidP :: PU [Node Text Text] JID |
||||
jidP = bindP $ xpElemNodes "jid" (xpContent xpPrim) |
||||
|
||||
xmppBind = do |
||||
res <- gets sResource |
||||
push $ bindSt res |
||||
SIQ (IQ Nothing Nothing _ Result r) <- pull |
||||
(JID n d (Just r)) <- case r of |
||||
Element "{urn:ietf:params:xml:ns:xmpp-bind}bind" [] |
||||
[NodeElement |
||||
jid@(Element "{urn:ietf:params:xml:ns:xmpp-bind}jid" [] _)] -> |
||||
return . fromText . Text.concat . elementText $ jid |
||||
_ -> error $ "bind failed:" ++ show r |
||||
push $ bindReqIQ res |
||||
answer <- pull |
||||
liftIO $ print answer |
||||
let SIQ (IQ Nothing Nothing _ Result b) = answer |
||||
let (JID n d (Just r)) = unpickleElem jidP b |
||||
modify (\s -> s{sResource = Just r}) |
||||
|
||||
bindP c = ignoreAttrs $ xpElemNs "bind" "urn:ietf:params:xml:ns:xmpp-bind" |
||||
xpUnit |
||||
c |
||||
|
||||
|
||||
|
||||
@ -0,0 +1,66 @@
@@ -0,0 +1,66 @@
|
||||
{-# LANGUAGE NoMonomorphismRestriction #-} |
||||
{-# LANGUAGE OverloadedStrings #-} |
||||
{-# LANGUAGE MultiParamTypeClasses #-} |
||||
{-# LANGUAGE TypeSynonymInstances #-} |
||||
{-# LANGUAGE FlexibleInstances #-} |
||||
{-# LANGUAGE TupleSections #-} |
||||
|
||||
-- Marshalling between XML and Native Types |
||||
|
||||
|
||||
module Network.XMPP.Pickle where |
||||
|
||||
import Control.Applicative((<$>)) |
||||
|
||||
import qualified Data.ByteString as BS |
||||
|
||||
import Data.Text as Text |
||||
import Data.Text.Encoding as Text |
||||
|
||||
import Network.XMPP.Types |
||||
|
||||
import Text.XML.Expat.Pickle |
||||
import Text.XML.Expat.Tree |
||||
|
||||
|
||||
mbToBool (Just _) = True |
||||
mbToBool _ = False |
||||
|
||||
xpElemEmpty name = xpWrap (\((),()) -> () , |
||||
\() -> ((),())) $ |
||||
xpElem name xpUnit xpUnit |
||||
|
||||
xpElemExists name = xpWrap (\x -> mbToBool x |
||||
,\x -> if x then Just () else Nothing) $ |
||||
xpOption (xpElemEmpty name) |
||||
|
||||
ignoreAttrs = xpWrap (snd, ((),)) |
||||
|
||||
mbl (Just l) = l |
||||
mbl Nothing = [] |
||||
|
||||
lmb [] = Nothing |
||||
lmb x = Just x |
||||
|
||||
right (Left l) = error l |
||||
right (Right r) = r |
||||
|
||||
unpickleElem p = right . unpickleTree' (xpRoot p) |
||||
pickleElem p = pickleTree $ xpRoot p |
||||
|
||||
xpEither l r = xpAlt eitherSel |
||||
[xpWrap (\x -> Left x, \(Left x) -> x) l |
||||
,xpWrap (\x -> Right x, \(Right x) -> x) r |
||||
] |
||||
where |
||||
eitherSel (Left _) = 0 |
||||
eitherSel (Right _) = 1 |
||||
|
||||
xpElemNs name ns attrs nodes = |
||||
xpWrap (\(((),a),n) -> (a,n), \(a,n) -> (((),a),n)) $ |
||||
xpElem name |
||||
(xpPair |
||||
(xpAttrFixed "xmlns" ns) |
||||
attrs |
||||
) |
||||
nodes |
||||
@ -1,79 +1,94 @@
@@ -1,79 +1,94 @@
|
||||
{-# LANGUAGE NoMonomorphismRestriction, OverloadedStrings #-} |
||||
{-# LANGUAGE TupleSections #-} |
||||
|
||||
module Network.XMPP.Stream where |
||||
|
||||
import Control.Applicative((<$>)) |
||||
import Control.Monad(unless) |
||||
import Control.Monad.Trans |
||||
import Control.Monad.Trans.State |
||||
import Control.Monad.IO.Class |
||||
|
||||
import Network.XMPP.Monad |
||||
import Network.XMPP.Pickle |
||||
import Network.XMPP.Types |
||||
|
||||
import Data.Conduit |
||||
import Data.Conduit.Hexpat as HXC |
||||
import Data.Conduit.List as CL |
||||
import qualified Data.List as L |
||||
import Data.Text as T |
||||
import Data.XML.Types |
||||
|
||||
import Text.XML.Stream.Elements |
||||
import Text.XML.Expat.Pickle |
||||
|
||||
-- import Text.XML.Stream.Elements |
||||
|
||||
|
||||
xmppStartStream = do |
||||
hostname <- gets sHostname |
||||
pushOpen $ streamE hostname |
||||
pushOpen $ pickleElem pickleStream ("1.0",Nothing, Just hostname) |
||||
features <- pulls xmppStream |
||||
modify (\s -> s {sFeatures = features}) |
||||
return () |
||||
|
||||
xmppRestartStream = do |
||||
raw <- gets sRawSrc |
||||
src <- gets sConSrc |
||||
newsrc <- lift (bufferSource $ raw $= HXC.parseBS parseOpts) |
||||
modify (\s -> s{sConSrc = newsrc}) |
||||
xmppStartStream |
||||
|
||||
|
||||
xmppStream :: ResourceThrow m => Sink Event m ServerFeatures |
||||
xmppStream :: Sink Event IO ServerFeatures |
||||
xmppStream = do |
||||
xmppStreamHeader |
||||
xmppStreamFeatures |
||||
|
||||
|
||||
xmppStreamHeader :: Resource m => Sink Event m () |
||||
xmppStreamHeader :: Sink Event IO () |
||||
xmppStreamHeader = do |
||||
hd <- CL.peek |
||||
case hd of |
||||
Just EventBeginDocument -> CL.drop 1 |
||||
_ -> return () |
||||
Just (EventBeginElement "{http://etherx.jabber.org/streams}stream" streamAttrs) <- CL.head |
||||
unless (checkVersion streamAttrs) $ error "Not XMPP version 1.0 " |
||||
throwOutJunk |
||||
(ver, _, _) <- unpickleElem pickleStream <$> openElementFromEvents |
||||
unless (ver == "1.0") $ error "Not XMPP version 1.0 " |
||||
return() |
||||
where |
||||
checkVersion = L.any (\x -> (fst x == "version") && (snd x == [ContentText "1.0"])) |
||||
|
||||
|
||||
xmppStreamFeatures |
||||
:: ResourceThrow m => Sink Event m ServerFeatures |
||||
xmppStreamFeatures = do |
||||
Element "{http://etherx.jabber.org/streams}features" [] features' <- elementFromEvents |
||||
let features = do |
||||
f <- features' |
||||
case f of |
||||
NodeElement e -> [e] |
||||
_ -> [] |
||||
let starttls = features >>= isNamed "{urn:ietf:params:xml:ns:xmpp-tls}starttls" |
||||
let starttlsRequired = starttls |
||||
>>= elementChildren |
||||
>>= isNamed "{urn:ietf:params:xml:ns:xmpp-tls}required" |
||||
let mechanisms = features |
||||
>>= isNamed "{urn:ietf:params:xml:ns:xmpp-sasl}mechanisms" |
||||
>>= elementChildren |
||||
>>= isNamed "{urn:ietf:params:xml:ns:xmpp-sasl}mechanism" |
||||
>>= elementText |
||||
return SF { stls = not $ L.null starttls |
||||
, stlsRequired = not $ L.null starttlsRequired |
||||
, saslMechanisms = mechanisms |
||||
, other = features |
||||
} |
||||
|
||||
streamE :: T.Text -> Element |
||||
streamE hostname = |
||||
Element (Name "stream" (Just "http://etherx.jabber.org/streams") (Just "stream")) |
||||
[ |
||||
("xml:language" , [ContentText "en"]) |
||||
, ("version", [ContentText "1.0"]) |
||||
, ("to", [ContentText hostname]) |
||||
] |
||||
[] |
||||
xmppStreamFeatures :: Sink Event IO ServerFeatures |
||||
xmppStreamFeatures = unpickleElem pickleStreamFeatures <$> elementFromEvents |
||||
|
||||
|
||||
-- Pickling |
||||
|
||||
pickleStream = xpWrap (snd, (((),()),)) . |
||||
xpElemAttrs "stream:stream" $ |
||||
xpPair |
||||
(xpPair |
||||
(xpAttrFixed "xmlns" "jabber:client" ) |
||||
(xpAttrFixed "xmlns:stream" "http://etherx.jabber.org/streams" ) |
||||
) |
||||
(xpTriple |
||||
(xpAttr "version" xpText) |
||||
(xpOption $ xpAttr "from" xpText) |
||||
(xpOption $ xpAttr "to" xpText) |
||||
) |
||||
|
||||
pickleTLSFeature = ignoreAttrs $ |
||||
xpElem "starttls" |
||||
(xpAttrFixed "xmlns" "urn:ietf:params:xml:ns:xmpp-tls") |
||||
(xpElemExists "required") |
||||
|
||||
pickleSaslFeature = ignoreAttrs $ |
||||
xpElem "mechanisms" |
||||
(xpAttrFixed "xmlns" "urn:ietf:params:xml:ns:xmpp-sasl") |
||||
(xpList0 $ |
||||
xpElemNodes "mechanism" (xpContent xpText) ) |
||||
|
||||
pickleStreamFeatures = xpWrap ( \(tls, sasl, rest) -> SF tls (mbl sasl) rest |
||||
, (\(SF tls sasl rest) -> (tls, lmb sasl, rest)) |
||||
) $ |
||||
xpElemNodes "stream:features" |
||||
(xpTriple |
||||
(xpOption pickleTLSFeature) |
||||
(xpOption pickleSaslFeature) |
||||
xpTrees |
||||
) |
||||
|
||||
|
||||
@ -1,76 +0,0 @@
@@ -1,76 +0,0 @@
|
||||
module Text.XML.Stream.Elements where |
||||
|
||||
import Control.Applicative ((<$>)) |
||||
import Control.Monad.Trans.Class |
||||
|
||||
import Data.Text as T |
||||
import Text.XML.Unresolved |
||||
import Data.XML.Types |
||||
|
||||
import Data.Conduit as C |
||||
import Data.Conduit.List as CL |
||||
|
||||
import Text.XML.Stream.Parse |
||||
|
||||
compressNodes :: [Node] -> [Node] |
||||
compressNodes [] = [] |
||||
compressNodes [x] = [x] |
||||
compressNodes (NodeContent (ContentText x) : NodeContent (ContentText y) : z) = |
||||
compressNodes $ NodeContent (ContentText $ x `T.append` y) : z |
||||
compressNodes (x:xs) = x : compressNodes xs |
||||
|
||||
elementFromEvents :: C.ResourceThrow m => C.Sink Event m Element |
||||
elementFromEvents = do |
||||
x <- CL.peek |
||||
case x of |
||||
Just (EventBeginElement n as) -> goE n as |
||||
_ -> lift $ C.resourceThrow $ InvalidEventStream $ "not an element: " ++ show x |
||||
where |
||||
many f = |
||||
go id |
||||
where |
||||
go front = do |
||||
x <- f |
||||
case x of |
||||
Nothing -> return $ front [] |
||||
Just y -> go (front . (:) y) |
||||
dropReturn x = CL.drop 1 >> return x |
||||
goE n as = do |
||||
CL.drop 1 |
||||
ns <- many goN |
||||
y <- CL.head |
||||
if y == Just (EventEndElement n) |
||||
then return $ Element n as $ compressNodes ns |
||||
else lift $ C.resourceThrow $ InvalidEventStream $ "Missing end element for " ++ show n ++ ", got: " ++ show y |
||||
goN = do |
||||
x <- CL.peek |
||||
case x of |
||||
Just (EventBeginElement n as) -> (Just . NodeElement) <$> goE n as |
||||
Just (EventInstruction i) -> dropReturn $ Just $ NodeInstruction i |
||||
Just (EventContent c) -> dropReturn $ Just $ NodeContent c |
||||
Just (EventComment t) -> dropReturn $ Just $ NodeComment t |
||||
Just (EventCDATA t) -> dropReturn $ Just $ NodeContent $ ContentText t |
||||
_ -> return Nothing |
||||
|
||||
|
||||
elementToEvents' :: Element -> [Event] |
||||
elementToEvents' (Element name as ns) = EventBeginElement name as : goN ns [] |
||||
where |
||||
goM [] = id |
||||
goM [x] = (goM' x :) |
||||
goM (x:xs) = (goM' x :) . goM xs |
||||
goM' (MiscInstruction i) = EventInstruction i |
||||
goM' (MiscComment t) = EventComment t |
||||
goE (Element name as ns) = |
||||
(EventBeginElement name as :) |
||||
. goN ns |
||||
. (EventEndElement name :) |
||||
goN [] = id |
||||
goN [x] = goN' x |
||||
goN (x:xs) = goN' x . goN xs |
||||
goN' (NodeElement e) = goE e |
||||
goN' (NodeInstruction i) = (EventInstruction i :) |
||||
goN' (NodeContent c) = (EventContent c :) |
||||
goN' (NodeComment t) = (EventComment t :) |
||||
|
||||
elementToEvents e@(Element name _ _) = elementToEvents' e ++ [EventEndElement name] |
||||
Loading…
Reference in new issue