Browse Source

Renamed some stream-related record fields

Prefixed the fields with `stream'. `ServerFeatures' was renamed
`StreamFeatures' to be more coherent with the terminology in RFC 6120.
master
Jon Kristensen 13 years ago
parent
commit
9eb793e1d3
  1. 4
      source/Network/Xmpp/Concurrent/Threads.hs
  2. 2
      source/Network/Xmpp/Internal.hs
  3. 6
      source/Network/Xmpp/Marshal.hs
  4. 6
      source/Network/Xmpp/Sasl.hs
  5. 2
      source/Network/Xmpp/Sasl/Mechanisms/DigestMd5.hs
  6. 113
      source/Network/Xmpp/Stream.hs
  7. 28
      source/Network/Xmpp/Tls.hs
  8. 77
      source/Network/Xmpp/Types.hs

4
source/Network/Xmpp/Concurrent/Threads.hs

@ -37,7 +37,7 @@ readWorker onStanza onConnectionClosed stateRef =
-- necessarily be interruptible -- necessarily be interruptible
s <- atomically $ do s <- atomically $ do
con <- readTMVar stateRef con <- readTMVar stateRef
state <- cState <$> readTMVar con state <- streamState <$> readTMVar con
when (state == Closed) when (state == Closed)
retry retry
return con return con
@ -83,7 +83,7 @@ startThreadsWith :: (Stanza -> IO ())
TMVar (TMVar Stream), TMVar (TMVar Stream),
ThreadId)) ThreadId))
startThreadsWith stanzaHandler eh con = do startThreadsWith stanzaHandler eh con = do
read <- withStream' (gets $ cSend . cHandle >>= \d -> return $ Right d) con read <- withStream' (gets $ streamSend . streamHandle >>= \d -> return $ Right d) con
case read of case read of
Left e -> return $ Left e Left e -> return $ Left e
Right read' -> do Right read' -> do

2
source/Network/Xmpp/Internal.hs

@ -20,7 +20,7 @@ module Network.Xmpp.Internal
( Stream(..) ( Stream(..)
, StreamState(..) , StreamState(..)
, StreamHandle(..) , StreamHandle(..)
, ServerFeatures(..) , StreamFeatures(..)
, openStream , openStream
, withStream , withStream
, startTls , startTls

6
source/Network/Xmpp/Marshal.hs

@ -253,10 +253,10 @@ xpStream = xpElemAttrs
) )
-- Pickler/Unpickler for the stream features - TLS, SASL, and the rest. -- Pickler/Unpickler for the stream features - TLS, SASL, and the rest.
xpStreamFeatures :: PU [Node] ServerFeatures xpStreamFeatures :: PU [Node] StreamFeatures
xpStreamFeatures = xpWrap xpStreamFeatures = xpWrap
(\(tls, sasl, rest) -> SF tls (mbl sasl) rest) (\(tls, sasl, rest) -> StreamFeatures tls (mbl sasl) rest)
(\(SF tls sasl rest) -> (tls, lmb sasl, rest)) (\(StreamFeatures tls sasl rest) -> (tls, lmb sasl, rest))
(xpElemNodes (xpElemNodes
(Name (Name
"features" "features"

6
source/Network/Xmpp/Sasl.hs

@ -71,11 +71,11 @@ xmppSasl :: [SaslHandler] -- ^ Acceptable authentication mechanisms and their
xmppSasl handlers = withStream $ do xmppSasl handlers = withStream $ do
-- Chooses the first mechanism that is acceptable by both the client and the -- Chooses the first mechanism that is acceptable by both the client and the
-- server. -- server.
mechanisms <- gets $ saslMechanisms . cFeatures mechanisms <- gets $ streamSaslMechanisms . streamFeatures
case (filter (\(name, _) -> name `elem` mechanisms)) handlers of case (filter (\(name, _) -> name `elem` mechanisms)) handlers of
[] -> return $ Right $ Just $ AuthNoAcceptableMechanism mechanisms [] -> return $ Right $ Just $ AuthNoAcceptableMechanism mechanisms
(_name, handler):_ -> do (_name, handler):_ -> do
cs <- gets cState cs <- gets streamState
case cs of case cs of
Closed -> return . Right $ Just AuthNoStream Closed -> return . Right $ Just AuthNoStream
_ -> do _ -> do
@ -134,7 +134,7 @@ xmppBind rsrc c = runErrorT $ do
case jid of case jid of
Right jid' -> do Right jid' -> do
ErrorT $ withStream (do ErrorT $ withStream (do
modify $ \s -> s{cJid = Just jid'} modify $ \s -> s{streamJid = Just jid'}
return $ Right jid') c -- not pretty return $ Right jid') c -- not pretty
return jid' return jid'
otherwise -> throwError XmppOtherFailure otherwise -> throwError XmppOtherFailure

2
source/Network/Xmpp/Sasl/Mechanisms/DigestMd5.hs

@ -45,7 +45,7 @@ xmppDigestMd5 :: Text -- ^ Authentication identity (authzid or username)
-> SaslM () -> SaslM ()
xmppDigestMd5 authcid authzid password = do xmppDigestMd5 authcid authzid password = do
(ac, az, pw) <- prepCredentials authcid authzid password (ac, az, pw) <- prepCredentials authcid authzid password
hn <- gets cHostName hn <- gets streamHostname
xmppDigestMd5' (fromJust hn) ac az pw xmppDigestMd5' (fromJust hn) ac az pw
where where
xmppDigestMd5' :: Text -> Text -> Maybe Text -> Text -> SaslM () xmppDigestMd5' :: Text -> Text -> Maybe Text -> Text -> SaslM ()

113
source/Network/Xmpp/Stream.hs

@ -1,4 +1,5 @@
{-# OPTIONS_HADDOCK hide #-} {-# OPTIONS_HADDOCK hide #-}
{-# LANGUAGE NoMonomorphismRestriction, OverloadedStrings #-} {-# LANGUAGE NoMonomorphismRestriction, OverloadedStrings #-}
{-# LANGUAGE TupleSections #-} {-# LANGUAGE TupleSections #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
@ -92,11 +93,11 @@ startStream = runErrorT $ do
stream <- liftIO $ mkStream state stream <- liftIO $ mkStream state
-- Set the `from' (which is also the expected to) attribute depending on the -- Set the `from' (which is also the expected to) attribute depending on the
-- state of the stream. -- state of the stream.
let expectedTo = case cState state of let expectedTo = case streamState state of
Plain -> if cJidWhenPlain state Plain -> if includeJidWhenPlain state
then cJid state else Nothing then toJid state else Nothing
Secured -> cJid state Secured -> toJid state
case cHostName state of case streamHostname state of
Nothing -> throwError XmppOtherFailure -- TODO: When does this happen? Nothing -> throwError XmppOtherFailure -- TODO: When does this happen?
Just hostname -> lift $ do Just hostname -> lift $ do
pushXmlDecl pushXmlDecl
@ -105,7 +106,7 @@ startStream = runErrorT $ do
, expectedTo , expectedTo
, Just (Jid Nothing hostname Nothing) , Just (Jid Nothing hostname Nothing)
, Nothing , Nothing
, cPreferredLang state , preferredLang state
) )
response <- ErrorT $ runEventsSink $ runErrorT $ streamS expectedTo response <- ErrorT $ runEventsSink $ runErrorT $ streamS expectedTo
case response of case response of
@ -117,15 +118,15 @@ startStream = runErrorT $ do
| lt == Nothing -> | lt == Nothing ->
closeStreamWithError stream StreamInvalidXml Nothing closeStreamWithError stream StreamInvalidXml Nothing
-- If `from' is set, we verify that it's the correct one. TODO: Should we check against the realm instead? -- If `from' is set, we verify that it's the correct one. TODO: Should we check against the realm instead?
| isJust from && (from /= Just (Jid Nothing (fromJust $ cHostName state) Nothing)) -> | isJust from && (from /= Just (Jid Nothing (fromJust $ streamHostname state) Nothing)) ->
closeStreamWithError stream StreamInvalidFrom Nothing closeStreamWithError stream StreamInvalidFrom Nothing
| to /= expectedTo -> | to /= expectedTo ->
closeStreamWithError stream StreamUndefinedCondition (Just $ Element "invalid-to" [] []) -- TODO: Suitable? closeStreamWithError stream StreamUndefinedCondition (Just $ Element "invalid-to" [] []) -- TODO: Suitable?
| otherwise -> do | otherwise -> do
modify (\s -> s{ cFeatures = features modify (\s -> s{ streamFeatures = features
, cStreamLang = lt , streamLang = lt
, cStreamId = id , streamId = id
, cFrom = from , streamFrom = from
} ) } )
return () return ()
-- Unpickling failed - we investigate the element. -- Unpickling failed - we investigate the element.
@ -180,10 +181,10 @@ flattenAttrs attrs = Prelude.map (\(name, content) ->
-- and calls xmppStartStream. -- and calls xmppStartStream.
restartStream :: StateT Stream IO (Either XmppFailure ()) restartStream :: StateT Stream IO (Either XmppFailure ())
restartStream = do restartStream = do
raw <- gets (cRecv . cHandle) raw <- gets (streamReceive . streamHandle)
let newSource = DCI.ResumableSource (loopRead raw $= XP.parseBytes def) let newSource = DCI.ResumableSource (loopRead raw $= XP.parseBytes def)
(return ()) (return ())
modify (\s -> s{cEventSource = newSource }) modify (\s -> s{streamEventSource = newSource })
startStream startStream
where where
loopRead read = do loopRead read = do
@ -203,7 +204,7 @@ streamS :: Maybe Jid -> StreamSink (Either Element ( Text
, Maybe Jid , Maybe Jid
, Maybe Text , Maybe Text
, Maybe LangTag , Maybe LangTag
, ServerFeatures )) , StreamFeatures ))
streamS expectedTo = do streamS expectedTo = do
header <- xmppStreamHeader header <- xmppStreamHeader
case header of case header of
@ -222,7 +223,7 @@ streamS expectedTo = do
case unpickleElem xpStream el of case unpickleElem xpStream el of
Left _ -> return $ Left el Left _ -> return $ Left el
Right r -> return $ Right r Right r -> return $ Right r
xmppStreamFeatures :: StreamSink ServerFeatures xmppStreamFeatures :: StreamSink StreamFeatures
xmppStreamFeatures = do xmppStreamFeatures = do
e <- lift $ elements =$ CL.head e <- lift $ elements =$ CL.head
case e of case e of
@ -246,8 +247,8 @@ openStream address port hostname = do
-- Surpresses StreamEndFailure exceptions, but may throw a StreamCloseError. -- Surpresses StreamEndFailure exceptions, but may throw a StreamCloseError.
closeStreams :: TMVar Stream -> IO (Either XmppFailure [Element]) closeStreams :: TMVar Stream -> IO (Either XmppFailure [Element])
closeStreams = withStream $ do closeStreams = withStream $ do
send <- gets (cSend . cHandle) send <- gets (streamSend . streamHandle)
cc <- gets (cClose . cHandle) cc <- gets (streamClose . streamHandle)
liftIO $ send "</stream:stream>" liftIO $ send "</stream:stream>"
void $ liftIO $ forkIO $ do void $ liftIO $ forkIO $ do
threadDelay 3000000 -- TODO: Configurable value threadDelay 3000000 -- TODO: Configurable value
@ -282,7 +283,7 @@ wrapIOException action = do
pushElement :: Element -> StateT Stream IO (Either XmppFailure Bool) pushElement :: Element -> StateT Stream IO (Either XmppFailure Bool)
pushElement x = do pushElement x = do
send <- gets (cSend . cHandle) send <- gets (streamSend . streamHandle)
wrapIOException $ send $ renderElement x wrapIOException $ send $ renderElement x
-- | Encode and send stanza -- | Encode and send stanza
@ -295,21 +296,21 @@ pushStanza s = withStream' . pushElement $ pickleElem xpStanza s
-- XMPP streams. RFC 6120 defines XMPP only in terms of XML 1.0. -- XMPP streams. RFC 6120 defines XMPP only in terms of XML 1.0.
pushXmlDecl :: StateT Stream IO (Either XmppFailure Bool) pushXmlDecl :: StateT Stream IO (Either XmppFailure Bool)
pushXmlDecl = do pushXmlDecl = do
con <- gets cHandle con <- gets streamHandle
wrapIOException $ (cSend con) "<?xml version=\"1.0\" encoding=\"UTF-8\" ?>" wrapIOException $ (streamSend con) "<?xml version=\"1.0\" encoding=\"UTF-8\" ?>"
pushOpenElement :: Element -> StateT Stream IO (Either XmppFailure Bool) pushOpenElement :: Element -> StateT Stream IO (Either XmppFailure Bool)
pushOpenElement e = do pushOpenElement e = do
sink <- gets (cSend . cHandle) sink <- gets (streamSend . streamHandle)
wrapIOException $ sink $ renderOpenElement e wrapIOException $ sink $ renderOpenElement e
-- `Connect-and-resumes' the given sink to the stream source, and pulls a -- `Connect-and-resumes' the given sink to the stream source, and pulls a
-- `b' value. -- `b' value.
runEventsSink :: Sink Event IO b -> StateT Stream IO (Either XmppFailure b) runEventsSink :: Sink Event IO b -> StateT Stream IO (Either XmppFailure b)
runEventsSink snk = do -- TODO: Wrap exceptions? runEventsSink snk = do -- TODO: Wrap exceptions?
source <- gets cEventSource source <- gets streamEventSource
(src', r) <- lift $ source $$++ snk (src', r) <- lift $ source $$++ snk
modify (\s -> s{cEventSource = src'}) modify (\s -> s{streamEventSource = src'})
return $ Right r return $ Right r
pullElement :: StateT Stream IO (Either XmppFailure Element) pullElement :: StateT Stream IO (Either XmppFailure Element)
@ -362,24 +363,24 @@ catchPush p = ExL.catch
-- Stream state used when there is no connection. -- Stream state used when there is no connection.
xmppNoStream :: Stream xmppNoStream :: Stream
xmppNoStream = Stream xmppNoStream = Stream {
{ cHandle = StreamHandle { cSend = \_ -> return False streamState = Closed
, cRecv = \_ -> ExL.throwIO , streamHandle = StreamHandle { streamSend = \_ -> return False
, streamReceive = \_ -> ExL.throwIO
XmppOtherFailure XmppOtherFailure
, cFlush = return () , streamFlush = return ()
, cClose = return () , streamClose = return ()
} }
, cEventSource = DCI.ResumableSource zeroSource (return ()) , streamEventSource = DCI.ResumableSource zeroSource (return ())
, cFeatures = SF Nothing [] [] , streamFeatures = StreamFeatures Nothing [] []
, cState = Closed , streamHostname = Nothing
, cHostName = Nothing , streamFrom = Nothing
, cJid = Nothing , streamId = Nothing
, cStreamLang = Nothing , streamLang = Nothing
, cStreamId = Nothing , streamJid = Nothing
, cPreferredLang = Nothing , preferredLang = Nothing
, cToJid = Nothing , toJid = Nothing
, cJidWhenPlain = False , includeJidWhenPlain = False
, cFrom = Nothing
} }
where where
zeroSource :: Source IO output zeroSource :: Source IO output
@ -396,35 +397,35 @@ connectTcp host port hostname = do
let eSource = DCI.ResumableSource let eSource = DCI.ResumableSource
((sourceHandle h $= logConduit) $= XP.parseBytes def) ((sourceHandle h $= logConduit) $= XP.parseBytes def)
(return ()) (return ())
let hand = StreamHandle { cSend = \d -> do let hand = StreamHandle { streamSend = \d -> do
let d64 = encode d let d64 = encode d
debugM "Pontarius.Xmpp" $ debugM "Pontarius.Xmpp" $
"Sending TCP data: " ++ (BSC8.unpack d64) "Sending TCP data: " ++ (BSC8.unpack d64)
++ "." ++ "."
catchPush $ BS.hPut h d catchPush $ BS.hPut h d
, cRecv = \n -> do , streamReceive = \n -> do
d <- BS.hGetSome h n d <- BS.hGetSome h n
let d64 = encode d let d64 = encode d
debugM "Pontarius.Xmpp" $ debugM "Pontarius.Xmpp" $
"Received TCP data: " ++ "Received TCP data: " ++
(BSC8.unpack d64) ++ "." (BSC8.unpack d64) ++ "."
return d return d
, cFlush = hFlush h , streamFlush = hFlush h
, cClose = hClose h , streamClose = hClose h
} }
let stream = Stream let stream = Stream
{ cHandle = hand { streamState = Plain
, cEventSource = eSource , streamHandle = hand
, cFeatures = (SF Nothing [] []) , streamEventSource = eSource
, cState = Plain , streamFeatures = StreamFeatures Nothing [] []
, cHostName = (Just hostname) , streamHostname = (Just hostname)
, cJid = Nothing , streamFrom = Nothing
, cPreferredLang = Nothing -- TODO: Allow user to set , streamId = Nothing
, cStreamLang = Nothing , streamLang = Nothing
, cStreamId = Nothing , streamJid = Nothing
, cToJid = Nothing -- TODO: Allow user to set , preferredLang = Nothing -- TODO: Allow user to set
, cJidWhenPlain = False -- TODO: Allow user to set , toJid = Nothing -- TODO: Allow user to set
, cFrom = Nothing , includeJidWhenPlain = False -- TODO: Allow user to set
} }
stream' <- mkStream stream stream' <- mkStream stream
return $ Right stream' return $ Right stream'
@ -441,7 +442,7 @@ connectTcp host port hostname = do
-- killStream :: TMVar Stream -> IO (Either ExL.SomeException ()) -- killStream :: TMVar Stream -> IO (Either ExL.SomeException ())
killStream :: TMVar Stream -> IO (Either XmppFailure ()) killStream :: TMVar Stream -> IO (Either XmppFailure ())
killStream = withStream $ do killStream = withStream $ do
cc <- gets (cClose . cHandle) cc <- gets (streamClose . streamHandle)
err <- wrapIOException cc err <- wrapIOException cc
-- (ExL.try cc :: IO (Either ExL.SomeException ())) -- (ExL.try cc :: IO (Either ExL.SomeException ()))
put xmppNoStream put xmppNoStream

