Browse Source

move TLS preference check to startTLS and add PreferPlain

master
Philipp Balzarek 13 years ago
parent
commit
8875fca4d7
  1. 19
      source/Network/Xmpp/Concurrent.hs
  2. 2
      source/Network/Xmpp/Internal.hs
  3. 94
      source/Network/Xmpp/Tls.hs
  4. 9
      source/Network/Xmpp/Types.hs

19
source/Network/Xmpp/Concurrent.hs

@ -137,24 +137,7 @@ session :: HostName -- ^ The hostname / realm
-> IO (Either XmppFailure (Session, Maybe AuthFailure)) -> IO (Either XmppFailure (Session, Maybe AuthFailure))
session realm config mbSasl = runErrorT $ do session realm config mbSasl = runErrorT $ do
stream <- ErrorT $ openStream realm (sessionStreamConfiguration config) stream <- ErrorT $ openStream realm (sessionStreamConfiguration config)
tlsFeat <- ErrorT $ withStream' (get >>= \stream' -> return $ Right $ streamTls $ streamFeatures stream') stream ErrorT $ tls stream
case sessionTlsBehaviour config of
RequireTls -> do
case tlsFeat of
Nothing -> do
lift $ errorM "Pontarius.XMPP" "TLS is required by the client but not offered by the server." >> return ()
throwError TlsNoServerSupport
Just _ -> ErrorT $ startTls stream
PreferTls -> do
case tlsFeat of
Nothing -> return ()
Just _ -> ErrorT $ startTls stream
RefuseTls -> do
case tlsFeat of
Just True -> do
lift $ errorM "Pontarius.XMPP" "TLS is refused by the client but required by the server."
throwError XmppOtherFailure
_ -> 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

2
source/Network/Xmpp/Internal.hs

@ -24,7 +24,7 @@ module Network.Xmpp.Internal
, StreamFeatures(..) , StreamFeatures(..)
, openStream , openStream
, withStream , withStream
, startTls , tls
, auth , auth
, pushStanza , pushStanza
, pullStanza , pullStanza

94
source/Network/Xmpp/Tls.hs

