module Network.Xmpp.Sasl
( xmppSasl
, digestMd5
, scramSha1
, plain
, auth
) where
import Control.Monad.Error
import Control.Monad.State.Strict
import Data.Text (Text)
import Data.XML.Pickle
import Data.XML.Types
import Network.Xmpp.Marshal
import Network.Xmpp.Sasl.Mechanisms
import Network.Xmpp.Sasl.Types
import Network.Xmpp.Stream
import Network.Xmpp.Types
import System.Log.Logger (debugM, errorM, infoM)
xmppSasl :: [SaslHandler]
-> Stream
-> IO (Either XmppFailure (Maybe AuthFailure))
xmppSasl handlers stream = do
debugM "Pontarius.Xmpp" "xmppSasl: Attempts to authenticate..."
flip withStream stream $ do
mechanisms <- gets $ streamSaslMechanisms . streamFeatures
case (filter (\(name, _) -> name `elem` mechanisms)) handlers of
[] -> return $ Right $ Just $ AuthNoAcceptableMechanism mechanisms
(_name, handler):_ -> do
cs <- gets streamConnectionState
case cs of
Closed -> do
lift $ errorM "Pontarius.Xmpp" "xmppSasl: Stream state closed."
return . Left $ XmppNoStream
_ -> runErrorT $ do
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
auth :: [SaslHandler]
-> Maybe Text
-> Stream
-> IO (Either XmppFailure (Maybe AuthFailure))
auth mechanisms resource con = runErrorT $ do
mbAuthFail <- ErrorT $ xmppSasl mechanisms con
case mbAuthFail of
Nothing -> do
_jid <- ErrorT $ xmppBind resource con
ErrorT $ flip withStream' con $ do
s <- get
case establishSession $ streamConfiguration s of
False -> return $ Right Nothing
True -> do
_ <-liftIO $ startSession con
return $ Right Nothing
f -> return f
bindBody :: Maybe Text -> Element
bindBody = pickleElem $
xpBind . xpOption $ xpElemNodes "resource" (xpContent xpId)
xmppBind :: Maybe Text -> Stream -> IO (Either XmppFailure Jid)
xmppBind rsrc c = runErrorT $ do
lift $ debugM "Pontarius.Xmpp" "Attempts to bind..."
answer <- ErrorT $ pushIQ "bind" Nothing Set Nothing (bindBody rsrc) c
case answer of
Right IQResult{iqResultPayload = Just b} -> do
lift $ debugM "Pontarius.Xmpp" "xmppBind: IQ result received; unpickling JID..."
let j = unpickleElem xpJid' b
case j of
Right jid' -> do
lift $ infoM "Pontarius.Xmpp" $ "Bound JID: " ++ show jid'
_ <- lift $ withStream ( do modify $ \s ->
s{streamJid = Just jid'})
c
return jid'
_ -> do
lift $ errorM "Pontarius.Xmpp"
$ "xmppBind: JID could not be unpickled from: "
++ show b
throwError $ XmppOtherFailure
_ -> do
lift $ errorM "Pontarius.XMPP" "xmppBind: IQ error received."
throwError XmppOtherFailure
where
xpJid' :: PU [Node] Jid
xpJid' = xpBind $ xpElemNodes jidName (xpContent xpJid)
jidName = "{urn:ietf:params:xml:ns:xmpp-bind}jid"
xpBind :: PU [Node] b -> PU [Node] b
xpBind c = xpElemNodes "{urn:ietf:params:xml:ns:xmpp-bind}bind" c
sessionXml :: Element
sessionXml = pickleElem
(xpElemBlank "{urn:ietf:params:xml:ns:xmpp-session}session")
()
startSession :: Stream -> IO Bool
startSession con = do
debugM "Pontarius.XMPP" "startSession: Pushing `session' IQ set stanza..."
answer <- pushIQ "session" Nothing Set Nothing sessionXml con
case answer of
Left e -> do
errorM "Pontarius.XMPP" $ "startSession: Error stanza received (" ++ (show e) ++ ")"
return False
Right _ -> do
debugM "Pontarius.XMPP" "startSession: Result stanza received."
return True