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.

95 lines
2.4 KiB

14 years ago
{-# LANGUAGE NoMonomorphismRestriction, OverloadedStrings #-}
{-# LANGUAGE TupleSections #-}
14 years ago
module Network.XMPP.Stream where
import Control.Applicative((<$>))
14 years ago
import Control.Monad(unless)
import Control.Monad.Trans.Class
14 years ago
import Control.Monad.Trans.State
import Control.Monad.IO.Class
14 years ago
import Network.XMPP.Monad
import Network.XMPP.Pickle
import Network.XMPP.Types
14 years ago
import Data.Conduit
import Data.Conduit.Hexpat as HXC
14 years ago
import Data.Conduit.List as CL
import qualified Data.List as L
import Data.Text as T
import Text.XML.Expat.Pickle
-- import Text.XML.Stream.Elements
14 years ago
xmppStartStream = do
hostname <- gets sHostname
pushOpen $ pickleElem pickleStream ("1.0",Nothing, Just hostname)
14 years ago
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
14 years ago
xmppStream :: Sink Event IO ServerFeatures
14 years ago
xmppStream = do
xmppStreamHeader
xmppStreamFeatures
xmppStreamHeader :: Sink Event IO ()
14 years ago
xmppStreamHeader = do
throwOutJunk
(ver, _, _) <- unpickleElem pickleStream <$> openElementFromEvents
unless (ver == "1.0") $ error "Not XMPP version 1.0 "
return()
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) )
14 years ago
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
)
14 years ago