@ -4,29 +4,25 @@
module Network.Xmpp.Tls where module Network.Xmpp.Tls where
import Control.Concurrent.STM.TMVar
import qualified Control.Exception.Lifted as Ex import qualified Control.Exception.Lifted as Ex
import Control.Monad import Control.Monad
import Control.Monad.Error import Control.Monad.Error
import Control.Monad.State.Strict import Control.Monad.State.Strict
import Crypto.Random.API
import qualified Data.ByteString as BS import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Char8 as BSC8 import qualified Data.ByteString.Char8 as BSC8
import qualified Data.ByteString.Lazy as BL
import Data.Conduit import Data.Conduit
import qualified Data.Conduit.Binary as CB import qualified Data.Conduit.Binary as CB
import Data.IORef
import Data.Typeable import Data.Typeable
import Data.XML.Types import Data.XML.Types
import Network.Xmpp.Stream
import Network.Xmpp.Types
import System.Log.Logger
import Control.Concurrent.STM.TMVar
import Data.IORef
import Crypto.Random.API
import Network.TLS import Network.TLS
import Network.TLS.Extra import Network.TLS.Extra
import Network.Xmpp.Stream
import Network.Xmpp.Types
import System.Log.Logger (debugM, errorM)
mkBackend con = Backend { backendSend = \bs -> void (streamSend con bs) mkBackend con = Backend { backendSend = \bs -> void (streamSend con bs)
, backendRecv = streamReceive con , backendRecv = streamReceive con
@ -37,48 +33,54 @@ 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" [] []
-- Pushes "<starttls/>, waits for "<proceed/>", performs the TLS handshake, and -- | Checks for TLS support and run starttls procedure if applicable
-- restarts the stream. tls :: TMVar Stream -> IO (Either XmppFailure ())
startTls :: TMVar Stream -> IO (Either XmppFailure ()) tls 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..." conf <- gets $ streamConfiguration
features <- lift $ gets streamFeatures sState <- gets streamState
config <- lift $ gets streamConfiguration case sState of
let params = tlsParams config
state <- gets streamState
case state of
Plain -> return () Plain -> return ()
Closed -> do Closed -> do
lift $ lift $ errorM "Pontarius.XMPP" "startTls: The stream is closed." liftIO $ errorM "Pontarius.XMPP" "startTls: The stream is closed."
throwError XmppNoStream throwError XmppNoStream
Secured -> do Secured -> do
lift $ lift $ errorM "Pontarius.XMPP" "startTls: The stream is already secured." liftIO $ errorM "Pontarius.XMPP" "startTls: The stream is already secured."
throwError TlsStreamSecured throwError TlsStreamSecured
con <- lift $ gets streamHandle features <- lift $ gets streamFeatures
when (streamTls features == Nothing) $ do case (tlsBehaviour conf, streamTls features) of
lift $ lift $ errorM "Pontarius.XMPP" "The server does not support TLS." (RequireTls , Just _ ) -> startTls
throwError TlsNoServerSupport (RequireTls , Nothing ) -> throwError TlsNoServerSupport
lift $ pushElement starttlsE (PreferTls , Just _ ) -> startTls
answer <- lift $ pullElement (PreferTls , Nothing ) -> return ()
case answer of (PreferPlain , Just True) -> startTls
Left e -> return $ Left e (PreferPlain , _ ) -> return ()
Right (Element "{urn:ietf:params:xml:ns:xmpp-tls}proceed" [] []) -> return $ Right () (RefuseTls , Just True) -> throwError XmppOtherFailure
Right (Element "{urn:ietf:params:xml:ns:xmpp-tls}failure" _ _) -> do (RefuseTls , _ ) -> return ()
lift $ lift $ errorM "Pontarius.XMPP" "startTls: TLS initiation failed." where
return . Left $ XmppOtherFailure startTls = do
(raw, _snk, psh, read, ctx) <- lift $ tlsinit params (mkBackend con) params <- gets $ tlsParams . streamConfiguration
let newHand = StreamHandle { streamSend = catchPush . psh lift $ pushElement starttlsE
, streamReceive = read answer <- lift $ pullElement
, streamFlush = contextFlush ctx case answer of
, streamClose = bye ctx >> streamClose con Left e -> return $ Left e
} Right (Element "{urn:ietf:params:xml:ns:xmpp-tls}proceed" [] []) ->
lift $ modify ( \x -> x {streamHandle = newHand}) return $ Right ()
either (lift . Ex.throwIO) return =<< lift restartStream Right (Element "{urn:ietf:params:xml:ns:xmpp-tls}failure" _ _) -> do
modify (\s -> s{streamState = Secured}) liftIO $ errorM "Pontarius.XMPP" "startTls: TLS initiation failed."
lift $ lift $ debugM "Pontarius.XMPP" "startTls: Stream secured." return . Left $ XmppOtherFailure
return () hand <- gets streamHandle
(raw, _snk, psh, read, ctx) <- lift $ tlsinit params (mkBackend hand)
let newHand = StreamHandle { streamSend = catchPush . psh
, streamReceive = read
, streamFlush = contextFlush ctx
, streamClose = bye ctx >> streamClose hand
}
lift $ modify ( \x -> x {streamHandle = newHand})
either (lift . Ex.throwIO) return =<< lift restartStream
modify (\s -> s{streamState = Secured})
return ()
client params gen backend = do client params gen backend = do
contextNew backend params gen contextNew backend params gen

9
source/Network/Xmpp/Types.hs

@ -1044,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
-- | How the client should behave in regards to TLS.
, tlsBehaviour :: TlsBehaviour
-- | Settings to be used for TLS negotitation -- | Settings to be used for TLS negotitation
, tlsParams :: TLSParams , tlsParams :: TLSParams
} }
@ -1055,6 +1057,7 @@ instance Default StreamConfiguration where
, socketDetails = Nothing , socketDetails = Nothing
, resolvConf = defaultResolvConf , resolvConf = defaultResolvConf
, establishSession = False , establishSession = False
, tlsBehaviour = PreferTls
, tlsParams = defaultParamsClient { pConnectVersion = TLS12 , tlsParams = defaultParamsClient { pConnectVersion = TLS12
, pAllowedVersions = [TLS12] , pAllowedVersions = [TLS12]
, pCiphers = ciphersuite_strong , pCiphers = ciphersuite_strong
@ -1105,8 +1108,6 @@ data SessionConfiguration = SessionConfiguration
, sessionClosedHandler :: XmppFailure -> IO () , sessionClosedHandler :: XmppFailure -> IO ()
-- | Function to generate the stream of stanza identifiers. -- | 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
@ -1118,10 +1119,12 @@ instance Default SessionConfiguration where
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. -- | How the client should behave in regards to TLS.
data TlsBehaviour = RequireTls -- ^ Require the use of TLS; disconnect if it's data TlsBehaviour = RequireTls -- ^ Require the use of TLS; disconnect if it's
-- not offered. -- not offered.
| PreferTls -- ^ Negotitate TLS if it's available. | PreferTls -- ^ Negotitate TLS if it's available.
| PreferPlain -- ^ Negotitate TLS only if the server requires
-- it
| RefuseTls -- ^ Never secure the stream with TLS. | RefuseTls -- ^ Never secure the stream with TLS.

Loading…
Cancel
Save