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.

139 lines
4.8 KiB

14 years ago
{-# LANGUAGE NoMonomorphismRestriction, OverloadedStrings #-}
{-# LANGUAGE TupleSections #-}
14 years ago
module Network.Xmpp.Stream where
14 years ago
import qualified Control.Exception as Ex
import Control.Monad.Error
import Control.Monad.State.Strict
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
import Network.Xmpp.Monad
import Network.Xmpp.Pickle
import Network.Xmpp.Types
14 years ago
import Text.XML.Stream.Elements
import Text.XML.Stream.Parse as XP
-- import Text.XML.Stream.Elements
-- Unpickles and returns a stream element. Throws a StreamXMLError on failure.
streamUnpickleElem :: PU [Node] a
-> Element
-> ErrorT StreamError (Pipe Event Void IO) a
streamUnpickleElem p x = do
case unpickleElem p x of
Left l -> throwError $ StreamXMLError l
Right r -> return r
-- 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
-- Discards all events before the first EventBeginElement.
14 years ago
throwOutJunk :: Monad m => Sink Event m ()
14 years ago
throwOutJunk = do
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
-- Returns an (empty) Element from a stream of XML events.
openElementFromEvents :: StreamSink Element
14 years ago
openElementFromEvents = do
lift throwOutJunk
hd <- lift CL.head
case hd of
Just (EventBeginElement name attrs) -> return $ Element name attrs []
_ -> throwError $ StreamConnectionError
-- Sends the initial stream:stream element and pulls the server features.
xmppStartStream :: XmppConMonad (Either StreamError ())
xmppStartStream = runErrorT $ do
hostname' <- gets sHostname
case hostname' of
Nothing -> throwError StreamConnectionError
Just hostname -> lift $ do
pushXmlDecl
pushOpenElement $
-- TODO: set lang tag
pickleElem xpStream ("1.0", Nothing, Just hostname, Nothing)
features <- ErrorT . pullToSink $ runErrorT xmppStream
modify (\s -> s {sFeatures = features})
return ()
-- Creates a new connection source (of Events) using the raw source (of bytes)
-- and calls xmppStartStream.
xmppRestartStream :: XmppConMonad (Either StreamError ())
xmppRestartStream = do
raw <- gets sRawSrc
newsrc <- liftIO . bufferSource $ raw $= XP.parseBytes def
modify (\s -> s{sConSrc = newsrc})
xmppStartStream
14 years ago
-- Reads the (partial) stream:stream and the server features from the stream.
xmppStream :: StreamSink ServerFeatures
14 years ago
xmppStream = do
xmppStreamHeader
xmppStreamFeatures
where
xmppStreamHeader :: StreamSink ()
xmppStreamHeader = do
lift $ throwOutJunk
-- TODO: Do somehting with the lang tag
(ver, _, _, lang) <- streamUnpickleElem xpStream
=<< 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 xpStreamFeatures r
-- Pickler/Unpickler for the stream, with the version, from and to attributes.
xpStream :: PU [Node] (Text, Maybe Text, Maybe Text, Maybe LangTag)
xpStream = xpElemAttrs
(Name "stream" (Just "http://etherx.jabber.org/streams") (Just "stream"))
(xp4Tuple
(xpAttr "version" xpId)
(xpOption $ xpAttr "from" xpId)
(xpOption $ xpAttr "to" xpId)
xpLangTag
)
-- Pickler/Unpickler for the stream features - TLS, SASL, and the rest.
xpStreamFeatures :: PU [Node] ServerFeatures
xpStreamFeatures = 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))