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.
129 lines
4.6 KiB
129 lines
4.6 KiB
|
14 years ago
|
{-# LANGUAGE NoMonomorphismRestriction, OverloadedStrings #-}
|
||
|
14 years ago
|
{-# LANGUAGE TupleSections #-}
|
||
|
14 years ago
|
|
||
|
14 years ago
|
module Network.Xmpp.Stream where
|
||
|
14 years ago
|
|
||
|
14 years ago
|
import qualified Control.Exception as Ex
|
||
|
|
import Control.Monad.Error
|
||
|
|
import Control.Monad.State.Strict
|
||
|
14 years ago
|
|
||
|
14 years ago
|
import Data.Conduit
|
||
|
|
import Data.Conduit.BufferedSource
|
||
|
|
import Data.Conduit.List as CL
|
||
|
|
import Data.Text as T
|
||
|
|
import Data.XML.Pickle
|
||
|
|
import Data.XML.Types
|
||
|
|
import Data.Void(Void)
|
||
|
14 years ago
|
|
||
|
14 years ago
|
import Network.Xmpp.Monad
|
||
|
|
import Network.Xmpp.Pickle
|
||
|
|
import Network.Xmpp.Types
|
||
|
14 years ago
|
|
||
|
14 years ago
|
import Text.XML.Stream.Elements
|
||
|
|
import Text.XML.Stream.Parse as XP
|
||
|
14 years ago
|
|
||
|
|
-- import Text.XML.Stream.Elements
|
||
|
|
|
||
|
14 years ago
|
-- Unpickles and returns a stream element. Throws a StreamXMLError on failure.
|
||
|
14 years ago
|
streamUnpickleElem :: PU [Node] a
|
||
|
|
-> Element
|
||
|
|
-> ErrorT StreamError (Pipe Event Void IO) a
|
||
|
|
streamUnpickleElem p x = do
|
||
|
14 years ago
|
case unpickleElem p x of
|
||
|
|
Left l -> throwError $ StreamXMLError l
|
||
|
|
Right r -> return r
|
||
|
14 years ago
|
|
||
|
14 years ago
|
-- This is the conduit sink that handles the stream XML events. We extend it
|
||
|
|
-- with ErrorT capabilities.
|
||
|
|
type StreamSink a = ErrorT StreamError (Pipe Event Void IO) a
|
||
|
14 years ago
|
|
||
|
14 years ago
|
-- Discards all events before the first EventBeginElement.
|
||
|
14 years ago
|
throwOutJunk :: Monad m => Sink Event m ()
|
||
|
14 years ago
|
throwOutJunk = do
|
||
|
14 years ago
|
next <- CL.peek
|
||
|
|
case next of
|
||
|
|
Nothing -> return () -- This will only happen if the stream is closed.
|
||
|
|
Just (EventBeginElement _ _) -> return ()
|
||
|
|
_ -> CL.drop 1 >> throwOutJunk
|
||
|
14 years ago
|
|
||
|
14 years ago
|
-- Returns an (empty) Element from a stream of XML events.
|
||
|
14 years ago
|
openElementFromEvents :: StreamSink Element
|
||
|
14 years ago
|
openElementFromEvents = do
|
||
|
14 years ago
|
lift throwOutJunk
|
||
|
|
hd <- lift CL.head
|
||
|
|
case hd of
|
||
|
|
Just (EventBeginElement name attrs) -> return $ Element name attrs []
|
||
|
|
_ -> throwError $ StreamConnectionError
|
||
|
14 years ago
|
|
||
|
14 years ago
|
-- Sends the initial stream:stream element and pulls the server features.
|
||
|
14 years ago
|
xmppStartStream :: XmppConMonad (Either StreamError ())
|
||
|
14 years ago
|
xmppStartStream = runErrorT $ do
|
||
|
14 years ago
|
hostname' <- gets sHostname
|
||
|
|
case hostname' of
|
||
|
|
Nothing -> throwError StreamConnectionError
|
||
|
14 years ago
|
Just hostname -> lift . pushOpenElement $
|
||
|
14 years ago
|
pickleElem pickleStream ("1.0", Nothing, Just hostname)
|
||
|
14 years ago
|
features <- ErrorT . pullToSink $ runErrorT xmppStream
|
||
|
14 years ago
|
modify (\s -> s {sFeatures = features})
|
||
|
|
return ()
|
||
|
|
|
||
|
|
-- Creates a new connection source (of Events) using the raw source (of bytes)
|
||
|
|
-- and calls xmppStartStream.
|
||
|
14 years ago
|
xmppRestartStream :: XmppConMonad (Either StreamError ())
|
||
|
14 years ago
|
xmppRestartStream = do
|
||
|
14 years ago
|
raw <- gets sRawSrc
|
||
|
|
newsrc <- liftIO . bufferSource $ raw $= XP.parseBytes def
|
||
|
|
modify (\s -> s{sConSrc = newsrc})
|
||
|
|
xmppStartStream
|
||
|
14 years ago
|
|
||
|
14 years ago
|
-- Reads the (partial) stream:stream and the server features from the stream.
|
||
|
14 years ago
|
xmppStream :: StreamSink ServerFeatures
|
||
|
14 years ago
|
xmppStream = do
|
||
|
14 years ago
|
xmppStreamHeader
|
||
|
|
xmppStreamFeatures
|
||
|
|
where
|
||
|
|
xmppStreamHeader :: StreamSink ()
|
||
|
|
xmppStreamHeader = do
|
||
|
|
lift $ throwOutJunk
|
||
|
|
(ver, _, _) <- streamUnpickleElem pickleStream =<< openElementFromEvents
|
||
|
|
unless (ver == "1.0") . throwError $ StreamWrongVersion ver
|
||
|
|
return ()
|
||
|
|
xmppStreamFeatures :: StreamSink ServerFeatures
|
||
|
|
xmppStreamFeatures = do
|
||
|
|
e <- lift $ elements =$ CL.head
|
||
|
|
case e of
|
||
|
|
Nothing -> liftIO $ Ex.throwIO StreamConnectionError
|
||
|
|
Just r -> streamUnpickleElem pickleStreamFeatures r
|
||
|
|
|
||
|
|
-- Pickler/Unpickler for the stream, with the version, from and to attributes.
|
||
|
14 years ago
|
pickleStream :: PU [Node] (Text, Maybe Text, Maybe Text)
|
||
|
14 years ago
|
pickleStream = xpElemAttrs
|
||
|
|
(Name "stream" (Just "http://etherx.jabber.org/streams") (Just "stream"))
|
||
|
|
(xpTriple
|
||
|
|
(xpAttr "version" xpId)
|
||
|
|
(xpOption $ xpAttr "from" xpId)
|
||
|
|
(xpOption $ xpAttr "to" xpId)
|
||
|
|
)
|
||
|
|
|
||
|
|
-- Pickler/Unpickler for the stream features - TLS, SASL, and the rest.
|
||
|
14 years ago
|
pickleStreamFeatures :: PU [Node] ServerFeatures
|
||
|
14 years ago
|
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)
|
||
|
|
(xpAll xpElemVerbatim)
|
||
|
|
)
|
||
|
|
)
|
||
|
|
where
|
||
|
|
pickleTLSFeature :: PU [Node] Bool
|
||
|
|
pickleTLSFeature = xpElemNodes "{urn:ietf:params:xml:ns:xmpp-tls}starttls"
|
||
|
|
(xpElemExists "required")
|
||
|
|
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))
|