28
source/Network/Xmpp/Tls.hs

@ -22,10 +22,10 @@ import Network.Xmpp.Types
import Control.Concurrent.STM.TMVar import Control.Concurrent.STM.TMVar
mkBackend con = Backend { backendSend = \bs -> void (cSend con bs) mkBackend con = Backend { backendSend = \bs -> void (streamSend con bs)
, backendRecv = cRecv con , backendRecv = streamReceive con
, backendFlush = cFlush con , backendFlush = streamFlush con
, backendClose = cClose con , backendClose = streamClose con
} }
where where
cutBytes n = do cutBytes n = do
@ -78,14 +78,14 @@ startTls :: TLS.TLSParams -> TMVar Stream -> IO (Either XmppFailure ())
startTls params con = Ex.handle (return . Left . TlsError) startTls params con = Ex.handle (return . Left . TlsError)
. flip withStream con . flip withStream con
. runErrorT $ do . runErrorT $ do
features <- lift $ gets cFeatures features <- lift $ gets streamFeatures
state <- gets cState state <- gets streamState
case state of case state of
Plain -> return () Plain -> return ()
Closed -> throwError XmppNoStream Closed -> throwError XmppNoStream
Secured -> throwError TlsStreamSecured Secured -> throwError TlsStreamSecured
con <- lift $ gets cHandle con <- lift $ gets streamHandle
when (stls features == Nothing) $ throwError TlsNoServerSupport when (streamTls features == Nothing) $ throwError TlsNoServerSupport
lift $ pushElement starttlsE lift $ pushElement starttlsE
answer <- lift $ pullElement answer <- lift $ pullElement
case answer of case answer of
@ -93,12 +93,12 @@ startTls params con = Ex.handle (return . Left . TlsError)
Right (Element "{urn:ietf:params:xml:ns:xmpp-tls}proceed" [] []) -> return $ Right () Right (Element "{urn:ietf:params:xml:ns:xmpp-tls}proceed" [] []) -> return $ Right ()
Right (Element "{urn:ietf:params:xml:ns:xmpp-tls}failure" _ _) -> return $ Left XmppOtherFailure Right (Element "{urn:ietf:params:xml:ns:xmpp-tls}failure" _ _) -> return $ Left XmppOtherFailure
(raw, _snk, psh, read, ctx) <- lift $ TLS.tlsinit debug params (mkBackend con) (raw, _snk, psh, read, ctx) <- lift $ TLS.tlsinit debug params (mkBackend con)
let newHand = StreamHandle { cSend = catchPush . psh let newHand = StreamHandle { streamSend = catchPush . psh
, cRecv = read , streamReceive = read
, cFlush = contextFlush ctx , streamFlush = contextFlush ctx
, cClose = bye ctx >> cClose con , streamClose = bye ctx >> streamClose con
} }
lift $ modify ( \x -> x {cHandle = newHand}) lift $ modify ( \x -> x {streamHandle = newHand})
either (lift . Ex.throwIO) return =<< lift restartStream either (lift . Ex.throwIO) return =<< lift restartStream
modify (\s -> s{cState = Secured}) modify (\s -> s{streamState = Secured})
return () return ()

