Browse Source

Add debug support (controlled by debug constant in Network.Xmpp.Monad)

master
Philipp Balzarek 14 years ago
parent
commit
ef607f550b
  1. 27
      source/Data/Conduit/TLS.hs
  2. 29
      source/Network/Xmpp/Monad.hs
  3. 4
      source/Network/Xmpp/TLS.hs

27
source/Data/Conduit/TLS.hs

@ -8,7 +8,7 @@ module Data.Conduit.TLS
) )
where where
import Control.Monad(liftM) import Control.Monad(liftM, when)
import Control.Monad.IO.Class import Control.Monad.IO.Class
import Crypto.Random import Crypto.Random
@ -22,29 +22,36 @@ import Network.TLS.Extra as TLSExtra
import System.IO(Handle) import System.IO(Handle)
tlsinit tlsinit :: (MonadIO m, MonadIO m1) =>
:: (MonadIO m, MonadIO m1) => Bool
TLSParams -> TLSParams
-> Handle -> m ( Source m1 BS.ByteString -> Handle -> m ( Source m1 BS.ByteString
, Sink BS.ByteString m1 () , Sink BS.ByteString m1 ()
, BS.ByteString -> IO () , BS.ByteString -> IO ()
, TLSCtx Handle , TLSCtx Handle
) )
tlsinit tlsParams handle = do tlsinit debug tlsParams handle = do
when debug . liftIO $ putStrLn "Debug mode enabled"
gen <- liftIO $ (newGenIO :: IO SystemRandom) -- TODO: Find better random source? gen <- liftIO $ (newGenIO :: IO SystemRandom) -- TODO: Find better random source?
clientContext <- client tlsParams gen handle clientContext <- client tlsParams gen handle
handshake clientContext handshake clientContext
let src = sourceState let src = sourceState
clientContext clientContext
(\con -> StateOpen con `liftM` recvData con) (\con -> do
dt <- recvData con
when debug (liftIO $ BS.putStrLn dt)
return $ StateOpen con dt)
let snk = sinkState let snk = sinkState
clientContext clientContext
(\con bs -> sendData con (BL.fromChunks [bs]) (\con bs -> do
>> return (StateProcessing con)) sendData con (BL.fromChunks [bs])
when debug (liftIO $ BS.putStrLn bs)
return (StateProcessing con))
(\_ -> return ()) (\_ -> return ())
return ( src return ( src
, snk , snk
, \s -> sendData clientContext $ BL.fromChunks [s] , \s -> do
when debug (liftIO $ BS.putStrLn s)
sendData clientContext $ BL.fromChunks [s]
, clientContext , clientContext
) )

29
source/Network/Xmpp/Monad.hs

@ -33,6 +33,12 @@ import Text.XML.Stream.Elements
import Text.XML.Stream.Parse as XP import Text.XML.Stream.Parse as XP
import Text.XML.Unresolved(InvalidEventStream(..)) import Text.XML.Unresolved(InvalidEventStream(..))
-- 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
pushElement :: Element -> XmppConMonad Bool pushElement :: Element -> XmppConMonad Bool
pushElement x = do pushElement x = do
sink <- gets sConPushBS sink <- gets sConPushBS
@ -94,7 +100,7 @@ pullStanza = do
Right r -> return r Right r -> return r
-- Performs the given IO operation, catches any errors and re-throws everything -- Performs the given IO operation, catches any errors and re-throws everything
-- except the `ResourceVanished' error. -- except 'ResourceVanished' and IllegalOperation, in which case it will return False instead
catchPush :: IO () -> IO Bool catchPush :: IO () -> IO Bool
catchPush p = Ex.catch catchPush p = Ex.catch
(p >> return True) (p >> return True)
@ -135,12 +141,18 @@ xmppRawConnect host hostname = do
con <- connectTo host (PortNumber 5222) con <- connectTo host (PortNumber 5222)
hSetBuffering con NoBuffering hSetBuffering con NoBuffering
return con return con
let raw = sourceHandle con let raw = if debug
then sourceHandle con $= debugConduit
else sourceHandle con
src <- liftIO . bufferSource $ raw $= XP.parseBytes def src <- liftIO . bufferSource $ raw $= XP.parseBytes def
let st = XmppConnection let st = XmppConnection
{ sConSrc = src { sConSrc = src
, sRawSrc = raw , sRawSrc = raw
, sConPushBS = (catchPush . BS.hPut con) , sConPushBS = if debug
then \d -> do
BS.putStrLn (BS.append "out: " d)
catchPush $ BS.hPut con d
else catchPush . BS.hPut con
, sConHandle = (Just con) , sConHandle = (Just con)
, sFeatures = (SF Nothing [] []) , sFeatures = (SF Nothing [] [])
, sConnectionState = XmppConnectionPlain , sConnectionState = XmppConnectionPlain
@ -211,4 +223,13 @@ xmppCloseStreams = do
case result of case result of
Left StreamStreamEnd -> return (elems, True) Left StreamStreamEnd -> return (elems, True)
Left _ -> return (elems, False) Left _ -> return (elems, False)
Right elem -> collectElems (elem:elems) Right elem -> collectElems (elem:elems)
debugConduit :: MonadIO m => Pipe BS.ByteString BS.ByteString m ()
debugConduit = forever $ do
s <- await
case s of
Just s -> do
liftIO $ BS.putStrLn (BS.append "in: " s)
yield s
Nothing -> return ()

4
source/Network/Xmpp/TLS.hs

@ -62,7 +62,7 @@ startTLS params = Ex.handle (return . Left . TLSError) . runErrorT $ do
-- TODO: find something more suitable -- TODO: find something more suitable
e -> lift . Ex.throwIO . StreamXMLError $ e -> lift . Ex.throwIO . StreamXMLError $
"Unexpected element: " ++ ppElement e "Unexpected element: " ++ ppElement e
(raw, _snk, psh, ctx) <- lift $ TLS.tlsinit params handle (raw, _snk, psh, ctx) <- lift $ TLS.tlsinit debug params handle
lift $ modify ( \x -> x lift $ modify ( \x -> x
{ sRawSrc = raw { sRawSrc = raw
-- , sConSrc = -- Note: this momentarily leaves us in an -- , sConSrc = -- Note: this momentarily leaves us in an
@ -72,4 +72,4 @@ startTLS params = Ex.handle (return . Left . TLSError) . runErrorT $ do
}) })
either (lift . Ex.throwIO) return =<< lift xmppRestartStream either (lift . Ex.throwIO) return =<< lift xmppRestartStream
modify (\s -> s{sConnectionState = XmppConnectionSecured}) modify (\s -> s{sConnectionState = XmppConnectionSecured})
return () return ()

Loading…
Cancel
Save