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.

110 lines
3.3 KiB

14 years ago
{-# LANGUAGE NoMonomorphismRestriction, OverloadedStrings #-}
{-# LANGUAGE TupleSections #-}
14 years ago
module Network.XMPP.Stream where
import Control.Applicative((<$>))
import Control.Monad(unless, forever)
import Control.Monad.Trans.Class
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.Default(def)
-- import qualified Data.Conduit.Hexpat as CH
import Data.Conduit.List as CL
import Data.Conduit.Text as CT
import Data.Default(def)
14 years ago
import qualified Data.List as L
import Data.Text as T
import Data.XML.Pickle
import Data.XML.Types
14 years ago
-- import qualified Text.XML.Stream.Parse as XP
import Text.XML.Stream.Elements
import Text.XML.Stream.Parse as XP
-- import Text.XML.Stream.Elements
14 years ago
throwOutJunk = do
next <- CL.peek
14 years ago
case next of
Nothing -> return ()
Just (EventBeginElement _ _) -> return ()
_ -> CL.drop 1 >> throwOutJunk
openElementFromEvents = do
throwOutJunk
Just (EventBeginElement name attrs) <- CL.head
return $ Element name attrs []
14 years ago
14 years ago
xmppStartStream :: XMPPMonad ()
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 ()
14 years ago
xmppRestartStream :: XMPPMonad ()
xmppRestartStream = do
raw <- gets sRawSrc
src <- gets sConSrc
let newsrc = raw $= XP.parseBytes def
modify (\s -> s{sConSrc = newsrc})
xmppStartStream
14 years ago
14 years ago
xmppStream :: Sink Event (ResourceT IO) ServerFeatures
14 years ago
xmppStream = do
xmppStreamHeader
xmppStreamFeatures
14 years ago
xmppStreamHeader :: Sink Event (ResourceT IO) ()
14 years ago
xmppStreamHeader = do
throwOutJunk
(ver, _, _) <- unpickleElem pickleStream <$> openElementFromEvents
unless (ver == "1.0") $ error "Not XMPP version 1.0 "
return()
14 years ago
xmppStreamFeatures :: Sink Event (ResourceT IO) ServerFeatures
xmppStreamFeatures = unpickleElem pickleStreamFeatures <$> elementFromEvents
-- Pickling
14 years ago
pickleStream :: PU [Node] (Text, Maybe Text, Maybe Text)
pickleStream = xpElemAttrs (Name "stream" (Just "http://etherx.jabber.org/streams") (Just "stream"))
(xpTriple
14 years ago
(xpAttr "version" xpId)
(xpOption $ xpAttr "from" xpId)
(xpOption $ xpAttr "to" xpId)
)
14 years ago
pickleTLSFeature :: PU [Node] Bool
pickleTLSFeature = xpElemNodes "{urn:ietf:params:xml:ns:xmpp-tls}starttls"
(xpElemExists "required")
14 years ago
pickleSaslFeature :: PU [Node] [Text]
pickleSaslFeature = xpElemNodes "{urn:ietf:params:xml:ns:xmpp-sasl}mechanisms"
(xpAll $ xpElemNodes
"{urn:ietf:params:xml:ns:xmpp-sasl}mechanism" (xpContent xpId) )
14 years ago
14 years ago
pickleStreamFeatures :: PU [Node] ServerFeatures
pickleStreamFeatures = xpWrap ( \(tls, sasl, rest) -> SF tls (mbl sasl) rest)
(\(SF tls sasl rest) -> (tls, lmb sasl, rest))
$
xpElemNodes (Name "features" (Just "http://etherx.jabber.org/streams") (Just "stream"))
(xpTriple
(xpOption pickleTLSFeature)
(xpOption pickleSaslFeature)
14 years ago
(xpAll xpElemVerbatim)
)
14 years ago