77
source/Network/Xmpp/Types.hs

@ -22,7 +22,7 @@ module Network.Xmpp.Types
, PresenceType(..) , PresenceType(..)
, SaslError(..) , SaslError(..)
, SaslFailure(..) , SaslFailure(..)
, ServerFeatures(..) , StreamFeatures(..)
, Stanza(..) , Stanza(..)
, StanzaError(..) , StanzaError(..)
, StanzaErrorCondition(..) , StanzaErrorCondition(..)
@ -755,52 +755,63 @@ langTagParser = do
tagChars :: [Char] tagChars :: [Char]
tagChars = ['a'..'z'] ++ ['A'..'Z'] tagChars = ['a'..'z'] ++ ['A'..'Z']
data ServerFeatures = SF data StreamFeatures = StreamFeatures
{ stls :: !(Maybe Bool) { streamTls :: !(Maybe Bool)
, saslMechanisms :: ![Text.Text] , streamSaslMechanisms :: ![Text.Text]
, other :: ![Element] , streamOtherFeatures :: ![Element] -- TODO: All feature elements instead?
} deriving Show } deriving Show
-- | Signals the state of the connection. -- | Signals the state of the stream connection.
data StreamState data StreamState
= Closed -- ^ No stream at this point. = Closed -- ^ No stream has been established
| Plain -- ^ Stream established, but not secured. | Plain -- ^ Stream established, but not secured via TLS
| Secured -- ^ Stream established and secured via TLS. | Secured -- ^ Stream established and secured via TLS
deriving (Show, Eq, Typeable) deriving (Show, Eq, Typeable)
-- | Defines operations for sending, receiving, flushing, and closing on a -- | Defines operations for sending, receiving, flushing, and closing on a
-- connection. -- stream.
data StreamHandle = data StreamHandle =
StreamHandle { cSend :: BS.ByteString -> IO Bool StreamHandle { streamSend :: BS.ByteString -> IO Bool
, cRecv :: Int -> IO BS.ByteString , streamReceive :: Int -> IO BS.ByteString
-- This is to hold the state of the XML parser (otherwise -- This is to hold the state of the XML parser (otherwise we
-- we will receive EventBeginDocument events and forget -- will receive EventBeginDocument events and forget about
-- about name prefixes). -- name prefixes). (TODO: Clarify)
, cFlush :: IO () , streamFlush :: IO ()
, cClose :: IO () , streamClose :: IO ()
} }
data Stream = Stream data Stream = Stream
{ cState :: !StreamState -- ^ State of connection { -- | State of the stream - 'Closed', 'Plain', or 'Secured'
, cHandle :: StreamHandle -- ^ Handle to send, receive, flush, and close streamState :: !StreamState -- ^ State of connection
-- on the connection. -- | Functions to send, receive, flush, and close on the stream
, cEventSource :: ResumableSource IO Event -- ^ Event conduit source, and , streamHandle :: StreamHandle
-- its associated finalizer -- | Event conduit source, and its associated finalizer
, cFeatures :: !ServerFeatures -- ^ Features as advertised by the server , streamEventSource :: ResumableSource IO Event
, cHostName :: !(Maybe Text) -- ^ Hostname of the server -- | Stream features advertised by the server
, cJid :: !(Maybe Jid) -- ^ Our JID , streamFeatures :: !StreamFeatures -- TODO: Maybe?
, cPreferredLang :: !(Maybe LangTag) -- ^ Default language when no explicit -- | The hostname we specified for the connection
, streamHostname :: !(Maybe Text)
-- | The hostname specified in the server's stream element's
-- `from' attribute
, streamFrom :: !(Maybe Jid)
-- | The identifier specified in the server's stream element's
-- `id' attribute
, streamId :: !(Maybe Text)
-- | The language tag value specified in the server's stream
-- element's `langtag' attribute; will be a `Just' value once
-- connected to the server
-- TODO: Verify
, streamLang :: !(Maybe LangTag)
-- | Our JID as assigned by the server
, streamJid :: !(Maybe Jid)
-- TODO: Move the below fields to a configuration record
, preferredLang :: !(Maybe LangTag) -- ^ Default language when no explicit
-- language tag is set -- language tag is set
, cStreamLang :: !(Maybe LangTag) -- ^ Will be a `Just' value once connected , toJid :: !(Maybe Jid) -- ^ JID to include in the stream element's `to'
-- to the server.
, cStreamId :: !(Maybe Text) -- ^ Stream ID as specified by the server.
, cToJid :: !(Maybe Jid) -- ^ JID to include in the stream element's `to'
-- attribute when the connection is secured. See -- attribute when the connection is secured. See
-- also below. -- also below.
, cJidWhenPlain :: !Bool -- ^ Whether or not to also include the Jid when , includeJidWhenPlain :: !Bool -- ^ Whether or not to also include the Jid when
-- the connection is plain. -- the connection is plain.
, cFrom :: !(Maybe Jid) -- ^ From as specified by the server in the stream
-- element's `from' attribute.
} }
withStream :: StateT Stream IO (Either XmppFailure c) -> TMVar Stream -> IO (Either XmppFailure c) withStream :: StateT Stream IO (Either XmppFailure c) -> TMVar Stream -> IO (Either XmppFailure c)

Loading…
Cancel
Save