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.
255 lines
9.5 KiB
255 lines
9.5 KiB
|
13 years ago
|
{-# OPTIONS_HADDOCK hide #-}
|
||
|
14 years ago
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||
|
14 years ago
|
{-# LANGUAGE OverloadedStrings #-}
|
||
|
|
|
||
|
13 years ago
|
module Network.Xmpp.Connection where
|
||
|
14 years ago
|
|
||
|
14 years ago
|
import Control.Applicative((<$>))
|
||
|
14 years ago
|
import Control.Concurrent (forkIO, threadDelay)
|
||
|
14 years ago
|
import Control.Monad
|
||
|
|
import Control.Monad.IO.Class
|
||
|
|
import Control.Monad.Trans.Class
|
||
|
14 years ago
|
--import Control.Monad.Trans.Resource
|
||
|
14 years ago
|
import qualified Control.Exception.Lifted as Ex
|
||
|
|
import qualified GHC.IO.Exception as GIE
|
||
|
14 years ago
|
import Control.Monad.State.Strict
|
||
|
14 years ago
|
|
||
|
14 years ago
|
import Data.ByteString as BS
|
||
|
|
import Data.Conduit
|
||
|
|
import Data.Conduit.Binary as CB
|
||
|
13 years ago
|
import Data.Conduit.BufferedSource
|
||
|
|
import qualified Data.Conduit.List as CL
|
||
|
|
import Data.IORef
|
||
|
14 years ago
|
import Data.Text(Text)
|
||
|
|
import Data.XML.Pickle
|
||
|
|
import Data.XML.Types
|
||
|
14 years ago
|
|
||
|
14 years ago
|
import Network
|
||
|
14 years ago
|
import Network.Xmpp.Types
|
||
|
|
import Network.Xmpp.Marshal
|
||
|
|
import Network.Xmpp.Pickle
|
||
|
14 years ago
|
|
||
|
14 years ago
|
import System.IO
|
||
|
14 years ago
|
|
||
|
14 years ago
|
import Text.XML.Stream.Elements
|
||
|
|
import Text.XML.Stream.Parse as XP
|
||
|
14 years ago
|
import Text.XML.Unresolved(InvalidEventStream(..))
|
||
|
14 years ago
|
|
||
|
14 years ago
|
-- Enable/disable debug output
|
||
|
|
-- This will dump all incoming and outgoing network taffic to the console,
|
||
|
|
-- prefixed with "in: " and "out: " respectively
|
||
|
|
debug :: Bool
|
||
|
|
debug = False
|
||
|
|
|
||
|
14 years ago
|
pushElement :: Element -> XmppConMonad Bool
|
||
|
14 years ago
|
pushElement x = do
|
||
|
13 years ago
|
send <- gets (cSend . sCon)
|
||
|
|
liftIO . send $ renderElement x
|
||
|
14 years ago
|
|
||
|
13 years ago
|
-- | Encode and send stanza
|
||
|
14 years ago
|
pushStanza :: Stanza -> XmppConMonad Bool
|
||
|
14 years ago
|
pushStanza = pushElement . pickleElem xpStanza
|
||
|
|
|
||
|
14 years ago
|
-- XML documents and XMPP streams SHOULD be preceeded by an XML declaration.
|
||
|
|
-- UTF-8 is the only supported XMPP encoding. The standalone document
|
||
|
|
-- declaration (matching "SDDecl" in the XML standard) MUST NOT be included in
|
||
|
|
-- XMPP streams. RFC 6120 defines XMPP only in terms of XML 1.0.
|
||
|
|
pushXmlDecl :: XmppConMonad Bool
|
||
|
|
pushXmlDecl = do
|
||
|
13 years ago
|
con <- gets sCon
|
||
|
|
liftIO $ (cSend con) "<?xml version='1.0' encoding='UTF-8' ?>"
|
||
|
14 years ago
|
|
||
|
14 years ago
|
pushOpenElement :: Element -> XmppConMonad Bool
|
||
|
14 years ago
|
pushOpenElement e = do
|
||
|
13 years ago
|
sink <- gets (cSend . sCon )
|
||
|
14 years ago
|
liftIO . sink $ renderOpenElement e
|
||
|
|
|
||
|
|
-- `Connect-and-resumes' the given sink to the connection source, and pulls a
|
||
|
|
-- `b' value.
|
||
|
13 years ago
|
pullToSinkEvents :: Sink Event IO b -> XmppConMonad b
|
||
|
|
pullToSinkEvents snk = do
|
||
|
|
source <- gets (cEventSource . sCon)
|
||
|
|
r <- lift $ source .$$+ snk
|
||
|
14 years ago
|
return r
|
||
|
14 years ago
|
|
||
|
14 years ago
|
pullElement :: XmppConMonad Element
|
||
|
14 years ago
|
pullElement = do
|
||
|
14 years ago
|
Ex.catches (do
|
||
|
13 years ago
|
e <- pullToSinkEvents (elements =$ await)
|
||
|
14 years ago
|
case e of
|
||
|
|
Nothing -> liftIO $ Ex.throwIO StreamConnectionError
|
||
|
|
Just r -> return r
|
||
|
|
)
|
||
|
14 years ago
|
[ Ex.Handler (\StreamEnd -> Ex.throwIO StreamStreamEnd)
|
||
|
14 years ago
|
, Ex.Handler (\(InvalidXmppXml s)
|
||
|
14 years ago
|
-> liftIO . Ex.throwIO $ StreamXMLError s)
|
||
|
14 years ago
|
, Ex.Handler $ \(e :: InvalidEventStream)
|
||
|
|
-> liftIO . Ex.throwIO $ StreamXMLError (show e)
|
||
|
|
|
||
|
14 years ago
|
]
|
||
|
14 years ago
|
|
||
|
14 years ago
|
-- Pulls an element and unpickles it.
|
||
|
14 years ago
|
pullPickle :: PU [Node] a -> XmppConMonad a
|
||
|
14 years ago
|
pullPickle p = do
|
||
|
|
res <- unpickleElem p <$> pullElement
|
||
|
|
case res of
|
||
|
14 years ago
|
Left e -> liftIO . Ex.throwIO $ StreamXMLError (show e)
|
||
|
14 years ago
|
Right r -> return r
|
||
|
|
|
||
|
13 years ago
|
-- | Pulls a stanza (or stream error) from the stream. Throws an error on a stream
|
||
|
14 years ago
|
-- error.
|
||
|
|
pullStanza :: XmppConMonad Stanza
|
||
|
14 years ago
|
pullStanza = do
|
||
|
14 years ago
|
res <- pullPickle xpStreamStanza
|
||
|
14 years ago
|
case res of
|
||
|
|
Left e -> liftIO . Ex.throwIO $ StreamError e
|
||
|
|
Right r -> return r
|
||
|
14 years ago
|
|
||
|
14 years ago
|
-- Performs the given IO operation, catches any errors and re-throws everything
|
||
|
14 years ago
|
-- except 'ResourceVanished' and IllegalOperation, in which case it will return False instead
|
||
|
13 years ago
|
catchSend :: IO () -> IO Bool
|
||
|
|
catchSend p = Ex.catch
|
||
|
14 years ago
|
(p >> return True)
|
||
|
|
(\e -> case GIE.ioe_type e of
|
||
|
|
GIE.ResourceVanished -> return False
|
||
|
14 years ago
|
GIE.IllegalOperation -> return False
|
||
|
14 years ago
|
_ -> Ex.throwIO e
|
||
|
|
)
|
||
|
|
|
||
|
13 years ago
|
-- -- XmppConnection state used when there is no connection.
|
||
|
14 years ago
|
xmppNoConnection :: XmppConnection
|
||
|
|
xmppNoConnection = XmppConnection
|
||
|
13 years ago
|
{ sCon = Connection { cSend = \_ -> return False
|
||
|
|
, cRecv = \_ -> Ex.throwIO
|
||
|
|
$ StreamConnectionError
|
||
|
|
, cEventSource = undefined
|
||
|
|
, cFlush = return ()
|
||
|
|
, cClose = return ()
|
||
|
|
}
|
||
|
14 years ago
|
, sFeatures = SF Nothing [] []
|
||
|
|
, sConnectionState = XmppConnectionClosed
|
||
|
|
, sHostname = Nothing
|
||
|
|
, sJid = Nothing
|
||
|
|
, sStreamLang = Nothing
|
||
|
|
, sStreamId = Nothing
|
||
|
|
, sPreferredLang = Nothing
|
||
|
|
, sToJid = Nothing
|
||
|
|
, sJidWhenPlain = False
|
||
|
|
, sFrom = Nothing
|
||
|
14 years ago
|
}
|
||
|
14 years ago
|
where
|
||
|
|
zeroSource :: Source IO output
|
||
|
|
zeroSource = liftIO . Ex.throwIO $ StreamConnectionError
|
||
|
14 years ago
|
|
||
|
14 years ago
|
-- Connects to the given hostname on port 5222 (TODO: Make this dynamic) and
|
||
|
14 years ago
|
-- updates the XmppConMonad XmppConnection state.
|
||
|
13 years ago
|
xmppConnectTCP :: HostName -> PortID -> Text -> XmppConMonad ()
|
||
|
|
xmppConnectTCP host port hostname = do
|
||
|
|
hand <- liftIO $ do
|
||
|
|
h <- connectTo host port
|
||
|
|
hSetBuffering h NoBuffering
|
||
|
|
return h
|
||
|
|
eSource <- liftIO . bufferSource $ (sourceHandle hand) $= XP.parseBytes def
|
||
|
|
let con = Connection { cSend = if debug
|
||
|
|
then \d -> do
|
||
|
|
BS.putStrLn (BS.append "out: " d)
|
||
|
|
catchSend $ BS.hPut hand d
|
||
|
|
else catchSend . BS.hPut hand
|
||
|
|
, cRecv = if debug then
|
||
|
|
\n -> do
|
||
|
|
bs <- BS.hGetSome hand n
|
||
|
|
BS.putStrLn bs
|
||
|
|
return bs
|
||
|
|
else BS.hGetSome hand
|
||
|
|
, cEventSource = eSource
|
||
|
|
, cFlush = hFlush hand
|
||
|
|
, cClose = hClose hand
|
||
|
|
}
|
||
|
14 years ago
|
let st = XmppConnection
|
||
|
13 years ago
|
{ sCon = con
|
||
|
14 years ago
|
, sFeatures = (SF Nothing [] [])
|
||
|
|
, sConnectionState = XmppConnectionPlain
|
||
|
|
, sHostname = (Just hostname)
|
||
|
|
, sJid = Nothing
|
||
|
14 years ago
|
, sPreferredLang = Nothing -- TODO: Allow user to set
|
||
|
|
, sStreamLang = Nothing
|
||
|
14 years ago
|
, sStreamId = Nothing
|
||
|
14 years ago
|
, sToJid = Nothing -- TODO: Allow user to set
|
||
|
|
, sJidWhenPlain = False -- TODO: Allow user to set
|
||
|
|
, sFrom = Nothing
|
||
|
14 years ago
|
}
|
||
|
14 years ago
|
put st
|
||
|
|
|
||
|
14 years ago
|
-- Execute a XmppConMonad computation.
|
||
|
|
xmppNewSession :: XmppConMonad a -> IO (a, XmppConnection)
|
||
|
14 years ago
|
xmppNewSession action = runStateT action xmppNoConnection
|
||
|
14 years ago
|
|
||
|
14 years ago
|
-- Closes the connection and updates the XmppConMonad XmppConnection state.
|
||
|
14 years ago
|
xmppKillConnection :: XmppConMonad (Either Ex.SomeException ())
|
||
|
14 years ago
|
xmppKillConnection = do
|
||
|
13 years ago
|
cc <- gets (cClose . sCon)
|
||
|
14 years ago
|
err <- liftIO $ (Ex.try cc :: IO (Either Ex.SomeException ()))
|
||
|
14 years ago
|
put xmppNoConnection
|
||
|
14 years ago
|
return err
|
||
|
14 years ago
|
|
||
|
13 years ago
|
xmppReplaceConnection :: XmppConnection -> XmppConMonad (Either Ex.SomeException ())
|
||
|
|
xmppReplaceConnection newCon = do
|
||
|
|
cc <- gets (cClose . sCon)
|
||
|
|
err <- liftIO $ (Ex.try cc :: IO (Either Ex.SomeException ()))
|
||
|
|
put newCon
|
||
|
|
return err
|
||
|
|
|
||
|
14 years ago
|
-- Sends an IQ request and waits for the response. If the response ID does not
|
||
|
|
-- match the outgoing ID, an error is thrown.
|
||
|
|
xmppSendIQ' :: StanzaId
|
||
|
14 years ago
|
-> Maybe Jid
|
||
|
14 years ago
|
-> IQRequestType
|
||
|
|
-> Maybe LangTag
|
||
|
|
-> Element
|
||
|
14 years ago
|
-> XmppConMonad (Either IQError IQResult)
|
||
|
14 years ago
|
xmppSendIQ' iqID to tp lang body = do
|
||
|
14 years ago
|
pushStanza . IQRequestS $ IQRequest iqID Nothing to lang tp body
|
||
|
14 years ago
|
res <- pullPickle $ xpEither xpIQError xpIQResult
|
||
|
|
case res of
|
||
|
|
Left e -> return $ Left e
|
||
|
|
Right iq' -> do
|
||
|
14 years ago
|
unless
|
||
|
|
(iqID == iqResultID iq') . liftIO . Ex.throwIO $
|
||
|
|
StreamXMLError
|
||
|
|
("In xmppSendIQ' IDs don't match: " ++ show iqID ++ " /= " ++
|
||
|
|
show (iqResultID iq') ++ " .")
|
||
|
14 years ago
|
return $ Right iq'
|
||
|
|
|
||
|
|
-- | Send "</stream:stream>" and wait for the server to finish processing and to
|
||
|
|
-- close the connection. Any remaining elements from the server and whether or
|
||
|
|
-- not we received a </stream:stream> element from the server is returned.
|
||
|
|
xmppCloseStreams :: XmppConMonad ([Element], Bool)
|
||
|
|
xmppCloseStreams = do
|
||
|
13 years ago
|
send <- gets (cSend . sCon)
|
||
|
|
cc <- gets (cClose . sCon)
|
||
|
14 years ago
|
liftIO $ send "</stream:stream>"
|
||
|
|
void $ liftIO $ forkIO $ do
|
||
|
|
threadDelay 3000000
|
||
|
|
(Ex.try cc) :: IO (Either Ex.SomeException ())
|
||
|
|
return ()
|
||
|
|
collectElems []
|
||
|
|
where
|
||
|
|
-- Pulls elements from the stream until the stream ends, or an error is
|
||
|
|
-- raised.
|
||
|
|
collectElems :: [Element] -> XmppConMonad ([Element], Bool)
|
||
|
|
collectElems elems = do
|
||
|
|
result <- Ex.try pullElement
|
||
|
|
case result of
|
||
|
|
Left StreamStreamEnd -> return (elems, True)
|
||
|
|
Left _ -> return (elems, False)
|
||
|
14 years ago
|
Right elem -> collectElems (elem:elems)
|
||
|
|
|
||
|
14 years ago
|
debugConduit :: Pipe l ByteString ByteString u IO b
|
||
|
14 years ago
|
debugConduit = forever $ do
|
||
|
|
s <- await
|
||
|
|
case s of
|
||
|
|
Just s -> do
|
||
|
|
liftIO $ BS.putStrLn (BS.append "in: " s)
|
||
|
|
yield s
|
||
|
|
Nothing -> return ()
|