Browse Source

Add TLS behaviour and settings to the `StreamConfiguration' object

master
Jon Kristensen 13 years ago
parent
commit
2548c94310
  1. 1
      examples/echoclient/Main.hs
  2. 2
      source/Network/Xmpp.hs
  3. 12
      source/Network/Xmpp/Concurrent.hs
  4. 13
      source/Network/Xmpp/Tls.hs
  5. 24
      source/Network/Xmpp/Types.hs

1
examples/echoclient/Main.hs

@ -53,7 +53,6 @@ main = do
sess' <- session sess' <- session
realm realm
def def
Nothing -- (Just exampleParams)
(Just ([scramSha1 username Nothing password], resource)) (Just ([scramSha1 username Nothing password], resource))
sess <- case sess' of sess <- case sess' of
Left err -> error $ "Error connection to XMPP server: " ++ show err Left err -> error $ "Error connection to XMPP server: " ++ show err

2
source/Network/Xmpp.hs

@ -147,8 +147,6 @@ module Network.Xmpp
, dupSession , dupSession
-- * Miscellaneous -- * Miscellaneous
, LangTag(..) , LangTag(..)
, exampleParams
, PortID(..)
, XmppFailure(..) , XmppFailure(..)
, StreamErrorInfo(..) , StreamErrorInfo(..)
, StreamErrorCondition(..) , StreamErrorCondition(..)

12
source/Network/Xmpp/Concurrent.hs

@ -130,18 +130,16 @@ writeWorker stCh writeR = forever $ do
-- acquire an XMPP resource. -- acquire an XMPP resource.
session :: HostName -- ^ The hostname / realm session :: HostName -- ^ The hostname / realm
-> SessionConfiguration -- ^ configuration details -> SessionConfiguration -- ^ configuration details
-> Maybe TLS.TLSParams -- ^ TLS settings, if securing the
-- connection to the server is
-- desired
-> Maybe ([SaslHandler], Maybe Text) -- ^ SASL handlers and the desired -> Maybe ([SaslHandler], Maybe Text) -- ^ SASL handlers and the desired
-- JID resource (or Nothing to let -- JID resource (or Nothing to let
-- the server decide) -- the server decide)
-> IO (Either XmppFailure (Session, Maybe AuthFailure)) -> IO (Either XmppFailure (Session, Maybe AuthFailure))
session realm config mbTls mbSasl = runErrorT $ do session realm config mbSasl = runErrorT $ do
stream <- ErrorT $ openStream realm (sessionStreamConfiguration config) stream <- ErrorT $ openStream realm (sessionStreamConfiguration config)
case mbTls of case sessionTlsBehaviour config of
Nothing -> return () RequireTls -> ErrorT $ startTls stream -- TODO: Check if server feature available
Just tls -> ErrorT $ startTls tls stream PreferTls -> ErrorT $ startTls stream -- TODO: Check if server feature available
RefuseTls -> return ()
aut <- case mbSasl of aut <- case mbSasl of
Nothing -> return Nothing Nothing -> return Nothing
Just (handlers, resource) -> ErrorT $ auth handlers resource stream Just (handlers, resource) -> ErrorT $ auth handlers resource stream

13
source/Network/Xmpp/Tls.hs

@ -37,21 +37,16 @@ mkBackend con = Backend { backendSend = \bs -> void (streamSend con bs)
starttlsE :: Element starttlsE :: Element
starttlsE = Element "{urn:ietf:params:xml:ns:xmpp-tls}starttls" [] [] starttlsE = Element "{urn:ietf:params:xml:ns:xmpp-tls}starttls" [] []
exampleParams :: TLSParams
exampleParams = defaultParamsClient
{ pConnectVersion = TLS12
, pAllowedVersions = [TLS12]
, pCiphers = ciphersuite_strong
}
-- Pushes "<starttls/>, waits for "<proceed/>", performs the TLS handshake, and -- Pushes "<starttls/>, waits for "<proceed/>", performs the TLS handshake, and
-- restarts the stream. -- restarts the stream.
startTls :: TLSParams -> TMVar Stream -> IO (Either XmppFailure ()) startTls :: TMVar Stream -> IO (Either XmppFailure ())
startTls params con = Ex.handle (return . Left . TlsError) startTls con = Ex.handle (return . Left . TlsError)
. flip withStream con . flip withStream con
. runErrorT $ do . runErrorT $ do
lift $ lift $ debugM "Pontarius.XMPP" "startTls: Securing stream..." lift $ lift $ debugM "Pontarius.XMPP" "startTls: Securing stream..."
features <- lift $ gets streamFeatures features <- lift $ gets streamFeatures
config <- lift $ gets streamConfiguration
let params = tlsParams config
state <- gets streamState state <- gets streamState
case state of case state of
Plain -> return () Plain -> return ()

24
source/Network/Xmpp/Types.hs

@ -47,6 +47,7 @@ module Network.Xmpp.Types
, Hostname(..) , Hostname(..)
, hostname , hostname
, SessionConfiguration(..) , SessionConfiguration(..)
, TlsBehaviour(..)
) )
where where
@ -67,7 +68,8 @@ import qualified Data.Text as Text
import Data.Typeable(Typeable) import Data.Typeable(Typeable)
import Data.XML.Types import Data.XML.Types
import qualified Network.TLS as TLS import Network.TLS hiding (Version)
import Network.TLS.Extra
import qualified Network as N import qualified Network as N
@ -666,7 +668,7 @@ data XmppFailure = StreamErrorFailure StreamErrorInfo -- ^ An error XML stream
-- failed. -- failed.
| XmppIllegalTcpDetails -- ^ The TCP details provided did not | XmppIllegalTcpDetails -- ^ The TCP details provided did not
-- validate. -- validate.
| TlsError TLS.TLSError -- ^ An error occurred in the | TlsError TLSError -- ^ An error occurred in the
-- TLS layer -- TLS layer
| TlsNoServerSupport -- ^ The server does not support | TlsNoServerSupport -- ^ The server does not support
-- the use of TLS -- the use of TLS
@ -1042,6 +1044,8 @@ data StreamConfiguration =
-- session bind as defined in the (outdated) -- session bind as defined in the (outdated)
-- RFC 3921 specification -- RFC 3921 specification
, establishSession :: Bool , establishSession :: Bool
-- | Settings to be used for TLS negotitation
, tlsParams :: TLSParams
} }
@ -1051,6 +1055,10 @@ instance Default StreamConfiguration where
, socketDetails = Nothing , socketDetails = Nothing
, resolvConf = defaultResolvConf , resolvConf = defaultResolvConf
, establishSession = False , establishSession = False
, tlsParams = defaultParamsClient { pConnectVersion = TLS12
, pAllowedVersions = [TLS12]
, pCiphers = ciphersuite_strong
}
} }
data Hostname = Hostname Text deriving (Eq, Show) data Hostname = Hostname Text deriving (Eq, Show)
@ -1095,7 +1103,10 @@ data SessionConfiguration = SessionConfiguration
sessionStreamConfiguration :: StreamConfiguration sessionStreamConfiguration :: StreamConfiguration
-- | Handler to be run when the session ends (for whatever reason). -- | Handler to be run when the session ends (for whatever reason).
, sessionClosedHandler :: XmppFailure -> IO () , sessionClosedHandler :: XmppFailure -> IO ()
-- | Function to generate the stream of stanza identifiers.
, sessionStanzaIDs :: IO StanzaID , sessionStanzaIDs :: IO StanzaID
-- | How the client should behave in regards to TLS.
, sessionTlsBehaviour :: TlsBehaviour
} }
instance Default SessionConfiguration where instance Default SessionConfiguration where
@ -1106,4 +1117,11 @@ instance Default SessionConfiguration where
atomically $ do atomically $ do
curId <- readTVar idRef curId <- readTVar idRef
writeTVar idRef (curId + 1 :: Integer) writeTVar idRef (curId + 1 :: Integer)
return . read. show $ curId} return . read. show $ curId
, sessionTlsBehaviour = PreferTls }
-- | How the client should behave in regards to TLS.
data TlsBehaviour = RequireTls -- ^ Require the use of TLS; disconnect if it's
-- not offered.
| PreferTls -- ^ Negotitate TLS if it's available.
| RefuseTls -- ^ Never secure the stream with TLS.

Loading…
Cancel
Save