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.
108 lines
3.8 KiB
108 lines
3.8 KiB
|
13 years ago
|
{-# OPTIONS_HADDOCK hide #-}
|
||
|
14 years ago
|
{-# LANGUAGE DeriveDataTypeable #-}
|
||
|
14 years ago
|
{-# LANGUAGE OverloadedStrings #-}
|
||
|
15 years ago
|
|
||
|
13 years ago
|
module Network.Xmpp.Tls where
|
||
|
15 years ago
|
|
||
|
14 years ago
|
import qualified Control.Exception.Lifted as Ex
|
||
|
14 years ago
|
import Control.Monad
|
||
|
14 years ago
|
import Control.Monad.Error
|
||
|
|
import Control.Monad.State.Strict
|
||
|
15 years ago
|
|
||
|
13 years ago
|
import qualified Data.ByteString as BS
|
||
|
|
import qualified Data.ByteString.Lazy as BL
|
||
|
|
import Data.Conduit
|
||
|
|
import qualified Data.Conduit.Binary as CB
|
||
|
13 years ago
|
import Data.Conduit.Tls as TLS
|
||
|
14 years ago
|
import Data.Typeable
|
||
|
14 years ago
|
import Data.XML.Types
|
||
|
15 years ago
|
|
||
|
13 years ago
|
import Network.Xmpp.Connection
|
||
|
14 years ago
|
import Network.Xmpp.Pickle(ppElement)
|
||
|
|
import Network.Xmpp.Stream
|
||
|
|
import Network.Xmpp.Types
|
||
|
15 years ago
|
|
||
|
13 years ago
|
mkBackend con = Backend { backendSend = \bs -> void (cSend con bs)
|
||
|
|
, backendRecv = cRecv con
|
||
|
|
, backendFlush = cFlush con
|
||
|
|
, backendClose = cClose con
|
||
|
|
}
|
||
|
|
where
|
||
|
|
cutBytes n = do
|
||
|
|
liftIO $ putStrLn "awaiting"
|
||
|
|
mbs <- await
|
||
|
|
liftIO $ putStrLn "done awaiting"
|
||
|
|
case mbs of
|
||
|
|
Nothing -> return BS.empty
|
||
|
|
Just bs -> do
|
||
|
|
let (a, b) = BS.splitAt n bs
|
||
|
|
liftIO . putStrLn $
|
||
|
|
"remaining" ++ (show $ BS.length b) ++ " of " ++ (show n)
|
||
|
|
|
||
|
|
unless (BS.null b) $ leftover b
|
||
|
|
return a
|
||
|
|
|
||
|
|
|
||
|
|
cutBytes n = do
|
||
|
|
liftIO $ putStrLn "awaiting"
|
||
|
|
mbs <- await
|
||
|
|
liftIO $ putStrLn "done awaiting"
|
||
|
|
case mbs of
|
||
|
|
Nothing -> return False
|
||
|
|
Just bs -> do
|
||
|
|
let (a, b) = BS.splitAt n bs
|
||
|
|
liftIO . putStrLn $
|
||
|
|
"remaining" ++ (show $ BS.length b) ++ " of " ++ (show n)
|
||
|
|
|
||
|
|
unless (BS.null b) $ leftover b
|
||
|
|
return True
|
||
|
|
|
||
|
|
|
||
|
14 years ago
|
starttlsE :: Element
|
||
|
14 years ago
|
starttlsE = Element "{urn:ietf:params:xml:ns:xmpp-tls}starttls" [] []
|
||
|
14 years ago
|
|
||
|
14 years ago
|
exampleParams :: TLS.TLSParams
|
||
|
13 years ago
|
exampleParams = TLS.defaultParamsClient
|
||
|
14 years ago
|
{ pConnectVersion = TLS.TLS10
|
||
|
|
, pAllowedVersions = [TLS.SSL3, TLS.TLS10, TLS.TLS11]
|
||
|
|
, pCiphers = [TLS.cipher_AES128_SHA1]
|
||
|
|
, pCompressions = [TLS.nullCompression]
|
||
|
|
, pUseSecureRenegotiation = False -- No renegotiation
|
||
|
|
, onCertificatesRecv = \_certificate ->
|
||
|
|
return TLS.CertificateUsageAccept
|
||
|
|
}
|
||
|
14 years ago
|
|
||
|
14 years ago
|
-- Pushes "<starttls/>, waits for "<proceed/>", performs the TLS handshake, and
|
||
|
13 years ago
|
-- restarts the stream.
|
||
|
13 years ago
|
startTls :: TLS.TLSParams -> Connection -> IO (Either TlsFailure ())
|
||
|
|
startTls params con = Ex.handle (return . Left . TlsError)
|
||
|
13 years ago
|
. flip withConnection con
|
||
|
|
. runErrorT $ do
|
||
|
14 years ago
|
features <- lift $ gets sFeatures
|
||
|
13 years ago
|
state <- gets sConnectionState
|
||
|
|
case state of
|
||
|
13 years ago
|
ConnectionPlain -> return ()
|
||
|
13 years ago
|
ConnectionClosed -> throwError TlsNoConnection
|
||
|
|
ConnectionSecured -> throwError TlsConnectionSecured
|
||
|
13 years ago
|
con <- lift $ gets cHand
|
||
|
13 years ago
|
when (stls features == Nothing) $ throwError TlsNoServerSupport
|
||
|
14 years ago
|
lift $ pushElement starttlsE
|
||
|
14 years ago
|
answer <- lift $ pullElement
|
||
|
|
case answer of
|
||
|
14 years ago
|
Element "{urn:ietf:params:xml:ns:xmpp-tls}proceed" [] [] -> return ()
|
||
|
14 years ago
|
Element "{urn:ietf:params:xml:ns:xmpp-tls}failure" _ _ ->
|
||
|
13 years ago
|
lift $ Ex.throwIO StreamOtherFailure
|
||
|
14 years ago
|
-- TODO: find something more suitable
|
||
|
13 years ago
|
e -> lift $ Ex.throwIO StreamOtherFailure
|
||
|
|
-- TODO: Log: "Unexpected element: " ++ ppElement e
|
||
|
13 years ago
|
(raw, _snk, psh, read, ctx) <- lift $ TLS.tlsinit debug params (mkBackend con)
|
||
|
13 years ago
|
let newHand = Hand { cSend = catchPush . psh
|
||
|
|
, cRecv = read
|
||
|
|
, cFlush = contextFlush ctx
|
||
|
|
, cClose = bye ctx >> cClose con
|
||
|
|
}
|
||
|
|
lift $ modify ( \x -> x {cHand = newHand})
|
||
|
|
either (lift . Ex.throwIO) return =<< lift restartStream
|
||
|
13 years ago
|
modify (\s -> s{sConnectionState = ConnectionSecured})
|
||
|
14 years ago
|
return ()
|