Browse Source

Sasl.hs: Extend logging

master
Jon Kristensen 13 years ago
parent
commit
5a5a9f244e
  1. 78
      source/Network/Xmpp/Sasl.hs

78
source/Network/Xmpp/Sasl.hs

@ -38,7 +38,7 @@ import qualified Data.Text.Encoding as Text
import Network.Xmpp.Stream import Network.Xmpp.Stream
import Network.Xmpp.Types import Network.Xmpp.Types
import System.Log.Logger (debugM) import System.Log.Logger (debugM, errorM)
import qualified System.Random as Random import qualified System.Random as Random
import Network.Xmpp.Sasl.Types import Network.Xmpp.Sasl.Types
@ -68,23 +68,35 @@ xmppSasl :: [SaslHandler] -- ^ Acceptable authentication mechanisms and their
-- corresponding handlers -- corresponding handlers
-> TMVar Stream -> TMVar Stream
-> IO (Either XmppFailure (Maybe AuthFailure)) -> IO (Either XmppFailure (Maybe AuthFailure))
xmppSasl handlers = withStream $ do xmppSasl handlers stream = do
-- Chooses the first mechanism that is acceptable by both the client and the debugM "Pontarius.Xmpp" "xmppSasl: Attempts to authenticate..."
-- server. flip withStream stream $ do
mechanisms <- gets $ streamSaslMechanisms . streamFeatures -- Chooses the first mechanism that is acceptable by both the client and the
case (filter (\(name, _) -> name `elem` mechanisms)) handlers of -- server.
[] -> return $ Right $ Just $ AuthNoAcceptableMechanism mechanisms mechanisms <- gets $ streamSaslMechanisms . streamFeatures
(_name, handler):_ -> do case (filter (\(name, _) -> name `elem` mechanisms)) handlers of
cs <- gets streamState [] -> return $ Right $ Just $ AuthNoAcceptableMechanism mechanisms
case cs of (_name, handler):_ -> do
Closed -> return . Left $ XmppNoStream cs <- gets streamState
_ -> runErrorT $ do case cs of
r <- ErrorT handler Closed -> do
case r of lift $ errorM "Pontarius.Xmpp" "xmppSasl: Stream state closed."
Just ae -> return $ Just ae return . Left $ XmppNoStream
Nothing -> do _ -> runErrorT $ do
_ <- ErrorT restartStream -- TODO: Log details about handler? SaslHandler "show" instance?
return Nothing lift $ lift $ debugM "Pontarius.Xmpp" "xmppSasl: Performing handler..."
r <- ErrorT handler
case r of
Just ae -> do
lift $ lift $ errorM "Pontarius.Xmpp" $
"xmppSasl: AuthFailure encountered: " ++
show ae
return $ Just ae
Nothing -> do
lift $ lift $ debugM "Pontarius.Xmpp" "xmppSasl: Authentication successful, restarting stream."
_ <- ErrorT restartStream
lift $ lift $ debugM "Pontarius.Xmpp" "xmppSasl: Stream restarted."
return Nothing
-- | Authenticate to the server using the first matching method and bind a -- | Authenticate to the server using the first matching method and bind a
-- resource. -- resource.
@ -93,12 +105,9 @@ auth :: [SaslHandler]
-> TMVar Stream -> TMVar Stream
-> IO (Either XmppFailure (Maybe AuthFailure)) -> IO (Either XmppFailure (Maybe AuthFailure))
auth mechanisms resource con = runErrorT $ do auth mechanisms resource con = runErrorT $ do
liftIO $ debugM "Pontarius.Xmpp" "pre-auth"
ErrorT $ xmppSasl mechanisms con ErrorT $ xmppSasl mechanisms con
liftIO $ debugM "Pontarius.Xmpp" "auth done"
jid <- ErrorT $ xmppBind resource con jid <- ErrorT $ xmppBind resource con
liftIO $ debugM "Pontarius.Xmpp" $ "bound resource" ++ show jid _ <- lift $ startSession con
lift $ startSession con
return Nothing return Nothing
-- Produces a `bind' element, optionally wrapping a resource. -- Produces a `bind' element, optionally wrapping a resource.
@ -114,20 +123,26 @@ bindBody = pickleElem $
-- resource and extract the JID from the non-error response. -- resource and extract the JID from the non-error response.
xmppBind :: Maybe Text -> TMVar Stream -> IO (Either XmppFailure Jid) xmppBind :: Maybe Text -> TMVar Stream -> IO (Either XmppFailure Jid)
xmppBind rsrc c = runErrorT $ do xmppBind rsrc c = runErrorT $ do
lift $ debugM "Pontarius.Xmpp" "Attempts to bind..."
answer <- ErrorT $ pushIQ "bind" Nothing Set Nothing (bindBody rsrc) c answer <- ErrorT $ pushIQ "bind" Nothing Set Nothing (bindBody rsrc) c
case answer of case answer of
Right IQResult{iqResultPayload = Just b} -> do Right IQResult{iqResultPayload = Just b} -> do
lift $ debugM "Pontarius.XMPP" "xmppBind: IQ result received; unpickling JID..."
let jid = unpickleElem xpJid b let jid = unpickleElem xpJid b
case jid of case jid of
Right jid' -> do Right jid' -> do
lift $ debugM "Pontarius.XMPP" $ "xmppBind: JID unpickled: " ++ show jid'
ErrorT $ withStream (do ErrorT $ withStream (do
modify $ \s -> s{streamJid = 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 -> do
"bind: could not parse JID" lift $ errorM "Pontarius.XMPP" $ "xmppBind: JID could not be unpickled from: "
-- TODO: Log: ("Bind couldn't unpickle JID from " ++ show answer) ++ show b
otherwise -> throwError $ XmppOtherFailure "bind: failed to bind" throwError $ XmppOtherFailure $ "xmppBind: JID could not be unpickled from: " ++ show b
otherwise -> do
lift $ errorM "Pontarius.XMPP" "xmppBind: IQ error received."
throwError $ XmppOtherFailure "bind: failed to bind"
where where
-- Extracts the character data in the `jid' element. -- Extracts the character data in the `jid' element.
xpJid :: PU [Node] Jid xpJid :: PU [Node] Jid
@ -154,9 +169,14 @@ sessionIQ = IQRequestS $ IQRequest { iqRequestID = "sess"
-- Sends the session IQ set element and waits for an answer. Throws an error if -- Sends the session IQ set element and waits for an answer. Throws an error if
-- if an IQ error stanza is returned from the server. -- if an IQ error stanza is returned from the server.
startSession :: TMVar Stream -> IO () startSession :: TMVar Stream -> IO Bool
startSession con = do startSession con = do
debugM "Pontarius.XMPP" "startSession: Pushing `session' IQ set stanza..."
answer <- pushIQ "session" Nothing Set Nothing sessionXml con answer <- pushIQ "session" Nothing Set Nothing sessionXml con
case answer of case answer of
Left e -> error $ show e Left e -> do
Right _ -> return () errorM "Pontarius.XMPP" $ "startSession: Error stanza received (" ++ (show e) ++ ")"
return False
Right _ -> do
debugM "Pontarius.XMPP" "startSession: Result stanza received."
return True

Loading…
Cancel
Save